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 5581 for branches/2014/dev_r4765_CNRS_agrif/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 – NEMO

Ignore:
Timestamp:
2015-07-10T13:28:53+02:00 (9 years ago)
Author:
timgraham
Message:

Merged head of trunk into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4765_CNRS_agrif/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r4693 r5581  
    2222   USE iom             ! I/O module 
    2323   USE eosbn2          ! equation of state            (eos bn2 routine) 
    24    USE trdmld_oce      ! ocean active mixed layer tracers trends variables 
     24   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
    2525   USE divcur          ! hor. divergence and curl      (div & cur routines) 
    26    USE sbc_ice, ONLY : lk_lim3 
    2726 
    2827   IMPLICIT NONE 
     
    5756      !! 
    5857      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
    59       CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     58      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name 
     59      CHARACTER(lc)       ::   clpath   ! full path to ocean output restart file 
    6060      !!---------------------------------------------------------------------- 
    6161      ! 
    6262      IF( kt == nit000 ) THEN   ! default definitions 
    6363         lrst_oce = .FALSE.    
    64          nitrst = nitend 
    65       ENDIF 
    66       IF( MOD( kt - 1, nstock ) == 0 ) THEN    
     64         IF( ln_rst_list ) THEN 
     65            nrst_lst = 1 
     66            nitrst = nstocklist( nrst_lst ) 
     67         ELSE 
     68            nitrst = nitend 
     69         ENDIF 
     70      ENDIF 
     71 
     72      ! frequency-based restart dumping (nn_stock) 
     73      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN    
    6774         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
    6875         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     
    7380      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1 
    7481      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN 
    75          ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    76          IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
    77          ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst 
    78          ENDIF 
    79          ! create the file 
    80          clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out) 
    81          IF(lwp) THEN 
    82             WRITE(numout,*) 
    83             SELECT CASE ( jprstlib ) 
    84             CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname 
    85             CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname 
    86             END SELECT 
    87             IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression' 
    88             IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
    89             ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
     82         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN  
     83            ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     84            IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     85            ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst 
    9086            ENDIF 
    91          ENDIF 
    92          ! 
    93          CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
    94          lrst_oce = .TRUE. 
     87            ! create the file 
     88            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out) 
     89            clpath = TRIM(cn_ocerst_outdir) 
     90            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     91            IF(lwp) THEN 
     92               WRITE(numout,*) 
     93               SELECT CASE ( jprstlib ) 
     94               CASE ( jprstdimg )   ;   WRITE(numout,*)                            & 
     95                   '             open ocean restart binary file: ',TRIM(clpath)//clname 
     96               CASE DEFAULT         ;   WRITE(numout,*)                            & 
     97                   '             open ocean restart NetCDF file: ',TRIM(clpath)//clname 
     98               END SELECT 
     99               IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression' 
     100               IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
     101               ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
     102               ENDIF 
     103            ENDIF 
     104            ! 
     105            CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
     106            lrst_oce = .TRUE. 
     107         ENDIF 
    95108      ENDIF 
    96109      ! 
     
    120133                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     ) 
    121134                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      ) 
    122       IF( lk_lim3 )  CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) ) 
    123135                     ! 
    124136                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields 
     
    133145                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       ) 
    134146#endif 
    135                   IF( lk_lim3 ) THEN 
    136                      CALL iom_rstput( kt, nitrst, numrow, 'iatte'  , iatte     ) !clem modif 
    137                      CALL iom_rstput( kt, nitrst, numrow, 'oatte'  , oatte     ) !clem modif 
    138                   ENDIF 
    139147      IF( kt == nitrst ) THEN 
    140148         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
    141          IF( .NOT. lk_trdmld )   lrst_oce = .FALSE. 
     149!!gm         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE. 
     150!!gm  not sure what to do here   ===>>>  ask to Sebastian 
     151         lrst_oce = .FALSE. 
     152            IF( ln_rst_list ) THEN 
     153               nrst_lst = MIN(nrst_lst + 1, SIZE(nstocklist,1)) 
     154               nitrst = nstocklist( nrst_lst ) 
     155            ENDIF 
     156            lrst_oce = .FALSE. 
    142157      ENDIF 
    143158      ! 
    144159   END SUBROUTINE rst_write 
     160 
    145161 
    146162   SUBROUTINE rst_read_open 
     
    153169      !!                the file has already been opened 
    154170      !!---------------------------------------------------------------------- 
    155       INTEGER  ::   jlibalt = jprstlib 
    156       LOGICAL  ::   llok 
    157       !!---------------------------------------------------------------------- 
    158  
    159       IF( numror .LE. 0 ) THEN 
     171      INTEGER        ::   jlibalt = jprstlib 
     172      LOGICAL        ::   llok 
     173      CHARACTER(lc)  ::   clpath   ! full path to ocean output restart file 
     174      !!---------------------------------------------------------------------- 
     175      ! 
     176      IF( numror <= 0 ) THEN 
    160177         IF(lwp) THEN                                             ! Contol prints 
    161178            WRITE(numout,*) 
     
    168185         ENDIF 
    169186 
     187         clpath = TRIM(cn_ocerst_indir) 
     188         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
    170189         IF ( jprstlib == jprstdimg ) THEN 
    171190           ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    172191           ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    173            INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
     192           INQUIRE( FILE = TRIM(cn_ocerst_indir)//'/'//TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    174193           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    175194         ENDIF 
    176          CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt ) 
     195         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt ) 
    177196      ENDIF 
    178197   END SUBROUTINE rst_read_open 
     
    211230         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   ) 
    212231         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
    213          IF( lk_lim3 )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
    214232      ELSE 
    215233         neuler = 0 
     
    247265         hdivb(:,:,:)   = hdivn(:,:,:) 
    248266         sshb (:,:)     = sshn (:,:) 
    249          IF( lk_lim3 ) THEN 
     267 
     268         IF( lk_vvl ) THEN 
    250269            DO jk = 1, jpk 
    251270               fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
    252271            END DO 
    253272         ENDIF 
    254       ENDIF 
    255       ! 
    256       IF( lk_lim3 ) THEN 
    257          CALL iom_get( numror, jpdom_autoglo, 'iatte' , iatte ) ! clem modif 
    258          CALL iom_get( numror, jpdom_autoglo, 'oatte' , oatte ) ! clem modif 
     273 
    259274      ENDIF 
    260275      ! 
Note: See TracChangeset for help on using the changeset viewer.