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.
zdf_oce.F90 in branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF/zdf_oce.F90 @ 8093

Last change on this file since 8093 was 8093, checked in by gm, 7 years ago

#1880 (HPC-09) - step-6: prepare some forthcoming evolutions (ZDF modules mainly)

  • Property svn:keywords set to Id
File size: 4.8 KB
RevLine 
[3]1MODULE zdf_oce
2   !!======================================================================
3   !!              ***  MODULE  zdf_oce  ***
4   !! Ocean physics : define vertical mixing variables
5   !!=====================================================================
[1492]6   !! history :  1.0  !  2002-06  (G. Madec) Original code
7   !!            3.2  !  2009-07  (G.Madec) addition of avm
[3]8   !!----------------------------------------------------------------------
[2715]9   USE par_oce        ! ocean parameters
10   USE in_out_manager ! I/O manager
11   USE lib_mpp        ! MPP library
[3]12
13   IMPLICIT NONE
14   PRIVATE
15
[2715]16   PUBLIC  zdf_oce_alloc    ! Called in nemogcm.F90
17
[7990]18   !                            !!* namelist namzdf: vertical physics *
[7931]19   !                             ! vertical closure scheme flags
20   LOGICAL , PUBLIC ::   ln_zdfcst   !: constant coefficients
21   LOGICAL , PUBLIC ::   ln_zdfric   !: Richardson depend coefficients
22   LOGICAL , PUBLIC ::   ln_zdftke   !: Turbulent Kinetic Energy closure
23   LOGICAL , PUBLIC ::   ln_zdfgls   !: Generic Length Sclare closure
[7990]24   !                             ! convection
[4147]25   LOGICAL , PUBLIC ::   ln_zdfevd   !: convection: enhanced vertical diffusion flag
[7931]26   INTEGER , PUBLIC ::      nn_evdm     !: =0/1 flag to apply enhanced avm or not
27   REAL(wp), PUBLIC ::      rn_evd      !: vertical eddy coeff. for enhanced vert. diff. (m2/s)
[4147]28   LOGICAL , PUBLIC ::   ln_zdfnpc   !: convection: non-penetrative convection flag
[7931]29   INTEGER , PUBLIC ::      nn_npc      !: non penetrative convective scheme call  frequency
30   INTEGER , PUBLIC ::      nn_npcp     !: non penetrative convective scheme print frequency
[7990]31   !                             ! double diffusion
32   LOGICAL , PUBLIC ::   ln_zdfddm   !: double diffusive mixing flag
33   REAL(wp), PUBLIC ::      rn_avts     !: maximum value of avs for salt fingering
34   REAL(wp), PUBLIC ::      rn_hsbfr    !: heat/salt buoyancy flux ratio
35   !                             ! gravity wave-induced vertical mixing
36   LOGICAL , PUBLIC ::   ln_zdfswm   !: surface  wave-induced mixing flag
37   LOGICAL , PUBLIC ::   ln_zdfiwm   !: internal wave-induced mixing flag
38   !                             ! time-stepping
39   LOGICAL , PUBLIC ::   ln_zdfexp   !: explicit vertical diffusion scheme flag
40   INTEGER , PUBLIC ::      nn_zdfexp   !: number of sub-time step (explicit time stepping)
[7931]41   !                             ! coefficients
42   REAL(wp), PUBLIC ::   rn_avm0     !: vertical eddy viscosity (m2/s)
43   REAL(wp), PUBLIC ::   rn_avt0     !: vertical eddy diffusivity (m2/s)
44   INTEGER , PUBLIC ::   nn_avb      !: constant or profile background on avt (=0/1)
45   INTEGER , PUBLIC ::   nn_havtb    !: horizontal shape or not for avtb (=0/1)   !                             ! convection
[3]46
[1537]47
[8093]48   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avm, avt, avs  !: vertical mixing coefficient (w-point) [m2/s]
49!!gm
[7990]50   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avmu , avmv    !: vertical viscosity coef at uw- & vw-pts  [m2/s]
[8093]51!!gm
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   avm_k, avt_k   !: avm, avt computed by turbulent closure alone
[7990]53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   en             !: now turbulent kinetic energy   [m2/s2]
[8093]54   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   avtb_2d        !: horizontal shape of background Kz profile
[2715]55   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:)     ::   avmb , avtb    !: background profile of avm and avt
[8093]56!!gm
[7990]57   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   bfrua, bfrva   !: bottom friction coefficients
58   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   tfrua, tfrva   !: top    friction coefficients
[8093]59!!gm
[5656]60
[1492]61   !!----------------------------------------------------------------------
[8093]62   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
[1492]63   !! $Id$
[2715]64   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
65   !!----------------------------------------------------------------------
66CONTAINS
67
68   INTEGER FUNCTION zdf_oce_alloc()
69      !!----------------------------------------------------------------------
70      !!            *** FUNCTION zdf_oce_alloc ***
71      !!----------------------------------------------------------------------
72      !
[7990]73      ALLOCATE( avm  (jpi,jpj,jpk) , avt  (jpi,jpj,jpk) , avs(jpi,jpj,jpk) ,        &
74         &      avm_k(jpi,jpj,jpk) , avt_k(jpi,jpj,jpk) , en (jpi,jpj,jpk) ,        & 
75         &      avmb(jpk) , bfrua(jpi,jpj) , tfrua(jpi, jpj) ,                      &
76         &      avtb(jpk) , bfrva(jpi,jpj) , tfrva(jpi, jpj) , avtb_2d(jpi,jpj) ,   &
77         &      avmu(jpi,jpj,jpk), avmv(jpi,jpj,jpk) ,  STAT = zdf_oce_alloc )
[2715]78         !
79      IF( zdf_oce_alloc /= 0 )   CALL ctl_warn('zdf_oce_alloc: failed to allocate arrays')
80      !
81   END FUNCTION zdf_oce_alloc
82
[3]83   !!======================================================================
84END MODULE zdf_oce
Note: See TracBrowser for help on using the repository browser.