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/wrk_OMP_test_for_Silvia/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2017/wrk_OMP_test_for_Silvia/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90 @ 8056

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

wrk_OMP: 2nd step: small error correction in zdfric & zdftke

  • Property svn:keywords set to Id
File size: 12.8 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   !!            4.0  !  2017-04  (G. Madec)  remove CPP ddm key & avm at t-point only
15   !!----------------------------------------------------------------------
16
17   !!----------------------------------------------------------------------
18   !!   zdf_ric_init  : initialization, namelist read, & parameters control
19   !!   zdf_ric       : update momentum and tracer Kz from the Richardson number
20   !!   ric_rst       : read/write RIC restart in ocean restart file
21   !!----------------------------------------------------------------------
22   USE oce            ! ocean dynamics and tracers variables
23   USE dom_oce        ! ocean space and time domain variables
24   USE zdf_oce        ! vertical physics: variables
25   USE phycst         ! physical constants
26   USE sbc_oce,  ONLY :   taum
27   USE eosbn2 ,  ONLY :   neos
28   !
29   USE in_out_manager ! I/O manager
30   USE iom            ! I/O manager library
31   USE timing         ! Timing
32   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
33
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   zdf_ric         ! called by zdfphy.F90
39   PUBLIC   ric_rst         ! called by zdfphy.F90
40   PUBLIC   zdf_ric_init    ! called by nemogcm.F90
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   !! * Substitutions
54#  include "domain_substitute.h90"
55   !!----------------------------------------------------------------------
56   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
57   !! $Id$
58   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
59   !!----------------------------------------------------------------------
60CONTAINS
61
62   SUBROUTINE zdf_ric_init
63      !!----------------------------------------------------------------------
64      !!                 ***  ROUTINE zdfbfr_init  ***
65      !!                   
66      !! ** Purpose :   Initialization of the vertical eddy diffusivity and
67      !!      viscosity coef. for the Richardson number dependent formulation.
68      !!
69      !! ** Method  :   Read the namzdf_ric namelist and check the parameter values
70      !!
71      !! ** input   :   Namelist namzdf_ric
72      !!
73      !! ** Action  :   increase by 1 the nstop flag is setting problem encounter
74      !!----------------------------------------------------------------------
75      INTEGER :: ji, jj, jk   ! dummy loop indices
76      INTEGER ::   ios        ! Local integer output status for namelist read
77      !!
78      NAMELIST/namzdf_ric/ rn_avmri, rn_alp   , nn_ric  , rn_ekmfc,  &
79         &                rn_mldmin, rn_mldmax, rn_wtmix, rn_wvmix, ln_mldw
80      !!----------------------------------------------------------------------
81      !
82      REWIND( numnam_ref )              ! Namelist namzdf_ric in reference namelist : Vertical diffusion Kz depends on Richardson number
83      READ  ( numnam_ref, namzdf_ric, IOSTAT = ios, ERR = 901)
84901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in reference namelist', lwp )
85
86      REWIND( numnam_cfg )              ! Namelist namzdf_ric in configuration namelist : Vertical diffusion Kz depends on Richardson number
87      READ  ( numnam_cfg, namzdf_ric, IOSTAT = ios, ERR = 902 )
88902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in configuration namelist', lwp )
89      IF(lwm) WRITE ( numond, namzdf_ric )
90      !
91      IF(lwp) THEN                   ! Control print
92         WRITE(numout,*)
93         WRITE(numout,*) 'zdf_ric : Ri depend vertical mixing scheme'
94         WRITE(numout,*) '~~~~~~~'
95         WRITE(numout,*) '   Namelist namzdf_ric : set Kz=F(Ri) parameters'
96         WRITE(numout,*) '      maximum vertical viscosity        rn_avmri  = ', rn_avmri
97         WRITE(numout,*) '      coefficient                       rn_alp    = ', rn_alp
98         WRITE(numout,*) '      exponent                          nn_ric    = ', nn_ric
99         WRITE(numout,*) '      Ekman layer enhanced mixing       ln_mldw   = ', ln_mldw
100         WRITE(numout,*) '         Ekman Factor Coeff             rn_ekmfc  = ', rn_ekmfc
101         WRITE(numout,*) '         minimum mixed layer depth      rn_mldmin = ', rn_mldmin
102         WRITE(numout,*) '         maximum mixed layer depth      rn_mldmax = ', rn_mldmax
103         WRITE(numout,*) '         Vertical eddy Diff. in the ML  rn_wtmix  = ', rn_wtmix
104         WRITE(numout,*) '         Vertical eddy Visc. in the ML  rn_wvmix  = ', rn_wvmix
105      ENDIF
106      !
107      CALL ric_rst( nit000, 'READ' )  !* read or initialize all required files
108      !
109   END SUBROUTINE zdf_ric_init
110
111
112   SUBROUTINE zdf_ric( ARG_2D, kt, pdept, p_sh2, p_avm, p_avt )
113      !!----------------------------------------------------------------------
114      !!                 ***  ROUTINE zdfric  ***
115      !!                   
116      !! ** Purpose :   Compute the before eddy viscosity and diffusivity as
117      !!                a function of the local richardson number.
118      !!
119      !! ** Method  :   Local richardson number dependent formulation of the
120      !!                vertical eddy viscosity and diffusivity coefficients.
121      !!                The eddy coefficients are given by:
122      !!                    avm = avm0 + avmb
123      !!                    avt = avm0 / (1 + rn_alp*ri)
124      !!                with Ri  = N^2 / dz(u)**2
125      !!                         = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ]
126      !!                    avm0= rn_avmri / (1 + rn_alp*Ri)**nn_ric
127      !!                where ri is the before local Richardson number,
128      !!                rn_avmri is the maximum value reaches by avm and avt
129      !!                and rn_alp, nn_ric are adjustable parameters.
130      !!                Typical values : rn_alp=5. and nn_ric=2.
131      !!
132      !!      As second step compute Ekman depth from wind stress forcing
133      !!      and apply namelist provided vertical coeff within this depth.
134      !!      The Ekman depth is:
135      !!              Ustar = SQRT(Taum/rho0)
136      !!              ekd= rn_ekmfc * Ustar / f0
137      !!      Large et al. (1994, eq.29) suggest rn_ekmfc=0.7; however, the derivation
138      !!      of the above equation indicates the value is somewhat arbitrary; therefore
139      !!      we allow the freedom to increase or decrease this value, if the
140      !!      Ekman depth estimate appears too shallow or too deep, respectively.
141      !!      Ekd is then limited by rn_mldmin and rn_mldmax provided in the
142      !!      namelist
143      !!        N.B. the mask are required for implicit scheme, and surface
144      !!      and bottom value already set in zdfphy.F90
145      !!
146      !! ** Action  :   avm, avt  mixing coeff (inner domain values only)
147      !!
148      !! References : Pacanowski & Philander 1981, JPO, 1441-1451.
149      !!              PFJ Lermusiaux 2001.
150      !!----------------------------------------------------------------------
151      INTEGER                    , INTENT(in   ) ::   ARG_2D         ! inner domain start-end i-indices
152      INTEGER                    , INTENT(in   ) ::   kt             ! ocean time-step
153      REAL(wp), DIMENSION(:,:,:) , INTENT(in   ) ::   pdept          ! depth of t-point  [m]
154      REAL(wp), DIMENSION(WRK_3D), INTENT(in   ) ::   p_sh2          ! shear production term
155      REAL(wp), DIMENSION(:,:,:) , INTENT(inout) ::   p_avm, p_avt   ! momentum and tracer Kz (w-points)
156      !!
157      INTEGER  ::   ji, jj, jk                  ! dummy loop indices
158      REAL(wp) ::   zcfRi, zav, zustar, zed     ! local scalars
159      REAL(wp), DIMENSION(WRK_2D) ::   zh_ekm   ! 2D workspace
160      !!----------------------------------------------------------------------
161      !
162      IF( nn_timing == 1 )   CALL timing_start('zdf_ric')
163      !
164      !                       !==  avm and avt = F(Richardson number)  ==!
165      DO jk = 2, jpkm1
166         DO jj = k_Jstr, k_Jend
167            DO ji = k_Jstr, k_Iend        ! coefficient = F(richardson number) (avm-weighted Ri)
168               zcfRi = 1._wp / (  1._wp + rn_alp * MAX(  0._wp , p_avm(ji,jj,jk) * rn2(ji,jj,jk) / ( p_sh2(ji,jj,jk) + 1.e-20 ) )  )
169               zav   = rn_avmri * zcfRi**nn_ric
170               !                          ! avm and avt coefficients
171               p_avm(ji,jj,jk) = MAX(  zav         , avmb(jk)  ) * wmask(ji,jj,jk)
172               p_avt(ji,jj,jk) = MAX(  zav * zcfRi , avtb(jk)  ) * wmask(ji,jj,jk)
173            END DO
174         END DO
175      END DO
176      !
177!!gm BUG <<<<====  This param can't work at low latitude
178!!gm               it provides there much to thick mixed layer ( summer 150m in GYRE configuration !!! )
179      !
180      IF( ln_mldw ) THEN      !==  set a minimum value in the Ekman layer  ==!
181         !
182         DO jj = k_Jstr, k_Jend     !* Ekman depth
183            DO ji = k_Jstr, k_Iend
184               zustar = SQRT( taum(ji,jj) * r1_rau0 )
185               zed    = rn_ekmfc * zustar / ( ABS( ff_t(ji,jj) ) + rsmall )     ! Ekman depth
186               zh_ekm(ji,jj) = MAX(  rn_mldmin , MIN( zed , rn_mldmax )  )      ! set allowed range
187            END DO
188         END DO
189         DO jk = 2, jpkm1           !* minimum mixing coeff. within the Ekman layer
190            DO jj = k_Jstr, k_Jend
191               DO ji = k_Jstr, k_Iend
192                  IF( pdept(ji,jj,jk) < zh_ekm(ji,jj) ) THEN
193                     p_avm(ji,jj,jk) = MAX(  p_avm(ji,jj,jk), rn_wvmix  ) * wmask(ji,jj,jk)
194                     p_avt(ji,jj,jk) = MAX(  p_avt(ji,jj,jk), rn_wtmix  ) * wmask(ji,jj,jk)
195                  ENDIF
196               END DO
197            END DO
198         END DO
199      ENDIF
200      !
201      IF( nn_timing == 1 )   CALL timing_stop('zdf_ric')
202      !
203   END SUBROUTINE zdf_ric
204
205
206   SUBROUTINE ric_rst( kt, cdrw )
207      !!---------------------------------------------------------------------
208      !!                   ***  ROUTINE ric_rst  ***
209      !!                     
210      !! ** Purpose :   Read or write TKE file (en) in restart file
211      !!
212      !! ** Method  :   use of IOM library
213      !!                if the restart does not contain TKE, en is either
214      !!                set to rn_emin or recomputed
215      !!----------------------------------------------------------------------
216      INTEGER         , INTENT(in) ::   kt     ! ocean time-step
217      CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
218      !
219      INTEGER ::   jit, jk    ! dummy loop indices
220      INTEGER ::   id1, id2   ! local integers
221      !!----------------------------------------------------------------------
222      !
223      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
224         !                                   ! ---------------
225         !           !* Read the restart file
226         IF( ln_rstart ) THEN
227            id1 = iom_varid( numror, 'avt_k', ldstop = .FALSE. )
228            id2 = iom_varid( numror, 'avm_k', ldstop = .FALSE. )
229            !
230            IF( MIN( id1, id2 ) > 0 ) THEN         ! restart exists => read it
231               CALL iom_get( numror, jpdom_autoglo, 'avt_k', avt_k )
232               CALL iom_get( numror, jpdom_autoglo, 'avm_k', avm_k )
233            ENDIF
234         ENDIF
235         !           !* otherwise Kz already set to the background value in zdf_phy_init
236         !
237      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
238         !                                   ! -------------------
239         IF(lwp) WRITE(numout,*) '---- ric-rst ----'
240         CALL iom_rstput( kt, nitrst, numrow, 'avt_k', avt_k )
241         CALL iom_rstput( kt, nitrst, numrow, 'avm_k', avm_k )
242         !
243      ENDIF
244      !
245   END SUBROUTINE ric_rst
246
247   !!======================================================================
248END MODULE zdfric
Note: See TracBrowser for help on using the repository browser.