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

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

JB : move one instruction for stupid compilers !

  • 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
251!---------------------------------------------------------------------
252  eps_day = SPACING(one_day)
253  lock_one_year = .TRUE.
254!-
255  jd = julian_day
256  sec = julian_sec
257  IF (sec > (one_day-eps_day)) THEN
258    add_day = INT(sec/one_day)
259    sec = sec-add_day*one_day
260    jd = jd+add_day
261  ENDIF
262  IF (sec < -eps_day) THEN
263    sec = sec+one_day
264    jd = jd-1
265  ENDIF
266!-
267  IF ( (one_year > 365.0).AND.(one_year < 366.0) ) THEN
268!-- Gregorian
269    jd = jd+2299160
270!-
271    l = jd+68569
272    n = (4*l)/146097
273    l = l-(146097*n+3)/4
274    i = (4000*(l+1))/1461001
275    l = l-(1461*i)/4+31
276    j = (80*l)/2447
277    d = l-(2447*j)/80
278    l = j/11
279    m = j+2-(12*l)
280    y = 100*(n-49)+i+l
281  ELSE IF (    (ABS(one_year-365.0) <= EPSILON(one_year)) &
282 &         .OR.(ABS(one_year-366.0) <= EPSILON(one_year)) ) THEN
283!-- No leap or All leap
284    y = jd/NINT(one_year)
285    l = jd-y*NINT(one_year)
286    m = 1
287    ml = 0
288    DO WHILE (ml+mon_len(m) <= l)
289      ml = ml+mon_len(m)
290      m = m+1
291    ENDDO
292    d = l-ml+1
293  ELSE
294!-- others
295    ml = NINT(one_year/12.)
296    y = jd/NINT(one_year)
297    l = jd-y*NINT(one_year)
298    m = (l/ml)+1
299    d = l-(m-1)*ml+1
300  ENDIF
301!-
302  day = d
303  month = m
304  year = y
305!------------------------------
306END SUBROUTINE ju2ymds_internal
307!-
308!===
309!-
310SUBROUTINE tlen2itau (input_str,dt,date,itau)
311!---------------------------------------------------------------------
312!- This subroutine transforms a string containing a time length
313!- into a number of time steps.
314!- To do this operation the date (in julian days is needed as the
315!- length of the month varies.
316!- The following convention is used :
317!-   n   : n time steps
318!-   nS  : n seconds is transformed into itaus
319!-   nH  : n hours
320!-   nD  : n days
321!-   nM  : n month
322!-   nY  : n years
323!- Combinations are also possible
324!-   nYmD : nyears plus m days !
325!---------------------------------------------------------------------
326  IMPLICIT NONE
327!-
328  CHARACTER(LEN=*),INTENT(IN) :: input_str
329  REAL,INTENT(IN)             :: dt,date
330!-
331  INTEGER,INTENT(OUT)         :: itau
332!-
333  INTEGER           :: y_pos,m_pos,d_pos,h_pos,s_pos
334  INTEGER           :: read_time
335  CHARACTER(LEN=13) :: fmt
336  CHARACTER(LEN=80) :: tmp_str
337!-
338  INTEGER :: year,month,day
339  REAL    :: sec,date_new,dd,ss
340!---------------------------------------------------------------------
341  itau = 0
342  CALL ju2ymds (date,year,month,day,sec)
343!-
344  y_pos = MAX(INDEX(input_str,'y'),INDEX(input_str,'Y'))
345  m_pos = MAX(INDEX(input_str,'m'),INDEX(input_str,'M'))
346  d_pos = MAX(INDEX(input_str,'d'),INDEX(input_str,'D'))
347  h_pos = MAX(INDEX(input_str,'h'),INDEX(input_str,'H'))
348  s_pos = MAX(INDEX(input_str,'s'),INDEX(input_str,'S'))
349!-
350  IF (MAX(y_pos,m_pos,d_pos,s_pos) > 0) THEN
351    tmp_str = input_str
352    DO WHILE ( MAX(y_pos,m_pos,d_pos,s_pos) > 0)
353!---- WRITE(*,*) tmp_str
354!---- WRITE(*,*) y_pos,m_pos,d_pos,s_pos
355      IF (y_pos > 0) THEN
356        WRITE(fmt,'("(I",I10.10,")")') y_pos-1
357        READ(tmp_str(1:y_pos-1),fmt) read_time
358        CALL ymds2ju (year+read_time,month,day,sec,date_new)
359        dd = date_new-date
360        ss = INT(dd)*one_day+dd-INT(dd)
361        itau = itau+NINT(ss/dt)
362        tmp_str = tmp_str(y_pos+1:LEN_TRIM(tmp_str))
363      ELSE IF (m_pos > 0) THEN
364        WRITE(fmt,'("(I",I10.10,")")') m_pos-1
365        READ(tmp_str(1:m_pos-1),fmt) read_time
366        CALL ymds2ju (year,month+read_time,day,sec,date_new)
367        dd = date_new-date
368        ss = INT(dd)*one_day+dd-INT(dd)
369        itau = itau+NINT(ss/dt)
370        tmp_str = tmp_str(m_pos+1:LEN_TRIM(tmp_str))
371      ELSE IF (d_pos > 0) THEN
372        WRITE(fmt,'("(I",I10.10,")")') d_pos-1
373        READ(tmp_str(1:d_pos-1),fmt) read_time
374        itau = itau+NINT(read_time*one_day/dt)
375        tmp_str = tmp_str(d_pos+1:LEN_TRIM(tmp_str))
376      ELSE IF (h_pos > 0) THEN
377        WRITE(fmt,'("(I",I10.10,")")') h_pos-1
378        READ(tmp_str(1:h_pos-1),fmt) read_time
379        itau = itau+NINT(read_time*60.*60./dt)
380        tmp_str = tmp_str(d_pos+1:LEN_TRIM(tmp_str))
381      ELSE IF  (s_pos > 0) THEN
382        WRITE(fmt,'("(I",I10.10,")")') s_pos-1
383        READ(tmp_str(1:s_pos-1),fmt) read_time
384        itau = itau+NINT(read_time/dt)
385        tmp_str = tmp_str(s_pos+1:LEN_TRIM(tmp_str))
386      ENDIF
387!-
388      y_pos = MAX(INDEX(tmp_str,'y'),INDEX(tmp_str,'Y'))
389      m_pos = MAX(INDEX(tmp_str,'m'),INDEX(tmp_str,'M'))
390      d_pos = MAX(INDEX(tmp_str,'d'),INDEX(tmp_str,'D'))
391      h_pos = MAX(INDEX(tmp_str,'h'),INDEX(tmp_str,'H'))
392      s_pos = MAX(INDEX(tmp_str,'s'),INDEX(tmp_str,'S'))
393    ENDDO
394  ELSE
395    WRITE(fmt,'("(I",I10.10,")")') LEN_TRIM(input_str)
396    READ(input_str(1:LEN_TRIM(input_str)),fmt) itau
397  ENDIF
398!-----------------------
399END SUBROUTINE tlen2itau
400!-
401!===
402!-
403REAL FUNCTION itau2date (itau,date0,deltat)
404!---------------------------------------------------------------------
405!- This function transforms itau into a date. The date with which
406!- the time axis is going to be labeled
407!-
408!- INPUT
409!-   itau   : current time step
410!-   date0  : Date at which itau was equal to 0
411!-   deltat : time step between itau s
412!-
413!- OUTPUT
414!-   itau2date : Date for the given itau
415!---------------------------------------------------------------------
416  IMPLICIT NONE
417!-
418  INTEGER  :: itau
419  REAL     :: date0,deltat
420!---------------------------------------------------------------------
421  itau2date = REAL(itau)*deltat/one_day+date0
422!---------------------
423END FUNCTION itau2date
424!-
425!===
426!-
427SUBROUTINE itau2ymds (itau,deltat,year,month,day,sec)
428!---------------------------------------------------------------------
429!- This subroutine transforms itau into a date. The date with which
430!- the time axis is going to be labeled
431!-
432!- INPUT
433!-   itau   : current time step
434!-   deltat : time step between itau s
435!-
436!- OUTPUT
437!-   year  : year
438!-   month : month
439!-   day   : day
440!-   sec   : seconds since midnight
441!---------------------------------------------------------------------
442  IMPLICIT NONE
443!-
444  INTEGER,INTENT(IN) :: itau
445  REAL,INTENT(IN)    :: deltat
446!-
447  INTEGER,INTENT(OUT) :: year,month,day
448  REAL,INTENT(OUT)    :: sec
449!-
450  INTEGER :: julian_day
451  REAL    :: julian_sec
452!---------------------------------------------------------------------
453  IF (.NOT.lock_startdate) THEN
454    CALL ipslerr (2,'itau2ymds', &
455 &   'You try to call this function, itau2ymds, but you didn''t', &
456 &   ' call ioconf_startdate to initialize date0 in calendar.', &
457 &   ' Please call ioconf_startdate before itau2ymds.')
458  ENDIF
459  julian_day = start_day
460  julian_sec = start_sec+REAL(itau)*deltat
461  CALL ju2ymds_internal (julian_day,julian_sec,year,month,day,sec)
462!-----------------------
463END SUBROUTINE itau2ymds
464!-
465!===
466!-
467REAL FUNCTION dtchdate (itau,date0,old_dt,new_dt)
468!---------------------------------------------------------------------
469!- This function changes the date so that the simulation can
470!- continue with the same itau but a different dt.
471!-
472!- INPUT
473!-   itau   : current time step
474!-   date0  : Date at which itau was equal to 0
475!-   old_dt : Old time step between itaus
476!-   new_dt : New time step between itaus
477!-
478!- OUTPUT
479!-   dtchdate : Date for the given itau
480!---------------------------------------------------------------------
481  IMPLICIT NONE
482!-
483  INTEGER,INTENT(IN) :: itau
484  REAL,INTENT(IN)    :: date0,old_dt,new_dt
485!-
486  REAL :: rtime
487!---------------------------------------------------------------------
488  rtime = itau2date (itau,date0,old_dt)
489  dtchdate = rtime-REAL(itau)*new_dt/one_day
490!--------------------
491END FUNCTION dtchdate
492!-
493!===
494!-
495SUBROUTINE isittime &
496 &  (itau,date0,dt,freq,last_action,last_check,do_action)
497!---------------------------------------------------------------------
498!- This subroutine checks the time as come for a given action.
499!- This is computed from the current time-step(itau).
500!- Thus we need to have the time delta (dt), the frequency
501!- of the action (freq) and the last time it was done
502!- (last_action in units of itau).
503!- In order to extrapolate when will be the next check we need
504!- the time step of the last call (last_check).
505!-
506!- The test is done on the following condition :
507!- the distance from the current time to the time for the next
508!- action is smaller than the one from the next expected
509!- check to the next action.
510!- When the test is done on the time steps simplifactions make
511!- it more difficult to read in the code.
512!- For the real time case it is easier to understand !
513!---------------------------------------------------------------------
514  IMPLICIT NONE
515!-
516  INTEGER,INTENT(IN) :: itau
517  REAL,INTENT(IN)    :: dt,freq
518  INTEGER,INTENT(IN) :: last_action,last_check
519  REAL,INTENT(IN)    :: date0
520!-
521  LOGICAL,INTENT(OUT)  :: do_action
522!-
523  REAL :: dt_action,dt_check
524  REAL :: date_last_act,date_next_check,date_next_act, &
525 &        date_now,date_mp1,date_mpf
526  INTEGER :: year,month,monthp1,day,next_check_itau,next_act_itau
527  INTEGER :: yearp,dayp
528  REAL :: sec,secp
529  LOGICAL :: check = .FALSE.
530!---------------------------------------------------------------------
531  IF (check) THEN
532    WRITE(*,*) &
533 &    "isittime 1.0 ",itau,date0,dt,freq,last_action,last_check
534  ENDIF
535!-
536  IF (last_check >= 0) THEN
537    dt_action = (itau-last_action)*dt
538    dt_check = (itau-last_check)*dt
539    next_check_itau = itau+(itau-last_check)
540!-
541!-- We are dealing with frequencies in seconds and thus operation
542!-- can be done on the time steps.
543!-
544    IF (freq > 0) THEN
545      IF (ABS(dt_action-freq) <= ABS(dt_action+dt_check-freq)) THEN
546        do_action = .TRUE.
547      ELSE
548        do_action = .FALSE.
549      ENDIF
550!-
551!---- Here we deal with frequencies in month and work on julian days.
552!-
553    ELSE
554      date_now = itau2date (itau,date0,dt)
555      date_last_act = itau2date (last_action,date0,dt)
556      CALL ju2ymds (date_last_act,year,month,day,sec)
557      monthp1 = month-freq
558      yearp = year
559!-
560!---- Here we compute what logically should be the next month
561!-
562      IF (month >= 13) THEN
563        yearp = year+1
564        monthp1 = monthp1-12
565      ENDIF
566      CALL ymds2ju (year,monthp1,day,sec,date_mpf)
567!-
568!---- But it could be that because of a shorter month or a bad
569!---- starting date that we end up further than we should be.
570!---- Thus we compute the first day of the next month.
571!---- We can not be beyond this date and if we are close
572!---- then we will take it as it is better.
573!-
574      monthp1 = month+ABS(freq)
575      yearp=year
576      IF (monthp1 >= 13) THEN
577        yearp = year+1
578        monthp1 = monthp1 -12
579      ENDIF
580      dayp = 1
581      secp = 0.0
582      CALL ymds2ju (yearp,monthp1,dayp,secp,date_mp1)
583!-
584!---- If date_mp1 is smaller than date_mpf or only less than 4 days
585!---- larger then we take it. This needed to ensure that short month
586!---- like February do not mess up the thing !
587!-
588      IF (date_mp1-date_mpf < 4.) THEN
589        date_next_act = date_mp1
590      ELSE
591        date_next_act = date_mpf
592      ENDIF
593      date_next_check = itau2date (next_check_itau,date0,dt)
594!-
595!---- Transform the dates into time-steps for the needed precisions.
596!-
597      next_act_itau = &
598 &      last_action+INT((date_next_act-date_last_act)*(one_day/dt))
599!-----
600      IF (   ABS(itau-next_act_itau) &
601 &        <= ABS( next_check_itau-next_act_itau)) THEN
602        do_action = .TRUE.
603        IF (check) THEN
604          WRITE(*,*) &
605 &         'ACT-TIME : itau, next_act_itau, next_check_itau : ', &
606 &         itau,next_act_itau,next_check_itau
607          CALL ju2ymds (date_now,year,month,day,sec)
608          WRITE(*,*) 'ACT-TIME : y, m, d, s : ',year,month,day,sec
609          WRITE(*,*) &
610 &         'ACT-TIME : date_mp1, date_mpf : ',date_mp1,date_mpf
611        ENDIF
612      ELSE
613        do_action = .FALSE.
614      ENDIF
615    ENDIF
616!-
617    IF (check) THEN
618      WRITE(*,*) "isittime 2.0 ", &
619 &     date_next_check,date_next_act,ABS(dt_action-freq), &
620 &     ABS(dt_action+dt_check-freq),dt_action,dt_check, &
621 &     next_check_itau,do_action
622    ENDIF
623  ELSE
624    do_action=.FALSE.
625  ENDIF
626!----------------------
627END SUBROUTINE isittime
628!-
629!===
630!-
631SUBROUTINE ioconf_calendar (str)
632!---------------------------------------------------------------------
633!- This routine allows to configure the calendar to be used.
634!- This operation is only allowed once and the first call to
635!- ymds2ju or ju2ymsd will lock the current configuration.
636!- the argument to ioconf_calendar can be any of the following :
637!-  - gregorian : This is the gregorian calendar (default here)
638!-  - noleap    : A calendar without leap years = 365 days
639!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
640!-                with 12 month of equal length
641!---------------------------------------------------------------------
642  IMPLICIT NONE
643!-
644  CHARACTER(LEN=*),INTENT(IN) :: str
645!-
646  INTEGER :: leng,ipos
647  CHARACTER(LEN=20) :: str_w
648!---------------------------------------------------------------------
649!-
650! Clean up the sring !
651!-
652  str_w = str
653  CALL strlowercase (str_w)
654!-
655  IF (.NOT.lock_one_year) THEN
656!---
657    lock_one_year=.TRUE.
658!---
659    SELECT CASE(TRIM(str_w))
660    CASE('gregorian','standard','proleptic_gregorian')
661      calendar_used = 'gregorian'
662      one_year = 365.2425
663      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
664    CASE('noleap','365_day','365d')
665      calendar_used = 'noleap'
666      one_year = 365.0
667      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
668    CASE('all_leap','366_day','366d')
669      calendar_used = 'all_leap'
670      one_year = 366.0
671      mon_len(:)=(/31,29,31,30,31,30,31,31,30,31,30,31/)
672    CASE('360_day','360d')
673      calendar_used = '360d'
674      one_year = 360.0
675      mon_len(:)=(/30,30,30,30,30,30,30,30,30,30,30,30/)
676    CASE('julian')
677      calendar_used = 'julian'
678      one_year = 365.25
679      mon_len(:)=(/31,28,31,30,31,30,31,31,30,31,30,31/)
680    CASE DEFAULT
681      ipos = INDEX(str_w,'d')
682      IF (ipos == 4) THEN
683        READ(str_w(1:3),'(I3)') leng
684        IF ( (MOD(leng,12) == 0).AND.(leng > 1) ) THEN
685          calendar_used = str_w
686          one_year = leng
687          mon_len(:) = leng/12
688        ELSE
689          CALL ipslerr (3,'ioconf_calendar', &
690 &         'The length of the year as to be a modulo of 12', &
691 &         'so that it can be divided into 12 month of equal length', &
692 &         TRIM(str_w))
693        ENDIF
694      ELSE
695        CALL ipslerr (3,'ioconf_calendar', &
696 &       'Unrecognized input, please check the man pages.', &
697 &       TRIM(str_w),' ')
698      ENDIF
699    END SELECT
700  ELSE
701    WRITE(str_w,'(f10.4)') one_year
702    CALL ipslerr (2,'ioconf_calendar', &
703 &   'The calendar was already used or configured. You are not', &
704 &   'allowed to change it again. '// &
705 &   'The following length of year is used : ',TRIM(ADJUSTL(str_w)))
706  ENDIF
707!-----------------------------
708END SUBROUTINE ioconf_calendar
709!-
710!===
711!-
712SUBROUTINE ioconf_startdate_simple (julian)
713!---------------------------------------------------------------------
714  IMPLICIT NONE
715!-
716  REAL,INTENT(IN) :: julian
717!-
718  INTEGER :: julian_day
719  REAL    :: julian_sec
720!---------------------------------------------------------------------
721  julian_day = INT(julian)
722  julian_sec = (julian-julian_day)*one_day
723!-
724  CALL ioconf_startdate_internal (julian_day,julian_sec)
725!-------------------------------------
726END SUBROUTINE ioconf_startdate_simple
727!-
728!===
729!-
730SUBROUTINE ioconf_startdate_ymds (year,month,day,sec)
731!---------------------------------------------------------------------
732  IMPLICIT NONE
733!-
734  INTEGER,INTENT(IN) :: year,month,day
735  REAL,INTENT(IN)    :: sec
736!-
737  INTEGER :: julian_day
738  REAL    :: julian_sec
739!---------------------------------------------------------------------
740  CALL ymds2ju_internal (year,month,day,sec,julian_day,julian_sec)
741!-
742  CALL ioconf_startdate_internal (julian_day,julian_sec)
743!-----------------------------------
744END SUBROUTINE ioconf_startdate_ymds
745!-
746!===
747!-
748SUBROUTINE ioconf_startdate_internal (julian_day,julian_sec)
749!---------------------------------------------------------------------
750! This subroutine allows to set the startdate for later
751! use. It allows the applications to access the date directly from
752! the timestep. In order to avoid any problems the start date will
753! be locked and can not be changed once set.
754!---------------------------------------------------------------------
755  IMPLICIT NONE
756!-
757  INTEGER,INTENT(IN)  :: julian_day
758  REAL,INTENT(IN)     :: julian_sec
759!-
760  CHARACTER(len=70) :: str70a,str70b
761!---------------------------------------------------------------------
762  IF (.NOT.lock_startdate) THEN
763    start_day = julian_day
764    start_sec = julian_sec
765    lock_startdate = .TRUE.
766  ELSE
767    WRITE(str70a,'("The date you tried to set : ",f10.4)') &
768 &   julian_day,julian_sec/one_day
769    WRITE(str70b, &
770 &   '("The date which was already set in the calendar : ",f10.4)') &
771 &   start_day+start_sec/one_day
772    CALL ipslerr (2,'ioconf_startdate', &
773 &   'The start date has already been set and you tried to change it', &
774 &   str70a,str70b)
775  ENDIF
776!---------------------------------------
777END SUBROUTINE ioconf_startdate_internal
778!-
779!===
780!-
781SUBROUTINE ioget_calendar_str (str)
782!---------------------------------------------------------------------
783!- This subroutine returns the name of the calendar used here.
784!- Three options exist :
785!-  - gregorian : This is the gregorian calendar (default here)
786!-  - noleap    : A calendar without leap years = 365 days
787!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
788!-                with 12 month of equal length
789!-
790!- This routine will lock the calendar.
791!- You do not want it to change after your inquiry.
792!---------------------------------------------------------------------
793  IMPLICIT NONE
794!-
795  CHARACTER(LEN=*),INTENT(OUT) :: str
796!---------------------------------------------------------------------
797  lock_one_year = .TRUE.
798!-
799  str = calendar_used
800!--------------------------------
801END SUBROUTINE ioget_calendar_str
802!-
803!===
804!-
805SUBROUTINE ioget_calendar_real1 (long_year)
806!---------------------------------------------------------------------
807!- This subroutine returns the name of the calendar used here.
808!- Three options exist :
809!-  - gregorian : This is the gregorian calendar (default here)
810!-  - noleap    : A calendar without leap years = 365 days
811!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
812!-                with 12 month of equal length
813!-
814!- This routine will lock the calendar.
815!- You do not want it to change after your inquiry.
816!---------------------------------------------------------------------
817  IMPLICIT NONE
818!-
819  REAL,INTENT(OUT) :: long_year
820!---------------------------------------------------------------------
821  long_year = one_year
822  lock_one_year = .TRUE.
823!----------------------------------
824END SUBROUTINE ioget_calendar_real1
825!-
826!===
827!-
828SUBROUTINE ioget_calendar_real2 (long_year,long_day)
829!---------------------------------------------------------------------
830!- This subroutine returns the name of the calendar used here.
831!- Three options exist :
832!-  - gregorian : This is the gregorian calendar (default here)
833!-  - noleap    : A calendar without leap years = 365 days
834!-  - xxxd      : A calendar of xxx days (has to be a modulo of 12)
835!-                with 12 month of equal length
836!-
837!- This routine will lock the calendar.
838!- You do not want it to change after your inquiry.
839!---------------------------------------------------------------------
840  IMPLICIT NONE
841!-
842  REAL,INTENT(OUT) :: long_year,long_day
843!---------------------------------------------------------------------
844  long_year = one_year
845  long_day  = one_day
846  lock_one_year = .TRUE.
847!----------------------------------
848END SUBROUTINE ioget_calendar_real2
849!-
850!===
851!-
852INTEGER FUNCTION ioget_mon_len (year,month)
853!!--------------------------------------------------------------------
854!! The "ioget_mon_len" function returns
855!! the number of days in a "month" of a "year",
856!! in the current calendar.
857!!
858!! INTEGER FUNCTION ioget_mon_len (year,month)
859!!
860!! INPUT
861!!
862!! (I) year  : year
863!! (I) month : month in the year (1 --> 12)
864!!
865!! OUTPUT
866!!
867!! (I) ioget_mon_len : number of days in the month
868!!--------------------------------------------------------------------
869  IMPLICIT NONE
870!-
871  INTEGER,INTENT(IN) :: year,month
872!-
873  INTEGER :: ml
874!---------------------------------------------------------------------
875  IF ( (month >= 1).AND.(month <= 12) ) THEN
876    IF ( (one_year > 365.0).AND.(one_year < 366.0) ) THEN
877!---- "Gregorian" or "Julian"
878      ml = mon_len(month)
879      IF (month == 2) THEN
880        IF (ABS(one_year-365.2425) <= EPSILON(one_year) ) THEN
881!-------- "Gregorian"
882          IF (    ((MOD(year,4) == 0).AND.(MOD(year,100) /= 0)) &
883              .OR.(MOD(year,400) == 0) ) THEN
884            ml = ml+1
885          ENDIF
886        ELSE
887!-------- "Julian"
888          IF (MOD(year,4) == 0) THEN
889            ml = ml+1
890          ENDIF
891        ENDIF
892      ENDIF
893      ioget_mon_len = ml
894    ELSE
895!---- "No leap" or "All leap" or "Calendar with regular month"
896      ioget_mon_len = mon_len(month)
897    ENDIF
898  ELSE
899    CALL ipslerr (3,'ioget_mon_len', &
900 &    'The number of the month','must be between','1 and 12')
901  ENDIF
902!-------------------------
903END FUNCTION ioget_mon_len
904!-
905!===
906!-
907SUBROUTINE ioget_timestamp (string)
908!---------------------------------------------------------------------
909  IMPLICIT NONE
910!-
911  CHARACTER(LEN=30),INTENT(OUT) :: string
912!-
913  INTEGER :: date_time(8)
914  CHARACTER(LEN=10) :: bigben(3)
915!---------------------------------------------------------------------
916  IF (INDEX(time_stamp,'XXXXXX') > 0) THEN
917    CALL DATE_AND_TIME (bigben(1),bigben(2),bigben(3),date_time)
918!---
919    WRITE(time_stamp, &
920 &   "(I4.4,'-',A3,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2,' GMT',a5)") &
921 &   date_time(1),cal(date_time(2)),date_time(3),date_time(5), &
922 &   date_time(6),date_time(7),bigben(3)
923  ENDIF
924!-
925  string = time_stamp
926!-----------------------------
927END SUBROUTINE ioget_timestamp
928!-
929!===
930!-
931SUBROUTINE time_add &
932 &  (year_s,month_s,day_s,sec_s,sec_increment, &
933 &   year_e,month_e,day_e,sec_e)
934!---------------------------------------------------------------------
935!- This subroutine allows to increment a date by a number of seconds.
936!---------------------------------------------------------------------
937  IMPLICIT NONE
938!-
939  INTEGER,INTENT(IN) :: year_s,month_s,day_s
940  REAL,INTENT(IN)    :: sec_s
941!-
942! Time in seconds to be added to the date
943!-
944  REAL,INTENT(IN)    :: sec_increment
945!-
946  INTEGER,INTENT(OUT) :: year_e,month_e,day_e
947  REAL,INTENT(OUT)    :: sec_e
948!-
949  INTEGER :: julian_day
950  REAL    :: julian_sec
951!---------------------------------------------------------------------
952  CALL ymds2ju_internal &
953 &  (year_s,month_s,day_s,sec_s,julian_day,julian_sec)
954!-
955  julian_sec = julian_sec+sec_increment
956!-
957  CALL ju2ymds_internal &
958 &  (julian_day,julian_sec,year_e,month_e,day_e,sec_e)
959!----------------------
960END SUBROUTINE time_add
961!-
962!===
963!-
964SUBROUTINE time_diff &
965 &  (year_s,month_s,day_s,sec_s,year_e,month_e,day_e,sec_e,sec_diff)
966!---------------------------------------------------------------------
967!- This subroutine allows to determine the number of seconds
968!- between two dates.
969!---------------------------------------------------------------------
970  IMPLICIT NONE
971!-
972  INTEGER,INTENT(IN) :: year_s,month_s,day_s
973  REAL,INTENT(IN)    :: sec_s
974  INTEGER,INTENT(IN) :: year_e,month_e,day_e
975  REAL,INTENT(IN)    :: sec_e
976!-
977! Time in seconds between the two dates
978!-
979  REAL,INTENT(OUT)    :: sec_diff
980!-
981  INTEGER :: julian_day_s,julian_day_e,day_diff
982  REAL    :: julian_sec_s,julian_sec_e
983!---------------------------------------------------------------------
984  CALL ymds2ju_internal &
985 &  (year_s,month_s,day_s,sec_s,julian_day_s,julian_sec_s)
986  CALL ymds2ju_internal &
987 &  (year_e,month_e,day_e,sec_e,julian_day_e,julian_sec_e)
988!-
989  day_diff = julian_day_e-julian_day_s
990  sec_diff = julian_sec_e-julian_sec_s
991!-
992  sec_diff = sec_diff+day_diff*one_day
993!-----------------------
994END SUBROUTINE time_diff
995!-
996!===
997!-
998END MODULE calendar
Note: See TracBrowser for help on using the repository browser.