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

source: trunk/NEMO/OPA_SRC/ZDF/zdfini.F90 @ 1537

Last change on this file since 1537 was 1537, checked in by ctlod, 15 years ago

ensure the restartability of the 2nd order advection scheme,see ticket: 489

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 8.3 KB
Line 
1MODULE zdfini
2   !!======================================================================
3   !!              ***  MODULE  zdfini  ***
4   !! Ocean physics : define vertical mixing variables
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   zdf_init    : initialization, namelist read, and parameters control
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE par_oce         ! mesh and scale factors
12   USE ldftra_oce      ! ocean active tracers: lateral physics
13   USE ldfdyn_oce      ! ocean dynamics lateral physics
14   USE zdf_oce         ! TKE vertical mixing         
15   USE lib_mpp         ! distribued memory computing
16   USE zdftke_old      ! TKE vertical mixing  (old scheme)
17   USE zdftke          ! TKE vertical mixing
18   USE zdfkpp          ! KPP vertical mixing         
19   USE zdfddm          ! double diffusion mixing     
20   USE zdfevd          ! enhanced vertical diffusion 
21   USE zdfric          ! Richardson vertical mixing   
22   USE tranpc          ! convection: non penetrative adjustment
23   USE ldfslp          ! iso-neutral slopes
24   USE restart         ! ocean restart
25
26   USE in_out_manager  ! I/O manager
27   USE iom             ! IOM library
28
29   IMPLICIT NONE
30   PRIVATE
31
32   !! *  Routine accessibility
33   PUBLIC zdf_init          ! routine called by opa.F90
34   !!----------------------------------------------------------------------
35   !!   OPA 9.0 , LOCEAN-IPSL (2005)
36   !! $Id$
37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39   
40CONTAINS
41
42   SUBROUTINE zdf_init
43      !!----------------------------------------------------------------------
44      !!                  ***  ROUTINE zdf_init  ***
45      !!
46      !! ** Purpose :   initializations of the vertical ocean physics
47      !!
48      !! ** Method  :   Read namelist namzdf, control logicals
49      !!
50      !! History :
51      !!        !  97-06  (G. Madec)  Original code from inimix
52      !!   8.5  !  02-08  (G. Madec)  F90 : free form
53      !!   9.0  !  05-06  (C. Ethe) KPP parameterization
54      !!----------------------------------------------------------------------
55      INTEGER ::   ioptio       ! temporary scalar
56      !!
57      NAMELIST/nam_zdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,   &
58         &              ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp
59      !!----------------------------------------------------------------------
60
61      REWIND( numnam )               ! Read nam_zdf namelist : vertical mixing parameters
62      READ  ( numnam, nam_zdf )
63
64      IF(lwp) THEN                   ! Parameter print
65         WRITE(numout,*)
66         WRITE(numout,*) 'zdf_init: vertical physics'
67         WRITE(numout,*) '~~~~~~~~'
68         WRITE(numout,*) '   Namelist nam_zdf : set vertical mixing mixing parameters'
69         WRITE(numout,*) '      vertical eddy viscosity             rn_avm0   = ', rn_avm0
70         WRITE(numout,*) '      vertical eddy diffusivity           rn_avt0   = ', rn_avt0
71         WRITE(numout,*) '      constant background or profile      nn_avb    = ', nn_avb
72         WRITE(numout,*) '      horizontal variation for avtb       nn_havtb  = ', nn_havtb
73         WRITE(numout,*) '      time splitting / backward scheme    ln_zdfexp = ', ln_zdfexp
74         WRITE(numout,*) '      number of time step                 nn_zdfexp = ', nn_zdfexp
75         WRITE(numout,*) '      enhanced vertical diffusion         ln_zdfevd = ', ln_zdfevd
76         WRITE(numout,*) '         applied on momentum (=1/0)       nn_evdm   = ', nn_evdm
77         WRITE(numout,*) '      vertical coefficient for evd        rn_avevd  = ', rn_avevd
78         WRITE(numout,*) '      non-penetrative convection (npc)    ln_zdfnpc = ', ln_zdfnpc
79         WRITE(numout,*) '      npc call  frequency                 nn_npc    = ', nn_npc
80         WRITE(numout,*) '      npc print frequency                 nn_npcp   = ', nn_npcp
81      ENDIF
82
83      ! Parameter & logicals controls
84      ! -----------------------------
85      ! ... check of vertical mixing scheme on tracers
86      !           ==> will be done in trazdf module
87
88      ! ... check of mixing coefficient
89      IF(lwp) WRITE(numout,*)
90      IF(lwp) WRITE(numout,*) '          vertical mixing option :'
91      ioptio = 0
92      IF( lk_zdfcst ) THEN
93         IF(lwp) WRITE(numout,*) '             constant eddy diffusion coefficients'
94         ioptio = ioptio+1
95      ENDIF
96      IF( lk_zdfric ) THEN
97         IF(lwp) WRITE(numout,*) '             Richardson dependent eddy coefficients'
98         ioptio = ioptio+1
99      ENDIF
100      IF( lk_zdftke_old ) THEN
101         IF(lwp) WRITE(numout,*) '             TKE dependent eddy coefficients'
102         ioptio = ioptio+1
103      ENDIF
104      IF( lk_zdftke ) THEN
105         IF(lwp) WRITE(numout,*) '             TKE dependent eddy coefficients'
106         ioptio = ioptio+1
107      ENDIF
108      IF( lk_zdfkpp ) THEN
109         IF(lwp) WRITE(numout,*) '             KPP dependent eddy coefficients'
110         ioptio = ioptio+1
111      ENDIF
112      IF( ioptio == 0 .OR. ioptio > 1 .AND. .NOT. lk_esopa ) &
113         CALL ctl_stop( ' one and only one vertical diffusion option has to be defined ' )
114
115      ! ... Convection
116      IF(lwp) WRITE(numout,*)
117      IF(lwp) WRITE(numout,*) '          convection :'
118      ioptio = 0
119      IF( ln_zdfnpc ) THEN
120         IF(lwp) WRITE(numout,*) '             use non penetrative convective scheme'
121         ioptio = ioptio+1
122      ENDIF
123      IF( ln_zdfevd ) THEN
124         IF(lwp) WRITE(numout,*) '             use enhanced vertical dif. scheme'
125         ioptio = ioptio+1
126      ENDIF
127      IF( lk_zdftke_old .OR. lk_zdftke ) THEN
128         IF(lwp) WRITE(numout,*) '             use the 1.5 turbulent closure'
129      ENDIF
130      IF( lk_zdfkpp ) THEN
131         IF(lwp) WRITE(numout,*) '             use the KPP closure scheme'
132         IF(lk_mpp) THEN
133            IF(lwp) WRITE(numout,cform_err)
134            IF(lwp) WRITE(numout,*) '             The KPP scheme is not ready to run in MPI'
135         ENDIF
136      ENDIF
137      IF ( ioptio > 1 .AND. .NOT. lk_esopa ) &
138           CALL ctl_stop( ' chose between ln_zdfnpc', '           and ln_zdfevd' )
139      IF( ioptio == 0 .AND. .NOT.( lk_zdftke_old .OR. lk_zdftke .OR. lk_zdfkpp ) ) &
140         CALL ctl_stop( ' except for TKE sor KPP physics, a convection scheme is', &
141         &              ' required: ln_zdfevd or ln_zdfnpc logicals' )
142
143
144      !                               !* Background eddy viscosity and diffusivity profil
145      IF( nn_avb == 0 ) THEN                ! Define avmb, avtb from namelist parameter
146         avmb(:) = rn_avm0
147         avtb(:) = rn_avt0                     
148      ELSE                                  ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)
149         avmb(:) = rn_avm0
150         avtb(:) = rn_avt0 + ( 3.0e-4 - 2 * rn_avt0 ) * 1.0e-4 * gdepw_0(:)   ! m2/s
151         IF(ln_sco .AND. lwp)   CALL ctl_warn( '          avtb profile not valid in sco' )
152      ENDIF
153      !
154      IF( ln_rstart ) THEN                  !  Read avmb, avtb in restart (if exist)
155         ! if ln_traadv_cen, avmb, avtb have been modified in traadv_cen2 module.
156         ! To ensure the restartability, avmb & avtb are written in the restart
157         ! file in traadv_cen2 end read here.
158         IF( iom_varid( numror, 'avmb', ldstop = .FALSE. ) > 0 ) THEN
159            CALL iom_get( numror, jpdom_unknown, 'avmb', avmb )
160            CALL iom_get( numror, jpdom_unknown, 'avtb', avtb )
161         ENDIF
162      ENDIF
163      !                                     ! 2D shape of the avtb
164      avtb_2d(:,:) = 1.e0                        ! uniform
165      !
166      IF( nn_havtb == 1 ) THEN                   ! decrease avtb in the equatorial band
167           !  -15S -5S : linear decrease from avt0 to avt0/10.
168           !  -5S  +5N : cst value avt0/10.
169           !   5N  15N : linear increase from avt0/10, to avt0
170           WHERE(-15. <= gphit .AND. gphit < -5 )   avtb_2d = (1.  - 0.09 * (gphit + 15.))
171           WHERE( -5. <= gphit .AND. gphit <  5 )   avtb_2d =  0.1
172           WHERE(  5. <= gphit .AND. gphit < 15 )   avtb_2d = (0.1 + 0.09 * (gphit -  5.))
173      ENDIF
174      !
175   END SUBROUTINE zdf_init
176
177   !!======================================================================
178END MODULE zdfini
Note: See TracBrowser for help on using the repository browser.