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

Contents of /trunk/IOIPSL/Calendar/isittime.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 335 - (show annotations)
Thu Sep 12 21:22:46 2019 UTC (4 years, 8 months ago) by guez
File size: 5031 byte(s)
Julian dates be in double precision

`ConfigureCompilerFlags.cmake` and `TAGS.cmake` are now copied into
LMDZE, to avoid dependency on the environment.

Julian dates must be in double precision, to get time step precision.

Add optional attribute to argument sec of procedure ju2ymds. We do
not need sec in procedure dynredem0.

In procedure ju2ymds, by construction, sec cannot be > `un_jour`.

Remove useless intermediary variables in procedure ymds2ju.

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

  ViewVC Help
Powered by ViewVC 1.1.21