/[lmdze]/trunk/IOIPSL/Calendar/isittime.f
ViewVC logotype

Annotation of /trunk/IOIPSL/Calendar/isittime.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 92 - (hide annotations)
Wed Mar 26 18:16:05 2014 UTC (10 years, 3 months ago) by guez
File size: 4994 byte(s)
Extracted procedures that were in module calendar into separate files.

1 guez 92 module isittime_m
2    
3     implicit none
4    
5     contains
6    
7     SUBROUTINE isittime &
8     & (itau, date0, dt, freq, last_action, last_check, do_action)
9    
10     ! This subroutine checks the time has come for a given action.
11     ! This is computed from the current time-step(itau).
12     ! Thus we need to have the time delta (dt), the frequency
13     ! of the action (freq) and the last time it was done
14     ! (last_action in units of itau).
15     ! In order to extrapolate when will be the next check we need
16     ! the time step of the last call (last_check).
17    
18     ! The test is done on the following condition:
19     ! the distance from the current time to the time for the next
20     ! action is smaller than the one from the next expected
21     ! check to the next action.
22     ! When the test is done on the time steps simplifactions make
23     ! it more difficult to read in the code.
24     ! For the real time case it is easier to understand !
25    
26     use calendar
27     use itau2date_m
28     use ju2ymds_m
29     use ymds2ju_m
30    
31     INTEGER, INTENT(IN):: itau
32     REAL, INTENT(IN):: dt, freq
33     INTEGER, INTENT(IN):: last_action, last_check
34     REAL, INTENT(IN):: date0
35    
36     LOGICAL, INTENT(OUT):: do_action
37    
38     REAL:: dt_action, dt_check
39     REAL:: date_last_act, date_next_check, date_next_act, &
40     & date_now, date_mp1, date_mpf
41     INTEGER:: year, month, monthp1, day, next_check_itau, next_act_itau
42     INTEGER:: yearp, dayp
43     REAL:: sec, secp
44     LOGICAL:: check = .FALSE.
45     !--------------------------------------------------------------------
46     IF (check) THEN
47     WRITE(*, *) &
48     & "isittime 1.0 ", itau, date0, dt, freq, last_action, last_check
49     ENDIF
50    
51     IF (last_check >= 0) THEN
52     dt_action = (itau-last_action)*dt
53     dt_check = (itau-last_check)*dt
54     next_check_itau = itau+(itau-last_check)
55    
56     !- We are dealing with frequencies in seconds and thus operation
57     !- can be done on the time steps.
58    
59     IF (freq > 0) THEN
60     IF (ABS(dt_action-freq) <= ABS(dt_action+dt_check-freq)) THEN
61     do_action = .TRUE.
62     ELSE
63     do_action = .FALSE.
64     ENDIF
65    
66     !--- Here we deal with frequencies in month and work on julian days.
67    
68     ELSE
69     date_now = itau2date (itau, date0, dt)
70     date_last_act = itau2date (last_action, date0, dt)
71     CALL ju2ymds (date_last_act, year, month, day, sec)
72     monthp1 = month - freq
73     yearp = year
74    
75     !--- Here we compute what logically should be the next month
76    
77     IF (month >= 13) THEN
78     yearp = year+1
79     monthp1 = monthp1-12
80     ENDIF
81     CALL ymds2ju (year, monthp1, day, sec, date_mpf)
82    
83     !--- But it could be that because of a shorter month or a bad
84     !--- starting date that we end up further than we should be.
85     !--- Thus we compute the first day of the next month.
86     !--- We can not be beyond this date and if we are close
87     !--- then we will take it as it is better.
88    
89     monthp1 = month+ABS(freq)
90     yearp=year
91     IF (monthp1 >= 13) THEN
92     yearp = year+1
93     monthp1 = monthp1 -12
94     ENDIF
95     dayp = 1
96     secp = 0.0
97     CALL ymds2ju (yearp, monthp1, dayp, secp, date_mp1)
98    
99     !--- If date_mp1 is smaller than date_mpf or only less than 4 days
100     !--- larger then we take it. This needed to ensure that short month
101     !--- like February do not mess up the thing !
102    
103     IF (date_mp1-date_mpf < 4.) THEN
104     date_next_act = date_mp1
105     ELSE
106     date_next_act = date_mpf
107     ENDIF
108     date_next_check = itau2date (next_check_itau, date0, dt)
109    
110     !--- Transform the dates into time-steps for the needed precisions.
111    
112     next_act_itau = &
113     & last_action+INT((date_next_act-date_last_act)*(un_jour/dt))
114    
115     IF ( ABS(itau-next_act_itau) &
116     & <= ABS( next_check_itau-next_act_itau)) THEN
117     do_action = .TRUE.
118     IF (check) THEN
119     WRITE(*, *) &
120     & 'ACT-TIME: itau, next_act_itau, next_check_itau: ', &
121     & itau, next_act_itau, next_check_itau
122     CALL ju2ymds (date_now, year, month, day, sec)
123     WRITE(*, *) 'ACT-TIME: y, m, d, s: ', year, month, day, sec
124     WRITE(*, *) &
125     & 'ACT-TIME: date_mp1, date_mpf: ', date_mp1, date_mpf
126     ENDIF
127     ELSE
128     do_action = .FALSE.
129     ENDIF
130     ENDIF
131    
132     IF (check) THEN
133     WRITE(*, *) "isittime 2.0 ", &
134     & date_next_check, date_next_act, ABS(dt_action-freq), &
135     & ABS(dt_action+dt_check-freq), dt_action, dt_check, &
136     & next_check_itau, do_action
137     ENDIF
138     ELSE
139     do_action=.FALSE.
140     ENDIF
141    
142     END SUBROUTINE isittime
143    
144     end module isittime_m

  ViewVC Help
Powered by ViewVC 1.1.21