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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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