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.
trdmod_trc_oce.F90 in branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trdmod_trc_oce.F90 @ 2636

Last change on this file since 2636 was 2636, checked in by gm, 13 years ago

dynamic mem: #785 ; move ctl_stop & warn in lib_mpp to avoid a circular dependency + ctl_stop improvment

  • Property svn:keywords set to Id
File size: 10.4 KB
Line 
1MODULE trdmod_trc_oce
2   !!======================================================================
3   !!                   ***  MODULE trdmod_trc_oce  ***
4   !! Ocean trends :   set tracer and momentum trend variables
5   !!======================================================================
6#if defined key_top   ||   defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_top'                                                TOP models
9   !!----------------------------------------------------------------------
10
11   USE par_oce       ! ocean parameters
12   USE par_trc       ! passive tracers parameters
13
14   IMPLICIT NONE
15   PUBLIC
16
17   !                                         !!* Namelist namtoptrd:  diagnostics on passive tracers trends
18   INTEGER  ::    nn_trd_trc                  !: time step frequency dynamics and tracers trends
19   INTEGER  ::    nn_ctls_trc                 !: control surface type for trends vertical integration
20   REAL(wp) ::    rn_ucf_trc                  !: unit conversion factor (for netCDF trends outputs)
21   LOGICAL  ::    ln_trdmld_trc_instant       !: flag to diagnose inst./mean ML trc trends
22   LOGICAL  ::    ln_trdmld_trc_restart       !: flag to restart mixed-layer trc diagnostics
23   CHARACTER(len=50) ::  cn_trdrst_trc_in     !: suffix of pass. tracer restart name (input)
24   CHARACTER(len=50) ::  cn_trdrst_trc_out    !: suffix of pass. tracer restart name (output)
25   LOGICAL, DIMENSION (jptra) ::   ln_trdtrc  !: large trends diagnostic to write or not (namelist)
26
27# if defined key_trdtrc && defined key_iomput
28   LOGICAL, PARAMETER ::   lk_trdtrc = .TRUE. 
29# else
30   LOGICAL, PARAMETER ::   lk_trdtrc = .FALSE.   !: ML trend flag
31# endif
32
33# if defined key_trdmld_trc   ||   defined key_esopa
34   !!----------------------------------------------------------------------
35   !!   'key_trdmld_trc'                     mixed layer trends diagnostics
36   !!----------------------------------------------------------------------
37
38   LOGICAL, PARAMETER ::   lk_trdmld_trc = .TRUE.    !: ML trend flag
39
40   INTEGER, PARAMETER ::            & !: mixed layer trends indices
41        jpmld_trc_xad     =  1,     & !:     zonal      \
42        jpmld_trc_yad     =  2,     & !:     meridonal   > advection
43        jpmld_trc_zad     =  3,     & !:     vertical   /
44        jpmld_trc_ldf     =  4,     & !:     lateral diffusion (geopot. or iso-neutral)
45        jpmld_trc_zdf     =  5,     & !:     vertical diffusion (TKE)
46        jpmld_trc_bbl     =  6,     & !:     bottom boundary layer (advective/diffusive)
47        jpmld_trc_dmp     =  7,     & !:     internal restoring trend
48        jpmld_trc_sbc     =  8,     & !:     forcing
49        jpmld_trc_sms     =  9,     & !:     sources minus sinks trend
50  !     jpmld_trc_xxx     = xx,     & !:     add here any additional trend    (** AND UPDATE JPLTRD_TRC BELOW **)
51        jpmld_trc_radn    = 10,     & !:     corr. trn<0 in trcrad
52        jpmld_trc_radb    = 11,     & !:     corr. trb<0 in trcrad (like atf) (** MUST BE BEFORE THE LAST ONE **)
53        jpmld_trc_atf     = 12        !:     asselin trend                    (** MUST BE    THE      LAST ONE**)
54
55   !! Trends diagnostics parameters
56   !!---------------------------------------------------------------------
57   INTEGER, PARAMETER :: jpltrd_trc = 12    !: number of mixed-layer trends arrays
58     
59   INTEGER            :: jpktrd_trc         !: max level for mixed-layer trends diag.
60
61   !! Arrays used for diagnosing mixed-layer trends
62   !!---------------------------------------------------------------------
63   CHARACTER(LEN=80) :: clname_trc, ctrd_trc(jpltrd_trc+1,2)
64
65   INTEGER, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   &
66      nmld_trc       , &                            !: mixed layer depth indexes
67      nbol_trc                                   !: mixed-layer depth indexes when read from file
68
69   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  wkx_trc  !:
70
71   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmld_trc     !: ML depth (m) corresponding to nmld_trc
72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmld_sum_trc !: needed to compute the leap-frog time mean of ML depth
73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmldbn_trc   !: idem
74
75   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  &
76      tml_trc    ,                        &      !: \ "now" mixed layer temperature/salinity
77      tmlb_trc   ,                        &      !: /  and associated "before" fields
78      tmlbb_trc  ,                        &      !: \  idem, but valid at the 1rst time step of the
79      tmlbn_trc  ,                        &      !: /  current analysis window
80      tml_sum_trc,                        &      !: mixed layer T, summed over the current analysis period
81      tml_sumb_trc,                       &      !: idem, but from the previous analysis period
82      tmltrd_atf_sumb_trc,                &      !: Asselin trends, summed over the previous analysis period
83      tmltrd_rad_sumb_trc                        !: trends due to trb correction in trcrad.F90, summed over the
84                                                 !:     previous analysis period
85                                                 
86   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  &     
87      tmlatfb_trc, tmlatfn_trc ,          &      !: "before" Asselin contrib. at beginning of the averaging
88                                                 !:     period (i.e. last contrib. from previous such period)
89                                                 !:     and "now" Asselin contrib. to the ML trc. trends
90      tmlatfm_trc,                        &      !: accumulator for Asselin trends (needed for storage only)
91      tmlradb_trc, tmlradn_trc ,          &      !: similar to Asselin above, but for the trend due to trb
92                                                 !:     correction in trcrad.F90
93      tmlradm_trc                                !: accumulator for the previous trcrad trend
94
95   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  &
96      tmltrd_trc,                         &      !: \ physical contributions to the total trend (for T/S),
97                                                 !: / cumulated over the current analysis window
98      tmltrd_sum_trc,                     &      !: sum of these trends over the analysis period
99      tmltrd_csum_ln_trc,                 &      !: now cumulated sum of trends over the "lower triangle"
100      tmltrd_csum_ub_trc                         !: before (prev. analysis period) cumulated sum over the
101                                                 !: upper triangle
102   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  &
103      tmltrdm_trc                                !: total cumulative trends over the analysis window
104
105# else
106   LOGICAL, PARAMETER ::   lk_trdmld_trc = .FALSE.   !: ML trend flag
107# endif
108
109# if defined key_lobster
110   CHARACTER(LEN=80) :: clname_bio, ctrd_bio(jpdiabio,2)
111   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  &
112      tmltrd_bio,                         &      !: \ biological contributions to the total trend ,
113                                                 !: / cumulated over the current analysis window
114      tmltrd_sum_bio,                     &      !: sum of these trends over the analysis period
115      tmltrd_csum_ln_bio,                 &      !: now cumulated sum of trends over the "lower triangle"
116      tmltrd_csum_ub_bio                         !: before (prev. analysis period) cumulated sum over the
117                                                 !: upper triangle
118# endif
119   !!----------------------------------------------------------------------
120   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
121   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/TRD/trdmld_oce.F90,v 1.2 2005/03/27 18:35:23 opalod Exp $
122   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
123   !!----------------------------------------------------------------------
124CONTAINS
125
126   INTEGER FUNCTION trd_mod_trc_oce_alloc()
127      !!----------------------------------------------------------------------
128      !!         *** ROUTINE trd_mod_trc_oce_alloc ***
129      !!----------------------------------------------------------------------
130      USE lib_mpp, ONLY: ctl_warn
131      INTEGER :: ierr(2)
132      !!----------------------------------------------------------------------
133
134      ierr(:) = 0
135
136# if defined key_trdmld_trc
137      ALLOCATE(nmld_trc(jpi,jpj),          nbol_trc(jpi,jpj),           &
138               wkx_trc(jpi,jpj,jpk),       rmld_trc(jpi,jpj),           &
139               rmld_sum_trc(jpi,jpj),      rmldbn_trc(jpi,jpj),         &
140               tml_trc(jpi,jpj,jptra),     tmlb_trc(jpi,jpj,jptra),     &
141               tmlbb_trc(jpi,jpj,jptra),   tmlbn_trc(jpi,jpj,jptra),    &
142               tml_sum_trc(jpi,jpj,jptra), tml_sumb_trc(jpi,jpj,jptra), &
143               tmltrd_atf_sumb_trc(jpi,jpj,jptra),                      &
144               tmltrd_rad_sumb_trc(jpi,jpj,jptra),                      &
145               !
146               tmlatfb_trc(jpi,jpj,jptra), tmlatfn_trc(jpi,jpj,jptra),  &
147               tmlatfm_trc(jpi,jpj,jptra), tmlradb_trc(jpi,jpj,jptra),  &
148               tmlradn_trc(jpi,jpj,jptra), tmlradm_trc(jpi,jpj,jptra),  &
149               !
150               tmltrd_trc(jpi,jpj,jpltrd_trc,jptra)        , &
151               tmltrd_sum_trc(jpi,jpj,jpltrd_trc,jptra)    , &
152               tmltrd_csum_ln_trc(jpi,jpj,jpltrd_trc,jptra), &
153               tmltrd_csum_ub_trc(jpi,jpj,jpltrd_trc,jptra), &
154               !
155               tmltrdm_trc(jpi,jpj,jptra),                   &
156               Stat=ierr(1))
157# endif
158# if defined key_lobster
159      ALLOCATE(tmltrd_bio(jpi,jpj,jpdiabio),         &
160               tmltrd_sum_bio(jpi,jpj,jpdiabio),     &
161               tmltrd_csum_ln_bio(jpi,jpj,jpdiabio), &
162               tmltrd_csum_ub_bio(jpi,jpj,jpdiabio), &
163               Stat=ierr(2))
164# endif
165
166      trd_mod_trc_oce_alloc = MAXVAL(ierr)
167
168      IF( trd_mod_trc_oce_alloc /= 0 )   CALL ctl_warn('trd_mod_trc_oce_alloc : failed to allocate arrays')
169
170# if defined key_trdmld_trc
171      jpktrd_trc = jpk      ! Initialise what used to be a parameter - max level for mixed-layer trends diag.
172# endif
173      !
174   END FUNCTION trd_mod_trc_oce_alloc
175
176#else
177   !!----------------------------------------------------------------------
178   !!  Empty module :                                     No passive tracer
179   !!----------------------------------------------------------------------
180#endif
181
182   !!======================================================================
183END MODULE trdmod_trc_oce
Note: See TracBrowser for help on using the repository browser.