New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
calendar.f90 in utils/tools/DOMAINcfg/src – NEMO

source: utils/tools/DOMAINcfg/src/calendar.f90

Last change on this file was 14623, checked in by ldebreu, 3 years ago

AGFdomcfg: 1) Update DOMAINcfg to be compliant with the removal of halo cells 2) Update most of the LBC ... subroutines to a recent NEMO 4 version #2638

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