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/dtasal.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/dtasal.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 
    2526   PRIVATE 
    2627 
    27    PUBLIC   dta_sal   ! called by step.F90 and inidta.F90 
    28     
    29    LOGICAL , PUBLIC, PARAMETER ::   lk_dtasal = .TRUE.    !: salinity data flag 
    30    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   s_dta    !: salinity data at given time-step 
    31  
    32    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal       ! structure of input SST (file informations, fields read) 
     28   PUBLIC   dta_sal    ! called by step.F90 and inidta.F90 
     29 
     30   LOGICAL , PUBLIC, PARAMETER                     ::   lk_dtasal = .TRUE. !: salinity data flag 
     31   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::   s_dta              !: salinity data at given time-step 
     32 
     33   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal   ! structure of input SST (file informations, fields read) 
    3334 
    3435   !! * Substitutions 
    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) 
     
    5253      !!                between two monthly values. 
    5354      !!---------------------------------------------------------------------- 
    54       INTEGER, INTENT(in) ::   kt             ! ocean time step 
     55      INTEGER, INTENT(in) ::   kt   ! ocean time step 
    5556      ! 
    56       INTEGER ::   ji, jj, jk, jl, jkk            ! dummy loop indicies 
    57       INTEGER ::   ik, ierror                     ! temporary integers 
     57      INTEGER ::   ji, jj, jk, jl, jkk       ! local loop indicies 
     58      INTEGER ::   ik, ierr, ierr0, ierr1, ierr2   ! local integers 
    5859#if defined key_tradmp 
    59       INTEGER ::   il0, il1, ii0, ii1, ij0, ij1   ! temporary integers 
     60      INTEGER ::   il0, il1, ii0, ii1, ij0, ij1   ! local integers 
    6061#endif 
    6162      REAL(wp)::   zl 
     
    8889            WRITE(numout,*) '~~~~~~~ ' 
    8990         ENDIF 
    90          ALLOCATE( sf_sal(1), STAT=ierror ) 
    91          IF( ierror > 0 ) THEN 
    92              CALL ctl_stop( 'dta_sal: unable to allocate sf_sal structure' )   ;   RETURN 
    93          ENDIF 
    94                                 ALLOCATE( sf_sal(1)%fnow(jpi,jpj,jpk)   ) 
    95          IF( sn_sal%ln_tint )   ALLOCATE( sf_sal(1)%fdta(jpi,jpj,jpk,2) ) 
     91 
     92                                   ! Allocate salinity data array  
     93                                ALLOCATE( s_dta(jpi,jpj,jpk)           , STAT=ierr  ) 
     94         IF( ierr > 0              )   CALL ctl_stop( 'STOP', 'dta_sal: unable to allocate s_dta array' ) 
     95                                   ! Allocate sf_tem structure 
     96                                ierr2 = 0 
     97                                ALLOCATE( sf_sal(1)                    , STAT=ierr0 ) 
     98                                ALLOCATE( sf_sal(1)%fnow(jpi,jpj,jpk)  , STAT=ierr1 ) 
     99         IF( sn_sal%ln_tint )   ALLOCATE( sf_sal(1)%fdta(jpi,jpj,jpk,2), STAT=ierr2 ) 
     100         IF( ierr0+ierr1+ierr2 > 0 )   CALL ctl_stop( 'STOP', 'dta_sal: unable to allocate sf_sal structure' ) 
    96101         !                         ! fill sf_sal with sn_sal and control print 
    97102         CALL fld_fill( sf_sal, (/ sn_sal /), cn_dir, 'dta_sal', 'Salinity data', 'namdta_sal' ) 
Note: See TracChangeset for help on using the changeset viewer.