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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_oce.F90 @ 3849

Last change on this file since 3849 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: 7.3 KB
Line 
1MODULE trdmld_oce
2   !!======================================================================
3   !!                   ***  MODULE trdmld_oce  ***
4   !! Ocean trends :   set tracer and momentum trend variables
5   !!======================================================================
6   !! History :  1.0  ! 2004-08  (C. Talandier)  New trends organization
7   !!----------------------------------------------------------------------
8   USE par_oce        ! ocean parameters
9
10   IMPLICIT NONE
11   PRIVATE
12
13   PUBLIC   trdmld_oce_alloc    ! Called in trdmld.F90
14
15#if defined key_trdmld
16   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .TRUE.    !: ML trend flag
17#else
18   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .FALSE.   !: ML trend flag
19#endif
20   !!* mixed layer trends indices
21   INTEGER, PARAMETER, PUBLIC ::   jpltrd = 11      !: number of mixed-layer trends arrays
22   INTEGER, PUBLIC            ::   jpktrd           !: max level for mixed-layer trends diag.
23   !
24   INTEGER, PUBLIC, PARAMETER ::   jpmld_xad =  1   !:  zonal     
25   INTEGER, PUBLIC, PARAMETER ::   jpmld_yad =  2   !:  meridonal   > advection
26   INTEGER, PUBLIC, PARAMETER ::   jpmld_zad =  3   !:  vertical   
27   INTEGER, PUBLIC, PARAMETER ::   jpmld_ldf =  4   !:  lateral diffusion (geopot. or iso-neutral)
28   INTEGER, PUBLIC, PARAMETER ::   jpmld_for =  5   !:  forcing
29   INTEGER, PUBLIC, PARAMETER ::   jpmld_zdf =  6   !:  vertical diffusion (TKE)
30   INTEGER, PUBLIC, PARAMETER ::   jpmld_bbc =  7   !:  geothermal flux
31   INTEGER, PUBLIC, PARAMETER ::   jpmld_bbl =  8   !:  bottom boundary layer (advective/diffusive)
32   INTEGER, PUBLIC, PARAMETER ::   jpmld_dmp =  9   !:  internal restoring trend
33   INTEGER, PUBLIC, PARAMETER ::   jpmld_npc = 10   !:  non penetrative convective adjustment
34!! INTEGER, PUBLIC, PARAMETER ::   jpmld_xxx = xx   !:  add here any additional trend (add change jpltrd)
35   INTEGER, PUBLIC, PARAMETER ::   jpmld_atf = 11   !:  asselin trend (**MUST BE THE LAST ONE**)
36
37#if   defined  key_trdmld   ||   defined key_esopa
38   !!----------------------------------------------------------------------
39   !!   'key_trdmld'                         mixed layer trends diagnostics
40   !!----------------------------------------------------------------------
41
42   !! Arrays used for diagnosing mixed-layer trends
43   !!---------------------------------------------------------------------
44   CHARACTER(LEN=80) , PUBLIC :: clname, ctrd(jpltrd+1,2)
45
46   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nmld   !: mixed layer depth indexes
47   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nbol   !: mixed-layer depth indexes when read from file
48
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wkx    !:
50
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  &
52      rmld   ,                      & !: mld depth (m) corresponding to nmld
53      tml    , sml  ,               & !: \ "now" mixed layer temperature/salinity
54      tmlb   , smlb ,               & !: /  and associated "before" fields
55      tmlbb  , smlbb,               & !: \  idem, but valid at the 1rst time step of the
56      tmlbn  , smlbn,               & !: /  current analysis window
57      tmltrdm, smltrdm,             & !: total cumulative trends over the analysis window
58      tml_sum,                      & !: mixed layer T, summed over the current analysis period
59      tml_sumb,                     & !: idem, but from the previous analysis period
60      tmltrd_atf_sumb,              & !: Asselin trends, summed over the previous analysis period
61      sml_sum,                      & !:
62      sml_sumb,                     & !:    ( idem for salinity )
63      smltrd_atf_sumb,              & !:
64      rmld_sum, rmldbn                !: needed to compute the leap-frog time mean of the ML depth
65
66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  &
67      tmlatfb, tmlatfn ,            & !: "before" Asselin contribution at begining of the averaging
68      smlatfb, smlatfn,             & !: period (i.e. last contrib. from previous such period) and
69                                      !: "now" Asselin contribution to the ML temp. & salinity trends
70      tmlatfm, smlatfm                !: accumulator for Asselin trends (needed for storage only)
71
72   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::  &
73      tmltrd,                       & !: \ physical contributions to the total trend (for T/S),
74      smltrd,                       & !: / cumulated over the current analysis window
75      tmltrd_sum,                   & !: sum of these trends over the analysis period
76      tmltrd_csum_ln,               & !: now cumulated sum of the trends over the "lower triangle"
77      tmltrd_csum_ub,               & !: before (prev. analysis period) cumulated sum over the upper triangle
78      smltrd_sum,                   & !:
79      smltrd_csum_ln,               & !:    ( idem for salinity )
80      smltrd_csum_ub                  !:
81
82   !! * Control permutation of array indices
83#  include "trdmld_oce_ftrans.h90"
84
85#endif
86   !!----------------------------------------------------------------------
87   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
88   !! $Id$
89   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
90   !!----------------------------------------------------------------------
91CONTAINS
92
93  INTEGER FUNCTION trdmld_oce_alloc()
94     !!----------------------------------------------------------------------
95     !!                 ***  FUNCTION trdmld_oce_alloc   ***
96     !!----------------------------------------------------------------------
97     USE lib_mpp
98     INTEGER :: ierr(5)
99     !!----------------------------------------------------------------------
100
101     ! Initialise jpktrd here as can no longer do it in MODULE body since
102     ! jpk is now a variable.
103     jpktrd = jpk   !: max level for mixed-layer trends diag.
104
105     ierr(:) = 0
106
107#if   defined  key_trdmld   ||   defined key_esopa
108     ALLOCATE( nmld(jpi,jpj), nbol(jpi,jpj),       &
109        &      wkx(jpi,jpj,jpk), rmld(jpi,jpj),    & 
110        &      tml(jpi,jpj)    , sml(jpi,jpj),     & 
111        &      tmlb(jpi,jpj)   , smlb(jpi,jpj) ,   &
112        &      tmlbb(jpi,jpj)  , smlbb(jpi,jpj), STAT = ierr(1) )
113
114     ALLOCATE( tmlbn(jpi,jpj)  , smlbn(jpi,jpj),   &
115        &      tmltrdm(jpi,jpj), smltrdm(jpi,jpj), &
116        &      tml_sum(jpi,jpj), tml_sumb(jpi,jpj),&
117        &      tmltrd_atf_sumb(jpi,jpj)           , STAT=ierr(2) )
118
119     ALLOCATE( sml_sum(jpi,jpj), sml_sumb(jpi,jpj), &
120        &      smltrd_atf_sumb(jpi,jpj),            &
121        &      rmld_sum(jpi,jpj), rmldbn(jpi,jpj),  &
122        &      tmlatfb(jpi,jpj), tmlatfn(jpi,jpj), STAT = ierr(3) )
123
124     ALLOCATE( smlatfb(jpi,jpj), smlatfn(jpi,jpj), & 
125        &      tmlatfm(jpi,jpj), smlatfm(jpi,jpj), &
126        &      tmltrd(jpi,jpj,jpltrd),   smltrd(jpi,jpj,jpltrd), STAT=ierr(4))
127
128     ALLOCATE( tmltrd_sum(jpi,jpj,jpltrd),tmltrd_csum_ln(jpi,jpj,jpltrd),      &
129        &      tmltrd_csum_ub(jpi,jpj,jpltrd), smltrd_sum(jpi,jpj,jpltrd),     &
130        &      smltrd_csum_ln(jpi,jpj,jpltrd), smltrd_csum_ub(jpi,jpj,jpltrd), STAT=ierr(5) )
131#endif
132      !
133      trdmld_oce_alloc = MAXVAL( ierr )
134      IF( lk_mpp                )   CALL mpp_sum ( trdmld_oce_alloc )
135      IF( trdmld_oce_alloc /= 0 )   CALL ctl_warn('trdmld_oce_alloc: failed to allocate arrays')
136      !
137   END FUNCTION trdmld_oce_alloc
138
139   !!======================================================================
140END MODULE trdmld_oce
Note: See TracBrowser for help on using the repository browser.