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 2715 for trunk/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_oce.F90 – NEMO

Ignore:
Timestamp:
2011-03-30T17:58:35+02:00 (13 years ago)
Author:
rblod
Message:

First attempt to put dynamic allocation on the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_oce.F90

    r2528 r2715  
    44   !! Ocean trends :   set tracer and momentum trend variables 
    55   !!====================================================================== 
    6    !! History :  9.0  !  04-08  (C. Talandier)  New trends organization 
     6   !! History :  1.0  ! 2004-08  (C. Talandier)  New trends organization 
    77   !!---------------------------------------------------------------------- 
    8    USE par_oce         ! ocean parameters 
     8   USE par_oce        ! ocean parameters 
    99 
    1010   IMPLICIT NONE 
    1111   PRIVATE 
     12 
     13   PUBLIC   trdmld_oce_alloc    ! Called in trdmld.F90 
    1214 
    1315#if defined key_trdmld 
     
    1719#endif 
    1820   !!* mixed layer trends indices 
    19    INTEGER, PARAMETER, PUBLIC ::   jpltrd = 11    !: number of mixed-layer trends arrays 
    20    INTEGER, PUBLIC   &  
    21 #if !defined key_agrif 
    22       , PARAMETER  & 
    23 #endif 
    24 ::   jpktrd = jpk   !: max level for mixed-layer trends diag. 
     21   INTEGER, PARAMETER, PUBLIC ::   jpltrd = 11      !: number of mixed-layer trends arrays 
     22   INTEGER, PUBLIC            ::   jpktrd           !: max level for mixed-layer trends diag. 
    2523   ! 
    2624   INTEGER, PUBLIC, PARAMETER ::   jpmld_xad =  1   !:  zonal       
     
    4644   CHARACTER(LEN=80) , PUBLIC :: clname, ctrd(jpltrd+1,2) 
    4745 
    48    INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nmld   !: mixed layer depth indexes  
    49    INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nbol   !: mixed-layer depth indexes when read from file 
     46   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nmld   !: mixed layer depth indexes  
     47   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nbol   !: mixed-layer depth indexes when read from file 
    5048 
    51    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   wkx    !: 
     49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wkx    !: 
    5250 
    53    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)  ::  & 
    5452      rmld   ,                      & !: mld depth (m) corresponding to nmld 
    5553      tml    , sml  ,               & !: \ "now" mixed layer temperature/salinity 
     
    6664      rmld_sum, rmldbn                !: needed to compute the leap-frog time mean of the ML depth 
    6765 
    68    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  & 
    6967      tmlatfb, tmlatfn ,            & !: "before" Asselin contribution at begining of the averaging 
    7068      smlatfb, smlatfn,             & !: period (i.e. last contrib. from previous such period) and  
     
    7270      tmlatfm, smlatfm                !: accumulator for Asselin trends (needed for storage only) 
    7371 
    74    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpltrd) ::  & 
     72   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::  & 
    7573      tmltrd,                       & !: \ physical contributions to the total trend (for T/S), 
    7674      smltrd,                       & !: / cumulated over the current analysis window 
     
    8381#endif 
    8482   !!---------------------------------------------------------------------- 
    85    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     83   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
    8684   !! $Id$  
    87    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     85   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     86   !!---------------------------------------------------------------------- 
     87CONTAINS 
     88 
     89  INTEGER FUNCTION trdmld_oce_alloc() 
     90     !!---------------------------------------------------------------------- 
     91     !!                 ***  FUNCTION trdmld_oce_alloc   *** 
     92     !!---------------------------------------------------------------------- 
     93     USE lib_mpp 
     94     INTEGER :: ierr(5) 
     95     !!---------------------------------------------------------------------- 
     96 
     97     ! Initialise jpktrd here as can no longer do it in MODULE body since 
     98     ! jpk is now a variable. 
     99     jpktrd = jpk   !: max level for mixed-layer trends diag. 
     100 
     101     ierr(:) = 0 
     102 
     103#if   defined  key_trdmld   ||   defined key_esopa 
     104     ALLOCATE( nmld(jpi,jpj), nbol(jpi,jpj),       & 
     105        &      wkx(jpi,jpj,jpk), rmld(jpi,jpj),    &  
     106        &      tml(jpi,jpj)    , sml(jpi,jpj),     &  
     107        &      tmlb(jpi,jpj)   , smlb(jpi,jpj) ,   & 
     108        &      tmlbb(jpi,jpj)  , smlbb(jpi,jpj), STAT = ierr(1) ) 
     109 
     110     ALLOCATE( tmlbn(jpi,jpj)  , smlbn(jpi,jpj),   & 
     111        &      tmltrdm(jpi,jpj), smltrdm(jpi,jpj), & 
     112        &      tml_sum(jpi,jpj), tml_sumb(jpi,jpj),& 
     113        &      tmltrd_atf_sumb(jpi,jpj)           , STAT=ierr(2) ) 
     114 
     115     ALLOCATE( sml_sum(jpi,jpj), sml_sumb(jpi,jpj), & 
     116        &      smltrd_atf_sumb(jpi,jpj),            & 
     117        &      rmld_sum(jpi,jpj), rmldbn(jpi,jpj),  & 
     118        &      tmlatfb(jpi,jpj), tmlatfn(jpi,jpj), STAT = ierr(3) ) 
     119 
     120     ALLOCATE( smlatfb(jpi,jpj), smlatfn(jpi,jpj), &  
     121        &      tmlatfm(jpi,jpj), smlatfm(jpi,jpj), & 
     122        &      tmltrd(jpi,jpj,jpltrd),   smltrd(jpi,jpj,jpltrd), STAT=ierr(4)) 
     123 
     124     ALLOCATE( tmltrd_sum(jpi,jpj,jpltrd),tmltrd_csum_ln(jpi,jpj,jpltrd),      & 
     125        &      tmltrd_csum_ub(jpi,jpj,jpltrd), smltrd_sum(jpi,jpj,jpltrd),     & 
     126        &      smltrd_csum_ln(jpi,jpj,jpltrd), smltrd_csum_ub(jpi,jpj,jpltrd), STAT=ierr(5) ) 
     127#endif 
     128      ! 
     129      trdmld_oce_alloc = MAXVAL( ierr ) 
     130      IF( lk_mpp                )   CALL mpp_sum ( trdmld_oce_alloc ) 
     131      IF( trdmld_oce_alloc /= 0 )   CALL ctl_warn('trdmld_oce_alloc: failed to allocate arrays') 
     132      ! 
     133   END FUNCTION trdmld_oce_alloc 
     134 
    88135   !!====================================================================== 
    89136END MODULE trdmld_oce 
Note: See TracChangeset for help on using the changeset viewer.