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 – 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

Location:
branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/sms_lobster.F90

    r2607 r2636  
    1111   !!             2.0  !  2007-04  (C. Deltel, G. Madec) Free form and modules 
    1212   !!---------------------------------------------------------------------- 
    13  
    1413#if defined key_lobster 
    1514   !!---------------------------------------------------------------------- 
     
    2120   IMPLICIT NONE 
    2221   PUBLIC 
    23  
    24    !!---------------------------------------------------------------------- 
    25    !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    26    !! $Id$  
    27    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    28    !!---------------------------------------------------------------------- 
    2922 
    3023   !!  biological parameters 
     
    108101   REAL(wp), ALLOCATABLE, SAVE,  DIMENSION(:,:) ::   cmask       !: ??? 
    109102 
    110    !!====================================================================== 
    111  
     103   !!---------------------------------------------------------------------- 
     104   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     105   !! $Id$  
     106   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     107   !!---------------------------------------------------------------------- 
    112108CONTAINS 
    113109 
    114    FUNCTION sms_lobster_alloc() 
     110   INTEGER FUNCTION sms_lobster_alloc() 
    115111      !!---------------------------------------------------------------------- 
    116112      !!        *** ROUTINE sms_lobster_alloc *** 
    117113      !!---------------------------------------------------------------------- 
    118       USE in_out_manager, ONLY: ctl_warn 
    119       INTEGER :: sms_lobster_alloc 
     114      USE lib_mpp, ONLY: ctl_warn 
    120115      !!---------------------------------------------------------------------- 
    121  
    122       ALLOCATE(remdmp(jpk,jp_lobster),                                & 
    123                neln(jpi,jpj),    xze(jpi,jpj),     xpar(jpi,jpj,jpk), & 
    124                dminl(jpi,jpj),   dmin3(jpi,jpj,jpk),                  & 
    125                sedpocb(jpi,jpj), sedpocn(jpi,jpj), sedpoca(jpi,jpj),  & 
    126                fbod(jpi,jpj),    cmask(jpi,jpj)  ,                    & 
    127                Stat=sms_lobster_alloc) 
    128  
    129       IF(sms_lobster_alloc /= 0)THEN 
    130          CALL ctl_warn('sms_lobster_alloc : failed to allocate arrays.') 
    131       END IF 
    132  
     116      ! 
     117      ALLOCATE( remdmp(jpk,jp_lobster),                                   & 
     118         &      neln(jpi,jpj),    xze(jpi,jpj),     xpar(jpi,jpj,jpk),    & 
     119         &      dminl(jpi,jpj),   dmin3(jpi,jpj,jpk),                     & 
     120         &      sedpocb(jpi,jpj), sedpocn(jpi,jpj), sedpoca(jpi,jpj),     & 
     121         &      fbod(jpi,jpj),    cmask(jpi,jpj)                    , STAT=sms_lobster_alloc ) 
     122         ! 
     123      IF( sms_lobster_alloc /= 0 )   CALL ctl_warn('sms_lobster_alloc : failed to allocate arrays') 
     124      ! 
    133125   END FUNCTION sms_lobster_alloc 
    134126 
     
    140132 
    141133   !!====================================================================== 
    142  
    143134END MODULE sms_lobster 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcnam_lobster.F90

    r2567 r2636  
    1010   !!   'key_lobster'   :                                 LOBSTER bio-model 
    1111   !!---------------------------------------------------------------------- 
    12    !! trc_nam_lobster      : LOBSTER model namelist read 
    13    !!---------------------------------------------------------------------- 
    14    USE oce_trc         ! Ocean variables 
    15    USE par_trc         ! TOP parameters 
    16    USE trc             ! TOP variables 
    17    USE sms_lobster     ! sms trends 
    18    USE in_out_manager  ! I/O manager 
     12   !! trc_nam_lobster   : LOBSTER model namelist read 
     13   !!---------------------------------------------------------------------- 
     14   USE oce_trc          ! Ocean variables 
     15   USE par_trc          ! TOP parameters 
     16   USE trc              ! TOP variables 
     17   USE sms_lobster      ! sms trends 
     18   USE in_out_manager   ! I/O manager 
     19   USE lib_mpp          ! MPP library 
    1920 
    2021   IMPLICIT NONE 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcopt.F90

    r2633 r2636  
    2121   USE sms_lobster 
    2222   USE prtctl_trc      ! Print control for debbuging 
     23   USE lib_mpp         ! MPP library 
    2324 
    2425   IMPLICIT NONE 
     
    6970 
    7071      IF( (wrk_in_use(2, 1,2)) .OR. (wrk_in_use(3, 2,3)) )THEN 
    71          CALL ctl_stop('trc_opt : requested workspace arrays unavailable.') 
    72          RETURN 
     72         CALL ctl_stop('trc_opt : requested workspace arrays unavailable')   ;   RETURN 
    7373      END IF 
    7474 
     
    138138      ENDIF 
    139139      ! 
    140       IF( (wrk_not_released(2, 1,2)) .OR. (wrk_not_released(3, 2,3)) )THEN 
    141          CALL ctl_stop('trc_opt : failed to release workspace arrays.') 
    142       END IF 
     140      IF( wrk_not_released(2, 1,2)  .OR.  wrk_not_released(3, 2,3)  )   & 
     141          CALL ctl_stop('trc_opt : failed to release workspace arrays') 
    143142      ! 
    144143   END SUBROUTINE trc_opt 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcsms_lobster.F90

    r2633 r2636  
    1313   !!   trcsms_lobster        :  Time loop of passive tracers sms 
    1414   !!---------------------------------------------------------------------- 
    15    USE oce_trc         ! 
     15   USE oce_trc          ! 
    1616   USE trc 
    1717   USE trcbio 
     
    2323   USE trdmod_trc 
    2424   USE trdmld_trc 
     25   USE lib_mpp          ! MPP library 
    2526 
    2627   IMPLICIT NONE 
     
    3233   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    3334   !! $Id$  
    34    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3536   !!---------------------------------------------------------------------- 
    36  
    3737CONTAINS 
    3838 
     
    5353      !! -------------------------------------------------------------------- 
    5454 
    55       IF(wrk_in_use(3,1))THEN 
    56          CALL ctl_stop('trc_sms_lobster : requested workspace array unavailable.') 
    57          RETURN 
    58       END IF 
     55      IF( wrk_in_use(3,1) ) THEN 
     56         CALL ctl_stop('trc_sms_lobster : requested workspace array unavailable')   ;   RETURN 
     57      ENDIF 
    5958 
    6059      CALL trc_opt( kt )      ! optical model 
     
    7271      IF( lk_trdmld_trc )  CALL trd_mld_bio( kt )   ! trends: Mixed-layer 
    7372 
    74       IF(wrk_not_released(3,1))THEN 
    75          CALL ctl_stop('trc_sms_lobster : failed to release workspace array.') 
    76       END IF 
    77  
     73      IF( wrk_not_released(3,1) )   CALL ctl_stop('trc_sms_lobster : failed to release workspace array.') 
     74      ! 
    7875   END SUBROUTINE trc_sms_lobster 
    7976 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv.F90

    r2633 r2636  
    1010   !!---------------------------------------------------------------------- 
    1111   !!   'key_top'                                                TOP models 
    12    !!---------------------------------------------------------------------- 
    1312   !!---------------------------------------------------------------------- 
    1413   !!   trc_adv      : compute ocean tracer advection trend 
     
    2726   USE ldftra_oce      ! lateral diffusion coefficient on tracers 
    2827   USE in_out_manager  ! I/O manager 
    29    USE prtctl_trc          ! Print control 
     28   USE lib_mpp         ! MPP library 
     29   USE prtctl_trc      ! Print control 
    3030 
    3131   IMPLICIT NONE 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r2610 r2636  
    33   !!                       ***  MODULE  trcnxt  *** 
    44   !! Ocean passive tracers:  time stepping on passives tracers 
    5    !!====================================================================== 
    65   !!====================================================================== 
    76   !! History :  7.0  !  1991-11  (G. Madec)  Original code 
     
    2726   !!   trc_nxt     : time stepping on passive tracers 
    2827   !!---------------------------------------------------------------------- 
    29    !! * Modules used 
    3028   USE oce_trc         ! ocean dynamics and tracers variables 
    3129   USE trc             ! ocean passive tracers variables 
     
    4341   PRIVATE 
    4442 
    45    !! * Routine accessibility 
    46    PUBLIC trc_nxt          ! routine called by step.F90 
    47    PUBLIC trc_nxt_alloc    ! routine called by nemogcm.F90 
     43   PUBLIC   trc_nxt          ! routine called by step.F90 
     44   PUBLIC   trc_nxt_alloc    ! routine called by nemogcm.F90 
    4845 
    4946   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt 
     47 
    5048   !!---------------------------------------------------------------------- 
    5149   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    5250   !! $Id$  
    53    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    5452   !!---------------------------------------------------------------------- 
    55  
    5653CONTAINS 
    5754 
    58    FUNCTION trc_nxt_alloc() 
     55   INTEGER FUNCTION trc_nxt_alloc() 
    5956      !!---------------------------------------------------------------------- 
    6057      !!                   ***  ROUTINE trc_nxt_alloc  *** 
    6158      !!---------------------------------------------------------------------- 
    62       INTEGER :: trc_nxt_alloc 
     59      USE lib_mpp, ONLY: ctl_warn 
    6360      !!---------------------------------------------------------------------- 
    64  
     61      ! 
    6562      ALLOCATE( r2dt(jpk), Stat=trc_nxt_alloc) 
    66  
    67       IF(trc_nxt_alloc /= 0)THEN 
    68          CALL ctl_warn('trc_nxt_alloc : failed to allocate array.') 
    69       ENDIF 
    70  
     63      ! 
     64      IF( trc_nxt_alloc /= 0 )   CALL ctl_warn('trc_nxt_alloc : failed to allocate array') 
     65      ! 
    7166   END FUNCTION trc_nxt_alloc 
    7267 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r2633 r2636  
    1616   !!   trc_sbc      : update the tracer trend at ocean surface 
    1717   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    19    USE oce_trc             ! ocean dynamics and active tracers variables 
    20    USE trc                 ! ocean  passive tracers variables 
    21    USE prtctl_trc          ! Print control for debbuging 
     18   USE oce_trc         ! ocean dynamics and active tracers variables 
     19   USE trc             ! ocean  passive tracers variables 
     20   USE prtctl_trc      ! Print control for debbuging 
    2221   USE trdmod_oce 
    2322   USE trdtra 
     23   USE lib_mpp         ! MPP library 
    2424 
    2525   IMPLICIT NONE 
    2626   PRIVATE 
    2727 
    28    !! * Routine accessibility 
    29    PUBLIC trc_sbc              ! routine called by step.F90 
     28   PUBLIC   trc_sbc   ! routine called by step.F90 
    3029 
    3130   !! * Substitutions 
     
    3433   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    3534   !! $Id$  
    36    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3736   !!---------------------------------------------------------------------- 
    38  
    3937CONTAINS 
    4038 
     
    6260      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released 
    6361      USE wrk_nemo, zemps => wrk_2d_1 
    64       !! * Arguments 
     62      ! 
    6563      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    66  
    67       !! * Local declarations 
     64      ! 
    6865      INTEGER  ::   ji, jj, jn           ! dummy loop indices 
    6966      REAL(wp) ::   zsrau, zse3t   ! temporary scalars 
     
    7370 
    7471      IF(wrk_in_use(2, 1))THEN 
    75          CALL ctl_stop('trc_sbc: requested workspace array unavailable.') 
    76          RETURN 
     72         CALL ctl_stop('trc_sbc: requested workspace array unavailable.')   ;   RETURN 
    7773      END IF 
    7874 
     
    126122      ENDIF 
    127123 
    128       IF(wrk_not_released(2, 1))THEN 
    129          CALL ctl_stop('trc_sbc: failed to release workspace array.') 
    130       END IF 
    131  
     124      IF( wrk_not_released(2, 1) )   CALL ctl_stop('trc_sbc: failed to release workspace array') 
     125      ! 
    132126   END SUBROUTINE trc_sbc 
    133127 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r2606 r2636  
    2020   USE trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine) 
    2121   USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine) 
     22   USE trdmod_oce 
     23   USE trdtra 
    2224   USE prtctl_trc      ! Print control 
    2325   USE in_out_manager  ! I/O manager 
    2426   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    25    USE trdmod_oce 
    26    USE trdtra 
     27   USE lib_mpp         ! MPP library 
    2728 
    2829   IMPLICIT NONE 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc.F90

    r2633 r2636  
    2323   USE zdfddm  , ONLY : avs  !: salinity vertical diffusivity coeff. at w-point 
    2424# endif 
    25    USE trcnam_trp      ! passive tracers transport namelist variables 
     25   USE trcnam_trp        ! passive tracers transport namelist variables 
    2626   USE trdmod_trc_oce    ! definition of main arrays used for trends computations 
    2727   USE in_out_manager    ! I/O manager 
     
    3030   USE ioipsl            ! NetCDF library 
    3131   USE lbclnk            ! ocean lateral boundary conditions (or mpp link) 
     32   USE lib_mpp           ! MPP library 
    3233   USE trdmld_trc_rst    ! restart for diagnosing the ML trends 
    3334   USE prtctl            ! print control 
     
    4748   CHARACTER (LEN=40) ::  clhstnam                                ! name of the trends NetCDF file 
    4849   INTEGER ::   nmoymltrd 
    49    INTEGER ::   ndextrd1(jpi*jpj) 
     50   INTEGER, ALLOCATABLE, SAVE, DIMENSION(:) ::   ndextrd1 
    5051   INTEGER, DIMENSION(jptra) ::   nidtrd, nh_t 
    5152   INTEGER ::   ndimtrd1                         
     
    8788               ztmltrdbio2(jpi,jpj,jpdiabio)     , & 
    8889#endif 
    89                Stat=trd_mld_trc_alloc) 
    90  
    91       IF(trd_mld_trc_alloc/=0)THEN 
    92          CALL ctl_warn('trd_mld_trc_alloc : failed to allocate arrays.') 
    93       END IF 
    94  
     90         &     ndextrd1(jpi*jpj)                 ,  STAT=trd_mld_trc_alloc) 
     91         ! 
     92      IF( lk_mpp                )   CALL mpp_sum ( trd_mld_trc_alloc ) 
     93      IF( trd_mld_trc_alloc /=0 )   CALL ctl_warn('trd_mld_trc_alloc : failed to allocate arrays.') 
    9594   END FUNCTION trd_mld_trc_alloc 
    9695 
     
    125124      !!---------------------------------------------------------------------- 
    126125 
    127       IF(wrk_in_use(2, 1))THEN 
    128          CALL ctl_stop('trd_mld_trc_zint : requested workspace array unavailable.') 
    129          RETURN 
     126      IF( wrk_in_use(2, 1) ) THEN 
     127         CALL ctl_stop('trd_mld_trc_zint : requested workspace array unavailable')   ;   RETURN 
    130128      END IF 
    131129 
     
    213211      END SELECT 
    214212 
    215       IF(wrk_not_released(2, 1))THEN 
    216          CALL ctl_stop('trd_mld_trc_zint : failed to release workspace array.') 
    217       END IF 
    218  
     213      IF( wrk_not_released(2, 1) )   CALL ctl_stop('trd_mld_trc_zint : failed to release workspace array.') 
     214      ! 
    219215    END SUBROUTINE trd_mld_trc_zint 
    220      
     216 
     217 
    221218    SUBROUTINE trd_mld_bio_zint( ptrc_trdmld, ktrd ) 
    222219      !!---------------------------------------------------------------------- 
     
    387384      !!       - See NEMO documentation (in preparation) 
    388385      !!---------------------------------------------------------------------- 
    389       USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released 
    390       USE wrk_nemo, wrk_3d_1, wrk_3d_2, wrk_3d_3, wrk_3d_4, & 
    391                     wrk_3d_5, wrk_3d_6, wrk_3d_7, wrk_3d_8, & 
    392                     wrk_3d_9 
     386      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released 
     387      USE wrk_nemo, ONLY:   wrk_3d_1, wrk_3d_2, wrk_3d_3, wrk_3d_4 
     388      USE wrk_nemo, ONLY:   wrk_3d_5, wrk_3d_6, wrk_3d_7, wrk_3d_8, wrk_3d_9 
     389      ! 
    393390      INTEGER, INTENT( in ) ::   kt                               ! ocean time-step index 
    394391      INTEGER ::   ji, jj, jk, jl, ik, it, itmod, jn 
     
    414411      !!---------------------------------------------------------------------- 
    415412 
    416       IF(wrk_in_use(3, 1,2,3,4,5,6,7,8,9))THEN 
    417          CALL ctl_stop('trd_mld_trc : requested workspace arrays unavailable.') 
    418          RETURN 
    419       END IF 
     413      IF( wrk_in_use(3, 1,2,3,4,5,6,7,8,9) ) THEN 
     414         CALL ctl_stop('trd_mld_trc : requested workspace arrays unavailable')   ;   RETURN 
     415      ENDIF 
    420416      ! Set-up pointers into sub-arrays of workspaces 
    421417      ztmltot   => wrk_3d_1(:,:,1:jptra) 
  • 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 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r2607 r2636  
    7878   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,  :) ::   trc2d    !:  additional 2d outputs   
    7979   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   trc3d    !:  additional 3d outputs   
    80     
    8180# endif 
    8281 
    83 #if defined key_diabio || defined key_trdmld_trc 
     82# if defined key_diabio || defined key_trdmld_trc 
    8483   !                                                              !!*  namtop_XXX namelist * 
    8584   INTEGER , PUBLIC                               ::   nn_writebio   !: time step frequency for biological outputs  
     
    8786   CHARACTER(len=20), PUBLIC, DIMENSION(jpdiabio) ::   ctrbiu      !: biological trends unit    
    8887   CHARACTER(len=80), PUBLIC, DIMENSION(jpdiabio) ::   ctrbil      !: biological trends long name 
    89 #endif 
     88# endif 
    9089# if defined key_diabio 
    9190   !! Biological trends 
     
    101100# endif 
    102101 
    103 #else 
    104    !!---------------------------------------------------------------------- 
    105    !!  Empty module :                                     No passive tracer 
    106    !!---------------------------------------------------------------------- 
    107 #endif 
    108  
    109102   !!---------------------------------------------------------------------- 
    110103   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    111104   !! $Id$  
    112105   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    113    !!====================================================================== 
    114 #if defined key_top 
     106   !!---------------------------------------------------------------------- 
    115107CONTAINS 
    116108 
    117    FUNCTION trc_alloc() 
     109   INTEGER FUNCTION trc_alloc() 
    118110      !!------------------------------------------------------------------- 
    119111      !!                    *** ROUTINE trc_alloc *** 
    120112      !!------------------------------------------------------------------- 
    121       USE in_out_manager, ONLY: ctl_warn 
     113      USE lib_mpp, ONLY: ctl_warn 
     114      !!------------------------------------------------------------------- 
    122115      ! 
    123       INTEGER :: trc_alloc 
    124       !!------------------------------------------------------------------- 
    125  
    126116      ALLOCATE(cvol(jpi,jpj,jpk),                                  & 
    127117               trn(jpi,jpj,jpk,jptra),                             & 
     
    132122# if defined key_diatrc && ! defined key_iomput 
    133123               trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d), & 
    134 #endif 
     124# endif 
    135125# if defined key_diabio 
    136126               trbio(jpi,jpj,jpk,jpdiabio),                        & 
    137 #endif 
    138                Stat=trc_alloc) 
     127# endif 
     128               STAT=trc_alloc) 
    139129 
    140       IF(trc_alloc /= 0)THEN 
    141          CALL ctl_warn('trc_alloc: failed to allocate arrays.') 
    142       END IF 
    143  
     130      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
     131      ! 
    144132   END FUNCTION trc_alloc 
     133    
     134#else 
     135   !!---------------------------------------------------------------------- 
     136   !!  Empty module :                                     No passive tracer 
     137   !!---------------------------------------------------------------------- 
    145138#endif 
    146139 
     140   !!====================================================================== 
    147141END MODULE trc 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r2528 r2636  
    2727   USE trcnam_my_trc     ! MY_TRC SMS namelist 
    2828   USE in_out_manager    ! I/O manager 
     29   USE lib_mpp           ! MPP library 
    2930   USE trdmod_trc_oce 
    3031 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/trcsms.F90

    r2528 r2636  
    3030   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    3131   !! $Id$  
    32    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3333   !!---------------------------------------------------------------------- 
    34  
    3534CONTAINS 
    3635 
Note: See TracChangeset for help on using the changeset viewer.