source: palm/trunk/SOURCE/date_and_time_mod.f90 @ 4186

Last change on this file since 4186 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 20.5 KB
Line 
1!> @file date_and_time_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: date_and_time_mod.f90 4182 2019-08-22 15:20:23Z suehring $
27! Corrected "Former revisions" section
28!
29! 4144 2019-08-06 09:11:47Z raasch
30! relational operators .EQ., .NE., etc. replaced by ==, /=, etc.
31!
32! 3839 2019-03-28 21:12:25Z moh.hefny
33! further tabs removed, unused variables removed
34!
35! 3655 2019-01-07 16:51:22Z knoop
36! further tabs removed
37!
38! 2544 2017-10-13 18:09:32Z maronga
39! Initial revision
40!
41!
42! Description:
43! ------------
44!> This routine calculates all needed information on date and time used by
45!> other modules
46!> @todo Further testing and revision of routines for updating indices of
47!>       emissions in the default mode
48!> @todo Add routine for recognizing leap years
49!> @todo Add recognition of exact days of week (Monday, Tuesday, etc.)
50!> @todo Reconsider whether to remove day_of_year_init from the namelist: we
51!>       already implemented changes for calculating it from date_init in
52!>       calc_date_and_time
53!> @todo time_utc during spin-up 
54!------------------------------------------------------------------------------!
55 MODULE date_and_time_mod
56
57    USE control_parameters,                                                   &
58        ONLY:  coupling_start_time, days_since_reference_point,               &
59               message_string, simulated_time, time_since_reference_point
60
61    USE kinds
62
63
64    IMPLICIT NONE
65
66    PRIVATE
67
68!-- Variables Declaration
69
70    INTEGER(iwp)        ::  day_of_year      = 0   !< day of the year (DOY)
71    INTEGER(iwp)        ::  day_of_year_init = 0   !< DOY at model start (default: 0)
72
73    ! --- Most of these indices are updated by the routine calc_date_and_time according to the current date and time of the simulation
74    INTEGER(iwp)        ::  hour_of_year = 1                        !< hour of the current year (1:8760(8784))
75    INTEGER(iwp)        ::  hour_of_day=1                           !< hour of the current day (1:24)
76    INTEGER(iwp)        ::  day_of_month=0                          !< day of the current month (1:31)
77    INTEGER(iwp)        ::  month_of_year=0                         !< month of the current year (1:12)
78    INTEGER(iwp)        ::  current_year=0                          !< current year
79    INTEGER(iwp)        ::  hour_call_emis=0                        !< index used to call the emissions just once every hour
80
81    INTEGER(iwp)        ::  index_mm                                !< index months of the default emission mode
82    INTEGER(iwp)        ::  index_dd                                !< index days of the default emission mode
83    INTEGER(iwp)        ::  index_hh                                !< index hours of the emission mode
84
85    REAL(wp)            ::  time_utc                     !< current model time in UTC
86    REAL(wp)            ::  time_utc_emis                !< current emission module time in UTC
87    REAL(wp)            ::  time_utc_init = 43200.0_wp   !< UTC time at model start
88    REAL(wp)            ::  time_update                  !< used to calculate actual second of the simulation
89 
90    REAL(wp), PARAMETER ::  d_hours_day    = 1.0_wp / 24.0_wp       !< inverse of hours per day (1/24)
91    REAL(wp), PARAMETER ::  d_seconds_hour = 1.0_wp / 3600.0_wp     !< inverse of seconds per hour (1/3600)
92    REAL(wp), PARAMETER ::  d_seconds_year = 1.0_wp / 31536000.0_wp !< inverse of the seconds per year (1/(365*86400))
93   
94    CHARACTER(len=8)    ::  date_init = "21062017"                  !< Starting date of simulation: We selected this because it was a monday
95 
96    !> --- Parameters
97    INTEGER, PARAMETER, DIMENSION(12) :: days = (/31,28,31,30,31,30,31,31,30,31,30,31/) ! total number of days for each month (no leap year)
98
99    SAVE
100
101!-- INTERFACES PART
102    !-- Read initial day and time of simulation
103    INTERFACE init_date_and_time
104       MODULE PROCEDURE init_date_and_time
105    END INTERFACE init_date_and_time
106
107    !-- Get hour index in the DEAFULT case of chemistry emissions :
108    INTERFACE time_default_indices
109       MODULE PROCEDURE time_mdh_indices
110       MODULE PROCEDURE time_hour_indices
111    END INTERFACE time_default_indices
112
113    !-- Get hour index in the PRE-PROCESSED case of chemistry emissions :
114    INTERFACE time_preprocessed_indices
115       MODULE PROCEDURE time_preprocessed_indices
116    END INTERFACE time_preprocessed_indices
117
118
119    !-- Calculate current date and time
120    INTERFACE calc_date_and_time
121       MODULE PROCEDURE calc_date_and_time
122    END INTERFACE
123
124
125    !-- Public Interfaces
126    PUBLIC calc_date_and_time, time_default_indices, init_date_and_time, time_preprocessed_indices
127
128    !-- Public Variables
129    PUBLIC date_init, d_hours_day, d_seconds_hour, d_seconds_year,               &
130           day_of_year, day_of_year_init, time_utc, time_utc_init, day_of_month, &
131           month_of_year, index_mm, index_dd, index_hh, hour_of_day, hour_of_year, &
132           hour_call_emis
133
134 CONTAINS
135
136
137 !------------------------------------------------------------------------------!
138 !> Reads starting date from namelist
139 !------------------------------------------------------------------------------!
140 
141    SUBROUTINE init_date_and_time
142
143       IMPLICIT NONE
144
145       !--    Variables Definition
146       INTEGER ::  i_mon       !< Index for going through the different months
147
148       IF  (day_of_year_init == 0) THEN
149          ! Day of the month at starting time
150          READ(UNIT=date_init(1:2),fmt=*)day_of_month
151
152          ! Month of the year at starting time
153          READ(UNIT=date_init(3:4),fmt=*)month_of_year
154
155          ! Year at starting time
156          READ(UNIT=date_init(5:8),fmt=*)current_year
157       
158       ENDIF
159
160
161       !-- Calculate initial hour of the day: the first hour of the day is from 00:00:00 to 00:59:59.
162
163       hour_of_day = INT( FLOOR( time_utc_init/3600.0_wp ) ) + 1
164
165       !-- Calculate initial day day_of_year_init in case date_init is given or day_of_year_init is given
166       IF ( day_of_year_init == 0 ) THEN
167
168          !> Condition for printing an error when date_init is not provided when day_of_year_init is not given in the namelist or when the format of the date is not the one required by PALM.
169          IF ( day_of_month > 0 .AND. day_of_month <= 31 .AND. month_of_year > 0 .AND. month_of_year <= 12) THEN
170       
171             IF ( month_of_year == 1 ) THEN  !!month of year is read in input
172
173                day_of_year_init = day_of_month
174
175             ELSE
176
177                day_of_year_init= SUM(days( 1:(month_of_year-1) )) + day_of_month  !day_of_month is read in input in this case
178
179             ENDIF
180!kanani: Revise, we cannot force users to provide date_init, maybe set a default value?
181!           ELSE
182!
183!              message_string = 'date_init not provided in the namelist or'             //          &
184!                               ' given in the wrong format: MUST BE DDMMYYYY'                       
185!              CALL message( 'calc_date_and_time', 'DT0100', 2, 2, 0, 6, 0 )
186     
187          ENDIF
188
189       ENDIF
190
191       
192       !-- Initial day of the year
193       day_of_year = day_of_year_init
194
195       !-- Initial hour of the year
196       hour_of_year = ( (day_of_year-1) * 24 ) + hour_of_day
197
198       !--Initial day of the month and month of the year
199       !> --------------------------------------------------------------------------------
200       !> The first case is when date_init is not provided: we only know day_of_year_init     
201       IF ( month_of_year == 0 .AND. day_of_month == 0) THEN
202
203         
204          IF ( day_of_year <= 31 ) THEN
205
206             month_of_year=1
207             day_of_month=day_of_year
208
209          ELSE
210
211             DO i_mon=2,12   !january is considered in the first case
212                IF ( day_of_year <= SUM(days(1:i_mon)) .AND. day_of_year > SUM(days(1:(i_mon-1))) ) THEN
213           
214                   month_of_year=i_mon
215
216                   day_of_month=INT(MOD(day_of_year, SUM(days(1:(i_mon-1))))) 
217
218                   GOTO 38
219
220                ENDIF
221
222             38 ENDDO
223          ENDIF
224       !> --------------------------------------------------------------------------------
225       !> in the second condition both day of month and month_of_year are either given in input (passed to date_init) or we are in some day successive to the initial one, so that day_of_month has already be computed in previous step
226       !>TBD: something to calculate the current year is missing
227       ELSEIF ( day_of_month > 0 .AND. day_of_month <= 31 .AND. month_of_year > 0 .AND. month_of_year <= 12) THEN
228 
229          !> calculate month_of_year. TBD: test the condition when day_of_year==31
230 
231          IF (day_of_year==1) THEN  !> this allows to turn from december to January when passing from a year to another
232 
233             month_of_year = 1
234       
235          ELSE IF (day_of_year > 1 .AND. day_of_year > SUM(days(1:month_of_year))) THEN
236
237             month_of_year = month_of_year + 1
238
239          ENDIF
240
241          !> calculate day_of_month
242          IF ( month_of_year == 1 ) THEN
243           
244            day_of_month=day_of_year
245
246          ELSE
247
248            day_of_month=INT(MOD(day_of_year, SUM(days(1:(month_of_year-1)))))
249
250          ENDIF
251
252
253       ELSE
254
255          !> Condition when date_init is provided but it is given in the wrong format
256          message_string = 'date_init not provided in the namelist or'            //          &
257                              ' given in the wrong format: MUST BE DDMMYYYY'                 
258          CALL message( 'init_date_and_time', 'DT0102', 2, 2, 0, 6, 0 ) 
259
260       ENDIF
261
262
263    END SUBROUTINE init_date_and_time
264
265!------------------------------------------------------------------------------!
266! Description:
267! ------------
268!> Calculate current date and time of the simulation
269!------------------------------------------------------------------------------!
270 
271    SUBROUTINE calc_date_and_time
272
273       IMPLICIT NONE
274
275!--    Variables Definition
276       INTEGER :: i_mon       !< Index for going through the different months
277
278       !> Update simulation time in seconds
279       time_update = simulated_time-coupling_start_time
280
281!--    Calculate current day of the simulated time
282       days_since_reference_point=INT(FLOOR( (time_utc_init + time_update) &
283                               / 86400.0_wp ) )
284
285!--    Calculate actual UTC time                       
286       time_utc = MOD((time_utc_init + time_since_reference_point), 86400.0_wp)
287       
288!sB    PRILIMINARY workaround for time_utc changes due to changes in time_since_reference_point in
289!sB    radiation_model_mod during runtime:
290       time_utc_emis = MOD((time_utc_init + time_update), 86400.0_wp)     
291
292!--    Calculate initial day of the year: it is calculated only once. In fact, day_of_year_init is initialized to 0 and then a positive value is passed. This condition is also called only when day_of_year_init is not given in the namelist.
293
294       IF ( day_of_year_init == 0 ) THEN
295
296          !> Condition for printing an error when date_init is not provided when day_of_year_init is not given in the namelist or when the format of the date is not the one required by PALM.
297          IF ( day_of_month > 0 .AND. day_of_month <= 31 .AND. month_of_year > 0 .AND. month_of_year <= 12) THEN
298       
299             IF ( month_of_year == 1 ) THEN  !!month of year is read in input
300
301                day_of_year_init = day_of_month
302
303             ELSE
304
305                day_of_year_init= SUM(days( 1:(month_of_year-1) )) + day_of_month  !day_of_month is read in input in this case
306
307             ENDIF
308!kanani: Revise, we cannot force users to provide date_init, maybe set a default value?
309!           ELSE
310!
311!              message_string = 'date_init not provided in the namelist or'             //          &
312!                               ' given in the wrong format: MUST BE DDMMYYYY'                       
313!              CALL message( 'calc_date_and_time', 'DT0100', 2, 2, 0, 6, 0 )
314     
315          ENDIF
316
317       ENDIF
318
319      !-- Calculate actual hour of the day: the first hour of the day is from 00:00:00 to 00:59:59.
320
321      hour_of_day = INT( FLOOR( time_utc_emis/3600.0_wp ) ) + 1
322
323!--    Calculate current day of the year !TBD: considetr leap years
324       IF ( (day_of_year_init + days_since_reference_point)  > 365 ) THEN
325
326          day_of_year=INT(MOD((day_of_year_init + days_since_reference_point), 365.0_wp))
327
328       ELSE
329         
330          day_of_year = day_of_year_init + days_since_reference_point
331
332       ENDIF
333
334!
335!--    Calculate current hour of the year
336       hour_of_year = ( (day_of_year-1) * 24 ) + hour_of_day  !> actual hour of the year
337       
338
339!
340!--    UPDATE actual day of the month and month of the year
341       !> --------------------------------------------------------------------------------
342       !> The first case is when date_init is not provided: we only know day_of_year_init     
343       IF ( month_of_year == 0 .AND. day_of_month == 0) THEN
344
345          !> The first case is when date_init is not provided: we only know day_of_year_init
346          !DO i_mon=1,12
347             !IF (day_of_year <= SUM(days(1:i_mon))) THEN
348          IF ( day_of_year <= 31 ) THEN
349
350             month_of_year=1
351             day_of_month=day_of_year
352
353          ELSE
354
355             DO i_mon=2,12   !january is considered in the first case
356                IF ( day_of_year <= SUM(days(1:i_mon)) .AND. day_of_year > SUM(days(1:(i_mon-1))) ) THEN
357           
358                   month_of_year=i_mon
359
360                   day_of_month=INT(MOD(day_of_year, SUM(days(1:(i_mon-1))))) 
361
362                   GOTO 38
363
364                ENDIF
365
366             38 ENDDO
367          ENDIF
368       !> --------------------------------------------------------------------------------
369       !> in the second condition both day of month and month_of_year are either given in input (passed to date_init) or we are in some day successive to the initial one, so that day_of_month has already be computed in previous step
370       !>TBD: something to calculate the current year is missing
371       ELSEIF ( day_of_month > 0 .AND. day_of_month <= 31 .AND. month_of_year > 0 .AND. month_of_year <= 12) THEN
372 
373          !> calculate month_of_year. TBD: test the condition when day_of_year==31
374 
375          IF (day_of_year==1) THEN  !> this allows to turn from december to January when passing from a year to another
376 
377             month_of_year = 1
378       
379          ELSE IF (day_of_year > 1 .AND. day_of_year > SUM(days(1:month_of_year))) THEN
380
381             month_of_year = month_of_year + 1
382
383          ENDIF
384
385          !> calculate day_of_month
386          IF ( month_of_year == 1 ) THEN
387           
388            day_of_month=day_of_year
389
390          ELSE
391
392            day_of_month=INT(MOD(day_of_year, SUM(days(1:(month_of_year-1)))))
393
394          ENDIF
395
396          ! fix the date if the day is 1st and earlier day is needed due to spinup
397          IF ( day_of_month < 1 ) THEN
398 
399             ! if the day is the first day in the year
400             IF ( month_of_year  ==  1 ) THEN
401                month_of_year = 12
402                day_of_month = 31
403 
404             ! other cases
405             ELSE
406                month_of_year = month_of_year - 1
407                day_of_month = days(month_of_year)
408             ENDIF
409 
410          ENDIF
411
412      ELSE
413
414          !> Condition when date_init is provided but it is given in the wrong format
415          message_string = 'date_init not provided in the namelist or'            //          &
416                              ' given in the wrong format: MUST BE DDMMYYYY'                 
417          CALL message( 'calc_date_and_time', 'DT0101', 2, 2, 0, 6, 0 ) 
418
419      ENDIF       
420
421    END SUBROUTINE calc_date_and_time
422
423
424!------------------------------------------------------------------------------!
425! Description:
426! ------------
427!> This routine determines the time factor index in the PRE-PROCESSED emissions mode.
428!------------------------------------------------------------------------------!
429
430 SUBROUTINE time_preprocessed_indices(index_hh)
431
432    USE indices
433
434    IMPLICIT NONE
435
436!
437!-- In/output
438    INTEGER, INTENT(INOUT) ::  index_hh    !> Index Hour
439!
440!-- Additional Variables for calculateing indices
441!-- Constants
442    INTEGER, PARAMETER ::  nhour = 24
443
444    IF (days_since_reference_point == 0) THEN
445
446       index_hh=hour_of_day
447
448    ELSE
449
450       index_hh=(days_since_reference_point*nhour)+(hour_of_day)
451
452    ENDIF
453
454
455 END SUBROUTINE time_preprocessed_indices
456
457
458!------------------------------------------------------------------------------!
459! Description:
460! ------------
461!> This routine determines the time factor index in the mdh case of the DEFAULT chemistry emissions mode.
462!------------------------------------------------------------------------------!
463
464 SUBROUTINE time_mdh_indices(daytype_mdh,mo, dd, hh, index_mm, index_dd, index_hh)
465
466    USE indices
467
468    IMPLICIT NONE
469
470    !> IN/OUTPUT
471    INTEGER, INTENT(INOUT) :: mo          !> Month of year
472    INTEGER, INTENT(INOUT) :: dd          !> Day of month
473    INTEGER, INTENT(INOUT) :: hh          !> Hour of day
474    INTEGER, INTENT(INOUT) :: index_mm    !> Index Month
475    INTEGER, INTENT(INOUT) :: index_dd    !> Index Day
476    INTEGER, INTENT(INOUT) :: index_hh    !> Index Hour
477
478    CHARACTER(len=80), INTENT(INOUT) :: daytype_mdh !> type of the day in mdh mode: one of 1-WORKDAY
479                                                    !                                      2-WEEKEND
480                                                    !                                      3-HOLIDAY
481
482    REAL(wp)                         :: frac_day=0 
483
484    !> ------------------------------------------------------------------------
485
486    INTEGER                          :: weekday
487
488    !> CONSTANTS
489    INTEGER, PARAMETER               :: nmonth = 12
490    INTEGER, PARAMETER               :: nday = 7
491    INTEGER, PARAMETER               :: nhour = 24
492
493    frac_day= (dd-1)/nday    !> indicates the week of the month, supposing the month starts on monday
494
495   ! 1:7      1:31  7                   (0:30)/7
496    weekday = dd-( nday * (INT( CEILING( frac_day ) ) ) ) ! for now we let the year start on Monday.
497
498    !TBD: set weekday correct based on date
499    index_mm = mo
500    index_dd = nmonth + weekday  !> Index of the days in the mdh mode (13:20)
501
502    SELECT CASE(TRIM(daytype_mdh))
503
504       CASE ("workday")
505       
506          index_hh = nmonth+ nday + hh 
507
508       CASE ("weekend")
509       
510          index_hh = nmonth+ nday + nhour + hh 
511
512       CASE ("holiday")
513       
514          index_hh = nmonth+ nday + 2*nhour + hh 
515
516    END SELECT
517
518
519 END SUBROUTINE time_mdh_indices
520
521!------------------------------------------------------------------------------!
522! Description:
523! ------------
524!> This routine determines the time factor index in the HOURLY case of the DEFAULT emissions mode.
525!------------------------------------------------------------------------------!
526
527 SUBROUTINE time_hour_indices(mo,dd,hh,index_hh)
528
529    USE indices
530
531    IMPLICIT NONE
532
533    !> IN/OUTPUT
534    INTEGER, INTENT(INOUT)              :: mo          !> Month
535    INTEGER, INTENT(INOUT)              :: hh          !> Hour
536    INTEGER, INTENT(INOUT)              :: dd          !> Day
537    INTEGER, INTENT(INOUT)              :: index_hh    !> Index Hour
538 
539    !> Additional Variables for calculateing indices
540    INTEGER                             :: index_mm    !> Index Month
541    INTEGER                             :: index_dd    !> Index Day
542    INTEGER                             :: i_mon       !> Index for going through the different months
543    INTEGER                             :: sum_dd      !> Sum days
544
545    !> CONSTANTS
546    INTEGER, PARAMETER                  :: nhour = 24
547    INTEGER, PARAMETER, DIMENSION(12)   :: days = (/31,28,31,30,31,30,31,31,30,31,30,31/) ! no leap year
548   
549
550    index_mm = mo-1
551    index_dd = dd-1
552    sum_dd=0
553
554    IF (mo == 1) THEN
555
556       index_hh=(index_dd*nhour)+hh
557
558    ELSE
559
560       DO i_mon=1,index_mm
561
562         sum_dd=sum_dd+days(i_mon)
563
564       ENDDO
565     
566       index_hh=(sum_dd*nhour)+(index_dd*nhour)+(hh)
567
568    ENDIF
569 
570
571 END SUBROUTINE time_hour_indices
572
573
574END MODULE date_and_time_mod
Note: See TracBrowser for help on using the repository browser.