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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90 @ 4460

Last change on this file since 4460 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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