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.
zdfric.F90 in branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

  • Property svn:keywords set to Id
File size: 15.9 KB
Line 
1MODULE zdfric
2   !!======================================================================
3   !!                       ***  MODULE  zdfric  ***
4   !! Ocean physics:  vertical mixing coefficient compute from the local
5   !!                 Richardson number dependent formulation
6   !!======================================================================
7   !! History :  OPA  ! 1987-09  (P. Andrich)  Original code
8   !!            4.0  ! 1991-11  (G. Madec)
9   !!            7.0  ! 1996-01  (G. Madec)  complete rewriting of multitasking suppression of common work arrays
10   !!            8.0  ! 1997-06  (G. Madec)  complete rewriting of zdfmix
11   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module
12   !!            3.3  ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase
13   !!            3.3.1! 2011-09  (P. Oddo) Mixed layer depth parameterization
14   !!----------------------------------------------------------------------
15#if defined key_zdfric
16   !!----------------------------------------------------------------------
17   !!   'key_zdfric'                                             Kz = f(Ri)
18   !!----------------------------------------------------------------------
19   !!   zdf_ric       : update momentum and tracer Kz from the Richardson
20   !!                  number computation
21   !!   zdf_ric_init  : initialization, namelist read, & parameters control
22   !!----------------------------------------------------------------------
23   USE oce            ! ocean dynamics and tracers variables
24   USE dom_oce        ! ocean space and time domain variables
25   USE zdf_oce        ! ocean vertical physics
26   USE in_out_manager ! I/O manager
27   USE lbclnk         ! ocean lateral boundary condition (or mpp link)
28   USE lib_mpp        ! MPP library
29   USE timing         ! Timing
30   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
31
32   USE eosbn2, ONLY : neos
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   zdf_ric         ! called by step.F90
38   PUBLIC   zdf_ric_init    ! called by opa.F90
39
40   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .TRUE.   !: Richardson vertical mixing flag
41
42   !                           !!* Namelist namzdf_ric : Richardson number dependent Kz *
43   INTEGER  ::   nn_ric         ! coefficient of the parameterization
44   REAL(wp) ::   rn_avmri       ! maximum value of the vertical eddy viscosity
45   REAL(wp) ::   rn_alp         ! coefficient of the parameterization
46   REAL(wp) ::   rn_ekmfc       ! Ekman Factor Coeff
47   REAL(wp) ::   rn_mldmin      ! minimum mixed layer (ML) depth   
48   REAL(wp) ::   rn_mldmax      ! maximum mixed layer depth
49   REAL(wp) ::   rn_wtmix       ! Vertical eddy Diff. in the ML
50   REAL(wp) ::   rn_wvmix       ! Vertical eddy Visc. in the ML
51   LOGICAL  ::   ln_mldw        ! Use or not the MLD parameters
52
53   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tmric   !: coef. for the horizontal mean at t-point
54
55   !! * Substitutions
56#  include "vectopt_loop_substitute.h90"
57   !!----------------------------------------------------------------------
58   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
59   !! $Id$
60   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
61   !!----------------------------------------------------------------------
62CONTAINS
63
64   INTEGER FUNCTION zdf_ric_alloc()
65      !!----------------------------------------------------------------------
66      !!                 ***  FUNCTION zdf_ric_alloc  ***
67      !!----------------------------------------------------------------------
68      ALLOCATE( tmric(jpi,jpj,jpk)   , STAT= zdf_ric_alloc )
69      !
70      IF( lk_mpp             )   CALL mpp_sum ( zdf_ric_alloc )
71      IF( zdf_ric_alloc /= 0 )   CALL ctl_warn('zdf_ric_alloc: failed to allocate arrays')
72   END FUNCTION zdf_ric_alloc
73
74
75   SUBROUTINE zdf_ric( kt )
76      !!----------------------------------------------------------------------
77      !!                 ***  ROUTINE zdfric  ***
78      !!                   
79      !! ** Purpose :   Compute the before eddy viscosity and diffusivity as
80      !!                a function of the local richardson number.
81      !!
82      !! ** Method  :   Local richardson number dependent formulation of the
83      !!                vertical eddy viscosity and diffusivity coefficients.
84      !!                The eddy coefficients are given by:
85      !!                    avm = avm0 + avmb
86      !!                    avt = avm0 / (1 + rn_alp*ri)
87      !!                with ri  = N^2 / dz(u)**2
88      !!                         = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ]
89      !!                    avm0= rn_avmri / (1 + rn_alp*ri)**nn_ric
90      !!      Where ri is the before local Richardson number,
91      !!            rn_avmri is the maximum value reaches by avm and avt
92      !!            avmb and avtb are the background (or minimum) values
93      !!            and rn_alp, nn_ric are adjustable parameters.
94      !!      Typical values used are : avm0=1.e-2 m2/s, avmb=1.e-6 m2/s
95      !!      avtb=1.e-7 m2/s, rn_alp=5. and nn_ric=2.
96      !!      a numerical threshold is impose on the vertical shear (1.e-20)
97      !!      As second step compute Ekman depth from wind stress forcing
98      !!      and apply namelist provided vertical coeff within this depth.
99      !!      The Ekman depth is:
100      !!              Ustar = SQRT(Taum/rho0)
101      !!              ekd= rn_ekmfc * Ustar / f0
102      !!      Large et al. (1994, eq.29) suggest rn_ekmfc=0.7; however, the derivation
103      !!      of the above equation indicates the value is somewhat arbitrary; therefore
104      !!      we allow the freedom to increase or decrease this value, if the
105      !!      Ekman depth estimate appears too shallow or too deep, respectively.
106      !!      Ekd is then limited by rn_mldmin and rn_mldmax provided in the
107      !!      namelist
108      !!        N.B. the mask are required for implicit scheme, and surface
109      !!      and bottom value already set in zdfini.F90
110      !!
111      !! References : Pacanowski & Philander 1981, JPO, 1441-1451.
112      !!              PFJ Lermusiaux 2001.
113      !!----------------------------------------------------------------------
114      USE phycst,   ONLY:   rsmall,rau0
115      USE sbc_oce,  ONLY:   taum
116      !!
117      INTEGER, INTENT( in ) ::   kt                           ! ocean time-step
118      !!
119      INTEGER  ::   ji, jj, jk                                ! dummy loop indices
120      REAL(wp) ::   zcoef, zdku, zdkv, zri, z05alp, zflageos  ! temporary scalars
121      REAL(wp) ::   zrhos, zustar
122      REAL(wp), DIMENSION(jpi,jpj) ::   zwx, ekm_dep 
123      !!----------------------------------------------------------------------
124      !
125      IF( nn_timing == 1 )  CALL timing_start('zdf_ric')
126      !
127      !                                                ! ===============
128      DO jk = 2, jpkm1                                 ! Horizontal slab
129         !                                             ! ===============
130         ! Richardson number (put in zwx(ji,jj))
131         ! -----------------
132         DO jj = 2, jpjm1
133            DO ji = fs_2, fs_jpim1
134               zcoef = 0.5 / e3w_n(ji,jj,jk)
135               !                                            ! shear of horizontal velocity
136               zdku = zcoef * (  ub(ji-1,jj,jk-1) + ub(ji,jj,jk-1)   &
137                  &             -ub(ji-1,jj,jk  ) - ub(ji,jj,jk  )  )
138               zdkv = zcoef * (  vb(ji,jj-1,jk-1) + vb(ji,jj,jk-1)   &
139                  &             -vb(ji,jj-1,jk  ) - vb(ji,jj,jk  )  )
140               !                                            ! richardson number (minimum value set to zero)
141               zri = rn2(ji,jj,jk) / ( zdku*zdku + zdkv*zdkv + 1.e-20 )
142               zwx(ji,jj) = MAX( zri, 0.e0 )
143            END DO
144         END DO
145         CALL lbc_lnk( zwx, 'W', 1. )                       ! Boundary condition   (sign unchanged)
146
147         ! Vertical eddy viscosity and diffusivity coefficients
148         ! -------------------------------------------------------
149         z05alp = 0.5_wp * rn_alp
150         DO jj = 1, jpjm1                                   ! Eddy viscosity coefficients (avm)
151            DO ji = 1, fs_jpim1
152               avmu(ji,jj,jk) = umask(ji,jj,jk) * rn_avmri / ( 1. + z05alp*( zwx(ji+1,jj)+zwx(ji,jj) ) )**nn_ric
153               avmv(ji,jj,jk) = vmask(ji,jj,jk) * rn_avmri / ( 1. + z05alp*( zwx(ji,jj+1)+zwx(ji,jj) ) )**nn_ric
154            END DO
155         END DO
156         DO jj = 2, jpjm1                                   ! Eddy diffusivity coefficients (avt)
157            DO ji = fs_2, fs_jpim1
158               avt(ji,jj,jk) = tmric(ji,jj,jk) / ( 1._wp + rn_alp * zwx(ji,jj) )           &
159                  &                            * (  avmu(ji,jj,jk) + avmu(ji-1,jj,jk)      &
160                  &                               + avmv(ji,jj,jk) + avmv(ji,jj-1,jk)  )   &
161                  &          + avtb(jk) * tmask(ji,jj,jk)
162            END DO
163         END DO
164         DO jj = 2, jpjm1                                   ! Add the background coefficient on eddy viscosity
165            DO ji = fs_2, fs_jpim1
166               avmu(ji,jj,jk) = avmu(ji,jj,jk) + avmb(jk) * umask(ji,jj,jk)
167               avmv(ji,jj,jk) = avmv(ji,jj,jk) + avmb(jk) * vmask(ji,jj,jk)
168            END DO
169         END DO
170         !                                             ! ===============
171      END DO                                           !   End of slab
172      !                                                ! ===============
173      !
174      IF( ln_mldw ) THEN
175
176      !  Compute Ekman depth from wind stress forcing.
177      ! -------------------------------------------------------
178      zflageos = ( 0.5 + SIGN( 0.5, neos - 1. ) ) * rau0
179      DO jj = 2, jpjm1
180            DO ji = fs_2, fs_jpim1
181            zrhos          = rhop(ji,jj,1) + zflageos * ( 1. - tmask(ji,jj,1) )
182            zustar         = SQRT( taum(ji,jj) / ( zrhos +  rsmall ) )
183            ekm_dep(ji,jj) = rn_ekmfc * zustar / ( ABS( ff(ji,jj) ) + rsmall )
184            ekm_dep(ji,jj) = MAX(ekm_dep(ji,jj),rn_mldmin) ! Minimun allowed
185            ekm_dep(ji,jj) = MIN(ekm_dep(ji,jj),rn_mldmax) ! Maximum allowed
186         END DO
187      END DO
188
189      ! In the first model level vertical diff/visc coeff.s
190      ! are always equal to the namelist values rn_wtmix/rn_wvmix
191      ! -------------------------------------------------------
192      DO jj = 2, jpjm1
193         DO ji = fs_2, fs_jpim1
194            avmv(ji,jj,1) = MAX( avmv(ji,jj,1), rn_wvmix )
195            avmu(ji,jj,1) = MAX( avmu(ji,jj,1), rn_wvmix )
196            avt( ji,jj,1) = MAX(  avt(ji,jj,1), rn_wtmix )
197         END DO
198      END DO
199
200      !  Force the vertical mixing coef within the Ekman depth
201      ! -------------------------------------------------------
202      DO jk = 2, jpkm1
203         DO jj = 2, jpjm1
204            DO ji = fs_2, fs_jpim1
205               IF( gdept_n(ji,jj,jk) < ekm_dep(ji,jj) ) THEN
206                  avmv(ji,jj,jk) = MAX( avmv(ji,jj,jk), rn_wvmix )
207                  avmu(ji,jj,jk) = MAX( avmu(ji,jj,jk), rn_wvmix )
208                  avt( ji,jj,jk) = MAX(  avt(ji,jj,jk), rn_wtmix )
209               ENDIF
210            END DO
211         END DO
212      END DO
213
214      DO jk = 1, jpkm1               
215         DO jj = 2, jpjm1
216            DO ji = fs_2, fs_jpim1
217               avmv(ji,jj,jk) = avmv(ji,jj,jk) * vmask(ji,jj,jk)
218               avmu(ji,jj,jk) = avmu(ji,jj,jk) * umask(ji,jj,jk)
219               avt( ji,jj,jk) = avt( ji,jj,jk) * tmask(ji,jj,jk)
220            END DO
221         END DO
222      END DO
223
224     ENDIF
225
226      CALL lbc_lnk( avt , 'W', 1. )                         ! Boundary conditions   (unchanged sign)
227      CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. )
228      !
229      !
230      IF( nn_timing == 1 )  CALL timing_stop('zdf_ric')
231      !
232   END SUBROUTINE zdf_ric
233
234
235   SUBROUTINE zdf_ric_init
236      !!----------------------------------------------------------------------
237      !!                 ***  ROUTINE zdfbfr_init  ***
238      !!                   
239      !! ** Purpose :   Initialization of the vertical eddy diffusivity and
240      !!      viscosity coef. for the Richardson number dependent formulation.
241      !!
242      !! ** Method  :   Read the namzdf_ric namelist and check the parameter values
243      !!
244      !! ** input   :   Namelist namzdf_ric
245      !!
246      !! ** Action  :   increase by 1 the nstop flag is setting problem encounter
247      !!----------------------------------------------------------------------
248      INTEGER :: ji, jj, jk   ! dummy loop indices
249      INTEGER ::   ios        ! Local integer output status for namelist read
250      !!
251      NAMELIST/namzdf_ric/ rn_avmri, rn_alp   , nn_ric  , rn_ekmfc,  &
252         &                rn_mldmin, rn_mldmax, rn_wtmix, rn_wvmix, ln_mldw
253      !!----------------------------------------------------------------------
254      !
255      REWIND( numnam_ref )              ! Namelist namzdf_ric in reference namelist : Vertical diffusion Kz depends on Richardson number
256      READ  ( numnam_ref, namzdf_ric, IOSTAT = ios, ERR = 901)
257901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in reference namelist', lwp )
258
259      REWIND( numnam_cfg )              ! Namelist namzdf_ric in configuration namelist : Vertical diffusion Kz depends on Richardson number
260      READ  ( numnam_cfg, namzdf_ric, IOSTAT = ios, ERR = 902 )
261902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in configuration namelist', lwp )
262      IF(lwm) WRITE ( numond, namzdf_ric )
263      !
264      IF(lwp) THEN                   ! Control print
265         WRITE(numout,*)
266         WRITE(numout,*) 'zdf_ric : Ri depend vertical mixing scheme'
267         WRITE(numout,*) '~~~~~~~'
268         WRITE(numout,*) '   Namelist namzdf_ric : set Kz(Ri) parameters'
269         WRITE(numout,*) '      maximum vertical viscosity     rn_avmri  = ', rn_avmri
270         WRITE(numout,*) '      coefficient                    rn_alp    = ', rn_alp
271         WRITE(numout,*) '      coefficient                    nn_ric    = ', nn_ric
272         WRITE(numout,*) '      Ekman Factor Coeff             rn_ekmfc  = ', rn_ekmfc
273         WRITE(numout,*) '      minimum mixed layer depth      rn_mldmin = ', rn_mldmin
274         WRITE(numout,*) '      maximum mixed layer depth      rn_mldmax = ', rn_mldmax
275         WRITE(numout,*) '      Vertical eddy Diff. in the ML  rn_wtmix  = ', rn_wtmix
276         WRITE(numout,*) '      Vertical eddy Visc. in the ML  rn_wvmix  = ', rn_wvmix
277         WRITE(numout,*) '      Use the MLD parameterization   ln_mldw   = ', ln_mldw
278      ENDIF
279      !
280      !                              ! allocate zdfric arrays
281      IF( zdf_ric_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_ric_init : unable to allocate arrays' )
282      !
283      DO jk = 1, jpk                 ! weighting mean array tmric for 4 T-points
284         DO jj = 2, jpj              ! which accounts for coastal boundary conditions           
285            DO ji = 2, jpi
286               tmric(ji,jj,jk) =  tmask(ji,jj,jk)                                  &
287                  &            / MAX( 1.,  umask(ji-1,jj  ,jk) + umask(ji,jj,jk)   &
288                  &                      + vmask(ji  ,jj-1,jk) + vmask(ji,jj,jk)  )
289            END DO
290         END DO
291      END DO
292      tmric(:,1,:) = 0._wp
293      !
294      DO jk = 1, jpk                 ! Initialization of vertical eddy coef. to the background value
295         avt (:,:,jk) = avtb(jk) * tmask(:,:,jk)
296         avmu(:,:,jk) = avmb(jk) * umask(:,:,jk)
297         avmv(:,:,jk) = avmb(jk) * vmask(:,:,jk)
298      END DO
299      !
300   END SUBROUTINE zdf_ric_init
301
302#else
303   !!----------------------------------------------------------------------
304   !!   Dummy module :              NO Richardson dependent vertical mixing
305   !!----------------------------------------------------------------------
306   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .FALSE.   !: Richardson mixing flag
307CONTAINS
308   SUBROUTINE zdf_ric_init         ! Dummy routine
309   END SUBROUTINE zdf_ric_init
310   SUBROUTINE zdf_ric( kt )        ! Dummy routine
311      WRITE(*,*) 'zdf_ric: You should not have seen this print! error?', kt
312   END SUBROUTINE zdf_ric
313#endif
314
315   !!======================================================================
316END MODULE zdfric
Note: See TracBrowser for help on using the repository browser.