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

source: trunk/NEMO/OPA_SRC/ZDF/zdfric.F90 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.3 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#if defined key_zdfric   ||   defined key_esopa
8   !!----------------------------------------------------------------------
9   !!   'key_zdfric'                                             Kz = f(Ri)
10   !!----------------------------------------------------------------------
11   !!   zdf_ric      : update momentum and tracer Kz from the Richardson
12   !!                  number computation
13   !!   zdf_ric_init : initialization, namelist read, & parameters control
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE zdf_oce         ! ocean vertical physics
19!  USE phycst          ! physical constants
20   USE in_out_manager  ! I/O manager
21   USE lbclnk          ! ocean lateral boundary condition (or mpp link)
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC zdf_ric   ! called by step.F90
28
29   !! * Shared module variables
30   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .TRUE.   !: Richardson vertical mixing flag
31
32   !! * Module variables
33   INTEGER ::               & !!! namric   richardson number dependent Kz
34      nric  = 2                ! coefficient of the parameterization
35   REAL(wp) ::              & !!! namric   richardson number dependent Kz
36      avmri = 100.e-4_wp ,  &  ! maximum value of the vertical eddy viscosity
37      alp   =   5._wp          ! coefficient of the parameterization
38   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
39      tmric                    ! coef. for the horizontal mean at t-point
40
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44
45CONTAINS
46
47   SUBROUTINE zdf_ric( kt )
48      !!----------------------------------------------------------------------
49      !!                 ***  ROUTINE zdfric  ***
50      !!                   
51      !! ** Purpose :   Compute the before eddy viscosity and diffusivity as
52      !!      a function of the local richardson number.
53      !!
54      !! ** Method  :   Local richardson number dependent formulation of the
55      !!      vertical eddy viscosity and diffusivity coefficients. the eddy
56      !!      coefficients are given by:
57      !!              avm = avm0 + avmb
58      !!              avt = avm0 / (1 + alp*ri)
59      !!      with    ri  = N^2 / dz(u)**2
60      !!                  = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ]
61      !!              avm0= avmri / (1 + alp*ri)**nric
62      !!      Where ri is the before local Richardson number, avmri the maximum
63      !!      value reaches by the vertical eddy coefficients, avmb and avtb
64      !!      the background (or minimum) values of these coefficients for
65      !!      momemtum and tracers, and alp, nric are adjustable parameters.
66      !!      typical values used are : avm0=1.e-2 m2/s, avmb=1.e-6 m2/s
67      !!      avtb=1.e-7 m2/s, alp=5. and nric=2.
68      !!      this formulation needs ri>=0 : ri is set to zero if dz(rau)<0.
69      !!      a numerical threshold is impose on the vertical shear (1.e-20)
70      !!        N.B. the mask are required for implicit scheme, and surface
71      !!      and bottom value already set in inimix.F
72      !!
73      !! References :
74      !!      pacanowski & philander 1981, j. phys. oceanogr., 1441-1451.
75      !! History :
76      !!        !  87-09  (P. Andrich)  Original code
77      !!        !  91-11  (G. Madec)
78      !!        !  93-03  (M. Guyon)  symetrical conditions
79      !!        !  96-01  (G. Madec)  complet rewriting of multitasking
80      !!                                  suppression of common work arrays
81      !!        !  97-06 (G. Madec)  complete rewriting of zdfmix
82      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
83      !!----------------------------------------------------------------------
84      !! * Arguments
85      INTEGER, INTENT( in ) ::   kt         ! ocean time-step indexocean time step
86
87      !! * Local declarations
88      INTEGER ::   ji, jj, jk               ! dummy loop indices
89      REAL(wp) ::   &
90         zcoef, zdku, zdkv, zri, z05alp     ! temporary scalars
91      REAL(wp), DIMENSION(jpi,jpj) ::   zwx ! temporary workspace
92      !!----------------------------------------------------------------------
93      !!  OPA 9.0, LODYC-IPSL (2003)
94      !!----------------------------------------------------------------------
95
96      IF( kt == nit000  ) CALL zdf_ric_init            ! Initialization (first time-step only)
97
98      !                                                ! ===============
99      DO jk = 2, jpkm1                                 ! Horizontal slab
100         !                                             ! ===============
101         ! Richardson number (put in zwx(ji,jj))
102         ! -----------------
103         ! minimum value set to zero
104         DO jj = 2, jpjm1
105            DO ji = 2, jpim1
106               zcoef = 0.5 / fse3w(ji,jj,jk)
107               ! shear of horizontal velocity
108               zdku = zcoef * (  ub(ji-1,jj,jk-1) + ub(ji,jj,jk-1)   &
109                                -ub(ji-1,jj,jk  ) - ub(ji,jj,jk  )  )
110               zdkv = zcoef * (  vb(ji,jj-1,jk-1) + vb(ji,jj,jk-1)   &
111                                -vb(ji,jj-1,jk  ) - vb(ji,jj,jk  )  )
112               ! richardson number (minimum value set to zero)
113               zri = rn2(ji,jj,jk) / ( zdku*zdku + zdkv*zdkv + 1.e-20 )
114               zwx(ji,jj) = MAX( zri, 0.e0 )
115            END DO
116         END DO
117
118         ! Boundary condition on zwx   (sign unchanged)
119         CALL lbc_lnk( zwx, 'W', 1. )
120
121
122         ! Vertical eddy viscosity and diffusivity coefficients
123         ! -------------------------------------------------------
124         ! Eddy viscosity coefficients
125         z05alp = 0.5 * alp
126         DO jj = 1, jpjm1
127            DO ji = 1, jpim1
128               avmu(ji,jj,jk) = umask(ji,jj,jk)   &
129                              * avmri / ( 1. + z05alp*( zwx(ji+1,jj)+zwx(ji,jj) ) )**nric
130               avmv(ji,jj,jk) = vmask(ji,jj,jk)   &
131                              * avmri / ( 1. + z05alp*( zwx(ji,jj+1)+zwx(ji,jj) ) )**nric
132            END DO
133         END DO
134
135         ! Eddy diffusivity coefficients
136         DO jj = 2, jpjm1
137            DO ji = 2, jpim1
138               avt(ji,jj,jk) = tmric(ji,jj,jk) / ( 1. + alp * zwx(ji,jj) )   &
139                             * (  avmu(ji,jj,jk) + avmu(ji-1, jj ,jk)        &
140                                + avmv(ji,jj,jk) + avmv( ji ,jj-1,jk)  )     &
141                             + avtb(jk) * tmask(ji,jj,jk)
142            END DO
143         END DO
144
145         ! Add the background coefficient on eddy viscosity
146         DO jj = 2, jpjm1
147            DO ji = 2, jpim1
148               avmu(ji,jj,jk) = avmu(ji,jj,jk) + avmb(jk) * umask(ji,jj,jk)
149               avmv(ji,jj,jk) = avmv(ji,jj,jk) + avmb(jk) * vmask(ji,jj,jk)
150            END DO
151         END DO
152         !                                             ! ===============
153      END DO                                           !   End of slab
154      !                                                ! ===============
155
156      ! Boundary conditions on (avt,avmu,avmv)   (unchanged sign)
157      ! -----------------------===============
158      CALL lbc_lnk( avt , 'W', 1. )
159      CALL lbc_lnk( avmu, 'U', 1. )
160      CALL lbc_lnk( avmv, 'V', 1. )
161
162   END SUBROUTINE zdf_ric
163
164
165   SUBROUTINE zdf_ric_init
166      !!----------------------------------------------------------------------
167      !!                 ***  ROUTINE zdfbfr_init  ***
168      !!                   
169      !! ** Purpose :   Initialization of the vertical eddy diffusivity and
170      !!      viscosity coef. for the Richardson number dependent formulation.
171      !!
172      !! ** Method  :   Read the namric namelist and check the parameter values
173      !!
174      !! ** input   :   Namelist namric
175      !!
176      !! ** Action  :   increase by 1 the nstop flag is setting problem encounter
177      !!
178      !! history :
179      !!  8.5  !  02-06  (G. Madec)  original code
180      !!----------------------------------------------------------------------
181      !! * local declarations
182      INTEGER :: ji, jj, jk        ! dummy loop indices
183
184      NAMELIST/namric/ avmri, alp, nric
185      !!----------------------------------------------------------------------
186      !!  OPA 8.5, LODYC-IPSL (2002)
187      !!----------------------------------------------------------------------
188
189      ! Read Namelist namric : richardson number dependent Kz
190      ! --------------------
191      REWIND ( numnam )
192      READ   ( numnam, namric )
193
194
195      ! Parameter control and print
196      ! ---------------------------
197      ! Control print
198      IF(lwp) WRITE(numout,*)
199      IF(lwp) WRITE(numout,*) 'zdf_ric : Ri depend vertical mixing scheme'
200      IF(lwp) WRITE(numout,*) '======='
201      IF(lwp) WRITE(numout,*) '          Namelist namric : set Kz(Ri) parameters'
202
203      IF(lwp) THEN
204         WRITE(numout,*)
205         WRITE(numout,*) '             maximum vertical viscosity     avmri  = ', avmri
206         WRITE(numout,*) '             coefficient                    alp    = ', alp
207         WRITE(numout,*) '             coefficient                    nric   = ', nric
208         WRITE(numout,*)
209      ENDIF
210
211
212      ! Work arrays for Ri number formulation
213      ! -------------------------------------
214
215      ! background eddy viscosity and diffusivity profiles
216      avmb(:) = avm0
217      avtb(:) = avt0
218
219      ! background profile of avm (fit the theoretical/observational
220      !     profile shown by Krauss (1990) and avt
221!!!   avtb(:) = 1.e-5 + 2.8e-8 * gdepw(:) ! m2/s
222
223      ! Increase the background in the surface layers
224      avmb(1) = 10.  * avmb(1)      ;      avtb(1) = 10.  * avtb(1)
225      avmb(2) = 10.  * avmb(2)      ;      avtb(2) = 10.  * avtb(2)
226      avmb(3) =  5.  * avmb(3)      ;      avtb(3) =  5.  * avtb(3)
227      avmb(4) =  2.5 * avmb(4)      ;      avtb(4) =  2.5 * avtb(4)
228
229      ! weighting mean array tmric for 4 T-points which accounts for coastal boundary conditions.
230      DO jk = 1, jpk
231         DO jj = 2, jpj
232            DO ji = 2, jpi
233               tmric(ji,jj,jk) =  tmask(ji,jj,jk)                                  &
234                               / MAX( 1.,  umask(ji-1,jj  ,jk) + umask(ji,jj,jk)   &
235                                         + vmask(ji  ,jj-1,jk) + vmask(ji,jj,jk)  )
236            END DO
237         END DO
238      END DO
239
240      tmric(:,1,:) = 0.e0
241
242      ! Initialization of vertical eddy coef. to the background value
243      DO jk = 1, jpk
244         avt (:,:,jk) = avtb(jk) * tmask(:,:,jk)
245         avmu(:,:,jk) = avmb(jk) * umask(:,:,jk)
246         avmv(:,:,jk) = avmb(jk) * vmask(:,:,jk)
247      END DO
248
249   END SUBROUTINE zdf_ric_init
250
251#else
252   !!----------------------------------------------------------------------
253   !!   Dummy module :              NO Richardson dependent vertical mixing
254   !!----------------------------------------------------------------------
255   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .FALSE.   !: Richardson mixing flag
256CONTAINS
257   SUBROUTINE zdf_ric( kt )        ! Dummy routine
258      WRITE(*,*) kt 
259   END SUBROUTINE zdf_ric
260#endif
261
262   !!======================================================================
263END MODULE zdfric
Note: See TracBrowser for help on using the repository browser.