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

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90 @ 7931

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

#1880 (HPC-09): remove key_zdfddm + phasing with last changes of HPC08 branch

  • Property svn:keywords set to Id
File size: 10.9 KB
Line 
1MODULE zdfini
2   !!======================================================================
3   !!                      ***  MODULE  zdfini  ***
4   !! Ocean physics :   read vertical mixing namelist and check consistancy
5   !!======================================================================
6   !! History :  8.0  ! 1997-06  (G. Madec)  Original code from inimix
7   !!            1.0  ! 2002-08  (G. Madec)  F90 : free form
8   !!             -   ! 2005-06  (C. Ethe) KPP scheme
9   !!             -   ! 2009-07  (G. Madec) add avmb, avtb in restart for cen2 advection
10   !!            3.7  ! 2014-12  (G. Madec) remove KPP scheme
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   zdf_init    : initialization, namelist read, and parameters control
15   !!----------------------------------------------------------------------
16   USE par_oce         ! mesh and scale factors
17   USE zdf_oce         ! TKE vertical mixing         
18   USE sbc_oce         ! surface module (only for nn_isf in the option compatibility test)
19   USE zdftke          ! TKE vertical mixing
20   USE zdfgls          ! GLS vertical mixing
21   USE zdfric          ! Richardson vertical mixing   
22   USE zdfddm          ! double diffusion mixing     
23   USE zdfevd          ! enhanced vertical diffusion 
24   USE tranpc          ! convection: non penetrative adjustment
25   USE ldfslp          ! iso-neutral slopes
26   !
27   USE in_out_manager  ! I/O manager
28   USE iom             ! IOM library
29   USE lib_mpp         ! distribued memory computing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   zdf_init   ! routine called by opa.F90
35   
36   !!----------------------------------------------------------------------
37   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
38   !! $Id$
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE zdf_init
44      !!----------------------------------------------------------------------
45      !!                  ***  ROUTINE zdf_init  ***
46      !!
47      !! ** Purpose :   initializations of the vertical ocean physics
48      !!
49      !! ** Method  :   Read namelist namzdf, control logicals
50      !!----------------------------------------------------------------------
51      INTEGER ::   ioptio, ios       ! local integers
52      !!
53      NAMELIST/namzdf/ ln_zdfcst, ln_zdfric, ln_zdftke, ln_zdfgls,   &     ! type of closure scheme
54         &             ln_zdfevd, nn_evdm, rn_evd ,                  &     ! convection : evd
55         &             ln_zdfnpc, nn_npc , nn_npcp,                  &     ! convection : npc
56         &             ln_zdfddm, rn_avts, rn_hsbfr,                 &     ! double diffusion
57         &             ln_zdftmx,                                    &     ! tidal mixing
58         &             ln_zdfqiao,                                   &     ! surface wave-induced mixing
59         &             ln_zdfexp, nn_zdfexp,                         &     ! time-stepping
60         &             rn_avm0, rn_avt0, nn_avb, nn_havtb                  ! coefficients
61
62
63!!org      NAMELIST/namzdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,  &
64!!org         &        ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp,       &
65!!org         &        ln_zdfqiao
66      !!----------------------------------------------------------------------
67
68      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
69      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901)
70901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp )
71
72      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
73      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 )
74902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp )
75      IF(lwm) WRITE ( numond, namzdf )
76
77      IF(lwp) THEN               !* Parameter print
78         WRITE(numout,*)
79         WRITE(numout,*) 'zdf_init : vertical physics'
80         WRITE(numout,*) '~~~~~~~~'
81         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters'
82         WRITE(numout,*) '      vertical closure scheme'
83         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfcst = ', ln_zdfcst
84         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfric = ', ln_zdfric
85         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdftke = ', ln_zdftke
86         WRITE(numout,*) '         constant vertical mixing coefficient    ln_zdfgls = ', ln_zdfgls
87         WRITE(numout,*) '      convection: '
88         WRITE(numout,*) '         enhanced vertical diffusion             ln_zdfevd = ', ln_zdfevd
89         WRITE(numout,*) '            applied on momentum (=1/0)             nn_evdm = ', nn_evdm
90         WRITE(numout,*) '            vertical coefficient for evd           rn_evd  = ', rn_evd
91         WRITE(numout,*) '         non-penetrative convection (npc)        ln_zdfnpc = ', ln_zdfnpc
92         WRITE(numout,*) '            npc call  frequency                    nn_npc  = ', nn_npc
93         WRITE(numout,*) '            npc print frequency                    nn_npcp = ', nn_npcp
94         WRITE(numout,*) '      double diffusive mixing                    ln_zdfddm = ', ln_zdfddm
95         WRITE(numout,*) '         maximum avs for dd mixing                 rn_avts = ', rn_avts
96         WRITE(numout,*) '         heat/salt buoyancy flux ratio             rn_hsbfr= ', rn_hsbfr
97         WRITE(numout,*) '      surface wave-induced mixing                ln_zdfqiao= ', ln_zdfqiao                                          ! surface wave induced mixing
98         WRITE(numout,*) '      tidal mixing                               ln_zdftmx = ', ln_zdftmx
99         WRITE(numout,*) '      time splitting / backward scheme           ln_zdfexp = ', ln_zdfexp
100         WRITE(numout,*) '         number of sub-time step (ln_zdfexp=T)   nn_zdfexp = ', nn_zdfexp
101         WRITE(numout,*) '      coefficients : '
102         WRITE(numout,*) '      vertical eddy viscosity             rn_avm0   = ', rn_avm0
103         WRITE(numout,*) '      vertical eddy diffusivity           rn_avt0   = ', rn_avt0
104         WRITE(numout,*) '      constant background or profile      nn_avb    = ', nn_avb
105         WRITE(numout,*) '      horizontal variation for avtb       nn_havtb  = ', nn_havtb
106      ENDIF
107
108      IF(ln_zdfddm) THEN                    ! double diffusive mixing'
109         ALLOCATE( avs(jpi,jpj,jpk) )
110         avs(:,:,:) = rn_avt0 * wmask(:,:,:) 
111      ENDIF
112
113
114      !                          !* Parameter & logical controls
115      !                          !  ----------------------------
116      !
117      !                               ! ... check of vertical mixing scheme on tracers
118      !                                              ==> will be done in trazdf module
119      !
120      !                               ! ... check of mixing coefficient
121      IF(lwp) WRITE(numout,*)
122      IF(lwp) WRITE(numout,*) '   vertical mixing option :'
123      ioptio = 0
124      IF( lk_zdfcst ) THEN
125         IF(lwp) WRITE(numout,*) '      constant eddy diffusion coefficients'
126         ioptio = ioptio+1
127      ENDIF
128      IF( lk_zdfric ) THEN
129         IF(lwp) WRITE(numout,*) '      Richardson dependent eddy coefficients'
130         ioptio = ioptio+1
131      ENDIF
132      IF( lk_zdftke ) THEN
133         IF(lwp) WRITE(numout,*) '      TKE dependent eddy coefficients'
134         ioptio = ioptio+1
135      ENDIF
136      IF( lk_zdfgls ) THEN
137         IF(lwp) WRITE(numout,*) '      GLS dependent eddy coefficients'
138         ioptio = ioptio+1
139      ENDIF
140      IF( ioptio == 0 .OR. ioptio > 1 )   &
141         &   CALL ctl_stop( ' one and only one vertical diffusion option has to be defined ' )
142      IF( ( lk_zdfric .OR. lk_zdfgls ) .AND. ln_isfcav )   &
143         &   CALL ctl_stop( ' only zdfcst and zdftke were tested with ice shelves cavities ' )
144      !
145      !                               ! ... Convection
146      IF(lwp) WRITE(numout,*)
147      IF(lwp) WRITE(numout,*) '   convection :'
148      !
149#if defined key_top
150      IF( ln_zdfnpc )   CALL ctl_stop( ' zdf_init: npc scheme is not working with key_top' )
151#endif
152      !
153      ioptio = 0
154      IF( ln_zdfnpc ) THEN
155         IF(lwp) WRITE(numout,*) '      use non penetrative convective scheme'
156         ioptio = ioptio+1
157      ENDIF
158      IF( ln_zdfevd ) THEN
159         IF(lwp) WRITE(numout,*) '      use enhanced vertical dif. scheme'
160         ioptio = ioptio+1
161      ENDIF
162      IF( lk_zdftke ) THEN
163         IF(lwp) WRITE(numout,*) '      use the 1.5 turbulent closure'
164      ENDIF
165      IF( lk_zdfgls ) THEN
166         IF(lwp) WRITE(numout,*) '      use the GLS closure scheme'
167      ENDIF
168      IF ( ioptio > 1 )   CALL ctl_stop( ' chose between ln_zdfnpc and ln_zdfevd' )
169      IF( ioptio == 0 .AND. .NOT.( lk_zdftke .OR. lk_zdfgls ) )           &
170         CALL ctl_stop( ' except for TKE or GLS physics, a convection scheme is',   &
171         &              ' required: ln_zdfevd or ln_zdfnpc logicals' )
172
173      !                               !* Background eddy viscosity and diffusivity profil
174      IF( nn_avb == 0 ) THEN                ! Define avmb, avtb from namelist parameter
175         avmb(:) = rn_avm0
176         avtb(:) = rn_avt0                     
177      ELSE                                  ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)
178         avmb(:) = rn_avm0
179         avtb(:) = rn_avt0 + ( 3.e-4_wp - 2._wp * rn_avt0 ) * 1.e-4_wp * gdepw_1d(:)   ! m2/s
180         IF(ln_sco .AND. lwp)   CALL ctl_warn( 'avtb profile not valid in sco' )
181      ENDIF
182      !
183      IF( ln_rstart ) THEN                  !  Read avmb, avtb in restart (if exist)
184         ! if ln_traadv_cen, avmb, avtb have been modified in traadv_cen2 module.
185         ! To ensure the restartability, avmb & avtb are written in the restart
186         ! file in traadv_cen2 end read here.
187         IF( iom_varid( numror, 'avmb', ldstop = .FALSE. ) > 0 ) THEN
188            CALL iom_get( numror, jpdom_unknown, 'avmb', avmb )
189            CALL iom_get( numror, jpdom_unknown, 'avtb', avtb )
190         ENDIF
191      ENDIF
192      !                                     ! 2D shape of the avtb
193      avtb_2d(:,:) = 1.e0                        ! uniform
194      !
195      IF( nn_havtb == 1 ) THEN                   ! decrease avtb in the equatorial band
196           !  -15S -5S : linear decrease from avt0 to avt0/10.
197           !  -5S  +5N : cst value avt0/10.
198           !   5N  15N : linear increase from avt0/10, to avt0
199           WHERE(-15. <= gphit .AND. gphit < -5 )   avtb_2d = (1.  - 0.09 * (gphit + 15.))
200           WHERE( -5. <= gphit .AND. gphit <  5 )   avtb_2d =  0.1
201           WHERE(  5. <= gphit .AND. gphit < 15 )   avtb_2d = (0.1 + 0.09 * (gphit -  5.))
202      ENDIF
203      !
204   END SUBROUTINE zdf_init
205
206   !!======================================================================
207END MODULE zdfini
Note: See TracBrowser for help on using the repository browser.