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.3.F90 on Ticket #1037 – Attachment – NEMO

Ticket #1037: daymod.3.F90

File daymod.3.F90, 17.9 KB (added by poddo, 11 years ago)

fixed minor bug when simulation finishes exactly at 00:00

Line 
1MODULE daymod
2   !!======================================================================
3   !!                       ***  MODULE  daymod  ***
4   !! Ocean        :  calendar
5   !!=====================================================================
6   !! History :  OPA  ! 1994-09  (M. Pontaud M. Imbard)  Original code
7   !!                 ! 1997-03  (O. Marti)
8   !!                 ! 1997-05  (G. Madec)
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
13   !!                 ! 2012-12  (P. Oddo) generalizzation of the algorithm
14   !!                       it is now possible to start at any time of the day
15   !!----------------------------------------------------------------------     
16
17   !!----------------------------------------------------------------------
18   !!   day        : calendar
19   !! 
20   !!           -------------------------------
21   !!           ----------- WARNING -----------
22   !!
23   !!   we suppose that the time step is deviding the number of second of in a day
24   !!             ---> MOD( rday, rdttra(1) ) == 0
25   !!
26   !!           ----------- WARNING -----------
27   !!           -------------------------------
28   !! 
29   !!----------------------------------------------------------------------
30   USE dom_oce         ! ocean space and time domain
31   USE phycst          ! physical constants
32   USE in_out_manager  ! I/O manager
33   USE iom             !
34   USE ioipsl, ONLY :   ymds2ju,ju2ymds   ! for calendar
35   USE prtctl          ! Print control
36   USE restart         !
37   USE trc_oce, ONLY : lk_offline ! offline flag
38   USE timing          ! Timing
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   day        ! called by step.F90
44   PUBLIC   day_init   ! called by istate.F90
45
46   INTEGER ::   nsecd, nsecd05, ndt, ndt05
47
48   !!----------------------------------------------------------------------
49   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
50   !! $Id$
51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   SUBROUTINE day_init
56      !!----------------------------------------------------------------------
57      !!                   ***  ROUTINE day_init  ***
58      !!
59      !! ** Purpose :   Initialization of the calendar values to their values 1 time step before nit000
60      !!                because day will be called at the beginning of step
61      !!
62      !! ** Action  : - nyear        : current year
63      !!              - nmonth       : current month of the year nyear
64      !!              - nday         : current day of the month nmonth
65      !!              - nday_year    : current day of the year nyear
66      !!              - nsec_year    : current time step counted in second since 00h jan 1st of the current year
67      !!              - nsec_month   : current time step counted in second since 00h 1st day of the current month
68      !!              - nsec_day     : current time step counted in second since 00h of the current day
69      !!              - nsec1jan000  : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year
70      !!              - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth
71      !!----------------------------------------------------------------------
72      INTEGER  ::   inbday, idweek
73      REAL(wp) ::   zjul,fracday
74      !!----------------------------------------------------------------------
75      !
76      ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0
77      IF( MOD( rday     , rdttra(1) ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' )
78      IF( MOD( rday     , 2.        ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    )
79      IF( MOD( rdttra(1), 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           )
80      nsecd   = NINT(rday           )
81      nsecd05 = NINT(0.5 * rday     )
82      ndt     = NINT(      rdttra(1))
83      ndt05   = NINT(0.5 * rdttra(1))
84
85      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
86
87      ! set the calandar from ndastp (read in restart file and namelist)
88
89      nyear   =   ndastp / 10000
90      nmonth  = ( ndastp - (nyear * 10000) ) / 100
91      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
92 
93      ! round adatrj to the to 0.1 sec
94      adatrj= NINT(adatrj*rday*10._wp,i8)/(rday*10._wp)
95
96      nsec_day= INT((adatrj-INT(adatrj,i8))*rday)
97
98      ! nsec_day equal zero means the simulation is between two days at 24:00 or 00:00
99      ! Since ndastp has not been upgraded to the new day (00:00) but it is still
100      ! at 24:00 we force the calendar to switch to the new day
101
102      IF (nsec_day.EQ.0.AND.adatrj.GT.0.0) nsec_day = rday
103
104      ! compute the julian of the present day
105      CALL ymds2ju( nyear, nmonth, nday, REAL(nsec_day), fjulday ) 
106
107      ! Compute date (year, month, day, second) 1/2 time-step before the integration start
108      CALL ju2ymds(fjulday-(ndt05/rday),nyear,nmonth,nday,fracday)
109      ! Compute the number of seconds elapsed from the start of the day(1/2step before)
110      nsec_day=INT(fracday)
111
112      ! Re-Compute the julian day at 1/2 time-step before the integration start
113      CALL ymds2ju( nyear, nmonth, nday, REAL(nsec_day), fjulday ) 
114
115      ! For long integration avoid truncation error at the start/end of a day
116      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   
117
118      nsec1jan000 = 0
119      CALL day_mth
120
121      IF (nmonth == 12) THEN
122         nsec1jan000 = nsec1jan000 - nsecd * nyear_len(0)
123      ENDIF 
124
125      ! day since january 1st
126      nday_year = nday + SUM( nmonth_len(1:nmonth - 1) )
127
128      !compute number of days between last monday and today     
129      CALL ymds2ju( 1900, 01, 01, 0.0, zjul )  ! compute julian day value of 01.01.1900 (our reference that was a Monday)
130      inbday = NINT(INT(fjulday) - zjul)       ! compute nb day between  01.01.1900 and current day 
131      idweek = MOD(inbday, 7)                  ! compute nb day between last monday and current day 
132
133      ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step
134      nsec_week  = idweek    * nsecd + nsec_day 
135      nsec_month = (nday-1)  * nsecd + nsec_day 
136      nsec_year  = (nday_year-1) * nsecd + nsec_day 
137
138      ! control print
139      IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i6)')' ==============>> 1/2 time step before the start of the run DATE Y/M/D = ',   &
140           &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day, '  nsec_week:', nsec_week
141
142      ! Up to now, calendar parameters are related to the end of previous run (nit000-1)
143      ! call day to set the calendar parameters at the begining of the current simulaton. needed by iom_init
144      CALL day( nit000 )
145      !
146   END SUBROUTINE day_init
147
148
149   SUBROUTINE day_mth
150      !!----------------------------------------------------------------------
151      !!                   ***  ROUTINE day_init  ***
152      !!
153      !! ** Purpose :   calendar values related to the months
154      !!
155      !! ** Action  : - nmonth_len    : length in days of the months of the current year
156      !!              - nyear_len     : length in days of the previous/current year
157      !!              - nmonth_half   : second since the beginning of the year and the halft of the months
158      !!              - nmonth_end    : second since the beginning of the year and the end of the months
159      !!----------------------------------------------------------------------
160      INTEGER  ::   jm               ! dummy loop indice
161      !!----------------------------------------------------------------------
162
163      ! length of the month of the current year (from nleapy, read in namelist)
164      IF ( nleapy < 2 ) THEN
165         nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /)
166         nyear_len(:) = 365
167         IF ( nleapy == 1 ) THEN   ! we are using calandar with leap years
168            IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN
169               nyear_len(0) = 366
170            ENDIF
171            IF ( MOD(nyear, 4) == 0 .AND. ( MOD(nyear, 400) == 0 .OR. MOD(nyear, 100) /= 0 ) ) THEN
172               nmonth_len(2) = 29
173               nyear_len(1) = 366
174            ENDIF
175         ENDIF
176      ELSE
177         nmonth_len(:) = nleapy   ! all months with nleapy days per year
178         nyear_len(:) = 12 * nleapy
179      ENDIF
180
181      ! half month in second since the begining of the year:
182      ! time since Jan 1st   0     1     2    ...    11    12    13
183      !          ---------*--|--*--|--*--| ... |--*--|--*--|--*--|--------------------------------------
184      !                 <---> <---> <--->  ...  <---> <---> <--->       
185      ! month number      0     1     2    ...    11    12    13
186      !
187      ! nmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) )
188      nmonth_half(0) = - nsecd05 * nmonth_len(0)
189      DO jm = 1, 13
190         nmonth_half(jm) = nmonth_half(jm-1) + nsecd05 * ( nmonth_len(jm-1) + nmonth_len(jm) )
191      END DO
192
193      nmonth_end(0) = 0
194      DO jm = 1, 13
195         nmonth_end(jm) = nmonth_end(jm-1) + nsecd * nmonth_len(jm)
196      END DO
197      !           
198   END SUBROUTINE
199
200
201   SUBROUTINE day( kt )
202      !!----------------------------------------------------------------------
203      !!                      ***  ROUTINE day  ***
204      !!
205      !! ** Purpose :   Compute the date with a day iteration IF necessary.
206      !!
207      !! ** Method  : - ???
208      !!
209      !! ** Action  : - nyear     : current year
210      !!              - nmonth    : current month of the year nyear
211      !!              - nday      : current day of the month nmonth
212      !!              - nday_year : current day of the year nyear
213      !!              - ndastp    : = nyear*10000 + nmonth*100 + nday
214      !!              - adatrj    : date in days since the beginning of the run
215      !!              - nsec_year : current time of the year (in second since 00h, jan 1st)
216      !!----------------------------------------------------------------------     
217      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices
218      !
219      CHARACTER (len=25) ::   charout
220      REAL(wp)           ::   zprec      ! fraction of day corresponding to 0.1 second
221      !!----------------------------------------------------------------------
222      !
223      IF( nn_timing == 1 )  CALL timing_start('day')
224      !
225      zprec = 0.1 / rday
226      !                                                 ! New time-step
227      nsec_year  = nsec_year  + ndt 
228      nsec_month = nsec_month + ndt                 
229      nsec_week  = nsec_week  + ndt
230      nsec_day   = nsec_day   + ndt               
231      adatrj  = adatrj  + rdttra(1) / rday
232      fjulday = fjulday + rdttra(1) / rday
233      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error
234      IF( ABS(adatrj  - REAL(NINT(adatrj ),wp)) < zprec )   adatrj  = REAL(NINT(adatrj ),wp)   ! avoid truncation error
235     
236      IF( nsec_day > nsecd) THEN                       ! New day
237         !
238         nday      = nday + 1
239         nday_year = nday_year + 1
240         nsec_day  = ndt05
241         !
242         IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! New month
243            nday   = 1
244            nmonth = nmonth + 1
245            nsec_month = ndt05
246            IF( nmonth == 13 ) THEN                     ! New year
247               nyear     = nyear + 1
248               nmonth    = 1
249               nday_year = 1
250               nsec_year = ndt05
251               nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1)
252               IF( nleapy == 1 )   CALL day_mth
253            ENDIF
254         ENDIF
255         !
256         ndastp = nyear * 10000 + nmonth * 100 + nday   ! New date
257         !
258         !compute first day of the year in julian days
259         CALL ymds2ju( nyear, 01, 01, 0.0, fjulstartyear )
260         !
261         IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt,   &
262              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year
263         IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') '         nsec_year = ', nsec_year,   &
264              &   '   nsec_month = ', nsec_month, '   nsec_day = ', nsec_day, '   nsec_week = ', nsec_week
265      ENDIF
266
267      IF( nsec_week > 7*nsecd )   nsec_week = ndt05     ! New week
268     
269      IF(ln_ctl) THEN
270         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
271         CALL prt_ctl_info(charout)
272      ENDIF
273
274      IF( .NOT. lk_offline ) CALL rst_opn( kt )               ! Open the restart file if needed and control lrst_oce
275      IF( lrst_oce         ) CALL day_rst( kt, 'WRITE' )      ! write day restart information
276      !
277      IF( nn_timing == 1 )  CALL timing_stop('day')
278      !
279   END SUBROUTINE day
280
281
282   SUBROUTINE day_rst( kt, cdrw )
283      !!---------------------------------------------------------------------
284      !!                   ***  ROUTINE ts_rst  ***
285      !!
286      !!  ** Purpose : Read or write calendar in restart file:
287      !!
288      !!  WRITE(READ) mode:
289      !!       kt        : number of time step since the begining of the experiment at the
290      !!                   end of the current(previous) run
291      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
292      !!                   end of the current(previous) run (REAL -> keep fractions of day)
293      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
294      !!
295      !!   According to namelist parameter nrstdt,
296      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
297      !!       nrstdt = 1  we verify that nit000 is equal to the last
298      !!                   time step of previous run + 1.
299      !!       In both those options, the  exact duration of the experiment
300      !!       since the beginning (cumulated duration of all previous restart runs)
301      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
302      !!       This is valid is the time step has remained constant.
303      !!
304      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
305      !!                    has been stored in the restart file.
306      !!----------------------------------------------------------------------
307      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
308      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
309      !
310      REAL(wp) ::   zkt, zndastp
311      !!----------------------------------------------------------------------
312     
313      IF( TRIM(cdrw) == 'READ' ) THEN
314
315         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN
316            ! Get Calendar informations
317            CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run
318            IF(lwp) THEN
319               WRITE(numout,*) ' *** Info read in restart : '
320               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
321               WRITE(numout,*) ' *** restart option'
322               SELECT CASE ( nrstdt )
323               CASE ( 0 )   ;   WRITE(numout,*) ' nrstdt = 0 : no control of nit000'
324               CASE ( 1 )   ;   WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)'
325               CASE ( 2 )   ;   WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart'
326               END SELECT
327               WRITE(numout,*)
328            ENDIF
329            ! Control of date
330            IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 )                                         & 
331                 &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
332                 &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' )
333            ! define ndastp and adatrj
334            IF ( nrstdt == 2 ) THEN 
335               ! read the parameters correspondting to nit000 - 1 (last time step of previous run)
336               CALL iom_get( numror, 'ndastp', zndastp )
337               ndastp = NINT( zndastp )
338               CALL iom_get( numror, 'adatrj', adatrj  )
339            ELSE 
340               ! parameters correspondting to nit000
341               ndastp = ndate0 
342               adatrj = ( REAL( nit000 -1, wp ) * rdttra(1) ) / rday 
343               ! note this is wrong if time step has changed during run
344            ENDIF
345         ELSE
346            ! parameters correspondting to nit000
347            ndastp = ndate0 
348            adatrj = ( REAL( nit000 -1, wp ) * rdttra(1) ) / rday 
349         ENDIF
350         IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error
351         !
352         IF(lwp) THEN
353            WRITE(numout,*) ' *** Info used values : '
354            WRITE(numout,*) '   date ndastp                                      : ', ndastp
355            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
356            WRITE(numout,*)
357         ENDIF
358         !
359      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
360         !
361         IF( kt == nitrst ) THEN
362            IF(lwp) WRITE(numout,*)
363            IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt
364            IF(lwp) WRITE(numout,*) '~~~~~~~'         
365         ENDIF
366         ! calendar control
367         CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step
368         CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date
369         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since
370         !                                                                     ! the begining of the run [s]
371      ENDIF
372      !
373   END SUBROUTINE day_rst
374
375   !!======================================================================
376END MODULE daymod