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 5341 for trunk/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

Ignore:
Timestamp:
2015-06-03T16:59:46+02:00 (9 years ago)
Author:
davestorkey
Message:

Merge of 2014/dev_r4650_UKMO11_restart_functionality branch into the trunk
as part of 3.6_stable build. See ticket #1347.

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r4990 r5341  
    2626   CHARACTER(lc) ::   cn_exp           !: experiment name used for output filename 
    2727   CHARACTER(lc) ::   cn_ocerst_in     !: suffix of ocean restart name (input) 
     28   CHARACTER(lc) ::   cn_ocerst_indir  !: restart input directory 
    2829   CHARACTER(lc) ::   cn_ocerst_out    !: suffix of ocean restart name (output) 
     30   CHARACTER(lc) ::   cn_ocerst_outdir !: restart output directory 
    2931   LOGICAL       ::   ln_rstart        !: start from (F) rest or (T) a restart file 
     32   LOGICAL       ::   ln_rst_list      !: output restarts at list of times (T) or by frequency (F) 
    3033   INTEGER       ::   nn_no            !: job number 
    3134   INTEGER       ::   nn_rstctl        !: control of the time step (0, 1 or 2) 
     
    3841   INTEGER       ::   nn_write         !: model standard output frequency 
    3942   INTEGER       ::   nn_stock         !: restart file frequency 
     43   INTEGER, DIMENSION(10) :: nn_stocklist  !: restart dump times 
    4044   LOGICAL       ::   ln_dimgnnn       !: type of dimgout. (F): 1 file for all proc 
    4145                                                       !:                  (T): 1 file per proc 
     
    7882   INTEGER       ::   nwrite                      !: model standard output frequency 
    7983   INTEGER       ::   nstock                      !: restart file frequency 
     84   INTEGER, DIMENSION(10) :: nstocklist           !: restart dump times 
    8085 
    8186   !!---------------------------------------------------------------------- 
     
    8590   LOGICAL ::   lrst_oce              !: logical to control the oce restart write  
    8691   INTEGER ::   numror, numrow        !: logical unit for cean restart (read and write) 
     92   INTEGER ::   nrst_lst              !: number of restart to output next 
    8793 
    8894   !!---------------------------------------------------------------------- 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r4689 r5341  
    6161      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar     ! domain parameters:  
    6262 
    63       CHARACTER(LEN=100) ::   clinfo           ! info character 
    64       CHARACTER(LEN=100) ::   cltmp            ! temporary character 
     63      CHARACTER(LEN=256) ::   clinfo           ! info character 
     64      CHARACTER(LEN=256) ::   cltmp            ! temporary character 
    6565      INTEGER            ::   iln              ! lengths of character 
    6666      INTEGER            ::   istop            ! temporary storage of nstop 
     
    393393      INTEGER, DIMENSION(4) :: idimsz               ! dimensions size   
    394394      INTEGER, DIMENSION(4) :: idimid               ! dimensions id 
    395       CHARACTER(LEN=100)    :: clinfo               ! info character 
     395      CHARACTER(LEN=256)    :: clinfo               ! info character 
    396396      CHARACTER(LEN= 12), DIMENSION(4) :: cltmp     ! temporary character 
    397397      INTEGER               :: if90id               ! nf90 file identifier 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r4990 r5341  
    5757      !! 
    5858      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
    59       CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     59      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name 
     60      CHARACTER(lc)       ::   clpath   ! full path to ocean output restart file 
    6061      !!---------------------------------------------------------------------- 
    6162      ! 
    6263      IF( kt == nit000 ) THEN   ! default definitions 
    6364         lrst_oce = .FALSE.    
    64          nitrst = nitend 
    65       ENDIF 
    66       IF( MOD( kt - 1, nstock ) == 0 ) THEN    
     65         IF( ln_rst_list ) THEN 
     66            nrst_lst = 1 
     67            nitrst = nstocklist( nrst_lst ) 
     68         ELSE 
     69            nitrst = nitend 
     70         ENDIF 
     71      ENDIF 
     72 
     73      ! frequency-based restart dumping (nn_stock) 
     74      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN    
    6775         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
    6876         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     
    7381      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1 
    7482      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 
     83         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN  
     84            ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     85            IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     86            ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst 
    9087            ENDIF 
    91          ENDIF 
    92          ! 
    93          CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
    94          lrst_oce = .TRUE. 
     88            ! create the file 
     89            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out) 
     90            clpath = TRIM(cn_ocerst_outdir) 
     91            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     92            IF(lwp) THEN 
     93               WRITE(numout,*) 
     94               SELECT CASE ( jprstlib ) 
     95               CASE ( jprstdimg )   ;   WRITE(numout,*)                            & 
     96                   '             open ocean restart binary file: ',TRIM(clpath)//clname 
     97               CASE DEFAULT         ;   WRITE(numout,*)                            & 
     98                   '             open ocean restart NetCDF file: ',TRIM(clpath)//clname 
     99               END SELECT 
     100               IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression' 
     101               IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
     102               ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
     103               ENDIF 
     104            ENDIF 
     105            ! 
     106            CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
     107            lrst_oce = .TRUE. 
     108         ENDIF 
    95109      ENDIF 
    96110      ! 
     
    142156!!gm  not sure what to do here   ===>>>  ask to Sebastian 
    143157         lrst_oce = .FALSE. 
     158            IF( ln_rst_list ) THEN 
     159               nrst_lst = MIN(nrst_lst + 1, SIZE(nstocklist,1)) 
     160               nitrst = nstocklist( nrst_lst ) 
     161            ENDIF 
     162            lrst_oce = .FALSE. 
    144163      ENDIF 
    145164      ! 
     
    156175      !!                the file has already been opened 
    157176      !!---------------------------------------------------------------------- 
    158       INTEGER  ::   jlibalt = jprstlib 
    159       LOGICAL  ::   llok 
     177      INTEGER        ::   jlibalt = jprstlib 
     178      LOGICAL        ::   llok 
     179      CHARACTER(lc)  ::   clpath   ! full path to ocean output restart file 
    160180      !!---------------------------------------------------------------------- 
    161181      ! 
     
    171191         ENDIF 
    172192 
     193         clpath = TRIM(cn_ocerst_indir) 
     194         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
    173195         IF ( jprstlib == jprstdimg ) THEN 
    174196           ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    175197           ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    176            INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
     198           INQUIRE( FILE = TRIM(cn_ocerst_indir)//'/'//TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    177199           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    178200         ENDIF 
    179          CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt ) 
     201         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt ) 
    180202      ENDIF 
    181203   END SUBROUTINE rst_read_open 
Note: See TracChangeset for help on using the changeset viewer.