step_c1d.F90 9.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173
  1. MODULE step_c1d
  2. !!======================================================================
  3. !! *** MODULE step_c1d ***
  4. !! Time-stepping : manager of the ocean, tracer and ice time stepping - c1d case
  5. !!======================================================================
  6. !! History : 2.0 ! 2004-04 (C. Ethe) adapted from step.F90 for C1D
  7. !! 3.0 ! 2008-04 (G. Madec) redo the adaptation to include SBC
  8. !!----------------------------------------------------------------------
  9. #if defined key_c1d
  10. !!----------------------------------------------------------------------
  11. !! 'key_c1d' 1D Configuration
  12. !!----------------------------------------------------------------------
  13. !! stp_c1d : NEMO system time-stepping in c1d case
  14. !!----------------------------------------------------------------------
  15. USE step_oce ! time stepping definition modules
  16. #if defined key_top
  17. USE trcstp ! passive tracer time-stepping (trc_stp routine)
  18. #endif
  19. USE dyncor_c1d ! Coriolis term (c1d case) (dyn_cor_1d )
  20. USE dynnxt_c1d ! time-stepping (dyn_nxt routine)
  21. USE dyndmp ! U & V momentum damping (dyn_dmp routine)
  22. USE restart ! restart
  23. IMPLICIT NONE
  24. PRIVATE
  25. PUBLIC stp_c1d ! called by opa.F90
  26. !! * Substitutions
  27. # include "domzgr_substitute.h90"
  28. # include "zdfddm_substitute.h90"
  29. !!----------------------------------------------------------------------
  30. !! NEMO/C1D 3.3 , NEMO Consortium (2010)
  31. !! $Id: step_c1d.F90 3977 2017-02-20 14:03:23Z ufla $
  32. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  33. !!----------------------------------------------------------------------
  34. CONTAINS
  35. SUBROUTINE stp_c1d( kstp )
  36. !!----------------------------------------------------------------------
  37. !! *** ROUTINE stp_c1d ***
  38. !!
  39. !! ** Purpose : - Time stepping of SBC including LIM (dynamic and thermodynamic eqs.)
  40. !! - Time stepping of OPA (momentum and active tracer eqs.)
  41. !! - Time stepping of TOP (passive tracer eqs.)
  42. !!
  43. !! ** Method : -1- Update forcings and data
  44. !! -2- Update vertical ocean physics
  45. !! -3- Compute the t and s trends
  46. !! -4- Update t and s
  47. !! -5- Compute the momentum trends
  48. !! -6- Update the horizontal velocity
  49. !! -7- Compute the diagnostics variables (rd,N2, div,cur,w)
  50. !! -8- Outputs and diagnostics
  51. !!----------------------------------------------------------------------
  52. INTEGER, INTENT(in) :: kstp ! ocean time-step index
  53. INTEGER :: jk ! dummy loop indice
  54. INTEGER :: indic ! error indicator if < 0
  55. !! ---------------------------------------------------------------------
  56. indic = 0 ! reset to no error condition
  57. IF( kstp == nit000 ) CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS)
  58. IF( kstp /= nit000 ) CALL day( kstp ) ! Calendar (day was already called at nit000 in day_init)
  59. CALL iom_setkt( kstp - nit000 + 1, cxios_context ) ! say to iom that we are at time step kstp
  60. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  61. ! Update data, open boundaries, surface boundary condition (including sea-ice)
  62. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  63. CALL sbc ( kstp ) ! Sea Boundary Condition (including sea-ice)
  64. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  65. ! Ocean physics update (ua, va, ta, sa used as workspace)
  66. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  67. CALL eos_rab( tsb, rab_b ) ! before local thermal/haline expension ratio at T-points
  68. CALL eos_rab( tsn, rab_n ) ! now local thermal/haline expension ratio at T-points
  69. CALL bn2( tsb, rab_b, rn2b ) ! before Brunt-Vaisala frequency
  70. CALL bn2( tsn, rab_n, rn2 ) ! now Brunt-Vaisala frequency
  71. ! VERTICAL PHYSICS
  72. CALL zdf_bfr( kstp ) ! bottom friction
  73. ! ! Vertical eddy viscosity and diffusivity coefficients
  74. IF( lk_zdfric ) CALL zdf_ric( kstp ) ! Richardson number dependent Kz
  75. IF( lk_zdftke ) CALL zdf_tke( kstp ) ! TKE closure scheme for Kz
  76. IF( lk_zdfgls ) CALL zdf_gls( kstp ) ! GLS closure scheme for Kz
  77. IF( lk_zdfkpp ) CALL zdf_kpp( kstp ) ! KPP closure scheme for Kz
  78. IF( lk_zdfcst ) THEN ! Constant Kz (reset avt, avm[uv] to the background value)
  79. avt (:,:,:) = rn_avt0 * tmask(:,:,:)
  80. avmu(:,:,:) = rn_avm0 * umask(:,:,:)
  81. avmv(:,:,:) = rn_avm0 * vmask(:,:,:)
  82. ENDIF
  83. IF( ln_rnf_mouth ) THEN ! increase diffusivity at rivers mouths
  84. DO jk = 2, nkrnf ; avt(:,:,jk) = avt(:,:,jk) + 2.e0 * rn_avt_rnf * rnfmsk(:,:) ; END DO
  85. ENDIF
  86. IF( ln_zdfevd ) CALL zdf_evd( kstp ) ! enhanced vertical eddy diffusivity
  87. IF( lk_zdftmx ) CALL zdf_tmx( kstp ) ! tidal vertical mixing
  88. IF( lk_zdfddm .AND. .NOT. lk_zdfkpp ) &
  89. & CALL zdf_ddm( kstp ) ! double diffusive mixing
  90. CALL zdf_mxl( kstp ) ! mixed layer depth
  91. ! write tke information in the restart file
  92. IF( lrst_oce .AND. lk_zdftke ) CALL tke_rst( kstp, 'WRITE' )
  93. ! write gls information in the restart file
  94. IF( lrst_oce .AND. lk_zdfgls ) CALL gls_rst( kstp, 'WRITE' )
  95. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  96. ! diagnostics and outputs (ua, va, ta, sa used as workspace)
  97. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  98. CALL dia_wri( kstp ) ! ocean model: outputs
  99. IF( lk_diahth ) CALL dia_hth( kstp ) ! Thermocline depth (20°C)
  100. #if defined key_top
  101. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  102. ! Passive Tracer Model
  103. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  104. CALL trc_stp( kstp ) ! time-stepping
  105. #endif
  106. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  107. ! Active tracers (ua, va used as workspace)
  108. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  109. tsa(:,:,:,:) = 0._wp ! set tracer trends to zero
  110. CALL tra_sbc( kstp ) ! surface boundary condition
  111. IF( ln_traqsr ) CALL tra_qsr( kstp ) ! penetrative solar radiation qsr
  112. IF( ln_tradmp ) CALL tra_dmp( kstp ) ! internal damping trends- tracers
  113. IF( lk_zdfkpp ) CALL tra_kpp( kstp ) ! KPP non-local tracer fluxes
  114. CALL tra_zdf( kstp ) ! vertical mixing
  115. CALL eos( tsn, rhd, rhop, gdept_0(:,:,:) ) ! now potential density for zdfmxl
  116. IF( ln_zdfnpc ) CALL tra_npc( kstp ) ! applied non penetrative convective adjustment on (t,s)
  117. CALL tra_nxt( kstp ) ! tracer fields at next time step
  118. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  119. ! Dynamics (ta, sa used as workspace)
  120. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  121. ua(:,:,:) = 0._wp ! set dynamics trends to zero
  122. va(:,:,:) = 0._wp
  123. IF( ln_dyndmp ) CALL dyn_dmp ( kstp ) ! internal damping trends- momentum
  124. CALL dyn_cor_c1d( kstp ) ! vorticity term including Coriolis
  125. CALL dyn_zdf ( kstp ) ! vertical diffusion
  126. CALL dyn_nxt_c1d( kstp ) ! lateral velocity at next time step
  127. !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  128. ! Control and restarts
  129. !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  130. CALL stp_ctl( kstp, indic )
  131. IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file
  132. IF( lrst_oce ) CALL rst_write( kstp ) ! write output ocean restart file
  133. !
  134. #if defined key_iomput
  135. IF( kstp == nitend .OR. indic < 0 ) CALL xios_context_finalize() ! needed for XIOS
  136. !
  137. #endif
  138. END SUBROUTINE stp_c1d
  139. #else
  140. !!----------------------------------------------------------------------
  141. !! Default key NO 1D Config
  142. !!----------------------------------------------------------------------
  143. CONTAINS
  144. SUBROUTINE stp_c1d ( kt ) ! dummy routine
  145. WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt
  146. END SUBROUTINE stp_c1d
  147. #endif
  148. !!======================================================================
  149. END MODULE step_c1d