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/DTA/dtatem.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/DTA/dtatem.F90

    r2528 r2715  
    1818   USE oce             ! ocean dynamics and tracers 
    1919   USE dom_oce         ! ocean space and time domain 
     20   USE phycst          ! physical constants 
    2021   USE fldread         ! read input fields 
    2122   USE in_out_manager  ! I/O manager 
    22    USE phycst          ! physical constants 
     23   USE lib_mpp         ! MPP library 
    2324 
    2425   IMPLICIT NONE 
     
    2728   PUBLIC   dta_tem    ! called by step.F90 and inidta.F90 
    2829 
    29    LOGICAL , PUBLIC, PARAMETER ::   lk_dtatem = .TRUE.  !: temperature data flag 
    30    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::  t_dta    !: temperature data at given time-step 
     30   LOGICAL , PUBLIC, PARAMETER                     ::   lk_dtatem = .TRUE. !: temperature data flag 
     31   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::   t_dta              !: temperature data at given time-step 
    3132 
    3233   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tem      ! structure of input SST (file informations, fields read) 
     
    3536#  include "domzgr_substitute.h90" 
    3637   !!---------------------------------------------------------------------- 
    37    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     38   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
    3839   !! $Id$  
    3940   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    5859      !! ** Action  :   define t_dta array at time-step kt 
    5960      !!---------------------------------------------------------------------- 
    60       INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
     61      INTEGER, INTENT( in ) ::   kt   ! ocean time-step 
    6162      ! 
    62       INTEGER ::   ji, jj, jk, jl, jkk            ! dummy loop indicies 
    63       INTEGER ::   ik, ierror                     ! temporary integers 
     63      INTEGER ::   ji, jj, jk, jl, jkk       ! dummy loop indicies 
     64      INTEGER ::   ik, ierr, ierr0, ierr1, ierr2   ! local integers 
    6465#if defined key_tradmp 
    65       INTEGER ::   il0, il1, ii0, ii1, ij0, ij1   ! temporary integers 
     66      INTEGER ::   il0, il1, ii0, ii1, ij0, ij1   ! local integers 
    6667#endif 
    6768      REAL(wp)::   zl 
     
    9596            WRITE(numout,*) '~~~~~~~ ' 
    9697         ENDIF 
    97          ALLOCATE( sf_tem(1), STAT=ierror ) 
    98          IF( ierror > 0 ) THEN 
    99              CALL ctl_stop( 'dta_tem: unable to allocate sf_tem structure' )   ;   RETURN 
    100          ENDIF 
    101                                 ALLOCATE( sf_tem(1)%fnow(jpi,jpj,jpk)   ) 
    102          IF( sn_tem%ln_tint )   ALLOCATE( sf_tem(1)%fdta(jpi,jpj,jpk,2) ) 
     98 
     99                                   ! Allocate temperature data array  
     100                                ALLOCATE( t_dta(jpi,jpj,jpk)           , STAT=ierr  ) 
     101         IF( ierr > 0              )   CALL ctl_stop( 'STOP', 'dta_tem: unable to allocate t_dta array' ) 
     102                                   ! Allocate sf_tem structure 
     103                                ierr2 = 0 
     104                                ALLOCATE( sf_tem(1)                    , STAT=ierr0 ) 
     105                                ALLOCATE( sf_tem(1)%fnow(jpi,jpj,jpk)  , STAT=ierr1 ) 
     106         IF( sn_tem%ln_tint )   ALLOCATE( sf_tem(1)%fdta(jpi,jpj,jpk,2), STAT=ierr2 ) 
     107         IF( ierr0+ierr1+ierr2 > 0 )   CALL ctl_stop( 'STOP', 'dta_tem: unable to allocate sf_tem structure' ) 
    103108         !                         ! fill sf_tem with sn_tem and control print 
    104109         CALL fld_fill( sf_tem, (/ sn_tem /), cn_dir, 'dta_tem', 'Temperature data', 'namdta_tem' ) 
Note: See TracChangeset for help on using the changeset viewer.