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

Last change on this file since 237 was 236, checked in by bellier, 16 years ago

calendar :

  • modification of tests to get rid of a truncation error in the determination of the date change.
  • addition in "itau2ymds" of a message to inform usage of undefined elements (call with "ioconf_startdate" not done)

restcom :

  • some orthographic correction

JB

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