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 @ 7990

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

#1880 (HPC-09): OPA remove avmu, avmv from zdf modules + move CALL tke(gls)_rst & gls_rst in zdftke(gls) + rename zdftmx and zdfqiao

  • Property svn:keywords set to Id
File size: 14.9 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 par_oce        ! ocean parameters
14   USE zdf_oce        ! vertical physics: shared variables         
15   USE zdfbfr         ! vertical physics: bottom friction
16   USE zdfric         ! vertical physics: Richardson vertical mixing   
17   USE zdftke         ! vertical physics: TKE vertical mixing
18   USE zdfgls         ! vertical physics: GLS vertical mixing
19   USE zdfddm         ! vertical physics: double diffusion mixing     
20   USE zdfevd         ! vertical physics: convection via enhanced vertical diffusion 
21   USE zdfiwm         ! vertical physics: internal wave-induced mixing 
22   USE zdfswm         ! vertical physics: surface  wave-induced mixing
23   USE zdfmxl         ! vertical physics: mixed layer
24   USE tranpc         ! convection: non penetrative adjustment
25   USE trc_oce        ! variables shared between passive tracer & ocean           
26   USE sbc_oce        ! surface module (only for nn_isf in the option compatibility test)
27   USE sbcrnf         ! surface boundary condition: runoff variables
28   !
29   USE in_out_manager ! I/O manager
30   USE iom            ! IOM library
31   USE lbclnk         ! lateral boundary conditions
32   USE lib_mpp        ! distribued memory computing
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   zdf_phy_init  ! called by nemogcm.F90
38   PUBLIC   zdf_phy       ! called by step.F90
39
40   INTEGER ::   nzdf_phy   ! type of vertical closure used
41   !                       ! associated indicators
42   INTEGER, PARAMETER ::   np_CST = 1   ! Constant Kz
43   INTEGER, PARAMETER ::   np_RIC = 2   ! Richardson number dependent Kz
44   INTEGER, PARAMETER ::   np_TKE = 3   ! Turbulente Kinetic Eenergy closure scheme for Kz
45   INTEGER, PARAMETER ::   np_GLS = 4   ! Generic Length Scale closure scheme for Kz
46     
47   !!----------------------------------------------------------------------
48   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
49   !! $Id$
50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE zdf_phy_init
55      !!----------------------------------------------------------------------
56      !!                  ***  ROUTINE zdf_phy_init  ***
57      !!
58      !! ** Purpose :   initializations of the vertical ocean physics
59      !!
60      !! ** Method  :   Read namelist namzdf, control logicals
61      !!                set horizontal shape and vertical profile of background mixing coef.
62      !!----------------------------------------------------------------------
63      INTEGER ::   ioptio, ios   ! local integers
64      !!
65      NAMELIST/namzdf/ ln_zdfcst, ln_zdfric, ln_zdftke, ln_zdfgls,   &     ! type of closure scheme
66         &             ln_zdfevd, nn_evdm, rn_evd ,                  &     ! convection : evd
67         &             ln_zdfnpc, nn_npc , nn_npcp,                  &     ! convection : npc
68         &             ln_zdfddm, rn_avts, rn_hsbfr,                 &     ! double diffusion
69         &             ln_zdfswm,                                    &     ! surface  wave-induced mixing
70         &             ln_zdfiwm,                                    &     ! internal  -      -      -
71         &             ln_zdfexp, nn_zdfexp,                         &     ! time-stepping
72         &             rn_avm0, rn_avt0, nn_avb, nn_havtb                  ! coefficients
73      !!----------------------------------------------------------------------
74      !
75      !                           !==  Namelist  ==!
76      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
77      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901)
78901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp )
79      !
80      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
81      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 )
82902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp )
83      IF(lwm)   WRITE ( numond, namzdf )
84      !
85      IF(lwp) THEN                      ! Parameter print
86         WRITE(numout,*)
87         WRITE(numout,*) 'zdf_phy_init: vertical physics'
88         WRITE(numout,*) '~~~~~~~~~~~~'
89         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters'
90         WRITE(numout,*) '      vertical closure scheme'
91         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfcst = ', ln_zdfcst
92         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfric = ', ln_zdfric
93         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdftke = ', ln_zdftke
94         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfgls = ', ln_zdfgls
95         WRITE(numout,*) '      convection: '
96         WRITE(numout,*) '         enhanced vertical diffusion             ln_zdfevd = ', ln_zdfevd
97         WRITE(numout,*) '            applied on momentum (=1/0)             nn_evdm = ', nn_evdm
98         WRITE(numout,*) '            vertical coefficient for evd           rn_evd  = ', rn_evd
99         WRITE(numout,*) '         non-penetrative convection (npc)        ln_zdfnpc = ', ln_zdfnpc
100         WRITE(numout,*) '            npc call  frequency                    nn_npc  = ', nn_npc
101         WRITE(numout,*) '            npc print frequency                    nn_npcp = ', nn_npcp
102         WRITE(numout,*) '      double diffusive mixing                    ln_zdfddm = ', ln_zdfddm
103         WRITE(numout,*) '         maximum avs for dd mixing                 rn_avts = ', rn_avts
104         WRITE(numout,*) '         heat/salt buoyancy flux ratio             rn_hsbfr= ', rn_hsbfr
105         WRITE(numout,*) '      gravity wave-induced mixing'
106         WRITE(numout,*) '         surface  wave (Qiao et al 2010)         ln_zdfswm = ', ln_zdfswm                                          ! surface wave induced mixing
107         WRITE(numout,*) '         internal wave (de Lavergne et al 2017)  ln_zdfiwm = ', ln_zdfiwm
108         WRITE(numout,*) '      time-steping scheme'
109         WRITE(numout,*) '         time splitting (T) / implicit (F)       ln_zdfexp = ', ln_zdfexp
110         WRITE(numout,*) '         number of sub-time step (ln_zdfexp=T)   nn_zdfexp = ', nn_zdfexp
111         WRITE(numout,*) '      coefficients : '
112         WRITE(numout,*) '         vertical eddy viscosity                 rn_avm0   = ', rn_avm0
113         WRITE(numout,*) '         vertical eddy diffusivity               rn_avt0   = ', rn_avt0
114         WRITE(numout,*) '         constant background or profile          nn_avb    = ', nn_avb
115         WRITE(numout,*) '         horizontal variation for avtb           nn_havtb  = ', nn_havtb
116      ENDIF
117
118      !                          !==  Background eddy viscosity and diffusivity  ==!
119      IF( nn_avb == 0 ) THEN             ! Define avmb, avtb from namelist parameter
120         avmb(:) = rn_avm0
121         avtb(:) = rn_avt0                     
122      ELSE                               ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)
123         avmb(:) = rn_avm0
124         avtb(:) = rn_avt0 + ( 3.e-4_wp - 2._wp * rn_avt0 ) * 1.e-4_wp * gdepw_1d(:)   ! m2/s
125         IF(ln_sco .AND. lwp)   CALL ctl_warn( 'avtb profile not valid in sco' )
126      ENDIF
127      !                                  ! 2D shape of the avtb
128      avtb_2d(:,:) = 1._wp                   ! uniform
129      !
130      IF( nn_havtb == 1 ) THEN               ! decrease avtb by a factor of ten in the equatorial band
131           !                                 !   -15S -5S : linear decrease from avt0 to avt0/10.
132           !                                 !   -5S  +5N : cst value avt0/10.
133           !                                 !    5N  15N : linear increase from avt0/10, to avt0
134           WHERE(-15. <= gphit .AND. gphit < -5 )   avtb_2d = (1.  - 0.09 * (gphit + 15.))
135           WHERE( -5. <= gphit .AND. gphit <  5 )   avtb_2d =  0.1
136           WHERE(  5. <= gphit .AND. gphit < 15 )   avtb_2d = (0.1 + 0.09 * (gphit -  5.))
137      ENDIF
138      !
139      !                                   ! set 1st/last level Av to zero one for all
140      avt(:,:,1) = 0._wp   ;   avs(:,:,1) = 0._wp   ;   avm(:,:,1) = 0._wp
141
142      !                          !==  Convection  ==!
143      !
144      IF( ln_zdfnpc .AND. ln_zdfevd )   CALL ctl_stop( 'zdf_phy_init: chose between ln_zdfnpc and ln_zdfevd' )
145      IF( lk_top    .AND. ln_zdfnpc )   CALL ctl_stop( 'zdf_phy_init: npc scheme is not working with key_top' )
146      IF(lwp) THEN
147         WRITE(numout,*)
148         IF    ( ln_zdfnpc ) THEN  ;   WRITE(numout,*) '      convection: use non penetrative convective scheme'
149         ELSEIF( ln_zdfevd ) THEN  ;   WRITE(numout,*) '      convection: use enhanced vertical diffusion scheme'
150         ELSE                      ;   WRITE(numout,*) '      convection: no specific scheme used'
151         ENDIF
152      ENDIF
153
154      IF(lwp) THEN               !==  Double Diffusion Mixing parameterization  ==!   (ddm)
155         WRITE(numout,*)
156         IF( ln_zdfddm ) THEN   ;   WRITE(numout,*) '      use double diffusive mixing: avs /= avt'
157         ELSE                   ;   WRITE(numout,*) '      No  double diffusive mixing: avs = avt'
158         ENDIF
159      ENDIF
160
161      !                          !==  type of vertical turbulent closure  ==!    (set nzdf_phy)
162      ioptio = 0 
163      IF( ln_zdfcst ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_CST   ;   ENDIF
164      IF( ln_zdfric ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_RIC   ;   CALL zdf_ric_init   ;   ENDIF
165      IF( ln_zdftke ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_TKE   ;   CALL zdf_tke_init   ;   ENDIF
166      IF( ln_zdfgls ) THEN   ;   ioptio = ioptio + 1   ;    nzdf_phy = np_GLS   ;   CALL zdf_gls_init   ;   ENDIF
167      !
168      IF( ioptio /= 1 )    CALL ctl_stop( 'zdf_phy_init: one and only one vertical diffusion option has to be defined ' )
169      IF( ln_isfcav ) THEN
170      IF( ln_zdfric .OR. ln_zdfgls )    CALL ctl_stop( 'zdf_phy_init: zdfric and zdfgls never tested with ice shelves cavities ' )
171      ENDIF
172
173      !                          !== gravity wave-driven mixing  ==!
174      IF( ln_zdfiwm )   CALL zdf_iwm_init       ! internal wave-driven mixing
175      IF( ln_zdfswm )   CALL zdf_swm_init       ! surface  wave-driven mixing
176
177      !                          !== bottom friction  ==!
178      CALL zdf_bfr_init
179      !
180      !                          !== time-stepping  ==!
181      ! Check/update of time stepping done in dynzdf_init/trazdf_init
182      !!gm move it here ?
183      !
184   END SUBROUTINE zdf_phy_init
185
186
187   SUBROUTINE zdf_phy( kt )
188      !!----------------------------------------------------------------------
189      !!                     ***  ROUTINE zdf_phy  ***
190      !!
191      !! ** Purpose :  Update ocean physics at each time-step
192      !!
193      !! ** Method  :
194      !!
195      !! ** Action  :   avm, avt vertical eddy viscosity and diffusivity at w-points
196      !!                nmld ??? mixed layer depth in level and meters   <<<<====verifier !
197      !!                bottom stress.....                               <<<<====verifier !
198      !!----------------------------------------------------------------------
199      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
200      !
201      INTEGER ::   ji, jj, jk   ! dummy loop indice
202      !! ---------------------------------------------------------------------
203      !
204      CALL zdf_bfr( kt )                        !* bottom friction (if quadratic)
205      !                       
206      SELECT CASE ( nzdf_phy )                  !* Vertical eddy viscosity and diffusivity coefficients at w-points
207      CASE( np_RIC )   ;   CALL zdf_ric( kt )         ! Richardson number dependent Kz
208      CASE( np_TKE )   ;   CALL zdf_tke( kt )         ! TKE closure scheme for Kz
209      CASE( np_GLS )   ;   CALL zdf_gls( kt )         ! GLS closure scheme for Kz
210      CASE( np_CST )                                  ! Constant Kz (reset avt, avm to the background value)
211         avt(2:jpim1,2:jpjm1,1:jpkm1) = rn_avt0 * wmask(2:jpim1,2:jpjm1,1:jpkm1)
212         avm(2:jpim1,2:jpjm1,1:jpkm1) = rn_avm0 * wmask(2:jpim1,2:jpjm1,1:jpkm1)
213      END SELECT
214      !
215      IF( ln_rnf_mouth ) THEN                   !* increase diffusivity at rivers mouths
216         DO jk = 2, nkrnf
217            avt(:,:,jk) = avt(:,:,jk) + 2._wp * rn_avt_rnf * rnfmsk(:,:) * wmask(:,:,jk)
218         END DO
219      ENDIF
220      !
221      IF( ln_zdfevd )   CALL zdf_evd( kt )      !* convection: enhanced vertical eddy diffusivity
222      !
223      !                                         !* double diffusive mixing
224      IF( ln_zdfddm ) THEN                            ! update avt and compute avs
225                        CALL zdf_ddm( kt )
226      ELSE                                            ! same mixing on all tracers
227         avs(2:jpim1,2:jpjm1,1:jpkm1) = avt(2:jpim1,2:jpjm1,1:jpkm1)
228      ENDIF
229      !
230      !                                         !* wave-induced mixing
231      IF( ln_zdfswm )   CALL zdf_swm( kt )            ! surface  wave (Qiao et al. 2004)
232      IF( ln_zdfiwm )   CALL zdf_iwm( kt )            ! internal wave (de Lavergne et al 2017)
233
234
235      !                                         !* Lateral boundary conditions (sign unchanged)
236      CALL lbc_lnk( avm, 'W', 1. )
237      CALL lbc_lnk( avt, 'W', 1. )
238      CALL lbc_lnk( avs, 'W', 1. )
239      !
240!!gm  ===>>>   TO BE REMOVED
241      DO jk = 1, jpkm1            !* vertical eddy viscosity at wu- and wv-points
242         DO jj = 2, jpjm1
243            DO ji = 2, jpim1
244               avmu(ji,jj,jk) = 0.5 * ( avm(ji,jj,jk) + avm(ji+1,jj  ,jk) ) * wumask(ji,jj,jk)
245               avmv(ji,jj,jk) = 0.5 * ( avm(ji,jj,jk) + avm(ji  ,jj+1,jk) ) * wvmask(ji,jj,jk)
246            END DO
247         END DO
248      END DO
249      CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. )      ! Lateral boundary conditions
250!!gm end
251
252
253      CALL zdf_mxl( kt )                        !* mixed layer depth, and level
254
255!!gm  !==>> to be moved in zdftke & zdfgls   
256                                                      ! write TKE or GLS information in the restart file
257      IF( lrst_oce .AND. ln_zdftke )   CALL tke_rst( kt, 'WRITE' )
258      IF( lrst_oce .AND. ln_zdfgls )   CALL gls_rst( kt, 'WRITE' )
259      !     
260   END SUBROUTINE zdf_phy
261
262   !!======================================================================
263END MODULE zdfphy
Note: See TracBrowser for help on using the repository browser.