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

Ignore:
Timestamp:
2011-03-01T20:04:06+01:00 (13 years ago)
Author:
gm
Message:

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trdmod_trc_oce.F90

    r2610 r2636  
    44   !! Ocean trends :   set tracer and momentum trend variables 
    55   !!====================================================================== 
    6    !!---------------------------------------------------------------------- 
    7    !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    8    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/TRD/trdmld_oce.F90,v 1.2 2005/03/27 18:35:23 opalod Exp $  
    9    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    10    !!---------------------------------------------------------------------- 
    11 #if defined key_top 
     6#if defined key_top   ||   defined key_esopa 
    127   !!---------------------------------------------------------------------- 
    138   !!   'key_top'                                                TOP models 
    149   !!---------------------------------------------------------------------- 
    1510 
    16    USE par_oce                        ! ocean parameters 
    17    USE par_trc                        ! passive tracers parameters 
     11   USE par_oce       ! ocean parameters 
     12   USE par_trc       ! passive tracers parameters 
    1813 
    1914   IMPLICIT NONE 
    2015   PUBLIC 
    2116 
    22    !!* Namelist namtoptrd:  diagnostics on passive tracers trends 
    23    INTEGER  ::    nn_trd_trc                 !: time step frequency dynamics and tracers trends 
    24    INTEGER  ::    nn_ctls_trc                !: control surface type for trends vertical integration 
     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 
    2520   REAL(wp) ::    rn_ucf_trc                  !: unit conversion factor (for netCDF trends outputs) 
    26    LOGICAL  ::    ln_trdmld_trc_instant    !: flag to diagnose inst./mean ML trc trends 
    27    LOGICAL  ::    ln_trdmld_trc_restart    !: flag to restart mixed-layer trc diagnostics 
    28    CHARACTER(len=50) ::  cn_trdrst_trc_in  !: suffix of pass. tracer restart name (input) 
    29    CHARACTER(len=50) ::  cn_trdrst_trc_out !: suffix of pass. tracer restart name (output) 
     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) 
    3025   LOGICAL, DIMENSION (jptra) ::   ln_trdtrc  !: large trends diagnostic to write or not (namelist) 
    3126 
    3227# if defined key_trdtrc && defined key_iomput 
    3328   LOGICAL, PARAMETER ::   lk_trdtrc = .TRUE.  
    34 #else 
     29# else 
    3530   LOGICAL, PARAMETER ::   lk_trdtrc = .FALSE.   !: ML trend flag 
    36 #endif 
     31# endif 
    3732 
    38 #if defined key_trdmld_trc 
     33# if defined key_trdmld_trc   ||   defined key_esopa 
    3934   !!---------------------------------------------------------------------- 
    4035   !!   'key_trdmld_trc'                     mixed layer trends diagnostics 
     
    108103      tmltrdm_trc                                !: total cumulative trends over the analysis window 
    109104 
    110 #else 
     105# else 
    111106   LOGICAL, PARAMETER ::   lk_trdmld_trc = .FALSE.   !: ML trend flag 
    112 #endif 
     107# endif 
    113108 
    114 #if defined key_lobster 
     109# if defined key_lobster 
    115110   CHARACTER(LEN=80) :: clname_bio, ctrd_bio(jpdiabio,2) 
    116111   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  & 
     
    121116      tmltrd_csum_ub_bio                         !: before (prev. analysis period) cumulated sum over the 
    122117                                                 !: upper triangle 
    123 #endif 
    124  
    125 #else 
     118# endif 
    126119   !!---------------------------------------------------------------------- 
    127    !!  Empty module :                                     No passive tracer 
     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) 
    128123   !!---------------------------------------------------------------------- 
    129 #endif 
    130  
    131 #if defined key_top 
    132124CONTAINS 
    133125 
    134    FUNCTION trd_mod_trc_oce_alloc() 
     126   INTEGER FUNCTION trd_mod_trc_oce_alloc() 
    135127      !!---------------------------------------------------------------------- 
    136128      !!         *** ROUTINE trd_mod_trc_oce_alloc *** 
    137129      !!---------------------------------------------------------------------- 
    138       USE in_out_manager, ONLY: ctl_warn 
    139       ! 
    140       INTEGER :: trd_mod_trc_oce_alloc 
    141       ! Locals 
     130      USE lib_mpp, ONLY: ctl_warn 
    142131      INTEGER :: ierr(2) 
    143132      !!---------------------------------------------------------------------- 
     
    145134      ierr(:) = 0 
    146135 
    147 #if defined key_trdmld_trc 
     136# if defined key_trdmld_trc 
    148137      ALLOCATE(nmld_trc(jpi,jpj),          nbol_trc(jpi,jpj),           & 
    149138               wkx_trc(jpi,jpj,jpk),       rmld_trc(jpi,jpj),           & 
     
    166155               tmltrdm_trc(jpi,jpj,jptra),                   & 
    167156               Stat=ierr(1)) 
    168 #endif 
    169 #if defined key_lobster 
     157# endif 
     158# if defined key_lobster 
    170159      ALLOCATE(tmltrd_bio(jpi,jpj,jpdiabio),         & 
    171160               tmltrd_sum_bio(jpi,jpj,jpdiabio),     & 
     
    173162               tmltrd_csum_ub_bio(jpi,jpj,jpdiabio), & 
    174163               Stat=ierr(2)) 
    175 #endif 
     164# endif 
    176165 
    177166      trd_mod_trc_oce_alloc = MAXVAL(ierr) 
    178167 
    179       IF(trd_mod_trc_oce_alloc /= 0)THEN 
    180          CALL ctl_warn('trd_mod_trc_oce_alloc : failed to allocate arrays.') 
    181       END IF 
     168      IF( trd_mod_trc_oce_alloc /= 0 )   CALL ctl_warn('trd_mod_trc_oce_alloc : failed to allocate arrays') 
    182169 
    183 #if defined key_trdmld_trc 
    184       ! Initialise what used to be a parameter - max level for mixed-layer  
    185       ! trends diag. 
    186       jpktrd_trc = jpk 
     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   !!---------------------------------------------------------------------- 
    187180#endif 
    188181 
    189    END FUNCTION trd_mod_trc_oce_alloc 
    190 #endif 
    191  
     182   !!====================================================================== 
    192183END MODULE trdmod_trc_oce 
Note: See TracChangeset for help on using the changeset viewer.