New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
zdfphy.F90 in branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfphy.F90 @ 8143

Last change on this file since 8143 was 8143, checked in by gm, 7 years ago

#1880 (HPC-09) - step-7: top/bottom drag computed at T-points, zdfbfr.F90 replaced by zdfdrg.F90 + changes in namelist

  • Property svn:keywords set to Id
File size: 17.2 KB
Line 
1MODULE zdfphy
2   !!======================================================================
3   !!                      ***  MODULE  zdfphy  ***
4   !! Vertical ocean physics :   manager of all vertical physics packages
5   !!======================================================================
6   !! History :  4.0  !  2017-04  (G. Madec)  original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   zdf_phy_init  : initialization of all vertical physics packages
11   !!   zdf_phy       : upadate at each time-step the vertical mixing coeff.
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers variables
14   USE zdf_oce        ! vertical physics: shared variables         
15   USE zdfdrg         ! vertical physics: top/bottom drag coef.
16   USE zdfsh2         ! vertical physics: shear production term of TKE
17   USE zdfric         ! vertical physics: RIChardson dependent vertical mixing   
18   USE zdftke         ! vertical physics: TKE vertical mixing
19   USE zdfgls         ! vertical physics: GLS vertical mixing
20   USE zdfddm         ! vertical physics: double diffusion mixing     
21   USE zdfevd         ! vertical physics: convection via enhanced vertical diffusion 
22   USE zdfiwm         ! vertical physics: internal wave-induced mixing 
23   USE zdfswm         ! vertical physics: surface  wave-induced mixing
24   USE zdfmxl         ! vertical physics: mixed layer
25   USE tranpc         ! convection: non penetrative adjustment
26   USE trc_oce        ! variables shared between passive tracer & ocean           
27   USE sbc_oce        ! surface module (only for nn_isf in the option compatibility test)
28   USE sbcrnf         ! surface boundary condition: runoff variables
29   !
30   USE in_out_manager ! I/O manager
31   USE iom            ! IOM library
32   USE lbclnk         ! lateral boundary conditions
33   USE lib_mpp        ! distribued memory computing
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   zdf_phy_init  ! called by nemogcm.F90
39   PUBLIC   zdf_phy       ! called by step.F90
40
41   INTEGER ::   nzdf_phy   ! type of vertical closure used
42   !                       ! associated indicators
43   INTEGER, PARAMETER ::   np_CST = 1   ! Constant Kz
44   INTEGER, PARAMETER ::   np_RIC = 2   ! Richardson number dependent Kz
45   INTEGER, PARAMETER ::   np_TKE = 3   ! Turbulente Kinetic Eenergy closure scheme for Kz
46   INTEGER, PARAMETER ::   np_GLS = 4   ! Generic Length Scale closure scheme for Kz
47
48   LOGICAL ::   l_zdfsh2   ! shear production term flag (=F for CST, =T otherwise (i.e. TKE, GLS, RIC))
49
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
52   !! $Id$
53   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55CONTAINS
56
57   SUBROUTINE zdf_phy_init
58      !!----------------------------------------------------------------------
59      !!                  ***  ROUTINE zdf_phy_init  ***
60      !!
61      !! ** Purpose :   initializations of the vertical ocean physics
62      !!
63      !! ** Method  :   Read namelist namzdf, control logicals
64      !!                set horizontal shape and vertical profile of background mixing coef.
65      !!----------------------------------------------------------------------
66      INTEGER ::   jk            ! dummy loop indices
67      INTEGER ::   ioptio, ios   ! local integers
68      !!
69      NAMELIST/namzdf/ ln_zdfcst, ln_zdfric, ln_zdftke, ln_zdfgls,   &     ! type of closure scheme
70         &             ln_zdfevd, nn_evdm, rn_evd ,                  &     ! convection : evd
71         &             ln_zdfnpc, nn_npc , nn_npcp,                  &     ! convection : npc
72         &             ln_zdfddm, rn_avts, rn_hsbfr,                 &     ! double diffusion
73         &             ln_zdfswm,                                    &     ! surface  wave-induced mixing
74         &             ln_zdfiwm,                                    &     ! internal  -      -      -
75         &             ln_zdfexp, nn_zdfexp,                         &     ! time-stepping
76         &             rn_avm0, rn_avt0, nn_avb, nn_havtb                  ! coefficients
77      !!----------------------------------------------------------------------
78      !
79      !                           !==  Namelist  ==!
80      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
81      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901)
82901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp )
83      !
84      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
85      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 )
86902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp )
87      IF(lwm)   WRITE ( numond, namzdf )
88      !
89      IF(lwp) THEN                      ! Parameter print
90         WRITE(numout,*)
91         WRITE(numout,*) 'zdf_phy_init: vertical physics'
92         WRITE(numout,*) '~~~~~~~~~~~~'
93         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters'
94         WRITE(numout,*) '      vertical closure scheme'
95         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfcst = ', ln_zdfcst
96         WRITE(numout,*) '         Richardson number dependent closure     ln_zdfric = ', ln_zdfric
97         WRITE(numout,*) '         Turbulent Kinetic Energy closure (TKE)  ln_zdftke = ', ln_zdftke
98         WRITE(numout,*) '         Generic Length Scale closure (GLS)      ln_zdfgls = ', ln_zdfgls
99         WRITE(numout,*) '      convection: '
100         WRITE(numout,*) '         enhanced vertical diffusion             ln_zdfevd = ', ln_zdfevd
101         WRITE(numout,*) '            applied on momentum (=1/0)             nn_evdm = ', nn_evdm
102         WRITE(numout,*) '            vertical coefficient for evd           rn_evd  = ', rn_evd
103         WRITE(numout,*) '         non-penetrative convection (npc)        ln_zdfnpc = ', ln_zdfnpc
104         WRITE(numout,*) '            npc call  frequency                    nn_npc  = ', nn_npc
105         WRITE(numout,*) '            npc print frequency                    nn_npcp = ', nn_npcp
106         WRITE(numout,*) '      double diffusive mixing                    ln_zdfddm = ', ln_zdfddm
107         WRITE(numout,*) '         maximum avs for dd mixing                 rn_avts = ', rn_avts
108         WRITE(numout,*) '         heat/salt buoyancy flux ratio             rn_hsbfr= ', rn_hsbfr
109         WRITE(numout,*) '      gravity wave-induced mixing'
110         WRITE(numout,*) '         surface  wave (Qiao et al 2010)         ln_zdfswm = ', ln_zdfswm                                          ! surface wave induced mixing
111         WRITE(numout,*) '         internal wave (de Lavergne et al 2017)  ln_zdfiwm = ', ln_zdfiwm
112         WRITE(numout,*) '      time-steping scheme'
113         WRITE(numout,*) '         time splitting (T) / implicit (F)       ln_zdfexp = ', ln_zdfexp
114         WRITE(numout,*) '         number of sub-time step (ln_zdfexp=T)   nn_zdfexp = ', nn_zdfexp
115         WRITE(numout,*) '      coefficients : '
116         WRITE(numout,*) '         vertical eddy viscosity                 rn_avm0   = ', rn_avm0
117         WRITE(numout,*) '         vertical eddy diffusivity               rn_avt0   = ', rn_avt0
118         WRITE(numout,*) '         constant background or profile          nn_avb    = ', nn_avb
119         WRITE(numout,*) '         horizontal variation for avtb           nn_havtb  = ', nn_havtb
120      ENDIF
121
122      !                          !==  Background eddy viscosity and diffusivity  ==!
123      IF( nn_avb == 0 ) THEN             ! Define avmb, avtb from namelist parameter
124         avmb(:) = rn_avm0
125         avtb(:) = rn_avt0                     
126      ELSE                               ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)
127         avmb(:) = rn_avm0
128         avtb(:) = rn_avt0 + ( 3.e-4_wp - 2._wp * rn_avt0 ) * 1.e-4_wp * gdepw_1d(:)   ! m2/s
129         IF(ln_sco .AND. lwp)   CALL ctl_warn( 'avtb profile not valid in sco' )
130      ENDIF
131      !                                  ! 2D shape of the avtb
132      avtb_2d(:,:) = 1._wp                   ! uniform
133      !
134      IF( nn_havtb == 1 ) THEN               ! decrease avtb by a factor of ten in the equatorial band
135           !                                 !   -15S -5S : linear decrease from avt0 to avt0/10.
136           !                                 !   -5S  +5N : cst value avt0/10.
137           !                                 !    5N  15N : linear increase from avt0/10, to avt0
138           WHERE(-15. <= gphit .AND. gphit < -5 )   avtb_2d = (1.  - 0.09 * (gphit + 15.))
139           WHERE( -5. <= gphit .AND. gphit <  5 )   avtb_2d =  0.1
140           WHERE(  5. <= gphit .AND. gphit < 15 )   avtb_2d = (0.1 + 0.09 * (gphit -  5.))
141      ENDIF
142      !
143      DO jk = 1, jpk                      ! set turbulent closure Kz to the background value (avt_k, avm_k)
144         avt_k(:,:,jk) = avtb_2d(:,:) * avtb(jk) * wmask (:,:,jk)
145         avm_k(:,:,jk) =                avmb(jk) * wmask (:,:,jk)
146      END DO
147!!gm  to be tested only the 1st & last levels
148!      avt  (:,:, 1 ) = 0._wp   ;   avs(:,:, 1 ) = 0._wp   ;   avm  (:,:, 1 ) = 0._wp
149!      avt  (:,:,jpk) = 0._wp   ;   avs(:,:,jpk) = 0._wp   ;   avm  (:,:,jpk) = 0._wp
150!!gm
151      avt  (:,:,:) = 0._wp   ;   avs(:,:,:) = 0._wp   ;   avm  (:,:,:) = 0._wp
152
153      !                          !==  Convection  ==!
154      !
155      IF( ln_zdfnpc .AND. ln_zdfevd )   CALL ctl_stop( 'zdf_phy_init: chose between ln_zdfnpc and ln_zdfevd' )
156      IF( lk_top    .AND. ln_zdfnpc )   CALL ctl_stop( 'zdf_phy_init: npc scheme is not working with key_top' )
157      IF(lwp) THEN
158         WRITE(numout,*)
159         IF    ( ln_zdfnpc ) THEN  ;   WRITE(numout,*) '      convection: use non penetrative convective scheme'
160         ELSEIF( ln_zdfevd ) THEN  ;   WRITE(numout,*) '      convection: use enhanced vertical diffusion scheme'
161         ELSE                      ;   WRITE(numout,*) '      convection: no specific scheme used'
162         ENDIF
163      ENDIF
164
165      IF(lwp) THEN               !==  Double Diffusion Mixing parameterization  ==!   (ddm)
166         WRITE(numout,*)
167         IF( ln_zdfddm ) THEN   ;   WRITE(numout,*) '      use double diffusive mixing: avs /= avt'
168         ELSE                   ;   WRITE(numout,*) '      No  double diffusive mixing: avs = avt'
169         ENDIF
170      ENDIF
171
172      !                          !==  type of vertical turbulent closure  ==!    (set nzdf_phy)
173      ioptio = 0 
174      IF( ln_zdfcst ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_CST   ;   ENDIF
175      IF( ln_zdfric ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_RIC   ;   CALL zdf_ric_init   ;   ENDIF
176      IF( ln_zdftke ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_TKE   ;   CALL zdf_tke_init   ;   ENDIF
177      IF( ln_zdfgls ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_GLS   ;   CALL zdf_gls_init   ;   ENDIF
178      !
179      IF( ioptio /= 1 )    CALL ctl_stop( 'zdf_phy_init: one and only one vertical diffusion option has to be defined ' )
180      IF( ln_isfcav ) THEN
181      IF( ln_zdfric .OR. ln_zdfgls )    CALL ctl_stop( 'zdf_phy_init: zdfric and zdfgls never tested with ice shelves cavities ' )
182      ENDIF
183      !                                ! shear production term flag
184      IF( ln_zdfcst ) THEN   ;   l_zdfsh2 = .FALSE.
185      ELSE                   ;   l_zdfsh2 = .TRUE.
186      ENDIF
187
188      !                          !== gravity wave-driven mixing  ==!
189      IF( ln_zdfiwm )   CALL zdf_iwm_init       ! internal wave-driven mixing
190      IF( ln_zdfswm )   CALL zdf_swm_init       ! surface  wave-driven mixing
191
192      !                          !== top/bottom friction  ==!
193      CALL zdf_drg_init
194      !
195      !                          !== time-stepping  ==!
196      ! Check/update of time stepping done in dynzdf_init/trazdf_init
197      !!gm move it here ?
198      !
199   END SUBROUTINE zdf_phy_init
200
201
202   SUBROUTINE zdf_phy( kt )
203      !!----------------------------------------------------------------------
204      !!                     ***  ROUTINE zdf_phy  ***
205      !!
206      !! ** Purpose :  Update ocean physics at each time-step
207      !!
208      !! ** Method  :
209      !!
210      !! ** Action  :   avm, avt vertical eddy viscosity and diffusivity at w-points
211      !!                nmld ??? mixed layer depth in level and meters   <<<<====verifier !
212      !!                bottom stress.....                               <<<<====verifier !
213      !!----------------------------------------------------------------------
214      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
215      !
216      INTEGER ::   ji, jj, jk   ! dummy loop indice
217      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zsh2   ! shear production
218      !! ---------------------------------------------------------------------
219      !
220      IF( l_zdfdrg ) THEN     !==  update top/bottom drag  ==!   (non-linear cases)
221         !
222         !                       !* bottom drag
223         CALL zdf_drg( kt, mbkt    , r_Cdmin_bot, r_Cdmax_bot,   &   ! <<== in
224            &              r_z0_bot,   r_ke0_bot,    rCd0_bot,   &
225            &                                        rCdU_bot  )     ! ==>> out : bottom drag [m/s]
226         IF( ln_isfcav ) THEN    !* top drag   (ocean cavities)
227            CALL zdf_drg( kt, mikt    , r_Cdmin_top, r_Cdmax_top,   &   ! <<== in
228               &              r_z0_top,   r_ke0_top,    rCd0_top,   &
229               &                                        rCdU_top  )     ! ==>> out : bottom drag [m/s]
230         ENDIF
231      ENDIF
232      !
233      !                       !==  Kz from chosen turbulent closure  ==!   (avm_k, avt_k)
234      !
235      IF( l_zdfsh2 )   &         !* shear production at w-points (energy conserving form)
236         CALL zdf_sh2( ub, vb, un, vn, avm_k,   &     ! <<== in
237            &                           zsh2    )     ! ==>> out : shear production
238      !
239      SELECT CASE ( nzdf_phy )                  !* Vertical eddy viscosity and diffusivity coefficients at w-points
240      CASE( np_RIC )   ;   CALL zdf_ric( kt, gdept_n, zsh2, avm_k, avt_k )    ! Richardson number dependent Kz
241      CASE( np_TKE )   ;   CALL zdf_tke( kt         , zsh2, avm_k, avt_k )    ! TKE closure scheme for Kz
242      CASE( np_GLS )   ;   CALL zdf_gls( kt         , zsh2, avm_k, avt_k )    ! GLS closure scheme for Kz
243!     CASE( np_CST )                                  ! Constant Kz (reset avt, avm to the background value)
244!         ! avt_k and avm_k set one for all at initialisation phase
245!!gm         avt(2:jpim1,2:jpjm1,1:jpkm1) = rn_avt0 * wmask(2:jpim1,2:jpjm1,1:jpkm1)
246!!gm         avm(2:jpim1,2:jpjm1,1:jpkm1) = rn_avm0 * wmask(2:jpim1,2:jpjm1,1:jpkm1)
247      END SELECT
248     
249      !                          !==  ocean Kz  ==!   (avt, avs, avm)
250      !
251      !                                         !* start from turbulent closure values
252      avt(:,:,2:jpkm1) = avt_k(:,:,2:jpkm1)
253      avm(:,:,2:jpkm1) = avm_k(:,:,2:jpkm1)
254      !
255      IF( ln_rnf_mouth ) THEN                   !* increase diffusivity at rivers mouths
256         DO jk = 2, nkrnf
257            avt(:,:,jk) = avt(:,:,jk) + 2._wp * rn_avt_rnf * rnfmsk(:,:) * wmask(:,:,jk)
258         END DO
259      ENDIF
260      !
261      IF( ln_zdfevd )   CALL zdf_evd( kt, avm, avt )  !* convection: enhanced vertical eddy diffusivity
262      !
263      !                                         !* double diffusive mixing
264      IF( ln_zdfddm ) THEN                            ! update avt and compute avs
265                        CALL zdf_ddm( kt, avm, avt, avs )
266      ELSE                                            ! same mixing on all tracers
267         avs(2:jpim1,2:jpjm1,1:jpkm1) = avt(2:jpim1,2:jpjm1,1:jpkm1)
268      ENDIF
269      !
270      !                                         !* wave-induced mixing
271      IF( ln_zdfswm )   CALL zdf_swm( kt, avm, avt, avs )   ! surface  wave (Qiao et al. 2004)
272      IF( ln_zdfiwm )   CALL zdf_iwm( kt, avm, avt, avs )   ! internal wave (de Lavergne et al 2017)
273
274
275      !                                         !* Lateral boundary conditions (sign unchanged)
276      CALL lbc_lnk( avm_k, 'W', 1. )                  ! needed to compute the shear production term
277      CALL lbc_lnk( avt_k, 'W', 1. )                  !!gm a priori useless ==>> to be tested
278      CALL lbc_lnk( avm  , 'W', 1. )                  ! needed to compute avm at u- and v-points
279      CALL lbc_lnk( avt  , 'W', 1. )                  !!gm  a priori only avm_k and avm are required
280      CALL lbc_lnk( avs  , 'W', 1. )                  !!gm  To be tested
281      !
282      IF( l_zdfdrg ) THEN     ! drag  have been updated (non-linear cases)
283         IF( ln_isfcav )   CALL lbc_lnk( rCdU_top, 'T', 1. )   ! top    drag
284                           CALL lbc_lnk( rCdU_bot, 'T', 1. )   ! bottom drag
285      ENDIF
286      !
287      CALL zdf_mxl( kt )                        !* mixed layer depth, and level
288
289      IF( lrst_oce ) THEN                       !* write TKE, GLS or RIC fields in the restart file
290         IF( ln_zdftke )   CALL tke_rst( kt, 'WRITE' )
291         IF( ln_zdfgls )   CALL gls_rst( kt, 'WRITE' )
292         IF( ln_zdfric )   CALL ric_rst( kt, 'WRITE' ) 
293      ENDIF
294      !
295   END SUBROUTINE zdf_phy
296
297   !!======================================================================
298END MODULE zdfphy
Note: See TracBrowser for help on using the repository browser.