source: palm/tags/release-6.0/SOURCE/date_and_time_mod.f90 @ 3800

Last change on this file since 3800 was 3467, checked in by suehring, 5 years ago

Branch salsa @3446 re-integrated into trunk

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