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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 10.4 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)  complet 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   !!----------------------------------------------------------------------
14#if defined key_zdfric   ||   defined key_esopa
15   !!----------------------------------------------------------------------
16   !!   'key_zdfric'                                             Kz = f(Ri)
17   !!----------------------------------------------------------------------
18   !!   zdf_ric      : update momentum and tracer Kz from the Richardson
19   !!                  number computation
20   !!   zdf_ric_init : initialization, namelist read, & parameters control
21   !!----------------------------------------------------------------------
22   USE oce             ! ocean dynamics and tracers variables
23   USE dom_oce         ! ocean space and time domain variables
24   USE zdf_oce         ! ocean vertical physics
25   USE in_out_manager  ! I/O manager
26   USE lbclnk          ! ocean lateral boundary condition (or mpp link)
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   zdf_ric         ! called by step.F90
32   PUBLIC   zdf_ric_init    ! called by opa.F90
33
34   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .TRUE.   !: Richardson vertical mixing flag
35
36   !                                    !!* Namelist namzdf_ric : Richardson number dependent Kz *
37   INTEGER  ::   nn_ric   = 2            ! coefficient of the parameterization
38   REAL(wp) ::   rn_avmri = 100.e-4_wp   ! maximum value of the vertical eddy viscosity
39   REAL(wp) ::   rn_alp   =   5._wp      ! coefficient of the parameterization
40
41   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   tmric                    ! coef. for the horizontal mean at t-point
42
43   !! * Substitutions
44#  include "domzgr_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010)
47   !! $Id$
48   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE zdf_ric( kt )
53      !!----------------------------------------------------------------------
54      !!                 ***  ROUTINE zdfric  ***
55      !!                   
56      !! ** Purpose :   Compute the before eddy viscosity and diffusivity as
57      !!              a function of the local richardson number.
58      !!
59      !! ** Method  :   Local richardson number dependent formulation of the
60      !!              vertical eddy viscosity and diffusivity coefficients.
61      !!                The eddy coefficients are given by:
62      !!                    avm = avm0 + avmb
63      !!                    avt = avm0 / (1 + rn_alp*ri)
64      !!              with ri  = N^2 / dz(u)**2
65      !!                       = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ]
66      !!                   avm0= rn_avmri / (1 + rn_alp*ri)**nn_ric
67      !!      Where ri is the before local Richardson number,
68      !!            rn_avmri is the maximum value reaches by avm and avt
69      !!            avmb and avtb are the background (or minimum) values
70      !!            and rn_alp, nn_ric are adjustable parameters.
71      !!      Typical values used are : avm0=1.e-2 m2/s, avmb=1.e-6 m2/s
72      !!      avtb=1.e-7 m2/s, rn_alp=5. and nn_ric=2.
73      !!      a numerical threshold is impose on the vertical shear (1.e-20)
74      !!        N.B. the mask are required for implicit scheme, and surface
75      !!      and bottom value already set in zdfini.F90
76      !!
77      !! References : Pacanowski & Philander 1981, JPO, 1441-1451.
78      !!----------------------------------------------------------------------
79      INTEGER, INTENT( in ) ::   kt         ! ocean time-step indexocean time step
80      !!
81      INTEGER  ::   ji, jj, jk               ! dummy loop indices
82      REAL(wp) ::   zcoef, zdku, zdkv, zri, z05alp     ! temporary scalars
83      REAL(wp), DIMENSION(jpi,jpj) ::   zwx ! temporary workspace
84      !!----------------------------------------------------------------------
85
86      !                                                ! ===============
87      DO jk = 2, jpkm1                                 ! Horizontal slab
88         !                                             ! ===============
89         ! Richardson number (put in zwx(ji,jj))
90         ! -----------------
91         DO jj = 2, jpjm1
92            DO ji = 2, jpim1
93               zcoef = 0.5 / fse3w(ji,jj,jk)
94               !                                            ! shear of horizontal velocity
95               zdku = zcoef * (  ub(ji-1,jj,jk-1) + ub(ji,jj,jk-1)   &
96                  &             -ub(ji-1,jj,jk  ) - ub(ji,jj,jk  )  )
97               zdkv = zcoef * (  vb(ji,jj-1,jk-1) + vb(ji,jj,jk-1)   &
98                  &             -vb(ji,jj-1,jk  ) - vb(ji,jj,jk  )  )
99               !                                            ! richardson number (minimum value set to zero)
100               zri = rn2(ji,jj,jk) / ( zdku*zdku + zdkv*zdkv + 1.e-20 )
101               zwx(ji,jj) = MAX( zri, 0.e0 )
102            END DO
103         END DO
104         CALL lbc_lnk( zwx, 'W', 1. )                       ! Boundary condition   (sign unchanged)
105
106
107         ! Vertical eddy viscosity and diffusivity coefficients
108         ! -------------------------------------------------------
109         z05alp = 0.5 * rn_alp
110         DO jj = 1, jpjm1                                   ! Eddy viscosity coefficients (avm)
111            DO ji = 1, jpim1
112               avmu(ji,jj,jk) = umask(ji,jj,jk)   &
113                  &           * rn_avmri / ( 1. + z05alp*( zwx(ji+1,jj)+zwx(ji,jj) ) )**nn_ric
114               avmv(ji,jj,jk) = vmask(ji,jj,jk)   &
115                  &           * rn_avmri / ( 1. + z05alp*( zwx(ji,jj+1)+zwx(ji,jj) ) )**nn_ric
116            END DO
117         END DO
118         DO jj = 2, jpjm1                                   ! Eddy diffusivity coefficients (avt)
119            DO ji = 2, jpim1
120               avt(ji,jj,jk) = tmric(ji,jj,jk) / ( 1. + rn_alp * zwx(ji,jj) )   &
121                  &          * (  avmu(ji,jj,jk) + avmu(ji-1, jj ,jk)        &
122                  &             + avmv(ji,jj,jk) + avmv( ji ,jj-1,jk)  )     &
123                  &          + avtb(jk) * tmask(ji,jj,jk)
124               !                                            ! Add the background coefficient on eddy viscosity
125               avmu(ji,jj,jk) = avmu(ji,jj,jk) + avmb(jk) * umask(ji,jj,jk)
126               avmv(ji,jj,jk) = avmv(ji,jj,jk) + avmb(jk) * vmask(ji,jj,jk)
127            END DO
128         END DO
129         !                                             ! ===============
130      END DO                                           !   End of slab
131      !                                                ! ===============
132      !
133      CALL lbc_lnk( avt , 'W', 1. )                         ! Boundary conditions   (unchanged sign)
134      CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. )
135      !
136   END SUBROUTINE zdf_ric
137
138
139   SUBROUTINE zdf_ric_init
140      !!----------------------------------------------------------------------
141      !!                 ***  ROUTINE zdfbfr_init  ***
142      !!                   
143      !! ** Purpose :   Initialization of the vertical eddy diffusivity and
144      !!      viscosity coef. for the Richardson number dependent formulation.
145      !!
146      !! ** Method  :   Read the namzdf_ric namelist and check the parameter values
147      !!
148      !! ** input   :   Namelist namzdf_ric
149      !!
150      !! ** Action  :   increase by 1 the nstop flag is setting problem encounter
151      !!----------------------------------------------------------------------
152      INTEGER :: ji, jj, jk        ! dummy loop indices
153      !!
154      NAMELIST/namzdf_ric/ rn_avmri, rn_alp, nn_ric
155      !!----------------------------------------------------------------------
156      !
157      REWIND( numnam )               ! Read Namelist namzdf_ric : richardson number dependent Kz
158      READ  ( numnam, namzdf_ric )
159      !
160      IF(lwp) THEN                   ! Control print
161         WRITE(numout,*)
162         WRITE(numout,*) 'zdf_ric : Ri depend vertical mixing scheme'
163         WRITE(numout,*) '~~~~~~~'
164         WRITE(numout,*) '   Namelist namzdf_ric : set Kz(Ri) parameters'
165         WRITE(numout,*) '      maximum vertical viscosity     rn_avmri = ', rn_avmri
166         WRITE(numout,*) '      coefficient                    rn_alp   = ', rn_alp
167         WRITE(numout,*) '      coefficient                    nn_ric   = ', nn_ric
168      ENDIF
169      !
170      DO jk = 1, jpk                 ! weighting mean array tmric for 4 T-points which accounts for coastal boundary conditions.
171         DO jj = 2, jpj             
172            DO ji = 2, jpi
173               tmric(ji,jj,jk) =  tmask(ji,jj,jk)                                  &
174                  &            / MAX( 1.,  umask(ji-1,jj  ,jk) + umask(ji,jj,jk)   &
175                  &                      + vmask(ji  ,jj-1,jk) + vmask(ji,jj,jk)  )
176            END DO
177         END DO
178      END DO
179      tmric(:,1,:) = 0.e0
180      !
181      DO jk = 1, jpk                 ! Initialization of vertical eddy coef. to the background value
182         avt (:,:,jk) = avtb(jk) * tmask(:,:,jk)
183         avmu(:,:,jk) = avmb(jk) * umask(:,:,jk)
184         avmv(:,:,jk) = avmb(jk) * vmask(:,:,jk)
185      END DO
186      !
187   END SUBROUTINE zdf_ric_init
188
189#else
190   !!----------------------------------------------------------------------
191   !!   Dummy module :              NO Richardson dependent vertical mixing
192   !!----------------------------------------------------------------------
193   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .FALSE.   !: Richardson mixing flag
194CONTAINS
195   SUBROUTINE zdf_ric_init         ! Dummy routine
196   END SUBROUTINE zdf_ric_init
197   SUBROUTINE zdf_ric( kt )        ! Dummy routine
198      WRITE(*,*) 'zdf_ric: You should not have seen this print! error?', kt
199   END SUBROUTINE zdf_ric
200#endif
201
202   !!======================================================================
203END MODULE zdfric
Note: See TracBrowser for help on using the repository browser.