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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90 @ 2346

Last change on this file since 2346 was 2303, checked in by rblod, 14 years ago

Suppress old TKE see ticket #742

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