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

Changeset 2606


Ignore:
Timestamp:
2011-02-22T18:14:24+01:00 (13 years ago)
Author:
trackstand2
Message:

Module arrays made allocatable

Location:
branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP
Files:
5 edited

Legend:

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

    r2528 r2606  
    3232   PRIVATE 
    3333 
    34    PUBLIC   trc_adv    ! routine called by step module 
     34   PUBLIC   trc_adv          ! routine called by step module 
     35   PUBLIC   trc_adv_alloc    ! routine called by nemogcm module 
    3536 
    3637   INTEGER ::   nadv   ! choice of the type of advection scheme 
    37    REAL(wp), DIMENSION(jpk) ::   r2dt  ! vertical profile time-step, = 2 rdttra 
     38   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt  ! vertical profile time-step, = 2 rdttra 
    3839      !                                ! except at nit000 (=rdttra) if neuler=0 
    3940 
     
    4849 
    4950CONTAINS 
     51 
     52   FUNCTION trc_adv_alloc() 
     53      !!---------------------------------------------------------------------- 
     54      !!                  ***  ROUTINE trc_adv_alloc  *** 
     55      !!---------------------------------------------------------------------- 
     56      INTEGER :: trc_adv_alloc 
     57      !!---------------------------------------------------------------------- 
     58 
     59      ALLOCATE(r2dt(jpk), Stat=trc_adv_alloc) 
     60 
     61      IF(trc_adv_alloc /= 0)THEN 
     62         CALL ctl_warn('trc_adv_alloc : failed to allocate array.') 
     63      END IF 
     64 
     65   END FUNCTION trc_adv_alloc 
     66 
    5067 
    5168   SUBROUTINE trc_adv( kt ) 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r2528 r2606  
    2929   PRIVATE 
    3030 
    31    PUBLIC trc_dmp      ! routine called by step.F90 
     31   PUBLIC trc_dmp            ! routine called by step.F90 
     32   PUBLIC trc_dmp_alloc      ! routine called by nemogcm.F90 
    3233 
    3334   LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .TRUE.   !: internal damping flag 
     
    4041   INTEGER  ::   nn_file_tr =    2   ! = 1 create a damping.coeff NetCDF file  
    4142 
    42    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   restotr   ! restoring coeff. on tracers (s-1) 
     43   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1) 
    4344 
    4445   !! * Substitutions 
     
    5152 
    5253CONTAINS 
     54 
     55   FUNCTION trc_dmp_alloc() 
     56      !!---------------------------------------------------------------------- 
     57      !!                   ***  ROUTINE trc_dmp_alloc  *** 
     58      !!---------------------------------------------------------------------- 
     59      INTEGER :: trc_dmp_alloc 
     60      !!---------------------------------------------------------------------- 
     61 
     62      ALLOCATE(restotr(jpi,jpj,jpk), Stat=trc_dmp_alloc) 
     63 
     64      IF(trc_dmp_alloc /= 0)THEN 
     65         CALL ctl_warn('trc_dmp_alloc : failed to allocate array.') 
     66      END IF 
     67 
     68   END FUNCTION trc_dmp_alloc 
     69 
    5370 
    5471   SUBROUTINE trc_dmp( kt ) 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r2528 r2606  
    4545   !! * Routine accessibility 
    4646   PUBLIC trc_nxt          ! routine called by step.F90 
     47   PUBLIC trc_nxt_alloc    ! routine called by nemogcm.F90 
    4748 
    48   REAL(wp), DIMENSION(jpk) ::   r2dt 
     49   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt 
    4950   !!---------------------------------------------------------------------- 
    5051   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    5455 
    5556CONTAINS 
     57 
     58   FUNCTION trc_nxt_alloc 
     59      !!---------------------------------------------------------------------- 
     60      !!                   ***  ROUTINE trc_nxt_alloc  *** 
     61      !!---------------------------------------------------------------------- 
     62      INTEGER :: trc_nxt_alloc 
     63      !!---------------------------------------------------------------------- 
     64 
     65      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 
     71   END FUNCTION trc_nxt_alloc 
     72 
    5673 
    5774   SUBROUTINE trc_nxt( kt ) 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r2528 r2606  
    2929   PRIVATE 
    3030 
    31    PUBLIC   trc_zdf    ! called by step.F90  
     31   PUBLIC   trc_zdf          ! called by step.F90  
     32   PUBLIC   trc_zdf_alloc    ! called by nemogcm.F90  
    3233 
    3334   INTEGER ::   nzdf = 0               ! type vertical diffusion algorithm used 
    3435      !                                ! defined from ln_zdf...  namlist logicals) 
    35    REAL(wp), DIMENSION(jpk) ::  r2dt   ! vertical profile time-step, = 2 rdttra 
     36   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::  r2dt   ! vertical profile time-step, = 2 rdttra 
    3637      !                                ! except at nit000 (=rdttra) if neuler=0 
    3738 
     
    4849CONTAINS 
    4950    
     51   FUNCTION trc_zdf_alloc() 
     52      !!---------------------------------------------------------------------- 
     53      !!                  ***  ROUTINE trc_zdf_alloc  *** 
     54      !!---------------------------------------------------------------------- 
     55      INTEGER :: trc_zdf_alloc 
     56      !!---------------------------------------------------------------------- 
     57 
     58      ALLOCATE(r2dt(jpk), Stat=trc_zdf_alloc) 
     59 
     60      IF(trc_zdf_alloc /= 0)THEN 
     61         CALL ctl_warn('trc_zdf_alloc : failed to allocate array.') 
     62      END IF 
     63 
     64   END FUNCTION trc_zdf_alloc 
     65 
     66 
    5067   SUBROUTINE trc_zdf( kt ) 
    5168      !!---------------------------------------------------------------------- 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/TRP/trdmod_trc_oce.F90

    r2528 r2606  
    6060   !! Trends diagnostics parameters 
    6161   !!--------------------------------------------------------------------- 
    62    INTEGER, PARAMETER ::            & 
    63       jpltrd_trc = 12,                  & !: number of mixed-layer trends arrays 
    64       jpktrd_trc = jpk                    !: max level for mixed-layer trends diag. 
     62   INTEGER, PARAMETER :: jpltrd_trc = 12    !: number of mixed-layer trends arrays 
     63       
     64   INTEGER            :: jpktrd_trc         !: max level for mixed-layer trends diag. 
    6565 
    6666   !! Arrays used for diagnosing mixed-layer trends  
     
    6868   CHARACTER(LEN=80) :: clname_trc, ctrd_trc(jpltrd_trc+1,2) 
    6969 
    70    INTEGER, DIMENSION(jpi,jpj) ::   & 
     70   INTEGER, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   & 
    7171      nmld_trc       , &                            !: mixed layer depth indexes  
    7272      nbol_trc                                   !: mixed-layer depth indexes when read from file 
    7373 
    74    REAL(wp), DIMENSION(jpi,jpj,jpk) ::  wkx_trc  !: 
     74   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  wkx_trc  !: 
    7575 
    76    REAL(wp), DIMENSION(jpi,jpj) ::  rmld_trc     !: ML depth (m) corresponding to nmld_trc 
    77    REAL(wp), DIMENSION(jpi,jpj) ::  rmld_sum_trc !: needed to compute the leap-frog time mean of ML depth 
    78    REAL(wp), DIMENSION(jpi,jpj) ::  rmldbn_trc   !: idem 
     76   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmld_trc     !: ML depth (m) corresponding to nmld_trc 
     77   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmld_sum_trc !: needed to compute the leap-frog time mean of ML depth 
     78   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::  rmldbn_trc   !: idem 
    7979 
    80    REAL(wp), DIMENSION(jpi,jpj,jptra) ::  & 
     80   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  & 
    8181      tml_trc    ,                        &      !: \ "now" mixed layer temperature/salinity 
    8282      tmlb_trc   ,                        &      !: /  and associated "before" fields 
     
    8989                                                 !:     previous analysis period 
    9090                                                  
    91    REAL(wp), DIMENSION(jpi,jpj,jptra) ::  &       
     91   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  &       
    9292      tmlatfb_trc, tmlatfn_trc ,          &      !: "before" Asselin contrib. at beginning of the averaging 
    9393                                                 !:     period (i.e. last contrib. from previous such period) 
     
    9898      tmlradm_trc                                !: accumulator for the previous trcrad trend 
    9999 
    100    REAL(wp), DIMENSION(jpi,jpj,jpltrd_trc,jptra) ::  & 
     100   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  & 
    101101      tmltrd_trc,                         &      !: \ physical contributions to the total trend (for T/S), 
    102102                                                 !: / cumulated over the current analysis window 
     
    105105      tmltrd_csum_ub_trc                         !: before (prev. analysis period) cumulated sum over the 
    106106                                                 !: upper triangle 
    107    REAL(wp), DIMENSION(jpi,jpj,jptra) ::  & 
     107   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  & 
    108108      tmltrdm_trc                                !: total cumulative trends over the analysis window 
    109109 
     
    114114#if defined key_lobster 
    115115   CHARACTER(LEN=80) :: clname_bio, ctrd_bio(jpdiabio,2) 
    116    REAL(wp), DIMENSION(jpi,jpj,jpdiabio) ::  & 
     116   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  & 
    117117      tmltrd_bio,                         &      !: \ biological contributions to the total trend , 
    118118                                                 !: / cumulated over the current analysis window 
     
    129129#endif 
    130130 
     131#if defined key_top 
     132CONTAINS 
     133 
     134   FUNCTION trd_mod_trc_oce_alloc 
     135      !!---------------------------------------------------------------------- 
     136      !!         *** ROUTINE trd_mod_trc_oce_alloc *** 
     137      !!---------------------------------------------------------------------- 
     138      USE in_out_manager, ONLY: ctl_warn 
     139      ! 
     140      INTEGER :: trd_mod_trc_oce_alloc 
     141      ! Locals 
     142      INTEGER :: ierr(2) 
     143      !!---------------------------------------------------------------------- 
     144 
     145      ierr(:) = 0 
     146 
     147#if defined key_trdmld_trc 
     148      ALLOCATE(nmld_trc(jpi,jpj),          nbol_trc(jpi,jpj),           & 
     149               wkx_trc(jpi,jpj,jpk),       rmld_trc(jpi,jpj),           & 
     150               rmld_sum_trc(jpi,jpj),      rmldbn_trc(jpi,jpj),         & 
     151               tml_trc(jpi,jpj,jptra),     tmlb_trc(jpi,jpj,jptra),     & 
     152               tmlbb_trc(jpi,jpj,jptra),   tmlbn_trc(jpi,jpj,jptra),    & 
     153               tml_sum_trc(jpi,jpj,jptra), tml_sumb_trc(jpi,jpj,jptra), & 
     154               tmltrd_atf_sumb_trc(jpi,jpj,jptra),                      & 
     155               tmltrd_rad_sumb_trc(jpi,jpj,jptra),                      & 
     156               ! 
     157               tmlatfb_trc(jpi,jpj,jptra), tmlatfn_trc(jpi,jpj,jptra),  & 
     158               tmlatfm_trc(jpi,jpj,jptra), tmlradb_trc(jpi,jpj,jptra),  & 
     159               tmlradn_trc(jpi,jpj,jptra), tmlradm_trc(jpi,jpj,jptra),  & 
     160               ! 
     161               tmltrd_trc(jpi,jpj,jpltrd_trc,jptra)        , & 
     162               tmltrd_sum_trc(jpi,jpj,jpltrd_trc,jptra)    , & 
     163               tmltrd_csum_ln_trc(jpi,jpj,jpltrd_trc,jptra), & 
     164               tmltrd_csum_ub_trc(jpi,jpj,jpltrd_trc,jptra), & 
     165               ! 
     166               tmltrdm_trc(jpi,jpj,jptra),                   & 
     167               Stat=ierr(1)) 
     168#endif 
     169#if defined key_lobster 
     170      ALLOCATE(tmltrd_bio(jpi,jpj,jpdiabio),         & 
     171               tmltrd_sum_bio(jpi,jpj,jpdiabio),     & 
     172               tmltrd_csum_ln_bio(jpi,jpj,jpdiabio), & 
     173               tmltrd_csum_ub_bio(jpi,jpj,jpdiabio), & 
     174               Stat=ierr(2)) 
     175#endif 
     176 
     177      trd_mod_trc_oce_alloc = MAXVAL(ierr) 
     178 
     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 
     182 
     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 
     187#endif 
     188 
     189   END FUNCTION trd_mod_trc_oce_alloc 
     190#endif 
    131191 
    132192END MODULE trdmod_trc_oce 
Note: See TracChangeset for help on using the changeset viewer.