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 2517 for branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 – NEMO

Ignore:
Timestamp:
2010-12-23T17:34:46+01:00 (14 years ago)
Author:
cetlod
Message:

v3.3beta:Ensure restartability of ORCA2_OFF_PISCES & define lk_offline flag for OFFLINE mode

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r2457 r2517  
    3434   USE trcrst_c14b     ! C14 bomb restart 
    3535   USE trcrst_my_trc   ! MY_TRC   restart 
    36 #if defined key_offline 
    37     USE daymod 
    38 #endif 
     36   USE daymod 
    3937   IMPLICIT NONE 
    4038   PRIVATE 
     
    6361      !!---------------------------------------------------------------------- 
    6462      ! 
    65 # if ! defined key_offline 
    66       IF( kt == nit000 ) lrst_trc = .FALSE.  
    67 # else 
    68       IF( kt == nit000 ) THEN 
    69         lrst_trc = .FALSE.  
    70         nitrst = nitend   
    71       ENDIF 
    72  
    73       IF( MOD( kt - 1, nstock ) == 0 ) THEN 
    74          ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
    75          nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
    76          IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    77       ENDIF 
    78 # endif 
    79      ! to get better performances with NetCDF format: 
    80      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    81      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
    82      IF( kt == nitrst - 2*nn_dttrc + 1 .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc + 1 .AND. .NOT. lrst_trc ) ) THEN 
     63      IF( lk_offline ) THEN 
     64         IF( kt == nit000 ) THEN 
     65            lrst_trc = .FALSE. 
     66            nitrst = nitend 
     67         ENDIF 
     68 
     69         IF( MOD( kt - 1, nstock ) == 0 ) THEN 
     70            ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
     71            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     72            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
     73         ENDIF 
     74      ELSE 
     75         IF( kt == nit000 ) lrst_trc = .FALSE. 
     76      ENDIF 
     77 
     78      ! to get better performances with NetCDF format: 
     79      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
     80      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
     81      IF( kt == nitrst - 2*nn_dttrc + 1 .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc + 1 .AND. .NOT. lrst_trc ) ) THEN 
    8382         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    8483         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    102101      !!---------------------------------------------------------------------- 
    103102      INTEGER  ::  jn      
    104       INTEGER  ::  iarak0  
    105       REAL(wp) ::  zarak0 
    106103      INTEGER  ::  jlibalt = jprstlib 
    107104      LOGICAL  ::  llok 
     
    126123      CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    127124 
    128       IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   iarak0 = 1 
    129       ELSE                                           ;   iarak0 = 0 
    130       ENDIF 
    131       CALL iom_get( numrtr, 'arak0', zarak0 ) 
    132  
    133       IF( iarak0 /= NINT( zarak0 ) )   &                           ! Control of the scheme 
    134          & CALL ctl_stop( ' ===>>>> : problem with advection scheme', & 
    135          & ' it must be the same type for both restart and previous run', & 
    136          & ' centered or euler '  ) 
    137       IF(lwp) WRITE(numout,*) 
    138       IF(lwp) WRITE(numout,*) '    arakawa option      : ', NINT( zarak0 ) 
    139  
    140125      ! READ prognostic variables and computes diagnostic variable 
    141126      DO jn = 1, jptra 
     
    171156 
    172157      CALL trc_rst_cal( kt, 'WRITE' )   ! calendar 
    173  
    174       IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   zarak0 = 1. 
    175       ELSE                                           ;   zarak0 = 0. 
    176       ENDIF 
    177       CALL iom_rstput( kt, nitrst, numrtw, 'arak0', zarak0 ) 
    178  
     158      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step 
    179159      ! prognostic variables  
    180160      ! --------------------  
     
    232212      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    233213      ! 
    234       REAL(wp) ::  zkt 
    235 #if defined key_offline 
     214      REAL(wp) ::  zkt, zrdttrc1 
    236215      REAL(wp) ::  zndastp 
    237 #endif 
    238216 
    239217      ! Time domain : restart 
     
    257235            &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
    258236            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
    259 #if defined key_offline 
    260          ! define ndastp and adatrj 
    261          IF ( nn_rsttr == 2 ) THEN 
    262             CALL iom_get( numrtr, 'ndastp', zndastp )  
    263             ndastp = NINT( zndastp ) 
    264             CALL iom_get( numrtr, 'adatrj', adatrj  ) 
    265          ELSE 
    266             ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
    267             adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    268             ! note this is wrong if time step has changed during run 
     237         IF( lk_offline ) THEN      ! set the date in offline mode 
     238            ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
     239            IF( iom_varid( numrtr, 'rdttrc1', ldstop = .FALSE. ) > 0 )   THEN 
     240               CALL iom_get( numrtr, 'rdttrc1', zrdttrc1 ) 
     241               IF( zrdttrc1 /= rdttrc(1) )   neuler = 0 
     242            ENDIF 
     243            !                          ! define ndastp and adatrj 
     244            IF ( nn_rsttr == 2 ) THEN 
     245               CALL iom_get( numrtr, 'ndastp', zndastp )  
     246               ndastp = NINT( zndastp ) 
     247               CALL iom_get( numrtr, 'adatrj', adatrj  ) 
     248            ELSE 
     249               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
     250               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     251               ! note this is wrong if time step has changed during run 
     252            ENDIF 
     253            ! 
     254            IF(lwp) THEN 
     255              WRITE(numout,*) ' *** Info used values : ' 
     256              WRITE(numout,*) '   date ndastp                                      : ', ndastp 
     257              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     258              WRITE(numout,*) 
     259            ENDIF 
     260            ! 
     261            CALL day_init          ! compute calendar 
     262            ! 
    269263         ENDIF 
    270264         ! 
    271          IF(lwp) THEN 
    272            WRITE(numout,*) ' *** Info used values : ' 
    273            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    274            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
    275            WRITE(numout,*) 
    276          ENDIF 
    277          ! 
    278          CALL day_init          ! compute calendar 
    279          ! 
    280 #endif 
    281  
    282265      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
    283266         ! 
     
    287270            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    288271         ENDIF 
    289          ! calendar control 
    290272         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step 
    291273         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date 
     
    304286      !!---------------------------------------------------------------------- 
    305287 
    306       INTEGER  :: ji, jj, jk, jn 
     288      INTEGER  :: jn 
    307289      REAL(wp) :: zdiag_var, zdiag_varmin, zdiag_varmax, zdiag_tot 
    308       REAL(wp) :: zder, zvol 
     290      REAL(wp) :: zder 
    309291      !!---------------------------------------------------------------------- 
    310292 
Note: See TracChangeset for help on using the changeset viewer.