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

source: trunk/NEMOGCM/NEMO/OPA_SRC/ZDF/zdf_oce.F90 @ 7881

Last change on this file since 7881 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • 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   !!----------------------------------------------------------------------
9   USE par_oce        ! ocean parameters
10   USE in_out_manager ! I/O manager
11   USE lib_mpp        ! MPP library
12
13   IMPLICIT NONE
14   PRIVATE
15
16   PUBLIC  zdf_oce_alloc    ! Called in nemogcm.F90
17
18#if defined key_zdfcst
19   LOGICAL, PARAMETER, PUBLIC ::   lk_zdfcst        = .TRUE.         !: constant vertical mixing flag
20#else
21   LOGICAL, PARAMETER, PUBLIC ::   lk_zdfcst        = .FALSE.        !: constant vertical mixing flag
22#endif
23
24   !                                 !!* namelist namzdf: vertical diffusion *
25   REAL(wp), PUBLIC ::   rn_avm0     !: vertical eddy viscosity (m2/s)
26   REAL(wp), PUBLIC ::   rn_avt0     !: vertical eddy diffusivity (m2/s)
27   INTEGER , PUBLIC ::   nn_avb      !: constant or profile background on avt (=0/1)
28   INTEGER , PUBLIC ::   nn_havtb    !: horizontal shape or not for avtb (=0/1)
29   LOGICAL , PUBLIC ::   ln_zdfexp   !: explicit vertical diffusion scheme flag
30   INTEGER , PUBLIC ::   nn_zdfexp   !: number of sub-time step (explicit time stepping)
31   LOGICAL , PUBLIC ::   ln_zdfevd   !: convection: enhanced vertical diffusion flag
32   INTEGER , PUBLIC ::   nn_evdm     !: =0/1 flag to apply enhanced avm or not
33   REAL(wp), PUBLIC ::   rn_avevd    !: vertical eddy coeff. for enhanced vert. diff. (m2/s)
34   LOGICAL , PUBLIC ::   ln_zdfnpc   !: convection: non-penetrative convection flag
35   INTEGER , PUBLIC ::   nn_npc      !: non penetrative convective scheme call  frequency
36   INTEGER , PUBLIC ::   nn_npcp     !: non penetrative convective scheme print frequency
37   LOGICAL , PUBLIC ::   ln_zdfqiao  !: Enhanced wave vertical mixing Qiao(2010) formulation flag
38
39
40   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:)     ::   avmb , avtb    !: background profile of avm and avt
41   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   avtb_2d        !: horizontal shape of background Kz profile
42   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   bfrua, bfrva   !: Bottom friction coefficients set in zdfbfr
43   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   tfrua, tfrva   !: top friction coefficients set in zdfbfr
44   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avmu , avmv    !: vertical viscosity coef at uw- & vw-pts       [m2/s]
45   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avm  , avt     !: vertical viscosity & diffusivity coef at w-pt [m2/s]
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   avt_k , avm_k  ! not enhanced Kz
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   avmu_k, avmv_k ! not enhanced Kz
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   en              !: now turbulent kinetic energy   [m2/s2]
49
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
52   !! $Id$
53   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55CONTAINS
56
57   INTEGER FUNCTION zdf_oce_alloc()
58      !!----------------------------------------------------------------------
59      !!            *** FUNCTION zdf_oce_alloc ***
60      !!----------------------------------------------------------------------
61      !
62      ALLOCATE(avmb(jpk) , bfrua(jpi,jpj) ,                         &
63         &     avtb(jpk) , bfrva(jpi,jpj) , avtb_2d(jpi,jpj) ,      &
64         &     tfrua(jpi, jpj), tfrva(jpi, jpj)              ,      &
65         &     avmu  (jpi,jpj,jpk), avm   (jpi,jpj,jpk)      ,      &
66         &     avmv  (jpi,jpj,jpk), avt   (jpi,jpj,jpk)      ,      &
67         &     avt_k (jpi,jpj,jpk), avm_k (jpi,jpj,jpk)      ,      & 
68         &     avmu_k(jpi,jpj,jpk), avmv_k(jpi,jpj,jpk)      ,      &
69         &     en    (jpi,jpj,jpk), 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.