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.
ldftra_oce.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/LDF – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra_oce.F90 @ 4409

Last change on this file since 4409 was 3211, checked in by spickles2, 13 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: 6.6 KB
RevLine 
[3]1MODULE ldftra_oce
2   !!=====================================================================
3   !!                      ***  MODULE  ldftra_oce  ***
4   !! Ocean physics :  lateral tracer mixing coefficient defined in memory
5   !!=====================================================================
[2715]6   !! History :  9.0  !  2002-11  (G. Madec)  Original code
[3]7   !!----------------------------------------------------------------------
[2715]8   USE par_oce        ! ocean parameters
9   USE in_out_manager ! I/O manager
10   USE lib_mpp         ! MPP library
[3]11
12   IMPLICIT NONE
13   PRIVATE
14
[2715]15   PUBLIC ldftra_oce_alloc ! called by nemo_init->nemo_alloc, nemogcm.F90
16
[3]17   !!----------------------------------------------------------------------
18   !! Lateral eddy diffusivity coefficients (tracers)
19   !!----------------------------------------------------------------------
[1601]20   !                                                !!* Namelist namtra_ldf : lateral mixing *
21   LOGICAL , PUBLIC ::   ln_traldf_lap   = .TRUE.    !: laplacian operator
22   LOGICAL , PUBLIC ::   ln_traldf_bilap = .FALSE.   !: bilaplacian operator
23   LOGICAL , PUBLIC ::   ln_traldf_level = .FALSE.   !: iso-level direction
24   LOGICAL , PUBLIC ::   ln_traldf_hor   = .FALSE.   !: horizontal (geopotential) direction
25   LOGICAL , PUBLIC ::   ln_traldf_iso   = .TRUE.    !: iso-neutral direction
[2528]26   LOGICAL , PUBLIC ::   ln_traldf_grif  = .FALSE.   !: griffies skew flux
27   LOGICAL , PUBLIC ::   ln_traldf_gdia  = .FALSE.   !: griffies skew flux streamfunction diagnostics
[1601]28   REAL(wp), PUBLIC ::   rn_aht_0        = 2000._wp  !: lateral eddy diffusivity (m2/s)
29   REAL(wp), PUBLIC ::   rn_ahtb_0       =    0._wp  !: lateral background eddy diffusivity (m2/s)
30   REAL(wp), PUBLIC ::   rn_aeiv_0       = 2000._wp  !: eddy induced velocity coefficient (m2/s)
[2528]31   REAL(wp), PUBLIC ::   rn_slpmax       = 0.01_wp   !: slope limit
[3]32
[1601]33   REAL(wp), PUBLIC ::   aht0, ahtb0, aeiv0         !!: OLD namelist names
[2528]34   LOGICAL , PUBLIC ::   l_triad_iso     = .FALSE.   !: calculate triads twice
35   LOGICAL , PUBLIC ::   l_no_smooth     = .FALSE.   !: no Shapiro smoothing
[3]36
37#if defined key_traldf_c3d
[3211]38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ahtt, ahtu, ahtv, ahtw   !: ** 3D coefficients **
39   !                                                                                   !  at T-,U-,V-,W-points
[3]40#elif defined key_traldf_c2d
[3211]41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ahtt, ahtu, ahtv, ahtw   !: ** 2D coefficients **
42   !                                                                                   !  at T-,U-,V-,W-points
[3]43#elif defined key_traldf_c1d
[3211]44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   ahtt, ahtu, ahtv, ahtw   !: ** 1D coefficients **
45   !                                                                                   !  at T-,U-,V-,W-points
[3]46#else
[3211]47   REAL(wp), PUBLIC                                      ::   ahtt, ahtu, ahtv, ahtw   !: ** 0D coefficients ** !
48   !                                                                                   !  at T-,U-,V-,W-points
[3]49#endif
50
51#if defined key_traldf_eiv
52   !!----------------------------------------------------------------------
53   !!   'key_traldf_eiv'                              eddy induced velocity
54   !!----------------------------------------------------------------------
[2528]55   LOGICAL, PUBLIC, PARAMETER               ::   lk_traldf_eiv   = .TRUE.   !: eddy induced velocity flag
[2715]56   
57   !                                                                              !!! eddy coefficients at U-, V-, W-points  [m2/s]
[3]58# if defined key_traldf_c3d
[2715]59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aeiu , aeiv , aeiw   !: ** 3D coefficients **
[3]60# elif defined key_traldf_c2d
[2715]61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   aeiu , aeiv , aeiw   !: ** 2D coefficients **
[3]62# elif defined key_traldf_c1d
[2715]63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   aeiu , aeiv , aeiw   !: ** 1D coefficients **
[3]64# else
[2715]65   REAL(wp), PUBLIC                                      ::   aeiu , aeiv , aeiw   !: ** 0D coefficients **
[3]66# endif
67# if defined key_diaeiv
[2715]68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   u_eiv, v_eiv, w_eiv   !: eddy induced velocity [m/s]
[3]69# endif
70
71#else
72   !!----------------------------------------------------------------------
73   !!   Default option :                           NO eddy induced velocity
74   !!----------------------------------------------------------------------
[32]75   LOGICAL , PUBLIC, PARAMETER ::   lk_traldf_eiv   = .FALSE.   !: eddy induced velocity flag
[1601]76   REAL(wp), PUBLIC            ::   aeiu, aeiv, aeiw            !: eddy induced coef. (not used)
[3]77#endif
78
[3211]79   !! * Control permutation of array indices
80#  include "ldftra_oce_ftrans.h90"
81
[3]82   !!----------------------------------------------------------------------
[2528]83   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1601]84   !! $Id$
[2528]85   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2715]86   !!----------------------------------------------------------------------
87CONTAINS
88
89   INTEGER FUNCTION ldftra_oce_alloc()
90     !!----------------------------------------------------------------------
91      !!                 ***  FUNCTION ldftra_oce_alloc  ***
92     !!----------------------------------------------------------------------
93     INTEGER, DIMENSION(3) :: ierr
94     !!----------------------------------------------------------------------
95     ierr(:) = 0
96
97#if defined key_traldf_c3d
98      ALLOCATE( ahtt(jpi,jpj,jpk) , ahtu(jpi,jpj,jpk) , ahtv(jpi,jpj,jpk) , ahtw(jpi,jpj,jpk) , STAT=ierr(1) )
99#elif defined key_traldf_c2d
100      ALLOCATE( ahtt(jpi,jpj    ) , ahtu(jpi,jpj    ) , ahtv(jpi,jpj    ) , ahtw(jpi,jpj    ) , STAT=ierr(1) )
101#elif defined key_traldf_c1d
102      ALLOCATE( ahtt(        jpk) , ahtu(        jpk) , ahtv(        jpk) , ahtw(        jpk) , STAT=ierr(1) )
103#endif
104      !
105#if defined key_traldf_eiv
106# if defined key_traldf_c3d
107      ALLOCATE( aeiu(jpi,jpj,jpk) , aeiv(jpi,jpj,jpk) , aeiw(jpi,jpj,jpk) , STAT=ierr(2) )
108# elif defined key_traldf_c2d
109      ALLOCATE( aeiu(jpi,jpj    ) , aeiv(jpi,jpj    ) , aeiw(jpi,jpj    ) , STAT=ierr(2) )
110# elif defined key_traldf_c1d
111      ALLOCATE( aeiu(        jpk) , aeiv(        jpk) , aeiw(        jpk) , STAT=ierr(2) )
112# endif
113# if defined key_diaeiv
114      ALLOCATE( u_eiv(jpi,jpj,jpk), v_eiv(jpi,jpj,jpk), w_eiv(jpi,jpj,jpk), STAT=ierr(3))
115# endif
116#endif
117      ldftra_oce_alloc = MAXVAL( ierr )
118      IF( ldftra_oce_alloc /= 0 )   CALL ctl_warn('ldftra_oce_alloc: failed to allocate arrays')
119      !
120   END FUNCTION ldftra_oce_alloc
121
[1601]122   !!=====================================================================
[3]123END MODULE ldftra_oce
Note: See TracBrowser for help on using the repository browser.