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 1130 – NEMO

Changeset 1130


Ignore:
Timestamp:
2008-06-24T17:00:56+02:00 (16 years ago)
Author:
smasson
Message:

daymod bugfix and enhancement, see ticket #216

Location:
trunk/NEMO/OPA_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/DOM/domain.F90

    r1102 r1130  
    1616   USE sbc_oce         ! surface boundary condition: ocean 
    1717   USE phycst          ! physical constants 
    18    USE daymod          ! calendar 
    1918   USE in_out_manager  ! I/O manager 
    2019   USE lib_mpp         ! distributed memory computing library 
     
    176175         WRITE(numout,*) '           multi file dimgout           ln_dimgnnn   = ', ln_dimgnnn 
    177176      ENDIF 
    178  
    179       ndastp = ndate0                ! Assign initial date to current date 
    180177 
    181178      ! ... Control of output frequency 
  • trunk/NEMO/OPA_SRC/daymod.F90

    r888 r1130  
    1515   !!---------------------------------------------------------------------- 
    1616   !!   day        : calendar 
     17   !!   
     18   !!           ------------------------------- 
     19   !!           ----------- WARNING ----------- 
     20   !! 
     21   !!   we suppose that the time step is deviding the number of second of in a day 
     22   !!             ---> MOD( rday, rdttra(1) ) == 0 
     23   !! 
     24   !!           ----------- WARNING ----------- 
     25   !!           ------------------------------- 
     26   !!   
    1727   !!---------------------------------------------------------------------- 
    1828   USE dom_oce         ! ocean space and time domain 
    1929   USE phycst          ! physical constants 
    2030   USE in_out_manager  ! I/O manager 
     31   USE iom             !  
    2132   USE prtctl          ! Print control 
     33   USE restart         !  
    2234 
    2335   IMPLICIT NONE 
     
    2537 
    2638   PUBLIC day        ! called by step.F90 
     39   PUBLIC day_init   ! called by istate.F90 
    2740 
    2841   INTEGER , PUBLIC ::   nyear       !: current year 
    2942   INTEGER , PUBLIC ::   nmonth      !: current month 
    3043   INTEGER , PUBLIC ::   nday        !: current day of the month 
     44   INTEGER , PUBLIC ::   ndastp      !: time step date in yyyymmdd format 
    3145   INTEGER , PUBLIC ::   nday_year   !: current day counted from jan 1st of the current year 
    3246   REAL(wp), PUBLIC ::   rsec_year   !: current time step counted in second since 00h jan 1st of the current year 
    3347   REAL(wp), PUBLIC ::   rsec_month  !: current time step counted in second since 00h 1st day of the current month 
    34    REAL(wp), PUBLIC ::   rsec_day    !: current time step counted in second since 00h         of the current day 
    35    INTEGER , PUBLIC ::   ndastp      !: time step date in year/month/day aammjj 
    36  
    37 !!gm supprimer adatrj et adatrj0 ==> remplacer par rsecday..... 
     48   REAL(wp), PUBLIC ::   rsec_day    !: current time step counted in second since 00h of the current day 
     49 
    3850   REAL(wp), PUBLIC ::   adatrj      !: number of elapsed days since the begining of the run 
    39    REAL(wp), PUBLIC ::   adatrj0     !: value of adatrj at nit000-1 (before the present run). 
    40    !                                 !  it is the accumulated duration of previous runs 
    41    !                                 !  that may have been run with different time steps. 
    42    INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len   !: length of the current year 
    43  
     51   !                                 !: it is the accumulated duration of previous runs 
     52   !                                 !: that may have been run with different time steps. 
     53   INTEGER , PUBLIC, DIMENSION(0:1)  ::   nyear_len    !: length in days of the previous/current year 
     54   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len   !: length in days of the months of the current year 
     55   REAL(wp), PUBLIC, DIMENSION(0:13) ::   rmonth_half  !: second since the beginning of the year and the halft of the months 
     56   REAL(wp), PUBLIC, DIMENSION(0:13) ::   rmonth_end   !: second since the beginning of the year and the end of the months 
     57   REAL(wp), PUBLIC                  ::   sec1jan000   !: second since Jan. 1st 00h of nit000 year 
     58 
     59   ! this two variables are wrong DO NOT USE THEM !!! 
    4460   INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month 
    4561      &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year) 
     
    4763      &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year) 
    4864 
    49    REAL(wp), PUBLIC, DIMENSION(0:14) ::   rmonth_half(0:14) 
    5065 
    5166   !!---------------------------------------------------------------------- 
     
    5772CONTAINS 
    5873 
     74   SUBROUTINE day_init 
     75      !!---------------------------------------------------------------------- 
     76      !!                   ***  ROUTINE day_init  *** 
     77      !!  
     78      !! ** Purpose :   Initialization of the calendar values to their values 1 time step before nit000  
     79      !!                because day will be called at the beginning of step 
     80      !! 
     81      !! ** Action  : - nyear        : current year 
     82      !!              - nmonth       : current month of the year nyear 
     83      !!              - nday         : current day of the month nmonth 
     84      !!              - nday_year    : current day of the year nyear 
     85      !!              - rsec_year    : current time step counted in second since 00h jan 1st of the current year 
     86      !!              - rsec_month   : current time step counted in second since 00h 1st day of the current month 
     87      !!              - rsec_day     : current time step counted in second since 00h of the current day 
     88      !!              - sec1jan000   : second since Jan. 1st 00h of nit000 year 
     89      !!              - nmonth_len, nyear_len, rmonth_half, rmonth_end through day_mth 
     90      !!---------------------------------------------------------------------- 
     91 
     92      ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 
     93      IF( MOD( rday, rdttra(1) ) /= 0 )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     94 
     95      CALL day_rst( nit000, 'READ' )  
     96 
     97      ! set the calandar from ndastp (read in restart file and namelist) 
     98 
     99      nyear   =   ndastp / 10000 
     100      nmonth  = ( ndastp - (nyear * 10000) ) / 100 
     101      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
     102 
     103      sec1jan000 = 0.e0 
     104      CALL day_mth 
     105       
     106      IF ( nday == 0 ) THEN     !   for ex if ndastp = ndate0 - 1 
     107         nmonth = nmonth - 1   
     108         nday = nmonth_len(nmonth) 
     109      ENDIF 
     110      IF ( nmonth == 0 ) THEN   ! go at the end of previous year 
     111         nmonth = 12 
     112         nyear = nyear - 1 
     113         sec1jan000 = sec1jan000 - rday * REAL( nyear_len(0), wp ) 
     114         IF( nleapy == 1 )   CALL day_mth 
     115      ENDIF 
     116       
     117      ! day since january 1st 
     118      nday_year = nday + SUM( nmonth_len(1:nmonth - 1) ) 
     119       
     120      ! number of seconds since the beginning of current year/month at the middle of the time-step 
     121      rsec_year  = REAL( nday_year, wp ) * rday - 0.5 * rdttra(1)   ! 1 time step before the middle of the first time step 
     122      rsec_month = REAL( nday     , wp ) * rday - 0.5 * rdttra(1)   ! because day will be called at the beginning of step 
     123      rsec_day   =                         rday - 0.5 * rdttra(1) 
     124 
     125      ! control print 
     126      IF(lwp) WRITE(numout,*)' ==============>> One time step before the start of the run DATE Y/M/D = ',   & 
     127           &                   nyear, '/', nmonth, '/', nday, '  rsec_day:', rsec_day 
     128       
     129   END SUBROUTINE day_init 
     130 
     131 
     132   SUBROUTINE day_mth 
     133      !!---------------------------------------------------------------------- 
     134      !!                   ***  ROUTINE day_init  *** 
     135      !!  
     136      !! ** Purpose :   calendar values related to the months 
     137      !! 
     138      !! ** Action  : - nmonth_len    : length in days of the months of the current year 
     139      !!              - nyear_len     : length in days of the previous/current year 
     140      !!              - rmonth_half   : second since the beginning of the year and the halft of the months 
     141      !!              - rmonth_end    : second since the beginning of the year and the end of the months 
     142      !!---------------------------------------------------------------------- 
     143      INTEGER  ::   jm               ! dummy loop indice 
     144      !!---------------------------------------------------------------------- 
     145 
     146      ! length of the month of the current year (from nleapy, read in namelist) 
     147      IF ( nleapy < 2 ) THEN  
     148         nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /) 
     149         nyear_len(:) = 365 
     150         IF ( nleapy == 1 ) THEN   ! we are using calandar with leap years 
     151            IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN 
     152               nyear_len(0) = 366 
     153            ENDIF 
     154            IF ( MOD(nyear, 4) == 0 .AND. ( MOD(nyear, 400) == 0 .OR. MOD(nyear, 100) /= 0 ) ) THEN 
     155               nmonth_len(2) = 29 
     156               nyear_len(1) = 366 
     157            ENDIF 
     158         ENDIF 
     159      ELSE 
     160         nmonth_len(:) = nleapy   ! all months with nleapy days per year 
     161         nyear_len(:) = 12 * nleapy 
     162      ENDIF 
     163 
     164      ! half month in second since the begining of the year: 
     165      ! time since Jan 1st   0     1     2    ...    11    12    13 
     166      !          ---------*--|--*--|--*--| ... |--*--|--*--|--*--|-------------------------------------- 
     167      !                 <---> <---> <--->  ...  <---> <---> <--->         
     168      ! month number      0     1     2    ...    11    12    13 
     169      ! 
     170      ! rmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) ) 
     171      rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len(0), wp ) 
     172      DO jm = 1, 13 
     173         rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm), wp ) 
     174      END DO 
     175      rmonth_half(:) = rmonth_half(:) + sec1jan000 
     176 
     177      rmonth_end(0) = 0. 
     178      DO jm = 1, 13 
     179         rmonth_end(jm) = rmonth_end(jm-1) + rday * REAL( nmonth_len(jm), wp ) 
     180      END DO 
     181                  
     182   END SUBROUTINE  
     183 
     184 
    59185   SUBROUTINE day( kt ) 
    60186      !!---------------------------------------------------------------------- 
     
    69195      !!              - nday      : current day of the month nmonth 
    70196      !!              - nday_year : current day of the year nyear 
    71       !!              - ndastp    : =nyear*10000+nmonth*100+nday 
     197      !!              - ndastp    : = nyear*10000 + nmonth*100 + nday 
    72198      !!              - adatrj    : date in days since the beginning of the run 
    73199      !!              - rsec_year : current time of the year (in second since 00h, jan 1st) 
     
    75201      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices 
    76202      ! 
    77       INTEGER  ::   js, jm               ! dummy loop indice 
    78203      CHARACTER (len=25) ::   charout 
    79204      !!---------------------------------------------------------------------- 
    80205 
    81       ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year. 
    82       !     ndastp has been initialized in domain.F90 or restart.F90 
    83       !----------------------------------------------------------------- 
    84  
    85       !                        ! ---------------- ! 
    86       IF( kt == -1 ) THEN      !  Initialisation  ! 
    87          !                     ! ---------------- ! 
    88          ! 
    89          IF( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart  
    90  
    91          ! set the calandar from adatrj0 and ndastp (read in restart file and namelist) 
    92          adatrj  =   adatrj0      !???? bug.... toujours rest   !!gm 
    93          nyear   =   ndastp / 10000 
    94          nmonth  = ( ndastp - (nyear * 10000) ) / 100 
    95          nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
    96  
    97          ! length of the month of the current year (from nleapy, read in namelist) 
    98          nmonth_len(0) = nbiss(12)   ;   nmonth_len(13) = nbiss(1) 
    99          SELECT CASE( nleapy ) 
    100          CASE( 1  )    
    101             IF( MOD( nyear, 4 ) == 0 ) THEN 
    102                ;          nmonth_len(1:12) = nbiss(:)      ! 366 days per year (leap year) 
    103             ELSE 
    104                ;          nmonth_len(1:12) = nobis(:)      ! 365 days per year 
    105             ENDIF 
    106          CASE( 0  )   ;   nmonth_len(1:12) = nobis(:)      ! 365 days per year 
    107          CASE( 2: )   ;   nmonth_len(1:13) = nleapy        ! 12*nleapy days per year 
    108          END SELECT 
    109  
    110          ! half month in second since the bigining of the year 
    111          rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len( 0 ) ) 
    112          DO jm = 1, 12 
    113             rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm) ) 
    114          END DO 
    115          rmonth_half(13) = rmonth_half( 1 ) + 365. * rday 
    116          rmonth_half(14) = rmonth_half( 2 ) + 365. * rday 
    117  
    118          ! day since january 1st (useful to read  daily forcing fields) 
    119          nday_year =  nday 
    120          DO js = 1, nmonth - 1             ! accumulates days of previous months of this year 
    121             nday_year = nday_year + nmonth_len(js) 
    122          END DO 
    123  
    124          ! number of seconds since... 
    125          IF( ln_rstart )   THEN 
    126             rsec_year  = REAL( nday_year ) * rday     - rdttra(1)      ! 00h 1st day of the current year 
    127             rsec_month = REAL( nday      ) * rday     - rdttra(1)      ! 00h 1st day of the current month 
    128             rsec_day   = REAL( nday      ) * rday     - rdttra(1)      ! 00h         of the current day 
     206      !                                                 ! New time-step 
     207      rsec_year  = rsec_year  + rdttra(1)  
     208      rsec_month = rsec_month + rdttra(1)                  
     209      rsec_day   = rsec_day   + rdttra(1)                  
     210      adatrj = adatrj + rdttra(1) / rday 
     211       
     212      IF( rsec_day > rday ) THEN                        ! NEW day 
     213         ! 
     214         nday      = nday + 1 
     215         nday_year = nday_year + 1 
     216         rsec_day  = 0.5 * rdttra(1)                  
     217         ! 
     218         IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! NEW month 
     219            nday   = 1 
     220            nmonth = nmonth + 1 
     221            rsec_month = 0.5 * rdttra(1) 
     222            IF( nmonth == 13 ) THEN                     ! NEW year 
     223               nyear     = nyear + 1 
     224               nmonth    = 1 
     225               nday_year = 1 
     226               rsec_year = 0.5 * rdttra(1) 
     227               sec1jan000 = sec1jan000 + rday * REAL( nyear_len(1), wp ) 
     228               IF( nleapy == 1 )   CALL day_mth 
     229            ENDIF 
     230         ENDIF 
     231         ! 
     232         ndastp = nyear * 10000 + nmonth * 100 + nday   ! NEW date 
     233         ! 
     234         IF(lwp) WRITE(numout,'(a,i8,a,i4,a,i2,a,i2,a,i3)') '======>> time-step =', kt,   & 
     235              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year 
     236         IF(lwp) WRITE(numout,'(a,F9.0,a,F9.0,a,F9.0)') '         rsec_year = ', rsec_year,   & 
     237              &   '   rsec_month = ', rsec_month, '   rsec_day = ', rsec_day 
     238      ENDIF 
     239       
     240      IF(ln_ctl) THEN 
     241         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     242         CALL prt_ctl_info(charout) 
     243      ENDIF 
     244 
     245      IF( lrst_oce )   CALL day_rst( kt, 'WRITE' ) 
     246      ! 
     247   END SUBROUTINE day 
     248 
     249 
     250   SUBROUTINE day_rst( kt, cdrw ) 
     251      !!--------------------------------------------------------------------- 
     252      !!                   ***  ROUTINE ts_rst  *** 
     253      !!  
     254      !!  ** Purpose : Read or write calendar in restart file: 
     255      !!  
     256      !!  WRITE(READ) mode: 
     257      !!       kt        : number of time step since the begining of the experiment at the  
     258      !!                   end of the current(previous) run 
     259      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the  
     260      !!                   end of the current(previous) run (REAL -> keep fractions of day) 
     261      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer) 
     262      !!  
     263      !!   According to namelist parameter nrstdt, 
     264      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary). 
     265      !!       nrstdt = 1  we verify that nit000 is equal to the last 
     266      !!                   time step of previous run + 1. 
     267      !!       In both those options, the  exact duration of the experiment 
     268      !!       since the beginning (cumulated duration of all previous restart runs) 
     269      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
     270      !!       This is valid is the time step has remained constant. 
     271      !! 
     272      !!       nrstdt = 2  the duration of the experiment in days (adatrj) 
     273      !!                    has been stored in the restart file. 
     274      !!---------------------------------------------------------------------- 
     275      INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
     276      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
     277      ! 
     278      REAL(wp) ::   zkt, zndastp 
     279      !!---------------------------------------------------------------------- 
     280       
     281      IF( TRIM(cdrw) == 'READ' ) THEN 
     282 
     283         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
     284            ! Get Calendar informations 
     285            CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run 
     286            IF(lwp) THEN 
     287               WRITE(numout,*) ' *** Info read in restart : ' 
     288               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
     289               WRITE(numout,*) ' *** restart option' 
     290               SELECT CASE ( nrstdt ) 
     291               CASE ( 0 )   ;   WRITE(numout,*) ' nrstdt = 0 : no control of nit000' 
     292               CASE ( 1 )   ;   WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
     293               CASE ( 2 )   ;   WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart' 
     294               END SELECT 
     295               WRITE(numout,*) 
     296            ENDIF 
     297            ! Control of date  
     298            IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 )                                         &  
     299                 &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 &  
     300                 &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) 
     301            ! define ndastp and adatrj 
     302            IF ( nrstdt == 2 ) THEN  
     303               CALL iom_get( numror, 'ndastp', zndastp ) 
     304               ndastp = NINT( zndastp ) 
     305               CALL iom_get( numror, 'adatrj', adatrj  ) 
     306            ELSE  
     307               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
     308               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday  
     309               ! note this is wrong if time step has changed during run  
     310            ENDIF 
    129311         ELSE 
    130             rsec_year  = REAL( nday_year - 1 ) * rday - rdttra(1)      ! 00h 1st day of the current year 
    131             rsec_month = REAL( nday      - 1 ) * rday - rdttra(1)      ! 00h 1st day of the current month 
    132             rsec_day   =                              - rdttra(1)      ! 00h         of the current day 
    133          ENDIF 
    134  
    135          ! control print 
    136          IF(lwp) WRITE(numout,*)' ==============>> time-step =', kt, ' Initial DATE Y/M/D = ',   & 
    137                &                   nyear, '/', nmonth, '/', nday, '  rsec_day:', rsec_day 
    138  
    139          !                     ! -------------------------------- !  
    140       ELSE                     !  Model calendar at time-step kt  ! 
    141          !                     ! -------------------------------- !  
    142  
    143          rsec_year  = rsec_year  + rdttra(1)                 ! New time-step 
    144          rsec_month = rsec_month + rdttra(1)                 ! New time-step 
    145          rsec_day   = rsec_day   + rdttra(1)                 ! New time-step 
    146  
    147          adatrj    = adatrj0 + ( kt - nit000 + 1 ) * rdttra(1) / rday 
    148  
    149          IF( rsec_day >= rday ) THEN 
    150             ! 
    151             rsec_day  = 0.e0                               ! NEW day 
    152             nday      = nday + 1 
    153             nday_year = nday_year + 1 
    154             ! 
    155             IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! NEW month 
    156                nday  = 1 
    157                rsec_month = 0.e0    
    158                nmonth = nmonth + 1 
    159                IF( nmonth == 13 ) THEN                     ! NEW year 
    160                   nyear     = nyear + 1 
    161                   nmonth    = 1 
    162                   nday_year = 1 
    163                   rsec_year = 0.e0 
    164                   !                                        ! update the length of the month 
    165                   IF( nleapy == 1 ) THEN                   ! of the current year (if necessary) 
    166                      IF( MOD( nyear, 4 ) == 0 ) THEN 
    167                         nmonth_len(1:12) = nbiss(:)              ! 366 days per year (leap year) 
    168                      ELSE 
    169                         nmonth_len(1:12) = nobis(:)              ! 365 days per year 
    170                      ENDIF 
    171                      ! half month in second since the bigining of the year 
    172                      rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len( 0 ) ) 
    173                      DO jm = 1, 12 
    174                         rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm) ) 
    175                      END DO 
    176                      rmonth_half(13) = rmonth_half( 1 ) + 365. * rday 
    177                      rmonth_half(14) = rmonth_half( 2 ) + 365. * rday 
    178                   ENDIF 
    179                ENDIF 
    180             ENDIF 
    181  
    182             ! 
    183             ndastp = nyear * 10000 + nmonth * 100 + nday   ! NEW date 
    184             ! 
    185            IF(lwp) WRITE(numout,'(a,i8,a,i4,a,i2,a,i2,a,i3)') '======>> time-step =', kt,   & 
    186               &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year 
    187            IF(lwp) WRITE(numout,'(a,F9.0,a,F9.0,a,F9.0)') '         rsec_year = ', rsec_year,   & 
    188               &   '   rsec_month = ', rsec_month, '   rsec_day = ', rsec_day 
    189          ENDIF 
    190  
    191          IF(ln_ctl) THEN 
    192             WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    193             CALL prt_ctl_info(charout) 
    194          ENDIF 
    195          ! 
    196       ENDIF 
    197  
    198    END SUBROUTINE day 
     312            ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam 
     313            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday  
     314         ENDIF 
     315         ! 
     316         IF(lwp) THEN 
     317            WRITE(numout,*) ' *** Info used values : ' 
     318            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
     319            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     320            WRITE(numout,*) 
     321         ENDIF 
     322         ! 
     323      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
     324         ! 
     325         IF( kt == nitrst ) THEN 
     326            IF(lwp) WRITE(numout,*) 
     327            IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt 
     328            IF(lwp) WRITE(numout,*) '~~~~~~~'          
     329         ENDIF 
     330         ! calendar control 
     331         CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step  
     332         CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
     333         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
     334         !                                                                     ! the begining of the run [s] 
     335      ENDIF 
     336      ! 
     337   END SUBROUTINE day_rst 
    199338 
    200339   !!====================================================================== 
  • trunk/NEMO/OPA_SRC/istate.F90

    r900 r1130  
    8181         neuler = 1                              ! Set time-step indicator at nit000 (leap-frog) 
    8282         CALL rst_read                           ! Read the restart file 
    83          CALL day( -1 )                          ! model calendar (using both namelist and restart infos) 
     83         CALL day_init                           ! model calendar (using both namelist and restart infos) 
    8484      ELSE 
    8585         !                                    ! Start from rest 
    8686         !                                    ! --------------- 
     87         numror = 0                              ! define numror = 0 -> no restart file to read 
    8788         neuler = 0                              ! Set time-step indicator at nit000 (euler forward) 
    88          adatrj = 0._wp 
    89          CALL day( -1 )                          ! model calendar (using namelist infos) 
    90          numror = 0                              ! define numror = 0 -> no restart file to read 
     89         CALL day_init                           ! model calendar (using both namelist and restart infos) 
    9190         !                                       ! Initialization of ocean to zero 
    9291         !     before fields       !       now fields           
  • trunk/NEMO/OPA_SRC/restart.F90

    r900 r1130  
    1818   USE oce             ! ocean dynamics and tracers  
    1919   USE phycst          ! physical constants 
    20    USE daymod          ! calendar 
    2120   USE cpl_oce, ONLY : lk_cpl              ! 
    2221   USE in_out_manager  ! I/O manager 
     
    8988            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname 
    9089            END SELECT 
    91             IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp 
    92             ELSE                          ;   WRITE(numout,*) '             kt = '             , kt,' date= ', ndastp 
     90            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
     91            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
    9392            ENDIF 
    9493         ENDIF 
     
    112111      INTEGER, INTENT(in) ::   kt   ! ocean time-step 
    113112      !!---------------------------------------------------------------------- 
    114  
    115       IF( kt == nitrst ) THEN 
    116          IF(lwp) WRITE(numout,*) 
    117          IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt 
    118          IF(lwp) WRITE(numout,*) '~~~~~~~'          
    119       ENDIF 
    120  
    121       ! calendar control 
    122       CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step  
    123       CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
    124       CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    125113      !                                                                     ! the begining of the run [s] 
    126114      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt               )   ! dynamics time step 
     
    179167      !!      for this last three records,  the previous characteristics  
    180168      !!      could be different with those used in the present run.  
    181       !! 
    182       !!   According to namelist parameter nrstdt, 
    183       !!       nrstdt = 0  no control on the date (nit000 is  arbitrary). 
    184       !!       nrstdt = 1  we verify that nit000 is equal to the last 
    185       !!                   time step of previous run + 1. 
    186       !!       In both those options, the  exact duration of the experiment 
    187       !!       since the beginning (cumulated duration of all previous restart runs) 
    188       !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
    189       !!       This is valid is the time step has remained constant. 
    190       !! 
    191       !!       nrstdt = 2  the duration of the experiment in days (adatrj) 
    192       !!                    has been stored in the restart file. 
    193       !!---------------------------------------------------------------------- 
    194       REAL(wp) ::   zkt, zrdt, zrdttra1, zndastp 
     169      !!---------------------------------------------------------------------- 
     170      REAL(wp) ::   zrdt, zrdttra1 
    195171      !!---------------------------------------------------------------------- 
    196172 
     
    198174         WRITE(numout,*) 
    199175         SELECT CASE ( jprstlib ) 
    200          CASE ( jpnf90 ) 
    201             WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
    202          CASE ( jprstdimg ) 
    203             WRITE(numout,*) 'rst_read : read oce binary restart file' 
     176         CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
     177         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    204178         END SELECT 
    205179         WRITE(numout,*) '~~~~~~~~' 
    206  
    207          WRITE(numout,*) ' *** Info on the present job : ' 
    208          WRITE(numout,*) '   time-step           : ', nit000 
    209          WRITE(numout,*) '   date ndastp         : ', ndastp 
    210          WRITE(numout,*) 
    211          WRITE(numout,*) ' *** restart option' 
    212          SELECT CASE ( nrstdt ) 
    213          CASE ( 0 )  
    214             WRITE(numout,*) ' nrstdt = 0 no control of nit000' 
    215          CASE ( 1 )  
    216             WRITE(numout,*) ' nrstdt = 1 we control the date of nit000' 
    217          CASE ( 2 ) 
    218             WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file' 
    219          CASE DEFAULT 
    220             WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date' 
    221             WRITE(numout,*) '  =======                  =========' 
    222          END SELECT 
    223          WRITE(numout,*) 
    224180      ENDIF 
    225181 
    226182      CALL iom_open( 'restart', numror, kiolib = jprstlib ) 
    227183 
    228       ! Calendar informations 
    229       CALL iom_get( numror, 'kt'     , zkt      )   ! time-step  
    230       CALL iom_get( numror, 'ndastp' , zndastp  )   ! date 
    231       IF(lwp) THEN 
    232          WRITE(numout,*) 
    233          WRITE(numout,*) ' *** Info on the restart file read : ' 
    234          WRITE(numout,*) '   time-step           : ', NINT( zkt ) 
    235          WRITE(numout,*) '   date ndastp         : ', NINT( zndastp ) 
    236          WRITE(numout,*) 
    237       ENDIF 
    238       ! Control of date 
    239       IF( nit000 - NINT( zkt )  /= 1 .AND. nrstdt /= 0 ) & 
    240            & CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', & 
    241            & ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) 
    242       ! re-initialisation of  adatrj0 
    243       adatrj0 = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    244       IF ( nrstdt == 2 ) THEN 
    245          ! by default ndatsp has been set to ndate0 in dom_nam 
    246          ! ndate0 has been read in the namelist (standard OPA 8) 
    247          ! here when nrstdt=2 we keep the  final date of previous run 
    248          ndastp = NINT( zndastp ) 
    249          CALL iom_get( numror, 'adatrj', adatrj )   ! number of elapsed days since the begining of last run 
    250       ENDIF 
    251184      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    252185      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN 
     
    258191         IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    259192      ENDIF 
    260       ! 
    261193      !                                                       ! Read prognostic variables 
    262194      CALL iom_get( numror, jpdom_autoglo, 'ub'   , ub    )        ! before i-component velocity 
Note: See TracChangeset for help on using the changeset viewer.