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

Last change on this file since 30 was 11, checked in by bellier, 17 years ago

JB: on the road to svn

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