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 4292 for branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 – NEMO

Ignore:
Timestamp:
2013-11-20T17:28:04+01:00 (10 years ago)
Author:
cetlod
Message:

dev_MERGE_2013 : 1st step of the merge, see ticket #1185

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r4206 r4292  
    2323   USE eosbn2          ! equation of state            (eos bn2 routine) 
    2424   USE trdmld_oce      ! ocean active mixed layer tracers trends variables 
    25    USE domvvl          ! variable volume 
    2625   USE divcur          ! hor. divergence and curl      (div & cur routines) 
    2726   USE sbc_ice, ONLY : lk_lim3 
     
    3029   PRIVATE 
    3130 
    32    PUBLIC   rst_opn    ! routine called by step module 
    33    PUBLIC   rst_write  ! routine called by step module 
    34    PUBLIC   rst_read   ! routine called by opa  module 
     31   PUBLIC   rst_opn         ! routine called by step module 
     32   PUBLIC   rst_write       ! routine called by step module 
     33   PUBLIC   rst_read        ! routine called by istate module 
     34   PUBLIC   rst_read_open   ! routine called in rst_read and (possibly) in dom_vvl_init 
    3535 
    3636   !! * Substitutions 
     
    120120                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     ) 
    121121                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      ) 
    122       IF( lk_vvl )   CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) ) 
    123122                     ! 
    124123                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields 
     
    144143   END SUBROUTINE rst_write 
    145144 
     145   SUBROUTINE rst_read_open 
     146      !!----------------------------------------------------------------------  
     147      !!                   ***  ROUTINE rst_read_open  *** 
     148      !!  
     149      !! ** Purpose :   Open read files for restart (format fixed by jprstlib ) 
     150      !!  
     151      !! ** Method  :   Use a non-zero, positive value of numror to assess whether or not 
     152      !!                the file has already been opened 
     153      !!---------------------------------------------------------------------- 
     154      INTEGER  ::   jlibalt = jprstlib 
     155      LOGICAL  ::   llok 
     156      !!---------------------------------------------------------------------- 
     157 
     158      IF( numror .LE. 0 ) THEN 
     159         IF(lwp) THEN                                             ! Contol prints 
     160            WRITE(numout,*) 
     161            SELECT CASE ( jprstlib ) 
     162            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
     163            CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
     164            END SELECT 
     165            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
     166            WRITE(numout,*) '~~~~~~~~' 
     167         ENDIF 
     168 
     169         IF ( jprstlib == jprstdimg ) THEN 
     170           ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
     171           ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
     172           INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
     173           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
     174         ENDIF 
     175         CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt ) 
     176      ENDIF 
     177   END SUBROUTINE rst_read_open 
    146178 
    147179   SUBROUTINE rst_read 
     
    154186      !!---------------------------------------------------------------------- 
    155187      REAL(wp) ::   zrdt, zrdttra1 
    156       INTEGER  ::   jk, jlibalt = jprstlib 
     188      INTEGER  ::   jk 
    157189      LOGICAL  ::   llok 
    158190      !!---------------------------------------------------------------------- 
    159191 
    160       IF(lwp) THEN                                             ! Contol prints 
    161          WRITE(numout,*) 
    162          SELECT CASE ( jprstlib ) 
    163          CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file ',TRIM(cn_ocerst_in)//'.nc' 
    164          CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    165          END SELECT 
    166          IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
    167          WRITE(numout,*) '~~~~~~~~' 
    168       ENDIF 
    169  
    170       IF ( jprstlib == jprstdimg ) THEN 
    171         ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    172         ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    173         INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    174         IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    175       ENDIF 
    176       CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt ) 
     192      CALL rst_read_open           ! open restart for reading (if not already opened) 
    177193 
    178194      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
     
    194210         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   ) 
    195211         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
    196          IF( lk_vvl )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
    197212      ELSE 
    198213         neuler = 0 
     
    230245         hdivb(:,:,:)   = hdivn(:,:,:) 
    231246         sshb (:,:)     = sshn (:,:) 
    232          IF( lk_vvl ) THEN 
    233             DO jk = 1, jpk 
    234                fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
    235             END DO 
    236          ENDIF 
    237247      ENDIF 
    238248      ! 
Note: See TracChangeset for help on using the changeset viewer.