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

source: trunk/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90 @ 6497

Last change on this file since 6497 was 5836, checked in by cetlod, 9 years ago

merge the simplification branch onto the trunk, see ticket #1612

  • Property svn:keywords set to Id
File size: 8.8 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
[5836]8   !!             -   ! 2005-06  (C. Ethe) KPP scheme
[1559]9   !!             -   ! 2009-07  (G. Madec) add avmb, avtb in restart for cen2 advection
[5836]10   !!            3.7  ! 2014-12  (G. Madec) remove KPP scheme
[1559]11   !!----------------------------------------------------------------------
[3]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         
[5836]18   USE sbc_oce         ! surface module (only for nn_isf in the option compatibility test)
[1533]19   USE zdftke          ! TKE vertical mixing
[2528]20   USE zdfgls          ! GLS vertical mixing
[5836]21   USE zdfric          ! Richardson vertical mixing   
[3]22   USE zdfddm          ! double diffusion mixing     
23   USE zdfevd          ! enhanced vertical diffusion 
24   USE tranpc          ! convection: non penetrative adjustment
[255]25   USE ldfslp          ! iso-neutral slopes
[5836]26   !
[3]27   USE in_out_manager  ! I/O manager
[1537]28   USE iom             ! IOM library
[5836]29   USE lib_mpp         ! distribued memory computing
[3]30
31   IMPLICIT NONE
32   PRIVATE
33
[1559]34   PUBLIC   zdf_init   ! routine called by opa.F90
35   
[3]36   !!----------------------------------------------------------------------
[2715]37   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[1156]38   !! $Id$
[2715]39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE zdf_init
44      !!----------------------------------------------------------------------
45      !!                  ***  ROUTINE zdf_init  ***
46      !!
47      !! ** Purpose :   initializations of the vertical ocean physics
48      !!
[297]49      !! ** Method  :   Read namelist namzdf, control logicals
[3]50      !!----------------------------------------------------------------------
[5836]51      INTEGER ::   ioptio, ios       ! local integers
[1537]52      !!
[1601]53      NAMELIST/namzdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,   &
[1537]54         &              ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp
[3]55      !!----------------------------------------------------------------------
56
[4147]57      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
58      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901)
59901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp )
[3]60
[4147]61      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters
62      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 )
63902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp )
[4624]64      IF(lwm) WRITE ( numond, namzdf )
[4147]65
[1559]66      IF(lwp) THEN               !* Parameter print
[3]67         WRITE(numout,*)
68         WRITE(numout,*) 'zdf_init: vertical physics'
69         WRITE(numout,*) '~~~~~~~~'
[1601]70         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters'
[1537]71         WRITE(numout,*) '      vertical eddy viscosity             rn_avm0   = ', rn_avm0
72         WRITE(numout,*) '      vertical eddy diffusivity           rn_avt0   = ', rn_avt0
73         WRITE(numout,*) '      constant background or profile      nn_avb    = ', nn_avb
74         WRITE(numout,*) '      horizontal variation for avtb       nn_havtb  = ', nn_havtb
[463]75         WRITE(numout,*) '      time splitting / backward scheme    ln_zdfexp = ', ln_zdfexp
[1537]76         WRITE(numout,*) '      number of time step                 nn_zdfexp = ', nn_zdfexp
[463]77         WRITE(numout,*) '      enhanced vertical diffusion         ln_zdfevd = ', ln_zdfevd
[1537]78         WRITE(numout,*) '         applied on momentum (=1/0)       nn_evdm   = ', nn_evdm
79         WRITE(numout,*) '      vertical coefficient for evd        rn_avevd  = ', rn_avevd
80         WRITE(numout,*) '      non-penetrative convection (npc)    ln_zdfnpc = ', ln_zdfnpc
81         WRITE(numout,*) '      npc call  frequency                 nn_npc    = ', nn_npc
82         WRITE(numout,*) '      npc print frequency                 nn_npcp   = ', nn_npcp
[3]83      ENDIF
84
[1559]85      !                          !* Parameter & logical controls
86      !                          !  ----------------------------
87      !
88      !                               ! ... check of vertical mixing scheme on tracers
89      !                                              ==> will be done in trazdf module
90      !
91      !                               ! ... check of mixing coefficient
[3]92      IF(lwp) WRITE(numout,*)
[1559]93      IF(lwp) WRITE(numout,*) '   vertical mixing option :'
[3]94      ioptio = 0
95      IF( lk_zdfcst ) THEN
[1559]96         IF(lwp) WRITE(numout,*) '      constant eddy diffusion coefficients'
[3]97         ioptio = ioptio+1
98      ENDIF
99      IF( lk_zdfric ) THEN
[1559]100         IF(lwp) WRITE(numout,*) '      Richardson dependent eddy coefficients'
[3]101         ioptio = ioptio+1
102      ENDIF
[2528]103      IF( lk_zdftke ) THEN
[1559]104         IF(lwp) WRITE(numout,*) '      TKE dependent eddy coefficients'
[3]105         ioptio = ioptio+1
106      ENDIF
[2528]107      IF( lk_zdfgls ) THEN
108         IF(lwp) WRITE(numout,*) '      GLS dependent eddy coefficients'
[1239]109         ioptio = ioptio+1
110      ENDIF
[5836]111      IF( ioptio == 0 .OR. ioptio > 1 )   &
[1559]112         &   CALL ctl_stop( ' one and only one vertical diffusion option has to be defined ' )
[5836]113      IF( ( lk_zdfric .OR. lk_zdfgls ) .AND. ln_isfcav )   &
[4990]114         &   CALL ctl_stop( ' only zdfcst and zdftke were tested with ice shelves cavities ' )
[1559]115      !
116      !                               ! ... Convection
[3]117      IF(lwp) WRITE(numout,*)
[1559]118      IF(lwp) WRITE(numout,*) '   convection :'
[4677]119      !
[5386]120#if defined key_top
121      IF( ln_zdfnpc )   CALL ctl_stop( ' zdf_init: npc scheme is not working with key_top' )
122#endif
[4677]123      !
[3]124      ioptio = 0
125      IF( ln_zdfnpc ) THEN
[1559]126         IF(lwp) WRITE(numout,*) '      use non penetrative convective scheme'
[3]127         ioptio = ioptio+1
128      ENDIF
129      IF( ln_zdfevd ) THEN
[1559]130         IF(lwp) WRITE(numout,*) '      use enhanced vertical dif. scheme'
[3]131         ioptio = ioptio+1
132      ENDIF
[2528]133      IF( lk_zdftke ) THEN
[1559]134         IF(lwp) WRITE(numout,*) '      use the 1.5 turbulent closure'
[3]135      ENDIF
[2528]136      IF( lk_zdfgls ) THEN
137         IF(lwp) WRITE(numout,*) '      use the GLS closure scheme'
138      ENDIF
[5836]139      IF ( ioptio > 1 )   CALL ctl_stop( ' chose between ln_zdfnpc and ln_zdfevd' )
140      IF( ioptio == 0 .AND. .NOT.( lk_zdftke .OR. lk_zdfgls ) )           &
141         CALL ctl_stop( ' except for TKE or GLS physics, a convection scheme is',   &
[474]142         &              ' required: ln_zdfevd or ln_zdfnpc logicals' )
[3]143
[1537]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
[4292]150         avtb(:) = rn_avt0 + ( 3.e-4_wp - 2._wp * rn_avt0 ) * 1.e-4_wp * gdepw_1d(:)   ! m2/s
[2715]151         IF(ln_sco .AND. lwp)   CALL ctl_warn( 'avtb profile not valid in sco' )
[1537]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      !
[3]175   END SUBROUTINE zdf_init
176
177   !!======================================================================
178END MODULE zdfini
Note: See TracBrowser for help on using the repository browser.