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

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90

Last change on this file was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 9.4 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
[2528]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
[3]28
29   USE in_out_manager  ! I/O manager
[1537]30   USE iom             ! IOM library
[3]31
32   IMPLICIT NONE
33   PRIVATE
34
[1559]35   PUBLIC   zdf_init   ! routine called by opa.F90
36   
[3]37   !!----------------------------------------------------------------------
[2715]38   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[1156]39   !! $Id$
[2715]40   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE zdf_init
45      !!----------------------------------------------------------------------
46      !!                  ***  ROUTINE zdf_init  ***
47      !!
48      !! ** Purpose :   initializations of the vertical ocean physics
49      !!
[297]50      !! ** Method  :   Read namelist namzdf, control logicals
[3]51      !!----------------------------------------------------------------------
52      INTEGER ::   ioptio       ! temporary scalar
[4147]53      INTEGER ::   ios
[1537]54      !!
[1601]55      NAMELIST/namzdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,   &
[1537]56         &              ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp
[3]57      !!----------------------------------------------------------------------
58
[4147]59      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
60      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901)
61901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp )
[3]62
[4147]63      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
64      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 )
65902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp )
[11101]66      IF(lwm .AND. nprint > 2) WRITE ( numond, namzdf )
[4147]67
[1559]68      IF(lwp) THEN               !* Parameter print
[3]69         WRITE(numout,*)
70         WRITE(numout,*) 'zdf_init: vertical physics'
71         WRITE(numout,*) '~~~~~~~~'
[1601]72         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters'
[1537]73         WRITE(numout,*) '      vertical eddy viscosity             rn_avm0   = ', rn_avm0
74         WRITE(numout,*) '      vertical eddy diffusivity           rn_avt0   = ', rn_avt0
75         WRITE(numout,*) '      constant background or profile      nn_avb    = ', nn_avb
76         WRITE(numout,*) '      horizontal variation for avtb       nn_havtb  = ', nn_havtb
[463]77         WRITE(numout,*) '      time splitting / backward scheme    ln_zdfexp = ', ln_zdfexp
[1537]78         WRITE(numout,*) '      number of time step                 nn_zdfexp = ', nn_zdfexp
[463]79         WRITE(numout,*) '      enhanced vertical diffusion         ln_zdfevd = ', ln_zdfevd
[1537]80         WRITE(numout,*) '         applied on momentum (=1/0)       nn_evdm   = ', nn_evdm
81         WRITE(numout,*) '      vertical coefficient for evd        rn_avevd  = ', rn_avevd
82         WRITE(numout,*) '      non-penetrative convection (npc)    ln_zdfnpc = ', ln_zdfnpc
83         WRITE(numout,*) '      npc call  frequency                 nn_npc    = ', nn_npc
84         WRITE(numout,*) '      npc print frequency                 nn_npcp   = ', nn_npcp
[11101]85         IF(lflush) CALL flush(numout)
[3]86      ENDIF
87
[1559]88      !                          !* Parameter & logical controls
89      !                          !  ----------------------------
90      !
91      !                               ! ... check of vertical mixing scheme on tracers
92      !                                              ==> will be done in trazdf module
93      !
94      !                               ! ... check of mixing coefficient
[3]95      IF(lwp) WRITE(numout,*)
[1559]96      IF(lwp) WRITE(numout,*) '   vertical mixing option :'
[3]97      ioptio = 0
98      IF( lk_zdfcst ) THEN
[1559]99         IF(lwp) WRITE(numout,*) '      constant eddy diffusion coefficients'
[3]100         ioptio = ioptio+1
101      ENDIF
102      IF( lk_zdfric ) THEN
[1559]103         IF(lwp) WRITE(numout,*) '      Richardson dependent eddy coefficients'
[3]104         ioptio = ioptio+1
105      ENDIF
[2528]106      IF( lk_zdftke ) THEN
[1559]107         IF(lwp) WRITE(numout,*) '      TKE dependent eddy coefficients'
[3]108         ioptio = ioptio+1
109      ENDIF
[2528]110      IF( lk_zdfgls ) THEN
111         IF(lwp) WRITE(numout,*) '      GLS dependent eddy coefficients'
[1239]112         ioptio = ioptio+1
113      ENDIF
[255]114      IF( lk_zdfkpp ) THEN
[1559]115         IF(lwp) WRITE(numout,*) '      KPP dependent eddy coefficients'
[255]116         ioptio = ioptio+1
117      ENDIF
[2715]118      IF( ioptio == 0 .OR. ioptio > 1 .AND. .NOT. lk_esopa )   &
[1559]119         &   CALL ctl_stop( ' one and only one vertical diffusion option has to be defined ' )
[5120]120      IF( ( lk_zdfric .OR. lk_zdfgls .OR. lk_zdfkpp ) .AND. ln_isfcav )   &
[4990]121         &   CALL ctl_stop( ' only zdfcst and zdftke were tested with ice shelves cavities ' )
[1559]122      !
123      !                               ! ... Convection
[3]124      IF(lwp) WRITE(numout,*)
[1559]125      IF(lwp) WRITE(numout,*) '   convection :'
[4677]126      !
[5386]127#if defined key_top
128      IF( ln_zdfnpc )   CALL ctl_stop( ' zdf_init: npc scheme is not working with key_top' )
129#endif
[4677]130      !
[3]131      ioptio = 0
132      IF( ln_zdfnpc ) THEN
[1559]133         IF(lwp) WRITE(numout,*) '      use non penetrative convective scheme'
[3]134         ioptio = ioptio+1
135      ENDIF
136      IF( ln_zdfevd ) THEN
[1559]137         IF(lwp) WRITE(numout,*) '      use enhanced vertical dif. scheme'
[3]138         ioptio = ioptio+1
139      ENDIF
[2528]140      IF( lk_zdftke ) THEN
[1559]141         IF(lwp) WRITE(numout,*) '      use the 1.5 turbulent closure'
[3]142      ENDIF
[2528]143      IF( lk_zdfgls ) THEN
144         IF(lwp) WRITE(numout,*) '      use the GLS closure scheme'
145      ENDIF
[255]146      IF( lk_zdfkpp ) THEN
[1559]147         IF(lwp) WRITE(numout,*) '      use the KPP closure scheme'
[255]148         IF(lk_mpp) THEN
149            IF(lwp) WRITE(numout,cform_err)
[1559]150            IF(lwp) WRITE(numout,*) 'The KPP scheme is not ready to run in MPI'
[255]151         ENDIF
152      ENDIF
[1559]153      IF ( ioptio > 1 .AND. .NOT. lk_esopa )   CALL ctl_stop( ' chose between ln_zdfnpc and ln_zdfevd' )
[2715]154      IF( ioptio == 0 .AND. .NOT.( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp ) )           &
155         CALL ctl_stop( ' except for TKE, GLS or KPP physics, a convection scheme is',   &
[474]156         &              ' required: ln_zdfevd or ln_zdfnpc logicals' )
[11101]157      !
158      IF(lwp .AND. lflush) CALL flush(numout)
[1537]159      !                               !* Background eddy viscosity and diffusivity profil
160      IF( nn_avb == 0 ) THEN                ! Define avmb, avtb from namelist parameter
161         avmb(:) = rn_avm0
162         avtb(:) = rn_avt0                     
163      ELSE                                  ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)
164         avmb(:) = rn_avm0
[4292]165         avtb(:) = rn_avt0 + ( 3.e-4_wp - 2._wp * rn_avt0 ) * 1.e-4_wp * gdepw_1d(:)   ! m2/s
[2715]166         IF(ln_sco .AND. lwp)   CALL ctl_warn( 'avtb profile not valid in sco' )
[1537]167      ENDIF
168      !
169      IF( ln_rstart ) THEN                  !  Read avmb, avtb in restart (if exist)
170         ! if ln_traadv_cen, avmb, avtb have been modified in traadv_cen2 module.
171         ! To ensure the restartability, avmb & avtb are written in the restart
172         ! file in traadv_cen2 end read here.
173         IF( iom_varid( numror, 'avmb', ldstop = .FALSE. ) > 0 ) THEN
174            CALL iom_get( numror, jpdom_unknown, 'avmb', avmb )
175            CALL iom_get( numror, jpdom_unknown, 'avtb', avtb )
176         ENDIF
177      ENDIF
178      !                                     ! 2D shape of the avtb
179      avtb_2d(:,:) = 1.e0                        ! uniform
180      !
181      IF( nn_havtb == 1 ) THEN                   ! decrease avtb in the equatorial band
182           !  -15S -5S : linear decrease from avt0 to avt0/10.
183           !  -5S  +5N : cst value avt0/10.
184           !   5N  15N : linear increase from avt0/10, to avt0
185           WHERE(-15. <= gphit .AND. gphit < -5 )   avtb_2d = (1.  - 0.09 * (gphit + 15.))
186           WHERE( -5. <= gphit .AND. gphit <  5 )   avtb_2d =  0.1
187           WHERE(  5. <= gphit .AND. gphit < 15 )   avtb_2d = (0.1 + 0.09 * (gphit -  5.))
188      ENDIF
189      !
[3]190   END SUBROUTINE zdf_init
191
192   !!======================================================================
193END MODULE zdfini
Note: See TracBrowser for help on using the repository browser.