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

Last change on this file since 4147 was 4144, checked in by raasch, 5 years ago

relational operators .EQ., .NE., etc. replaced by ==, /=, etc.

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