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 NEMO/trunk/src/OCE/ZDF – NEMO

source: NEMO/trunk/src/OCE/ZDF/zdf_oce.F90 @ 10364

Last change on this file since 10364 was 10364, checked in by acc, 5 years ago

Introduce Adaptive-Implicit vertical advection option to the trunk. This is code merged from branches/2018/dev_r9956_ENHANCE05_ZAD_AIMP (see ticket #2042). The structure for the option is complete but is currently only successful with the flux-limited advection scheme (ln_traadv_mus). The use of this scheme with flux corrected advection schemes is not recommended until improvements to the nonoscillatory algorithm have been completed (work in progress elsewhere). The scheme is activated via a new namelist switch (ln_zad_Aimp) and is off by default.

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