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.
trdmxl_oce.F90 in branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_oce.F90 @ 11738

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

The Dr Hook changes from my perl code.

File size: 8.3 KB
Line 
1MODULE trdmxl_oce
2   !!======================================================================
3   !!                   ***  MODULE trdmxl_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 + new trdmxl formulation
8   !!----------------------------------------------------------------------
9   USE par_oce        ! ocean parameters
10
11   USE yomhook, ONLY: lhook, dr_hook
12   USE parkind1, ONLY: jprb, jpim
13
14   IMPLICIT NONE
15   PRIVATE
16
17   PUBLIC   trdmxl_oce_alloc    ! Called in trdmxl.F90
18
19   !                                                !* mixed layer trend indices
20   INTEGER, PUBLIC, PARAMETER ::   jpltrd = 12      !: number of mixed-layer trends arrays
21   INTEGER, PUBLIC            ::   jpktrd           !: max level for mixed-layer trends diag.
22   !
23   INTEGER, PUBLIC, PARAMETER ::   jpmxl_xad =  1   !: i-componant of advection   
24   INTEGER, PUBLIC, PARAMETER ::   jpmxl_yad =  2   !: j-componant of advection
25   INTEGER, PUBLIC, PARAMETER ::   jpmxl_zad =  3   !: k-component of advection
26   INTEGER, PUBLIC, PARAMETER ::   jpmxl_ldf =  4   !: lateral diffusion (geopot. or iso-neutral)
27   INTEGER, PUBLIC, PARAMETER ::   jpmxl_zdf =  5   !: vertical diffusion 
28   INTEGER, PUBLIC, PARAMETER ::   jpmxl_npc =  6   !: non penetrative convective adjustment
29   INTEGER, PUBLIC, PARAMETER ::   jpmxl_bbc =  7   !: geothermal flux
30   INTEGER, PUBLIC, PARAMETER ::   jpmxl_bbl =  8   !: bottom boundary layer (advective/diffusive)
31   INTEGER, PUBLIC, PARAMETER ::   jpmxl_for =  9   !: forcing
32   INTEGER, PUBLIC, PARAMETER ::   jpmxl_dmp = 10   !: internal restoring trend
33   INTEGER, PUBLIC, PARAMETER ::   jpmxl_zdfp = 11  !: iso-neutral diffusion:"pure" vertical diffusion
34   INTEGER, PUBLIC, PARAMETER ::   jpmxl_atf  = 12  !: asselin trend (**MUST BE THE LAST ONE**)
35   !                                                            !!* Namelist namtrd_mxl:  trend diagnostics in the mixed layer *
36   INTEGER           , PUBLIC ::   nn_ctls  = 0                  !: control surface type for trends vertical integration
37   REAL(wp)          , PUBLIC ::   rn_rho_c = 0.01               !: density criteria for MLD definition
38   REAL(wp)          , PUBLIC ::   rn_ucf   = 1.                 !: unit conversion factor (for netCDF trends outputs)
39                                                                 !  =1. (=86400.) for degC/s (degC/day) and psu/s (psu/day)
40   CHARACTER(len=32), PUBLIC ::   cn_trdrst_in  = "restart_mxl"  !: suffix of ocean restart name (input)
41   CHARACTER(len=32), PUBLIC ::   cn_trdrst_out = "restart_mxl"  !: suffix of ocean restart name (output)
42   LOGICAL          , PUBLIC ::   ln_trdmxl_instant = .FALSE.    !: flag to diagnose inst./mean ML T/S trends
43   LOGICAL          , PUBLIC ::   ln_trdmxl_restart = .FALSE.    !: flag to restart mixed-layer diagnostics
44
45
46   !! Arrays used for diagnosing mixed-layer trends
47   !!---------------------------------------------------------------------
48   CHARACTER(LEN=80) , PUBLIC :: clname, ctrd(jpltrd+1,2)
49
50   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nmxl   !: mixed layer depth indexes
51   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nbol   !: mixed-layer depth indexes when read from file
52
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wkx    !:
54
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  &
56      hmxl   ,                      & !: mixed layer depth (m) corresponding to nmld
57      tml    , sml  ,               & !: \ "now" mixed layer temperature/salinity
58      tmlb   , smlb ,               & !: /  and associated "before" fields
59      tmlbb  , smlbb,               & !: \  idem, but valid at the 1rst time step of the
60      tmlbn  , smlbn,               & !: /  current analysis window
61      tmltrdm, smltrdm,             & !: total cumulative trends over the analysis window
62      tml_sum,                      & !: mixed layer T, summed over the current analysis period
63      tml_sumb,                     & !: idem, but from the previous analysis period
64      tmltrd_atf_sumb,              & !: Asselin trends, summed over the previous analysis period
65      sml_sum,                      & !:
66      sml_sumb,                     & !:    ( idem for salinity )
67      smltrd_atf_sumb,              & !:
68      hmxl_sum, hmxlbn                !: needed to compute the leap-frog time mean of the ML depth
69
70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  &
71      tmlatfb, tmlatfn ,            & !: "before" Asselin contribution at begining of the averaging
72      smlatfb, smlatfn,             & !: period (i.e. last contrib. from previous such period) and
73                                      !: "now" Asselin contribution to the ML temp. & salinity trends
74      tmlatfm, smlatfm                !: accumulator for Asselin trends (needed for storage only)
75
76   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::  &
77      tmltrd,                       & !: \ physical contributions to the total trend (for T/S),
78      smltrd,                       & !: / cumulated over the current analysis window
79      tmltrd_sum,                   & !: sum of these trends over the analysis period
80      tmltrd_csum_ln,               & !: now cumulated sum of the trends over the "lower triangle"
81      tmltrd_csum_ub,               & !: before (prev. analysis period) cumulated sum over the upper triangle
82      smltrd_sum,                   & !:
83      smltrd_csum_ln,               & !:    ( idem for salinity )
84      smltrd_csum_ub                  !:
85
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 trdmxl_oce_alloc()
94     !!----------------------------------------------------------------------
95     !!                 ***  FUNCTION trdmxl_oce_alloc   ***
96     !!----------------------------------------------------------------------
97     USE lib_mpp
98     INTEGER :: ierr(5)
99     INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
100     INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
101     REAL(KIND=jprb)               :: zhook_handle
102
103     CHARACTER(LEN=*), PARAMETER :: RoutineName='TRDMXL_OCE_ALLOC'
104
105     IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
106
107     !!----------------------------------------------------------------------
108
109     ! Initialise jpktrd here as can no longer do it in MODULE body since
110     ! jpk is now a variable.
111     jpktrd = jpk   !: max level for mixed-layer trends diag.
112
113     ierr(:) = 0
114
115     ALLOCATE( nmxl (jpi,jpj)    , nbol (jpi,jpj),    &
116        &      wkx  (jpi,jpj,jpk), hmxl (jpi,jpj),    & 
117        &      tml  (jpi,jpj)    , sml  (jpi,jpj),    & 
118        &      tmlb (jpi,jpj)    , smlb (jpi,jpj),    &
119        &      tmlbb(jpi,jpj)    , smlbb(jpi,jpj), STAT = ierr(1) )
120
121     ALLOCATE( tmlbn(jpi,jpj)  , smlbn(jpi,jpj),   &
122        &      tmltrdm(jpi,jpj), smltrdm(jpi,jpj), &
123        &      tml_sum(jpi,jpj), tml_sumb(jpi,jpj),&
124        &      tmltrd_atf_sumb(jpi,jpj)           , STAT=ierr(2) )
125
126     ALLOCATE( sml_sum(jpi,jpj), sml_sumb(jpi,jpj), &
127        &      smltrd_atf_sumb(jpi,jpj),            &
128        &      hmxl_sum(jpi,jpj), hmxlbn(jpi,jpj),  &
129        &      tmlatfb(jpi,jpj), tmlatfn(jpi,jpj), STAT = ierr(3) )
130
131     ALLOCATE( smlatfb(jpi,jpj), smlatfn(jpi,jpj), & 
132        &      tmlatfm(jpi,jpj), smlatfm(jpi,jpj), &
133        &      tmltrd(jpi,jpj,jpltrd),   smltrd(jpi,jpj,jpltrd), STAT=ierr(4))
134
135     ALLOCATE( tmltrd_sum(jpi,jpj,jpltrd),tmltrd_csum_ln(jpi,jpj,jpltrd),      &
136        &      tmltrd_csum_ub(jpi,jpj,jpltrd), smltrd_sum(jpi,jpj,jpltrd),     &
137        &      smltrd_csum_ln(jpi,jpj,jpltrd), smltrd_csum_ub(jpi,jpj,jpltrd), STAT=ierr(5) )
138      !
139      trdmxl_oce_alloc = MAXVAL( ierr )
140      IF( lk_mpp                )   CALL mpp_sum ( trdmxl_oce_alloc )
141      IF( trdmxl_oce_alloc /= 0 )   CALL ctl_warn('trdmxl_oce_alloc: failed to allocate arrays')
142      !
143     IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
144   END FUNCTION trdmxl_oce_alloc
145
146   !!======================================================================
147END MODULE trdmxl_oce
Note: See TracBrowser for help on using the repository browser.