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.
zdfddm.F90 in tags/start/NEMO/OFF_SRC/ZDF – NEMO

source: tags/start/NEMO/OFF_SRC/ZDF/zdfddm.F90 @ 8345

Last change on this file since 8345 was 325, checked in by opalod, 19 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.0 KB
Line 
1MODULE zdfddm
2   !!======================================================================
3   !!                       ***  MODULE  zdfddm  ***
4   !! Ocean physics : double diffusion mixing parameterization
5   !!======================================================================
6#if defined key_zdfddm   ||   defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_zdfddm' :                                     double diffusion
9   !!----------------------------------------------------------------------
10   !!   zdf_ddm       : compute the Ks for salinity
11   !!   zdf_ddm_init  : read namelist and control the parameters
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce             ! ocean dynamics and tracers variables
15   USE dom_oce         ! ocean space and time domain variables
16   USE zdf_oce         ! ocean vertical physics variables
17   USE in_out_manager  ! I/O manager
18   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! * Routine accessibility
24   PUBLIC zdf_ddm     ! called by step.F90
25
26   !! * Shared module variables
27   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfddm = .TRUE.    !: double diffusive mixing flag
28   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &   !:
29      avs ,               &  !: salinity vertical diffusivity coeff. at w-point
30      rrau                   !: heat/salt buoyancy flux ratio
31
32   !! * Module variables
33   REAL(wp) ::            & !!! * double diffusive mixing namelist *
34      avts  = 1.e-4_wp      ! maximum value of avs for salt fingering
35
36   !! * Substitutions
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !!   OPA 9.0 , LODYC-IPSL  (2003)
40   !!----------------------------------------------------------------------
41
42CONTAINS
43
44   SUBROUTINE zdf_ddm( kt )
45      !!----------------------------------------------------------------------
46      !!                  ***  ROUTINE zdf_ddm  ***
47      !!                   
48      !! ** Purpose :   Add to the vertical eddy diffusivity coefficient the
49      !!      effect of salt fingering and diffusive convection.
50      !!
51      !! ** Method  :   Diapycnal mixing is increased in case of double
52      !!      diffusive mixing (i.e. salt fingering and diffusive layering)
53      !!      following Merryfield et al. (1999). The rate of double diffusive
54      !!      mixing depend on the buoyancy ratio: Rrau=alpha/beta dk[T]/dk[S]
55      !!      which is computed in rn2.F
56      !!         * salt fingering (Schmitt 1981):
57      !!      for Rrau > 1 and rn2 > 0 : zavfs = avts / ( 1 + (Rrau/hsbfr)^6 )
58      !!      for Rrau > 1 and rn2 > 0 : zavfs = O
59      !!      otherwise                : zavft = 0.7 zavs / Rrau
60      !!         * diffusive layering (Federov 1988):
61      !!      for 0< Rrau < 1 and rn2 > 0 : zavdt = 1.3635e-6 
62      !!                                 * exp( 4.6 exp(-0.54 (1/Rrau-1) ) )
63      !!      otherwise                   : zavdt = 0
64      !!      for .5 < Rrau < 1 and rn2 > 0 : zavds = zavdt (1.885 Rrau -0.85)
65      !!      for  0 < Rrau <.5 and rn2 > 0 : zavds = zavdt 0.15 Rrau     
66      !!      otherwise                     : zavds = 0
67      !!         * update the eddy diffusivity:
68      !!      avt = avt + zavft + zavdt
69      !!      avs = avs + zavfs + zavds
70      !!      avmu, avmv are required to remain at least above avt and avs.
71      !!     
72      !! ** Action  :   avt, avs : update vertical eddy diffusivity coef.
73      !!                           for temperature and salinity
74      !!
75      !! References :
76      !!      Merryfield et al., JPO, 29, 1124-1142, 1999.
77      !! History :
78      !!        !  00-08  (G. Madec)  double diffusive mixing
79      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
80      !!----------------------------------------------------------------------
81      !! * Arguments
82      INTEGER, INTENT( in ) ::   kt         ! ocean time-step indexocean time step
83
84      !!----------------------------------------------------------------------
85
86
87      IF ( kt == nit000 )   CALL zdf_ddm_init          ! Initialization (first time-step only)
88
89
90   END SUBROUTINE zdf_ddm
91   
92   
93   SUBROUTINE zdf_ddm_init
94      !!----------------------------------------------------------------------
95      !!                  ***  ROUTINE zdf_ddm_init  ***
96      !!
97      !! ** Purpose :   Initialization of double diffusion mixing scheme
98      !!
99      !! ** Method  :   Read the nammbf namelist and check the parameter values
100      !!      called by zdf_ddm at the first timestep (nit000)
101      !!
102      !! History :
103      !!   8.5  !  02-08  (G. Madec)  Original code
104      !!----------------------------------------------------------------------
105      NAMELIST/namddm/ avts
106      !!----------------------------------------------------------------------
107
108      ! Read Namelist namddm : double diffusion mixing scheme
109      ! --------------------
110      REWIND ( numnam )
111      READ   ( numnam, namddm )
112
113
114      ! Parameter control and print
115      ! ---------------------------
116      IF(lwp) THEN
117         WRITE(numout,*)
118         WRITE(numout,*) 'zdf_ddm : double diffusive mixing'
119         WRITE(numout,*) '~~~~~~~'
120         WRITE(numout,*) '          Namelist namddm : set dd mixing parameter'
121         WRITE(numout,*) '             maximum avs for dd mixing      avts   = ', avts
122         WRITE(numout,*)
123      ENDIF
124
125   END SUBROUTINE zdf_ddm_init
126
127#else
128   !!----------------------------------------------------------------------
129   !!   Default option :          Dummy module          No double diffusion
130   !!----------------------------------------------------------------------
131   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfddm = .FALSE.   !: double diffusion flag
132CONTAINS
133   SUBROUTINE zdf_ddm( kt )           ! Dummy routine
134      WRITE(*,*) 'zdf_ddm: You should not have seen this print! error?', kt
135   END SUBROUTINE zdf_ddm
136#endif
137
138   !!======================================================================
139END MODULE zdfddm
Note: See TracBrowser for help on using the repository browser.