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.
trdtrc_oce.F90 in branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/TRP/trdtrc_oce.F90

Last change on this file was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

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