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.
daymod.F90 in NEMO/trunk/src/OCE/DOM – NEMO

source: NEMO/trunk/src/OCE/DOM/daymod.F90 @ 13286

Last change on this file since 13286 was 13286, checked in by smasson, 4 years ago

trunk: merge extra halos branch in trunk, see #2366

  • Property svn:keywords set to Id
File size: 21.0 KB
RevLine 
[3]1MODULE daymod
2   !!======================================================================
3   !!                       ***  MODULE  daymod  ***
[7646]4   !! Ocean :   management of the model calendar
[3]5   !!=====================================================================
[1559]6   !! History :  OPA  ! 1994-09  (M. Pontaud M. Imbard)  Original code
7   !!                 ! 1997-03  (O. Marti)
[3764]8   !!                 ! 1997-05  (G. Madec)
[1559]9   !!                 ! 1997-08  (M. Imbard)
10   !!   NEMO     1.0  ! 2003-09  (G. Madec)  F90 + nyear, nmonth, nday
11   !!                 ! 2004-01  (A.M. Treguier) new calculation based on adatrj
12   !!                 ! 2006-08  (G. Madec)  surface module major update
[6140]13   !!                 ! 2015-11  (D. Lea) Allow non-zero initial time of day
[3764]14   !!----------------------------------------------------------------------
[3]15
16   !!----------------------------------------------------------------------
17   !!   day        : calendar
18   !!----------------------------------------------------------------------
[7646]19   !!                    ----------- WARNING -----------
20   !!                    -------------------------------
21   !!   sbcmod assume that the time step is dividing the number of second of
[12489]22   !!   in a day, i.e. ===> MOD( rday, rn_Dt ) == 0
[7646]23   !!   except when user defined forcing is used (see sbcmod.F90)
24   !!----------------------------------------------------------------------
[6140]25   USE dom_oce        ! ocean space and time domain
26   USE phycst         ! physical constants
[7646]27   USE ioipsl  , ONLY :   ymds2ju      ! for calendar
28   USE trc_oce , ONLY :   l_offline   ! offline flag
29   !
[6140]30   USE in_out_manager ! I/O manager
[7646]31   USE prtctl         ! Print control
[6140]32   USE iom            !
33   USE timing         ! Timing
34   USE restart        ! restart
[3]35
36   IMPLICIT NONE
37   PRIVATE
38
[1559]39   PUBLIC   day        ! called by step.F90
40   PUBLIC   day_init   ! called by istate.F90
[3764]41   PUBLIC   day_mth    ! Needed by TAM
[3]42
[6140]43   INTEGER, PUBLIC ::   nsecd, nsecd05, ndt, ndt05   !: (PUBLIC for TAM)
[1730]44
[3]45   !!----------------------------------------------------------------------
[9598]46   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[888]47   !! $Id$
[10068]48   !! Software governed by the CeCILL license (see ./LICENSE)
[15]49   !!----------------------------------------------------------------------
[3]50CONTAINS
51
[1130]52   SUBROUTINE day_init
53      !!----------------------------------------------------------------------
54      !!                   ***  ROUTINE day_init  ***
[3764]55      !!
56      !! ** Purpose :   Initialization of the calendar values to their values 1 time step before nit000
[1130]57      !!                because day will be called at the beginning of step
58      !!
59      !! ** Action  : - nyear        : current year
[12377]60      !!              - nmonth       : current month of the current nyear
61      !!              - nday         : current   day of the current nmonth
62      !!              - nday_year    : current   day of the current nyear
63      !!              - nsec_year    : seconds between 00h jan 1st of the current  year and half of the current time step
64      !!              - nsec_month   : seconds between 00h 1st day of the current month and half of the current time step
65      !!              - nsec_monday  : seconds between 00h         of the   last Monday and half of the current time step
66      !!              - nsec_day     : seconds between 00h         of the current   day and half of the current time step
67      !!              - nsec1jan000  : seconds between Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year
68      !!              - nmonth_len, nyear_len, nmonth_beg through day_mth
[1130]69      !!----------------------------------------------------------------------
[12377]70      INTEGER  ::   inbday, imonday, isecrst   ! local integers
[7646]71      REAL(wp) ::   zjul             ! local scalar
[2528]72      !!----------------------------------------------------------------------
[3294]73      !
[5563]74      ! max number of seconds between each restart
[12489]75      IF( REAL( nitend - nit000 + 1 ) * rn_Dt > REAL( HUGE( nsec1jan000 ) ) ) THEN
[5563]76         CALL ctl_stop( 'The number of seconds between each restart exceeds the integer 4 max value: 2^31-1. ',   &
77            &           'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' )
78      ENDIF
[12377]79      nsecd   = NINT(       rday )
[7646]80      nsecd05 = NINT( 0.5 * rday )
[12489]81      ndt     = NINT(       rn_Dt  )
82      ndt05   = NINT( 0.5 * rn_Dt  )
[1130]83
[7646]84      IF( .NOT. l_offline )   CALL day_rst( nit000, 'READ' )
[1130]85
86      ! set the calandar from ndastp (read in restart file and namelist)
87      nyear   =   ndastp / 10000
88      nmonth  = ( ndastp - (nyear * 10000) ) / 100
[3764]89      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )
[1130]90
[6140]91      nhour   =   nn_time0 / 100
92      nminute = ( nn_time0 - nhour * 100 )
[12377]93      isecrst = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss)
[6140]94
[12377]95      CALL ymds2ju( nyear, nmonth, nday, REAL(isecrst,wp), fjulday ) 
[1730]96      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error
[12377]97      IF( nhour*NINT(rhhmm*rmmss) + nminute*NINT(rmmss) - ndt05 .LT. 0 ) fjulday = fjulday+1.       ! move back to the day at nit000 (and not at nit000 - 1)
98
[1730]99      nsec1jan000 = 0
[1130]100      CALL day_mth
[3764]101
[1130]102      IF ( nday == 0 ) THEN     !   for ex if ndastp = ndate0 - 1
[3764]103         nmonth = nmonth - 1
[1130]104         nday = nmonth_len(nmonth)
105      ENDIF
106      IF ( nmonth == 0 ) THEN   ! go at the end of previous year
107         nmonth = 12
108         nyear = nyear - 1
[1730]109         nsec1jan000 = nsec1jan000 - nsecd * nyear_len(0)
[1130]110         IF( nleapy == 1 )   CALL day_mth
111      ENDIF
[3764]112
[1130]113      ! day since january 1st
114      nday_year = nday + SUM( nmonth_len(1:nmonth - 1) )
[2528]115
[12377]116      !compute number of days between last Monday and today
[13226]117      CALL ymds2ju( 1900, 01, 01, 0.0_wp, zjul )     ! compute julian day value of 01.01.1900 (our reference that was a Monday)
[12377]118      inbday = FLOOR(fjulday - zjul)              ! compute nb day between  01.01.1900 and start of current day
119      imonday = MOD(inbday, 7)                    ! compute nb day between last monday and current day
120      IF (imonday .LT. 0) imonday = imonday + 7   ! Avoid negative values for dates before 01.01.1900
[2528]121
122      ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step
[12377]123      IF( isecrst - ndt05 .GT. 0 ) THEN
[6140]124         ! 1 timestep before current middle of first time step is still the same day
[12377]125         nsec_year  = (nday_year-1) * nsecd + isecrst - ndt05 
126         nsec_month = (nday-1)      * nsecd + isecrst - ndt05   
[6140]127      ELSE
128         ! 1 time step before the middle of the first time step is the previous day
[12377]129         nsec_year  = nday_year     * nsecd + isecrst - ndt05 
130         nsec_month = nday          * nsecd + isecrst - ndt05   
[6140]131      ENDIF
[12377]132      nsec_monday   = imonday       * nsecd + isecrst - ndt05
133      nsec_day      =                         isecrst - ndt05 
134      IF( nsec_day    .LT. 0 ) nsec_day    = nsec_day    + nsecd
135      IF( nsec_monday .LT. 0 ) nsec_monday = nsec_monday + nsecd*7
[1130]136
137      ! control print
[8329]138      IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i8,a,i8,a,i8,a,i8)')   &
139           &                   ' =======>> 1/2 time step before the start of the run DATE Y/M/D = ',   &
[12377]140           &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day, '  nsec_monday:', nsec_monday, '  &
[6140]141           &                   nsec_month:', nsec_month , '  nsec_year:' , nsec_year
[1725]142
[12377]143      nsec000_1jan000 = nsec1jan000 + nsec_year + ndt05
144      nsecend_1jan000 = nsec000_1jan000 + ndt * ( nitend - nit000 + 1 )
145     
[1725]146      ! Up to now, calendar parameters are related to the end of previous run (nit000-1)
147      ! call day to set the calendar parameters at the begining of the current simulaton. needed by iom_init
148      CALL day( nit000 )
[3294]149      !
[9367]150      IF( lwxios ) THEN
151! define variables in restart file when writing with XIOS
152          CALL iom_set_rstw_var_active('kt')
153          CALL iom_set_rstw_var_active('ndastp')
154          CALL iom_set_rstw_var_active('adatrj')
155          CALL iom_set_rstw_var_active('ntime')
156      ENDIF
157
[1130]158   END SUBROUTINE day_init
159
160
161   SUBROUTINE day_mth
162      !!----------------------------------------------------------------------
163      !!                   ***  ROUTINE day_init  ***
[3764]164      !!
[1130]165      !! ** Purpose :   calendar values related to the months
166      !!
[12377]167      !! ** Action  : - nyear_len     : length in days of the previous/current year
168      !!              - nmonth_len    : length in days of the months of the current year
169      !!              - nmonth_half   : second since the beginning of the current year and the halft of the months
170      !!              - nmonth_end    : second since the beginning of the current year and the end of the months
[1130]171      !!----------------------------------------------------------------------
[12377]172      INTEGER  ::   jm ,jy                   ! dummy loop indice
173      INTEGER, DIMENSION(12) ::   idaymt     ! length in days of the 12 months for non-leap year
[1130]174      !!----------------------------------------------------------------------
175
176      ! length of the month of the current year (from nleapy, read in namelist)
[3764]177      IF ( nleapy < 2 ) THEN
[12377]178         ! default values
179         idaymt(1:12) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /)
180         nmonth_len(-11: 25) = (/ idaymt(1:12), idaymt(1:12), idaymt(1:12), idaymt(1) /)
[1130]181         nyear_len(:) = 365
[12377]182         !
[1130]183         IF ( nleapy == 1 ) THEN   ! we are using calandar with leap years
[12377]184            DO jy = -1,1
185               IF ( MOD(nyear+jy, 4) == 0 .AND. ( MOD(nyear+jy, 400) == 0 .OR. MOD(nyear+jy, 100) /= 0 ) ) THEN
186                  nmonth_len(2 + 12*jy) = 29
187                  nyear_len( 1 +    jy) = 366
188               ENDIF
189            ENDDO
[1130]190         ENDIF
191      ELSE
192         nmonth_len(:) = nleapy   ! all months with nleapy days per year
193         nyear_len(:) = 12 * nleapy
194      ENDIF
195
196      ! time since Jan 1st   0     1     2    ...    11    12    13
197      !          ---------*--|--*--|--*--| ... |--*--|--*--|--*--|--------------------------------------
[3764]198      !                 <---> <---> <--->  ...  <---> <---> <--->
[1130]199      ! month number      0     1     2    ...    11    12    13
[12377]200      nmonth_beg(1) = 0
201      DO jm = 2, 25
202         nmonth_beg(jm) = nmonth_beg(jm-1) + nsecd * nmonth_len(jm-1)
[1130]203      END DO
[12377]204      DO jm = 0,-11,-1
205         nmonth_beg(jm) = nmonth_beg(jm+1) - nsecd * nmonth_len(jm)
[1130]206      END DO
[3764]207      !
208   END SUBROUTINE
[1130]209
210
[15]211   SUBROUTINE day( kt )
[3]212      !!----------------------------------------------------------------------
[15]213      !!                      ***  ROUTINE day  ***
[3764]214      !!
[3]215      !! ** Purpose :   Compute the date with a day iteration IF necessary.
216      !!
217      !! ** Method  : - ???
218      !!
219      !! ** Action  : - nyear     : current year
220      !!              - nmonth    : current month of the year nyear
221      !!              - nday      : current day of the month nmonth
222      !!              - nday_year : current day of the year nyear
[1130]223      !!              - ndastp    : = nyear*10000 + nmonth*100 + nday
[15]224      !!              - adatrj    : date in days since the beginning of the run
[1730]225      !!              - nsec_year : current time of the year (in second since 00h, jan 1st)
[3764]226      !!----------------------------------------------------------------------
[888]227      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices
228      !
229      CHARACTER (len=25) ::   charout
[1730]230      REAL(wp)           ::   zprec      ! fraction of day corresponding to 0.1 second
[3]231      !!----------------------------------------------------------------------
[3294]232      !
[9019]233      IF( ln_timing )   CALL timing_start('day')
[3294]234      !
[1730]235      zprec = 0.1 / rday
[1130]236      !                                                 ! New time-step
[12377]237      nsec_year    = nsec_year    + ndt
238      nsec_month   = nsec_month   + ndt
239      nsec_monday  = nsec_monday  + ndt
[3764]240      nsec_day   = nsec_day   + ndt
[12489]241      adatrj  = adatrj  + rn_Dt / rday
242      fjulday = fjulday + rn_Dt / rday
[1730]243      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error
244      IF( ABS(adatrj  - REAL(NINT(adatrj ),wp)) < zprec )   adatrj  = REAL(NINT(adatrj ),wp)   ! avoid truncation error
[3764]245
[2528]246      IF( nsec_day > nsecd ) THEN                       ! New day
[888]247         !
[1130]248         nday      = nday + 1
249         nday_year = nday_year + 1
[1730]250         nsec_day  = ndt05
[1130]251         !
[2528]252         IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! New month
[1130]253            nday   = 1
254            nmonth = nmonth + 1
[1730]255            nsec_month = ndt05
[2528]256            IF( nmonth == 13 ) THEN                     ! New year
[1130]257               nyear     = nyear + 1
258               nmonth    = 1
259               nday_year = 1
[1730]260               nsec_year = ndt05
261               nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1)
[1130]262               IF( nleapy == 1 )   CALL day_mth
[3]263            ENDIF
[888]264         ENDIF
[1130]265         !
[2528]266         ndastp = nyear * 10000 + nmonth * 100 + nday   ! New date
[1130]267         !
[2528]268         !compute first day of the year in julian days
[13226]269         CALL ymds2ju( nyear, 01, 01, 0.0_wp, fjulstartyear )
[2528]270         !
[1191]271         IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt,   &
[1130]272              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year
[1730]273         IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') '         nsec_year = ', nsec_year,   &
[12377]274              &   '   nsec_month = ', nsec_month, '   nsec_day = ', nsec_day, '   nsec_monday = ', nsec_monday
[1130]275      ENDIF
[2528]276
[12377]277      IF( nsec_monday > 7*nsecd )   nsec_monday = ndt05     ! New week
[3764]278
[12377]279      IF(sn_cfctl%l_prtctl) THEN
[1130]280         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
[13286]281         CALL prt_ctl_info( charout )
[1130]282      ENDIF
[3]283
[7646]284      IF( .NOT. l_offline ) CALL rst_opn( kt )               ! Open the restart file if needed and control lrst_oce
[2528]285      IF( lrst_oce         ) CALL day_rst( kt, 'WRITE' )      ! write day restart information
[1130]286      !
[9019]287      IF( ln_timing )   CALL timing_stop('day')
[3294]288      !
[1130]289   END SUBROUTINE day
[3]290
291
[1130]292   SUBROUTINE day_rst( kt, cdrw )
293      !!---------------------------------------------------------------------
[9124]294      !!                   ***  ROUTINE day_rst  ***
[3764]295      !!
[1130]296      !!  ** Purpose : Read or write calendar in restart file:
[3764]297      !!
[1130]298      !!  WRITE(READ) mode:
[3764]299      !!       kt        : number of time step since the begining of the experiment at the
[1130]300      !!                   end of the current(previous) run
[3764]301      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
[1130]302      !!                   end of the current(previous) run (REAL -> keep fractions of day)
303      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
[3764]304      !!
[1130]305      !!   According to namelist parameter nrstdt,
306      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
307      !!       nrstdt = 1  we verify that nit000 is equal to the last
308      !!                   time step of previous run + 1.
309      !!       In both those options, the  exact duration of the experiment
310      !!       since the beginning (cumulated duration of all previous restart runs)
[12489]311      !!       is not stored in the restart and is assumed to be (nit000-1)*rn_Dt.
[1130]312      !!       This is valid is the time step has remained constant.
313      !!
314      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
315      !!                    has been stored in the restart file.
316      !!----------------------------------------------------------------------
317      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
318      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
319      !
[6140]320      REAL(wp) ::   zkt, zndastp, zdayfrac, ksecs, ktime
[12377]321      INTEGER  ::   ihour, iminute, isecond
[1130]322      !!----------------------------------------------------------------------
[3764]323
[1130]324      IF( TRIM(cdrw) == 'READ' ) THEN
[3]325
[1130]326         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN
327            ! Get Calendar informations
[9367]328            CALL iom_get( numror, 'kt', zkt, ldxios = lrxios )   ! last time-step of previous run
[1130]329            IF(lwp) THEN
330               WRITE(numout,*) ' *** Info read in restart : '
331               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
332               WRITE(numout,*) ' *** restart option'
333               SELECT CASE ( nrstdt )
334               CASE ( 0 )   ;   WRITE(numout,*) ' nrstdt = 0 : no control of nit000'
335               CASE ( 1 )   ;   WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)'
336               CASE ( 2 )   ;   WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart'
337               END SELECT
338               WRITE(numout,*)
[888]339            ENDIF
[3764]340            ! Control of date
341            IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 )                                         &
342                 &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 &
[1130]343                 &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' )
344            ! define ndastp and adatrj
[3764]345            IF ( nrstdt == 2 ) THEN
[6140]346               ! read the parameters corresponding to nit000 - 1 (last time step of previous run)
[9367]347               CALL iom_get( numror, 'ndastp', zndastp, ldxios = lrxios )
[1130]348               ndastp = NINT( zndastp )
[9367]349               CALL iom_get( numror, 'adatrj', adatrj , ldxios = lrxios )
350          CALL iom_get( numror, 'ntime' , ktime  , ldxios = lrxios )
[12377]351               nn_time0 = NINT(ktime)
[6140]352               ! calculate start time in hours and minutes
[12377]353               zdayfrac = adatrj - REAL(INT(adatrj), wp)
354          ksecs = NINT(zdayfrac * rday)          ! Nearest second to catch rounding errors in adatrj         
355               ihour = ksecs / NINT( rhhmm*rmmss )
356          iminute = ksecs / NINT(rmmss) - ihour*NINT(rhhmm)
[6140]357           
358               ! Add to nn_time0
359               nhour   =   nn_time0 / 100
360               nminute = ( nn_time0 - nhour * 100 )
[12377]361          nminute = nminute + iminute
[6140]362         
[12377]363               IF( nminute >= NINT(rhhmm) ) THEN
364             nminute = nminute - NINT(rhhmm)
365        nhour = nhour+1
[6140]366          ENDIF
367          nhour=nhour+ihour
[12377]368          IF( nhour >= NINT(rjjhh) ) THEN
369        nhour = nhour - NINT(rjjhh)
370             adatrj = adatrj + 1.
[6140]371          ENDIF         
372          nn_time0 = nhour * 100 + nminute
[12377]373               adatrj = REAL(INT(adatrj), wp)                    ! adatrj set to integer as nn_time0 updated         
[3764]374            ELSE
[6140]375               ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day)
376               ndastp = ndate0        ! ndate0 read in the namelist in dom_nam
377               nhour   =   nn_time0 / 100
378               nminute = ( nn_time0 - nhour * 100 )
[12377]379               isecond = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss)
380               IF( isecond - ndt05 .lt. 0 )   ndastp = ndastp - 1      ! Start hour is specified in the namelist (default 0)
[12489]381               adatrj = ( REAL( nit000-1, wp ) * rn_Dt ) / rday
[3764]382               ! note this is wrong if time step has changed during run
[1130]383            ENDIF
384         ELSE
[6140]385            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day)
386            ndastp = ndate0           ! ndate0 read in the namelist in dom_nam
387            nhour   =   nn_time0 / 100
388       nminute = ( nn_time0 - nhour * 100 )
[12377]389            isecond = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss)
390            IF( isecond - ndt05 .LT. 0 )   ndastp = ndastp - 1         ! Start hour is specified in the namelist (default 0)
[12489]391            adatrj = ( REAL( nit000-1, wp ) * rn_Dt ) / rday
[3]392         ENDIF
[1730]393         IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error
[1130]394         !
395         IF(lwp) THEN
396            WRITE(numout,*) ' *** Info used values : '
397            WRITE(numout,*) '   date ndastp                                      : ', ndastp
398            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
[6140]399       WRITE(numout,*) '   nn_time0                                         : ',nn_time0
[1130]400            WRITE(numout,*)
[719]401         ENDIF
[888]402         !
[1130]403      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
404         !
405         IF( kt == nitrst ) THEN
406            IF(lwp) WRITE(numout,*)
407            IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt
[3764]408            IF(lwp) WRITE(numout,*) '~~~~~~~'
[1130]409         ENDIF
410         ! calendar control
[9367]411         IF( lwxios ) CALL iom_swap(      cwxios_context          )
412         CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp)  , ldxios = lwxios )   ! time-step
413         CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp)  , ldxios = lwxios )   ! date
414         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj             , ldxios = lwxios            )   ! number of elapsed days since
415         !                                                                                                   ! the begining of the run [s]
416         CALL iom_rstput( kt, nitrst, numrow, 'ntime'  , REAL( nn_time0, wp), ldxios = lwxios ) ! time
417         IF( lwxios ) CALL iom_swap(      cxios_context          )
[3]418      ENDIF
[1130]419      !
420   END SUBROUTINE day_rst
[3]421
422   !!======================================================================
423END MODULE daymod
Note: See TracBrowser for help on using the repository browser.