source: IOIPSL/trunk/src/calendar.f90 @ 3474

Last change on this file since 3474 was 1519, checked in by mmaipsl, 13 years ago

Use ipsldbg function for all check in calendar.
Ease debugging date problems in callers.

  • Property svn:keywords set to Id
File size: 32.6 KB
Line 
1MODULE calendar
2!-
3!$Id$
4!-
5! This software is governed by the CeCILL license
6! See IOIPSL/IOIPSL_License_CeCILL.txt
7!---------------------------------------------------------------------
8!- This is the calendar which going to be used to do all
9!- calculations on time. Three types of calendars are possible :
10!-
11!-  - gregorian :
12!-      The normal calendar. The time origin for the
13!-      julian day in this case is 24 Nov -4713
14!-      (other names : 'standard','proleptic_gregorian')
15!-  - noleap :
16!-      A 365 day year without leap years.
17!-      The origin for the julian days is in this case 1 Jan 0
18!-      (other names : '365_day','365d')
19!-  - all_leap :
20!-      A 366 day year with leap years.
21!-      The origin for the julian days is in this case ????
22!-      (other names : '366_day','366d'
23!-  - julian :
24!-      same as gregorian, but with all leap century years
25!-  - xxxd :
26!-      Year of xxx days with month of equal length.
27!-      The origin for the julian days is then also 1 Jan 0
28!-
29!- As one can see it is difficult to go from one calendar to the other.
30!- All operations involving julian days will be wrong.
31!- This calendar will lock as soon as possible
32!- the length of the year and forbid any further modification.
33!-
34!- For the non leap-year calendar the method is still brute force.
35!- We need to find an Integer series which takes care of the length
36!- of the various month. (Jan)
37!-
38!-   one_day  : one day in seconds
39!-   one_year : one year in days
40!---------------------------------------------------------------------
41  USE stringop,ONLY  : strlowercase
42  USE errioipsl,ONLY : ipslerr, ipsldbg, ipslout
43!-
44  PRIVATE
45  PUBLIC :: ymds2ju,ju2ymds,tlen2itau,isittime,ioconf_calendar, &
46 &          ioget_calendar,ioget_mon_len,ioget_year_len,itau2date, &
47 &          ioget_timestamp,ioconf_startdate,itau2ymds, &
48 &          time_diff,time_add,lock_calendar
49!-
50  INTERFACE ioget_calendar
51    MODULE PROCEDURE &
52 &    ioget_calendar_real1,ioget_calendar_real2,ioget_calendar_str
53  END INTERFACE
54!-
55  INTERFACE ioconf_startdate
56     MODULE PROCEDURE &
57 &    ioconf_startdate_simple,ioconf_startdate_internal, &
58 &    ioconf_startdate_ymds
59  END INTERFACE
60!-
61  REAL,PARAMETER :: one_day = 86400.0
62  LOGICAL,SAVE :: lock_startdate = .FALSE.
63!-
64  CHARACTER(LEN=30),SAVE :: time_stamp='XXXXXXXXXXXXXXXX'
65!-
66!- Description of calendar
67!-
68  CHARACTER(LEN=20),SAVE :: calendar_used="gregorian"
69  LOGICAL,SAVE :: lock_one_year = .FALSE.
70  REAL,SAVE :: one_year = 365.2425
71  INTEGER,SAVE :: mon_len(12)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
72!-
73  CHARACTER(LEN=3),PARAMETER :: &
74 &  cal(12) = (/'JAN','FEB','MAR','APR','MAY','JUN', &
75 &              'JUL','AUG','SEP','OCT','NOV','DEC'/)
76!-
77  REAL,SAVE :: start_day,start_sec
78!-
79CONTAINS
80!-
81!===
82!-
83SUBROUTINE lock_calendar (new_status,old_status)
84!!--------------------------------------------------------------------
85!! The "lock_calendar" routine
86!! allows to lock or unlock the calendar,
87!! and to know the current status of the calendar.
88!! Be careful !
89!!
90!! SUBROUTINE lock_calendar (new_status,old_status)
91!!
92!! Optional INPUT argument
93!!
94!! (L) new_status : new status of the calendar
95!!
96!! Optional OUTPUT argument
97!!
98!! (L) old_status : current status of the calendar
99!!--------------------------------------------------------------------
100  IMPLICIT NONE
101!-
102  LOGICAL,OPTIONAL,INTENT(IN)  :: new_status
103  LOGICAL,OPTIONAL,INTENT(OUT) :: old_status
104!---------------------------------------------------------------------
105  IF (PRESENT(old_status)) THEN
106    old_status = lock_one_year
107  ENDIF
108  IF (PRESENT(new_status)) THEN
109    lock_one_year = new_status
110  ENDIF
111!---------------------------
112END SUBROUTINE lock_calendar
113!-
114!===
115!-
116SUBROUTINE ymds2ju (year,month,day,sec,julian)
117!---------------------------------------------------------------------
118  IMPLICIT NONE
119!-
120  INTEGER,INTENT(IN) :: year,month,day
121  REAL,INTENT(IN)    :: sec
122!-
123  REAL,INTENT(OUT) :: julian
124!-
125  INTEGER :: julian_day
126  REAL    :: julian_sec
127!---------------------------------------------------------------------
128  CALL ymds2ju_internal (year,month,day,sec,julian_day,julian_sec)
129!-
130  julian = julian_day+julian_sec/one_day
131!---------------------
132END SUBROUTINE ymds2ju
133!-
134!===
135!-
136SUBROUTINE ymds2ju_internal (year,month,day,sec,julian_day,julian_sec)
137!---------------------------------------------------------------------
138!- Converts year, month, day and seconds into a julian day
139!-
140!- In 1968 in a letter to the editor of Communications of the ACM
141!- (CACM, volume 11, number 10, October 1968, p.657) Henry F. Fliegel
142!- and Thomas C. Van Flandern presented such an algorithm.
143!-
144!- See also : http://www.magnet.ch/serendipity/hermetic/cal_stud/jdn.htm
145!-
146!- In the case of the Gregorian calendar we have chosen to use
147!- the Lilian day numbers. This is the day counter which starts
148!- on the 15th October 1582.
149!- This is the day at which Pope Gregory XIII introduced the
150!- Gregorian calendar.
151!- Compared to the true Julian calendar, which starts some
152!- 7980 years ago, the Lilian days are smaler and are dealt with
153!- easily on 32 bit machines. With the true Julian days you can only
154!- the fraction of the day in the real part to a precision of
155!- a 1/4 of a day with 32 bits.
156!---------------------------------------------------------------------
157  IMPLICIT NONE
158!-
159  INTEGER,INTENT(IN) :: year,month,day
160  REAL,INTENT(IN)    :: sec
161!-
162  INTEGER,INTENT(OUT) :: julian_day
163  REAL,INTENT(OUT)    :: julian_sec
164!-
165  INTEGER :: jd,m,y,d,ml
166!---------------------------------------------------------------------
167  lock_one_year = .TRUE.
168!-
169  m = month
170  y = year
171  d = day
172!-
173!- We deduce the calendar from the length of the year as it
174!- is faster than an INDEX on the calendar variable.
175!-
176  IF ( (one_year > 365.0).AND.(one_year < 366.0) ) THEN
177!-- "Gregorian"
178    jd = (1461*(y+4800+INT((m-14)/12)))/4 &
179 &      +(367*(m-2-12*(INT((m-14)/12))))/12 &
180 &      -(3*((y+4900+INT((m-14)/12))/100))/4 &
181 &      +d-32075
182    jd = jd-2299160
183  ELSE IF (    (ABS(one_year-365.0) <= EPSILON(one_year))  &
184 &         .OR.(ABS(one_year-366.0) <= EPSILON(one_year)) ) THEN
185!-- "No leap" or "All leap"
186    ml = SUM(mon_len(1:m-1))
187    jd = y*NINT(one_year)+ml+(d-1)
188  ELSE
189!-- Calendar with regular month
190    ml = NINT(one_year/12.)
191    jd = y*NINT(one_year)+(m-1)*ml+(d-1)
192  ENDIF
193!-
194  julian_day = jd
195  julian_sec = sec
196!------------------------------
197END SUBROUTINE ymds2ju_internal
198!-
199!===
200!-
201SUBROUTINE ju2ymds (julian,year,month,day,sec)
202!---------------------------------------------------------------------
203  IMPLICIT NONE
204!-
205  REAL,INTENT(IN) :: julian
206!-
207  INTEGER,INTENT(OUT) :: year,month,day
208  REAL,INTENT(OUT)    :: sec
209!-
210  INTEGER :: julian_day
211  REAL    :: julian_sec
212!---------------------------------------------------------------------
213  julian_day = INT(julian)
214  julian_sec = (julian-julian_day)*one_day
215!-
216  CALL ju2ymds_internal(julian_day,julian_sec,year,month,day,sec)
217!---------------------
218END SUBROUTINE ju2ymds
219!-
220!===
221!-
222SUBROUTINE ju2ymds_internal (julian_day,julian_sec,year,month,day,sec)
223!---------------------------------------------------------------------
224!- This subroutine computes from the julian day the year,
225!- month, day and seconds
226!-
227!- In 1968 in a letter to the editor of Communications of the ACM
228!- (CACM, volume 11, number 10, October 1968, p.657) Henry F. Fliegel
229!- and Thomas C. Van Flandern presented such an algorithm.
230!-
231!- See also : http://www.magnet.ch/serendipity/hermetic/cal_stud/jdn.htm
232!-
233!- In the case of the Gregorian calendar we have chosen to use
234!- the Lilian day numbers. This is the day counter which starts
235!- on the 15th October 1582. This is the day at which Pope
236!- Gregory XIII introduced the Gregorian calendar.
237!- Compared to the true Julian calendar, which starts some 7980
238!- years ago, the Lilian days are smaler and are dealt with easily
239!- on 32 bit machines. With the true Julian days you can only the
240!- fraction of the day in the real part to a precision of a 1/4 of
241!- a day with 32 bits.
242!---------------------------------------------------------------------
243  IMPLICIT NONE
244!-
245  INTEGER,INTENT(IN) :: julian_day
246  REAL,INTENT(IN)    :: julian_sec
247!-
248  INTEGER,INTENT(OUT) :: year,month,day
249  REAL,INTENT(OUT)    :: sec
250!-
251  INTEGER :: l,n,i,jd,j,d,m,y,ml
252  INTEGER :: add_day
253  REAL :: eps_day
254!---------------------------------------------------------------------
255  eps_day = SPACING(one_day)
256  lock_one_year = .TRUE.
257!-
258  jd = julian_day
259  sec = julian_sec
260  IF (sec > (one_day-eps_day)) THEN
261    add_day = INT(sec/one_day)
262    sec = sec-add_day*one_day
263    jd = jd+add_day
264  ENDIF
265  IF (sec < -eps_day) THEN
266    sec = sec+one_day
267    jd = jd-1
268  ENDIF
269!-
270  IF ( (one_year > 365.0).AND.(one_year < 366.0) ) THEN
271!-- Gregorian
272    jd = jd+2299160
273!-
274    l = jd+68569
275    n = (4*l)/146097
276    l = l-(146097*n+3)/4
277    i = (4000*(l+1))/1461001
278    l = l-(1461*i)/4+31
279    j = (80*l)/2447
280    d = l-(2447*j)/80
281    l = j/11
282    m = j+2-(12*l)
283    y = 100*(n-49)+i+l
284  ELSE IF (    (ABS(one_year-365.0) <= EPSILON(one_year)) &
285 &         .OR.(ABS(one_year-366.0) <= EPSILON(one_year)) ) THEN
286!-- No leap or All leap
287    y = jd/NINT(one_year)
288    l = jd-y*NINT(one_year)
289    m = 1
290    ml = 0
291    DO WHILE (ml+mon_len(m) <= l)
292      ml = ml+mon_len(m)
293      m = m+1
294    ENDDO
295    d = l-ml+1
296  ELSE
297!-- others
298    ml = NINT(one_year/12.)
299    y = jd/NINT(one_year)
300    l = jd-y*NINT(one_year)
301    m = (l/ml)+1
302    d = l-(m-1)*ml+1
303  ENDIF
304!-
305  day = d
306  month = m
307  year = y
308!------------------------------
309END SUBROUTINE ju2ymds_internal
310!-
311!===
312!-
313SUBROUTINE tlen2itau (input_str,dt,date,itau)
314!---------------------------------------------------------------------
315!- This subroutine transforms a string containing a time length
316!- into a number of time steps.
317!- To do this operation the date (in julian days is needed as the
318!- length of the month varies.
319!- The following convention is used :
320!-   n   : n time steps
321!-   nS  : n seconds is transformed into itaus
322!-   nH  : n hours
323!-   nD  : n days
324!-   nM  : n month
325!-   nY  : n years
326!- Combinations are also possible
327!-   nYmD : nyears plus m days !
328!---------------------------------------------------------------------
329  IMPLICIT NONE
330!-
331  CHARACTER(LEN=*),INTENT(IN) :: input_str
332  REAL,INTENT(IN)             :: dt,date
333!-
334  INTEGER,INTENT(OUT)         :: itau
335!-
336  INTEGER           :: y_pos,m_pos,d_pos,h_pos,s_pos
337  INTEGER           :: read_time
338  CHARACTER(LEN=13) :: fmt
339  CHARACTER(LEN=80) :: tmp_str
340!-
341  INTEGER :: year,month,day
342  REAL    :: sec,date_new,dd,ss
343!---------------------------------------------------------------------
344  itau = 0
345  CALL ju2ymds (date,year,month,day,sec)
346!-
347  y_pos = MAX(INDEX(input_str,'y'),INDEX(input_str,'Y'))
348  m_pos = MAX(INDEX(input_str,'m'),INDEX(input_str,'M'))
349  d_pos = MAX(INDEX(input_str,'d'),INDEX(input_str,'D'))
350  h_pos = MAX(INDEX(input_str,'h'),INDEX(input_str,'H'))
351  s_pos = MAX(INDEX(input_str,'s'),INDEX(input_str,'S'))
352!-
353  IF (MAX(y_pos,m_pos,d_pos,s_pos) > 0) THEN
354    tmp_str = input_str
355    DO WHILE ( MAX(y_pos,m_pos,d_pos,s_pos) > 0)
356!---- WRITE(ipslout,*) tmp_str
357!---- WRITE(ipslout,*) y_pos,m_pos,d_pos,s_pos
358      IF (y_pos > 0) THEN
359        WRITE(fmt,'("(I",I10.10,")")') y_pos-1
360        READ(tmp_str(1:y_pos-1),fmt) read_time
361        CALL ymds2ju (year+read_time,month,day,sec,date_new)
362        dd = date_new-date
363        ss = INT(dd)*one_day+dd-INT(dd)
364        itau = itau+NINT(ss/dt)
365        tmp_str = tmp_str(y_pos+1:LEN_TRIM(tmp_str))
366      ELSE IF (m_pos > 0) THEN
367        WRITE(fmt,'("(I",I10.10,")")') m_pos-1
368        READ(tmp_str(1:m_pos-1),fmt) read_time
369        CALL ymds2ju (year,month+read_time,day,sec,date_new)
370        dd = date_new-date
371        ss = INT(dd)*one_day+dd-INT(dd)
372        itau = itau+NINT(ss/dt)
373        tmp_str = tmp_str(m_pos+1:LEN_TRIM(tmp_str))
374      ELSE IF (d_pos > 0) THEN
375        WRITE(fmt,'("(I",I10.10,")")') d_pos-1
376        READ(tmp_str(1:d_pos-1),fmt) read_time
377        itau = itau+NINT(read_time*one_day/dt)
378        tmp_str = tmp_str(d_pos+1:LEN_TRIM(tmp_str))
379      ELSE IF (h_pos > 0) THEN
380        WRITE(fmt,'("(I",I10.10,")")') h_pos-1
381        READ(tmp_str(1:h_pos-1),fmt) read_time
382        itau = itau+NINT(read_time*60.*60./dt)
383        tmp_str = tmp_str(d_pos+1:LEN_TRIM(tmp_str))
384      ELSE IF  (s_pos > 0) THEN
385        WRITE(fmt,'("(I",I10.10,")")') s_pos-1
386        READ(tmp_str(1:s_pos-1),fmt) read_time
387        itau = itau+NINT(read_time/dt)
388        tmp_str = tmp_str(s_pos+1:LEN_TRIM(tmp_str))
389      ENDIF
390!-
391      y_pos = MAX(INDEX(tmp_str,'y'),INDEX(tmp_str,'Y'))
392      m_pos = MAX(INDEX(tmp_str,'m'),INDEX(tmp_str,'M'))
393      d_pos = MAX(INDEX(tmp_str,'d'),INDEX(tmp_str,'D'))
394      h_pos = MAX(INDEX(tmp_str,'h'),INDEX(tmp_str,'H'))
395      s_pos = MAX(INDEX(tmp_str,'s'),INDEX(tmp_str,'S'))
396    ENDDO
397  ELSE
398    WRITE(fmt,'("(I",I10.10,")")') LEN_TRIM(input_str)
399    READ(input_str(1:LEN_TRIM(input_str)),fmt) itau
400  ENDIF
401!-----------------------
402END SUBROUTINE tlen2itau
403!-
404!===
405!-
406REAL FUNCTION itau2date (itau,date0,deltat)
407!---------------------------------------------------------------------
408!- This function transforms itau into a date. The date with which
409!- the time axis is going to be labeled
410!-
411!- INPUT
412!-   itau   : current time step
413!-   date0  : Date at which itau was equal to 0
414!-   deltat : time step between itau s
415!-
416!- OUTPUT
417!-   itau2date : Date for the given itau
418!---------------------------------------------------------------------
419  IMPLICIT NONE
420!-
421  INTEGER  :: itau
422  REAL     :: date0,deltat
423!---------------------------------------------------------------------
424  itau2date = REAL(itau)*deltat/one_day+date0
425!---------------------
426END FUNCTION itau2date
427!-
428!===
429!-
430SUBROUTINE itau2ymds (itau,deltat,year,month,day,sec)
431!---------------------------------------------------------------------
432!- This subroutine transforms itau into a date. The date with which
433!- the time axis is going to be labeled
434!-
435!- INPUT
436!-   itau   : current time step
437!-   deltat : time step between itau s
438!-
439!- OUTPUT
440!-   year  : year
441!-   month : month
442!-   day   : day
443!-   sec   : seconds since midnight
444!---------------------------------------------------------------------
445  IMPLICIT NONE
446!-
447  INTEGER,INTENT(IN) :: itau
448  REAL,INTENT(IN)    :: deltat
449!-
450  INTEGER,INTENT(OUT) :: year,month,day
451  REAL,INTENT(OUT)    :: sec
452!-
453  INTEGER :: julian_day
454  REAL    :: julian_sec
455!---------------------------------------------------------------------
456  IF (.NOT.lock_startdate) THEN
457    CALL ipslerr (2,'itau2ymds', &
458 &   'You try to call this function, itau2ymds, but you didn''t', &
459 &   ' call ioconf_startdate to initialize date0 in calendar.', &
460 &   ' Please call ioconf_startdate before itau2ymds.')
461  ENDIF
462  julian_day = start_day
463  julian_sec = start_sec+REAL(itau)*deltat
464  CALL ju2ymds_internal (julian_day,julian_sec,year,month,day,sec)
465!-----------------------
466END SUBROUTINE itau2ymds
467!-
468!===
469!-
470REAL FUNCTION dtchdate (itau,date0,old_dt,new_dt)
471!---------------------------------------------------------------------
472!- This function changes the date so that the simulation can
473!- continue with the same itau but a different dt.
474!-
475!- INPUT
476!-   itau   : current time step
477!-   date0  : Date at which itau was equal to 0
478!-   old_dt : Old time step between itaus
479!-   new_dt : New time step between itaus
480!-
481!- OUTPUT
482!-   dtchdate : Date for the given itau
483!---------------------------------------------------------------------
484  IMPLICIT NONE
485!-
486  INTEGER,INTENT(IN) :: itau
487  REAL,INTENT(IN)    :: date0,old_dt,new_dt
488!-
489  REAL :: rtime
490!---------------------------------------------------------------------
491  rtime = itau2date (itau,date0,old_dt)
492  dtchdate = rtime-REAL(itau)*new_dt/one_day
493!--------------------
494END FUNCTION dtchdate
495!-
496!===
497!-
498SUBROUTINE isittime &
499 &  (itau,date0,dt,freq,last_action,last_check,do_action)
500!---------------------------------------------------------------------
501!- This subroutine checks the time as come for a given action.
502!- This is computed from the current time-step(itau).
503!- Thus we need to have the time delta (dt), the frequency
504!- of the action (freq) and the last time it was done
505!- (last_action in units of itau).
506!- In order to extrapolate when will be the next check we need
507!- the time step of the last call (last_check).
508!-
509!- The test is done on the following condition :
510!- the distance from the current time to the time for the next
511!- action is smaller than the one from the next expected
512!- check to the next action.
513!- When the test is done on the time steps simplifications make
514!- it more difficult to read in the code.
515!- For the real time case it is easier to understand !
516!---------------------------------------------------------------------
517  IMPLICIT NONE
518!-
519  INTEGER,INTENT(IN) :: itau
520  REAL,INTENT(IN)    :: dt,freq
521  INTEGER,INTENT(IN) :: last_action,last_check
522  REAL,INTENT(IN)    :: date0
523!-
524  LOGICAL,INTENT(OUT)  :: do_action
525!-
526  REAL :: dt_action,dt_check
527  REAL :: date_last_act,date_next_check,date_next_act, &
528 &        date_now,date_mp1,date_mpf
529  INTEGER :: year,month,monthp1,day,next_check_itau,next_act_itau
530  INTEGER :: yearp,dayp
531  REAL :: sec,secp
532  LOGICAL :: l_dbg
533!---------------------------------------------------------------------
534  CALL ipsldbg (old_status=l_dbg)
535!---------------------------------------------------------------------
536  IF (l_dbg) THEN
537    WRITE(ipslout,*) &
538 &    "isittime 1.0 ",itau,date0,dt,freq,last_action,last_check
539  ENDIF
540!-
541  IF (last_check >= 0) THEN
542    dt_action = (itau-last_action)*dt
543    dt_check = (itau-last_check)*dt
544    next_check_itau = itau+(itau-last_check)
545!-
546!-- We are dealing with frequencies in seconds and thus operation
547!-- can be done on the time steps.
548!-
549    IF (freq > 0) THEN
550      IF (ABS(dt_action-freq) <= ABS(dt_action+dt_check-freq)) THEN
551        do_action = .TRUE.
552      ELSE
553        do_action = .FALSE.
554      ENDIF
555!-
556!---- Here we deal with frequencies in month and work on julian days.
557!-
558    ELSE
559      date_now = itau2date (itau,date0,dt)
560      date_last_act = itau2date (last_action,date0,dt)
561      CALL ju2ymds (date_last_act,year,month,day,sec)
562      monthp1 = month-freq
563      yearp = year
564!-
565!---- Here we compute what logically should be the next month
566!-
567      IF (month >= 13) THEN
568        yearp = year+1
569        monthp1 = monthp1-12
570      ENDIF
571      CALL ymds2ju (year,monthp1,day,sec,date_mpf)
572!-
573!---- But it could be that because of a shorter month or a bad
574!---- starting date that we end up further than we should be.
575!---- Thus we compute the first day of the next month.
576!---- We can not be beyond this date and if we are close
577!---- then we will take it as it is better.
578!-
579      monthp1 = month+ABS(freq)
580      yearp=year
581      IF (monthp1 >= 13) THEN
582        yearp = year+1
583        monthp1 = monthp1 -12
584      ENDIF
585      dayp = 1
586      secp = 0.0
587      CALL ymds2ju (yearp,monthp1,dayp,secp,date_mp1)
588!-
589!---- If date_mp1 is smaller than date_mpf or only less than 4 days
590!---- larger then we take it. This needed to ensure that short month
591!---- like February do not mess up the thing !
592!-
593      IF (date_mp1-date_mpf < 4.) THEN
594        date_next_act = date_mp1
595      ELSE
596        date_next_act = date_mpf
597      ENDIF
598      date_next_check = itau2date (next_check_itau,date0,dt)
599!-
600!---- Transform the dates into time-steps for the needed precisions.
601!-
602      next_act_itau = &
603 &      last_action+INT((date_next_act-date_last_act)*(one_day/dt))
604!-----
605      IF (   ABS(itau-next_act_itau) &
606 &        <= ABS( next_check_itau-next_act_itau)) THEN
607        do_action = .TRUE.
608        IF (l_dbg) THEN
609          WRITE(ipslout,*) &
610 &         'ACT-TIME : itau, next_act_itau, next_check_itau : ', &
611 &         itau,next_act_itau,next_check_itau
612          CALL ju2ymds (date_now,year,month,day,sec)
613          WRITE(ipslout,*) 'ACT-TIME : y, m, d, s : ',year,month,day,sec
614          WRITE(ipslout,*) &
615 &         'ACT-TIME : date_mp1, date_mpf : ',date_mp1,date_mpf
616        ENDIF
617      ELSE
618        do_action = .FALSE.
619      ENDIF
620    ENDIF
621!-
622    IF (l_dbg) THEN
623      WRITE(ipslout,*) "isittime 2.0 ", &
624 &     date_next_check,date_next_act,ABS(dt_action-freq), &
625 &     ABS(dt_action+dt_check-freq),dt_action,dt_check, &
626 &     next_check_itau,do_action
627    ENDIF
628  ELSE
629    do_action=.FALSE.
630  ENDIF
631!----------------------
632END SUBROUTINE isittime
633!-
634!===
635!-
636SUBROUTINE ioconf_calendar (str)
637!---------------------------------------------------------------------
638!- This routine allows to configure the calendar to be used.
639!- This operation is only allowed once and the first call to
640!- ymds2ju or ju2ymsd will lock the current configuration.
641!- the argument to ioconf_calendar can be any of the following :
642!-  - gregorian : This is the gregorian calendar (default here)
643!-  - noleap    : A calendar without leap years = 365 days
644!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
645!-                with 12 month of equal length
646!---------------------------------------------------------------------
647  IMPLICIT NONE
648!-
649  CHARACTER(LEN=*),INTENT(IN) :: str
650!-
651  INTEGER :: leng,ipos
652  CHARACTER(LEN=20) :: str_w
653!---------------------------------------------------------------------
654!-
655! Clean up the string !
656!-
657  str_w = str
658  CALL strlowercase (str_w)
659!-
660  IF (.NOT.lock_one_year) THEN
661!---
662    lock_one_year=.TRUE.
663!---
664    SELECT CASE(TRIM(str_w))
665    CASE('gregorian','standard','proleptic_gregorian')
666      calendar_used = 'gregorian'
667      one_year = 365.2425
668      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
669    CASE('noleap','365_day','365d')
670      calendar_used = 'noleap'
671      one_year = 365.0
672      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
673    CASE('all_leap','366_day','366d')
674      calendar_used = 'all_leap'
675      one_year = 366.0
676      mon_len(:)=(/31,29,31,30,31,30,31,31,30,31,30,31/)
677    CASE('360_day','360d')
678      calendar_used = '360d'
679      one_year = 360.0
680      mon_len(:)=(/30,30,30,30,30,30,30,30,30,30,30,30/)
681    CASE('julian')
682      calendar_used = 'julian'
683      one_year = 365.25
684      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
685    CASE DEFAULT
686      ipos = INDEX(str_w,'d')
687      IF (ipos == 4) THEN
688        READ(str_w(1:3),'(I3)') leng
689        IF ( (MOD(leng,12) == 0).AND.(leng > 1) ) THEN
690          calendar_used = str_w
691          one_year = leng
692          mon_len(:) = leng/12
693        ELSE
694          CALL ipslerr (3,'ioconf_calendar', &
695 &         'The length of the year as to be a modulo of 12', &
696 &         'so that it can be divided into 12 month of equal length', &
697 &         TRIM(str_w))
698        ENDIF
699      ELSE
700        CALL ipslerr (3,'ioconf_calendar', &
701 &       'Unrecognized input, please check the man pages.', &
702 &       TRIM(str_w),' ')
703      ENDIF
704    END SELECT
705  ELSE IF (TRIM(str_w) /= TRIM(calendar_used)) THEN
706    WRITE(str_w,'(f10.4)') one_year
707    CALL ipslerr (2,'ioconf_calendar', &
708 &   'The calendar was already used or configured to : '// &
709 &    TRIM(calendar_used)//'.', &
710 &   'You are not allowed to change it to : '//TRIM(str)//'.', &
711 &   'The following length of year is used : '//TRIM(ADJUSTL(str_w)))
712  ENDIF
713!-----------------------------
714END SUBROUTINE ioconf_calendar
715!-
716!===
717!-
718SUBROUTINE ioconf_startdate_simple (julian)
719!---------------------------------------------------------------------
720  IMPLICIT NONE
721!-
722  REAL,INTENT(IN) :: julian
723!-
724  INTEGER :: julian_day
725  REAL    :: julian_sec
726!---------------------------------------------------------------------
727  julian_day = INT(julian)
728  julian_sec = (julian-julian_day)*one_day
729!-
730  CALL ioconf_startdate_internal (julian_day,julian_sec)
731!-------------------------------------
732END SUBROUTINE ioconf_startdate_simple
733!-
734!===
735!-
736SUBROUTINE ioconf_startdate_ymds (year,month,day,sec)
737!---------------------------------------------------------------------
738  IMPLICIT NONE
739!-
740  INTEGER,INTENT(IN) :: year,month,day
741  REAL,INTENT(IN)    :: sec
742!-
743  INTEGER :: julian_day
744  REAL    :: julian_sec
745!---------------------------------------------------------------------
746  CALL ymds2ju_internal (year,month,day,sec,julian_day,julian_sec)
747!-
748  CALL ioconf_startdate_internal (julian_day,julian_sec)
749!-----------------------------------
750END SUBROUTINE ioconf_startdate_ymds
751!-
752!===
753!-
754SUBROUTINE ioconf_startdate_internal (julian_day,julian_sec)
755!---------------------------------------------------------------------
756! This subroutine allows to set the startdate for later
757! use. It allows the applications to access the date directly from
758! the timestep. In order to avoid any problems the start date will
759! be locked and can not be changed once set.
760!---------------------------------------------------------------------
761  IMPLICIT NONE
762!-
763  INTEGER,INTENT(IN)  :: julian_day
764  REAL,INTENT(IN)     :: julian_sec
765!-
766  CHARACTER(len=70) :: str70a,str70b
767!---------------------------------------------------------------------
768  IF (.NOT.lock_startdate) THEN
769    start_day = julian_day
770    start_sec = julian_sec
771    lock_startdate = .TRUE.
772  ELSE
773    WRITE(str70a,'("The date you tried to set : ",f10.4)') &
774 &   julian_day,julian_sec/one_day
775    WRITE(str70b, &
776 &   '("The date which was already set in the calendar : ",f10.4)') &
777 &   start_day+start_sec/one_day
778    CALL ipslerr (2,'ioconf_startdate', &
779 &   'The start date has already been set and you tried to change it', &
780 &   str70a,str70b)
781  ENDIF
782!---------------------------------------
783END SUBROUTINE ioconf_startdate_internal
784!-
785!===
786!-
787SUBROUTINE ioget_calendar_str (str)
788!---------------------------------------------------------------------
789!- This subroutine returns the name of the calendar used here.
790!- Three options exist :
791!-  - gregorian : This is the gregorian calendar (default here)
792!-  - noleap    : A calendar without leap years = 365 days
793!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
794!-                with 12 month of equal length
795!-
796!- This routine will lock the calendar.
797!- You do not want it to change after your inquiry.
798!---------------------------------------------------------------------
799  IMPLICIT NONE
800!-
801  CHARACTER(LEN=*),INTENT(OUT) :: str
802!---------------------------------------------------------------------
803  lock_one_year = .TRUE.
804!-
805  str = calendar_used
806!--------------------------------
807END SUBROUTINE ioget_calendar_str
808!-
809!===
810!-
811SUBROUTINE ioget_calendar_real1 (long_year)
812!---------------------------------------------------------------------
813!- This subroutine returns the name of the calendar used here.
814!- Three options exist :
815!-  - gregorian : This is the gregorian calendar (default here)
816!-  - noleap    : A calendar without leap years = 365 days
817!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
818!-                with 12 month of equal length
819!-
820!- This routine will lock the calendar.
821!- You do not want it to change after your inquiry.
822!---------------------------------------------------------------------
823  IMPLICIT NONE
824!-
825  REAL,INTENT(OUT) :: long_year
826!---------------------------------------------------------------------
827  long_year = one_year
828  lock_one_year = .TRUE.
829!----------------------------------
830END SUBROUTINE ioget_calendar_real1
831!-
832!===
833!-
834SUBROUTINE ioget_calendar_real2 (long_year,long_day)
835!---------------------------------------------------------------------
836!- This subroutine returns the name of the calendar used here.
837!- Three options exist :
838!-  - gregorian : This is the gregorian calendar (default here)
839!-  - noleap    : A calendar without leap years = 365 days
840!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
841!-                with 12 month of equal length
842!-
843!- This routine will lock the calendar.
844!- You do not want it to change after your inquiry.
845!---------------------------------------------------------------------
846  IMPLICIT NONE
847!-
848  REAL,INTENT(OUT) :: long_year,long_day
849!---------------------------------------------------------------------
850  long_year = one_year
851  long_day  = one_day
852  lock_one_year = .TRUE.
853!----------------------------------
854END SUBROUTINE ioget_calendar_real2
855!-
856!===
857!-
858INTEGER FUNCTION ioget_mon_len (year,month)
859!!--------------------------------------------------------------------
860!! The "ioget_mon_len" function returns
861!! the number of days in a "month" of a "year",
862!! in the current calendar.
863!!
864!! INTEGER FUNCTION ioget_mon_len (year,month)
865!!
866!! INPUT
867!!
868!! (I) year  : year
869!! (I) month : month in the year (1 --> 12)
870!!
871!! OUTPUT
872!!
873!! (I) ioget_mon_len : number of days in the month
874!!--------------------------------------------------------------------
875  IMPLICIT NONE
876!-
877  INTEGER,INTENT(IN) :: year,month
878!-
879  INTEGER :: ml
880!---------------------------------------------------------------------
881  IF ( (month >= 1).AND.(month <= 12) ) THEN
882    IF ( (one_year > 365.0).AND.(one_year < 366.0) ) THEN
883!---- "Gregorian" or "Julian"
884      ml = mon_len(month)
885      IF (month == 2) THEN
886        IF (ABS(one_year-365.2425) <= EPSILON(one_year) ) THEN
887!-------- "Gregorian"
888          IF (    ((MOD(year,4) == 0).AND.(MOD(year,100) /= 0)) &
889              .OR.(MOD(year,400) == 0) ) THEN
890            ml = ml+1
891          ENDIF
892        ELSE
893!-------- "Julian"
894          IF (MOD(year,4) == 0) THEN
895            ml = ml+1
896          ENDIF
897        ENDIF
898      ENDIF
899      ioget_mon_len = ml
900    ELSE
901!---- "No leap" or "All leap" or "Calendar with regular month"
902      ioget_mon_len = mon_len(month)
903    ENDIF
904  ELSE
905    CALL ipslerr (3,'ioget_mon_len', &
906 &    'The number of the month','must be between','1 and 12')
907  ENDIF
908!-------------------------
909END FUNCTION ioget_mon_len
910!-
911!===
912!-
913INTEGER FUNCTION ioget_year_len (year)
914!!--------------------------------------------------------------------
915!! The "ioget_year_len" function returns
916!! the number of days in "year", in the current calendar.
917!!
918!! INTEGER FUNCTION ioget_year_len (year)
919!!
920!! INPUT
921!!
922!! (I) year  : year
923!!
924!! OUTPUT
925!!
926!! (I) ioget_year_len : number of days in the year
927!!--------------------------------------------------------------------
928  IMPLICIT NONE
929!-
930  INTEGER,INTENT(IN) :: year
931!-
932  INTEGER :: yl
933!---------------------------------------------------------------------
934  SELECT CASE(TRIM(calendar_used))
935  CASE('gregorian')
936    yl = 365
937    IF (    ((MOD(year,4) == 0).AND.(MOD(year,100) /= 0)) &
938        .OR.(MOD(year,400) == 0) ) THEN
939      yl = yl+1
940    ENDIF
941  CASE('julian')
942    yl = 365
943    IF (MOD(year,4) == 0) THEN
944      yl = yl+1
945    ENDIF
946  CASE DEFAULT
947    yl = NINT(one_year)
948  END SELECT
949  ioget_year_len = yl
950!--------------------------
951END FUNCTION ioget_year_len
952!-
953!===
954!-
955SUBROUTINE ioget_timestamp (string)
956!---------------------------------------------------------------------
957  IMPLICIT NONE
958!-
959  CHARACTER(LEN=30),INTENT(OUT) :: string
960!-
961  INTEGER :: date_time(8)
962  CHARACTER(LEN=10) :: bigben(3)
963!---------------------------------------------------------------------
964  IF (INDEX(time_stamp,'XXXXXX') > 0) THEN
965    CALL DATE_AND_TIME (bigben(1),bigben(2),bigben(3),date_time)
966!---
967    WRITE(time_stamp, &
968 &   "(I4.4,'-',A3,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2,' GMT',a5)") &
969 &   date_time(1),cal(date_time(2)),date_time(3),date_time(5), &
970 &   date_time(6),date_time(7),bigben(3)
971  ENDIF
972!-
973  string = time_stamp
974!-----------------------------
975END SUBROUTINE ioget_timestamp
976!-
977!===
978!-
979SUBROUTINE time_add &
980 &  (year_s,month_s,day_s,sec_s,sec_increment, &
981 &   year_e,month_e,day_e,sec_e)
982!---------------------------------------------------------------------
983!- This subroutine allows to increment a date by a number of seconds.
984!---------------------------------------------------------------------
985  IMPLICIT NONE
986!-
987  INTEGER,INTENT(IN) :: year_s,month_s,day_s
988  REAL,INTENT(IN)    :: sec_s
989!-
990! Time in seconds to be added to the date
991!-
992  REAL,INTENT(IN)    :: sec_increment
993!-
994  INTEGER,INTENT(OUT) :: year_e,month_e,day_e
995  REAL,INTENT(OUT)    :: sec_e
996!-
997  INTEGER :: julian_day
998  REAL    :: julian_sec
999!---------------------------------------------------------------------
1000  CALL ymds2ju_internal &
1001 &  (year_s,month_s,day_s,sec_s,julian_day,julian_sec)
1002!-
1003  julian_sec = julian_sec+sec_increment
1004!-
1005  CALL ju2ymds_internal &
1006 &  (julian_day,julian_sec,year_e,month_e,day_e,sec_e)
1007!----------------------
1008END SUBROUTINE time_add
1009!-
1010!===
1011!-
1012SUBROUTINE time_diff &
1013 &  (year_s,month_s,day_s,sec_s,year_e,month_e,day_e,sec_e,sec_diff)
1014!---------------------------------------------------------------------
1015!- This subroutine allows to determine the number of seconds
1016!- between two dates.
1017!---------------------------------------------------------------------
1018  IMPLICIT NONE
1019!-
1020  INTEGER,INTENT(IN) :: year_s,month_s,day_s
1021  REAL,INTENT(IN)    :: sec_s
1022  INTEGER,INTENT(IN) :: year_e,month_e,day_e
1023  REAL,INTENT(IN)    :: sec_e
1024!-
1025! Time in seconds between the two dates
1026!-
1027  REAL,INTENT(OUT)    :: sec_diff
1028!-
1029  INTEGER :: julian_day_s,julian_day_e,day_diff
1030  REAL    :: julian_sec_s,julian_sec_e
1031!---------------------------------------------------------------------
1032  CALL ymds2ju_internal &
1033 &  (year_s,month_s,day_s,sec_s,julian_day_s,julian_sec_s)
1034  CALL ymds2ju_internal &
1035 &  (year_e,month_e,day_e,sec_e,julian_day_e,julian_sec_e)
1036!-
1037  day_diff = julian_day_e-julian_day_s
1038  sec_diff = julian_sec_e-julian_sec_s
1039!-
1040  sec_diff = sec_diff+day_diff*one_day
1041!-----------------------
1042END SUBROUTINE time_diff
1043!-
1044!===
1045!-
1046END MODULE calendar
Note: See TracBrowser for help on using the repository browser.