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/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_oce.F90 @ 3325

Last change on this file since 3325 was 3318, checked in by gm, 12 years ago

Ediag branche: #927 split TRA/DYN trd computation

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