Ignore:
Timestamp:
Oct 2, 2018 12:21:11 PM (6 years ago)
Author:
kanani
Message:

Merge chemistry branch at r3297 to trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/date_and_time_mod.f90

    r2718 r3298  
    2525! -----------------
    2626! $Id$
     27! - Minor formatting (kanani)
     28! - Added Routines for DEFAULT mode of chemistry emissions (Russo)
     29! - Added routine for reading-in real dates: format has to be in DDMMYYYY and
     30!   passed in the namelist parameter date_init (Russo)
     31! - Added calculation of several time indices useful in several routines
     32!   of the model (Russo)
     33!
     34! 2718 2018-01-02 08:49:38Z maronga
    2735! Corrected "Former revisions" section
    2836!
     
    4654!> This routine calculates all needed information on date and time used by
    4755!> other modules
     56!> @todo Further testing and revision of routines for updating indices of
     57!>       emissions in the default mode
     58!> @todo Add routine for recognizing leap years
     59!> @todo Add recognition of exact days of week (Monday, Tuesday, etc.)
     60!> @todo Reconsider whether to remove day_of_year_init from the namelist: we
     61!>       already implemented changes for calculating it from date_init in
     62!>       calc_date_and_time
    4863!------------------------------------------------------------------------------!
    4964 MODULE date_and_time_mod
    50  
    51     USE control_parameters,                                                    &
    52         ONLY: time_since_reference_point
    53  
     65
     66    USE control_parameters,                                                   &
     67        ONLY:  coupling_start_time, days_since_reference_point,               &
     68               message_string, simulated_time, time_since_reference_point
     69
    5470    USE kinds
    5571
     72
    5673    IMPLICIT NONE
    5774
    5875    PRIVATE
    59    
    60     PUBLIC   calc_date_and_time, d_hours_day, d_seconds_hour, d_seconds_year,  &
    61              day_of_year, day_of_year_init, time_utc, time_utc_init
    62 
    63 
    64     INTEGER(iwp) ::  day_of_year              !< day of the year (DOY)
    65     INTEGER(iwp) ::  day_of_year_init = 172   !< DOY at model start (default: 21 June)
    66 
    67     REAL(wp) ::  time_utc                     !< current model time in UTC
    68     REAL(wp) ::  time_utc_init = 43200.0_wp   !< UTC time at model start
    69 
     76
     77!-- Variables Declaration
     78
     79    INTEGER(iwp)        ::  day_of_year      = 0   !< day of the year (DOY)
     80    INTEGER(iwp)        ::  day_of_year_init = 0   !< DOY at model start (default: 0)
     81
     82    ! --- Most of these indices are updated by the routine calc_date_and_time according to the current date and time of the simulation
     83    INTEGER(iwp)        ::  hour_of_year = 1                        !< hour of the current year (1:8760(8784))
     84    INTEGER(iwp)        ::  hour_of_day=1                           !< hour of the current day (1:24)
     85    INTEGER(iwp)        ::  day_of_month=0                          !< day of the current month (1:31)
     86    INTEGER(iwp)        ::  month_of_year=0                         !< month of the current year (1:12)
     87    INTEGER(iwp)        ::  current_year=0                          !< current year
     88    INTEGER(iwp)        ::  hour_call_emis=0                        !< index used to call the emissions just once every hour
     89
     90    INTEGER(iwp)        ::  ihour           
     91    INTEGER(iwp)        ::  index_mm                                !< index months of the default emission mode
     92    INTEGER(iwp)        ::  index_dd                                !< index days of the default emission mode
     93    INTEGER(iwp)        ::  index_hh                                !< index hours of the default emission mode
     94
     95    REAL(wp)            ::  time_utc                     !< current model time in UTC
     96    REAL(wp)            ::  time_utc_emis                !< current emission module time in UTC
     97    REAL(wp)            ::  time_utc_init = 43200.0_wp   !< UTC time at model start
     98    REAL(wp)            ::  time_update                  !< used to calculate actual second of the simulation
     99 
    70100    REAL(wp), PARAMETER ::  d_hours_day    = 1.0_wp / 24.0_wp       !< inverse of hours per day (1/24)
    71101    REAL(wp), PARAMETER ::  d_seconds_hour = 1.0_wp / 3600.0_wp     !< inverse of seconds per hour (1/3600)
    72102    REAL(wp), PARAMETER ::  d_seconds_year = 1.0_wp / 31536000.0_wp !< inverse of the seconds per year (1/(365*86400))
    73103   
     104    CHARACTER(len=8)    ::  date_init = "31122018"                  !< Starting date of simulation: We selected this because it was a monday
     105 
     106    !> --- Parameters
     107    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)
     108
    74109    SAVE
    75110
     111!-- INTERFACES PART
     112    !-- Read initial day and time of simulation
     113    INTERFACE init_date_and_time
     114       MODULE PROCEDURE init_date_and_time
     115    END INTERFACE init_date_and_time
     116
     117    !-- Get hour index in the DEAFULT case of chemistry emissions :
     118    INTERFACE time_default_indices
     119       MODULE PROCEDURE time_mdh_indices
     120       MODULE PROCEDURE time_hour_indices
     121    END INTERFACE time_default_indices
     122
     123    !-- Calculate current date and time
     124    INTERFACE calc_date_and_time
     125       MODULE PROCEDURE calc_date_and_time
     126    END INTERFACE
     127
     128
     129    !-- Public Interfaces
     130    PUBLIC calc_date_and_time, time_default_indices, init_date_and_time
     131
     132    !-- Public Variables
     133    PUBLIC date_init, d_hours_day, d_seconds_hour, d_seconds_year,               &
     134           day_of_year, day_of_year_init, time_utc, time_utc_init, day_of_month, &
     135           month_of_year, index_mm, index_dd, index_hh, hour_of_day, hour_of_year, &
     136           hour_call_emis
     137
    76138 CONTAINS
     139
     140
     141 !------------------------------------------------------------------------------!
     142 !> Reads starting date from namelist
     143 !------------------------------------------------------------------------------!
     144 
     145    SUBROUTINE init_date_and_time
     146
     147       IMPLICIT NONE
     148
     149       IF  (day_of_year_init == 0) THEN
     150          ! Day of the month at starting time
     151          READ(UNIT=date_init(1:2),fmt=*)day_of_month
     152
     153          ! Month of the year at starting time
     154          READ(UNIT=date_init(3:4),fmt=*)month_of_year
     155
     156          ! Year at starting time
     157          READ(UNIT=date_init(5:8),fmt=*)current_year
     158       
     159       ENDIF
     160
     161    END SUBROUTINE init_date_and_time
    77162
    78163!------------------------------------------------------------------------------!
    79164! Description:
    80165! ------------
    81 !> Calculate current day of the year and time in UTC
     166!> Calculate current date and time of the simulation
    82167!------------------------------------------------------------------------------!
    83168 
     
    86171       IMPLICIT NONE
    87172
    88 !
    89 !--    Calculate current day of the year
    90        day_of_year = day_of_year_init + INT(FLOOR( (time_utc_init + time_since_reference_point)&
    91                                / 86400.0_wp ), KIND=iwp)
    92                        
     173!--    Variables Definition
     174       INTEGER                          :: i_mon       !< Index for going through the different months
     175
     176       !> Update simulation time in seconds
     177       time_update = simulated_time-coupling_start_time
     178
     179!--    Calculate current day of the simulated time
     180       days_since_reference_point=INT(FLOOR( (time_utc_init + time_update) &
     181                               / 86400.0_wp ) )
     182
     183!--    Calculate actual UTC time                       
    93184       time_utc = MOD((time_utc_init + time_since_reference_point), 86400.0_wp)
    94185       
     186!sB    PRILIMINARY workaround for time_utc bug concerning time_since_reference_point:
     187       time_utc_emis = MOD((time_utc_init + time_update), 86400.0_wp)     
     188
     189!--    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.
     190
     191       IF ( day_of_year_init == 0 ) THEN
     192
     193          !> 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.
     194          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
     195       
     196             IF ( month_of_year == 1 ) THEN  !!month of year is read in input
     197
     198                day_of_year_init = day_of_month
     199
     200             ELSE
     201
     202                day_of_year_init= SUM(days( 1:(month_of_year-1) )) + day_of_month  !day_of_month is read in input in this case
     203
     204             ENDIF
     205!kanani: Revise, we cannot force users to provide date_init, maybe set a default value?
     206!           ELSE
     207!
     208!              message_string = 'date_init not provided in the namelist or'             //          &
     209!                               ' given in the wrong format: MUST BE DDMMYYYY'                       
     210!              CALL message( 'calc_date_and_time', 'DT0100', 2, 2, 0, 6, 0 )
     211     
     212          ENDIF
     213
     214       ENDIF
     215
     216      !-- Calculate actual hour of the day: the first hour of the day is from 00:00:00 to 00:59:59.
     217
     218      hour_of_day = INT( FLOOR( time_utc_emis/3600.0_wp ) ) + 1
     219
     220!--    Calculate current day of the year !TBD: considetr leap years
     221       IF ( (day_of_year_init + days_since_reference_point)  .GT. 365 ) THEN
     222
     223          day_of_year=INT(MOD((day_of_year_init + days_since_reference_point), 365.0_wp))
     224
     225       ELSE
     226         
     227          day_of_year = day_of_year_init + days_since_reference_point
     228
     229       ENDIF
     230
     231!
     232!--    Calculate current hour of the year
     233       hour_of_year = ( (day_of_year-1) * 24 ) + hour_of_day  !> actual hour of the year
     234       
     235
     236!
     237!--    UPDATE actual day of the month and month of the year
     238       !> --------------------------------------------------------------------------------
     239       !> The first case is when date_init is not provided: we only know day_of_year_init     
     240       IF ( month_of_year == 0 .AND. day_of_month == 0) THEN
     241
     242          !> The first case is when date_init is not provided: we only know day_of_year_init
     243          !DO i_mon=1,12
     244             !IF (day_of_year .LE. SUM(days(1:i_mon))) THEN
     245          IF ( day_of_year .LE. 31 ) THEN
     246
     247             month_of_year=1
     248             day_of_month=day_of_year
     249
     250          ELSE
     251
     252             DO i_mon=2,12   !january is considered in the first case
     253                IF ( day_of_year .LE. SUM(days(1:i_mon)) .AND. day_of_year .GT. SUM(days(1:(i_mon-1))) ) THEN
     254           
     255                   month_of_year=i_mon
     256
     257                   day_of_month=INT(MOD(day_of_year, SUM(days(1:(i_mon-1)))))
     258
     259                   GOTO 38
     260
     261                ENDIF
     262
     263             38 ENDDO
     264          ENDIF
     265       !> --------------------------------------------------------------------------------
     266       !> 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
     267       !>TBD: something to calculate the current year is missing
     268       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
     269 
     270          !> calculate month_of_year. TBD: test the condition when day_of_year==31
     271 
     272          IF (day_of_year==1) THEN  !> this allows to turn from december to January when passing from a year to another
     273 
     274             month_of_year = 1
     275       
     276          ELSE IF (day_of_year .GT. 1 .AND. day_of_year .GT. SUM(days(1:month_of_year))) THEN
     277
     278             month_of_year = month_of_year + 1
     279
     280          ENDIF
     281
     282          !> calculate day_of_month
     283          IF ( month_of_year == 1 ) THEN
     284           
     285            day_of_month=day_of_year
     286
     287          ELSE
     288
     289            day_of_month=INT(MOD(day_of_year, SUM(days(1:(month_of_year-1)))))
     290
     291          ENDIF
     292
     293
     294
     295
     296      ELSE
     297
     298          !> Condition when date_init is provided but it is given in the wrong format
     299          message_string = 'date_init not provided in the namelist or'            //          &
     300                              ' given in the wrong format: MUST BE DDMMYYYY'                 
     301          CALL message( 'calc_date_and_time', 'DT0101', 2, 2, 0, 6, 0 )
     302
     303      ENDIF       
     304     
     305    END SUBROUTINE calc_date_and_time
     306
     307!TBD: check the routines used for update of emission indices in the DEFAULT MODE
     308!------------------------------------------------------------------------------!
     309! Description:
     310! ------------
     311!> This routine determines the time factor index in the mdh case of the DEFAULT chemistry emissions mode.
     312!------------------------------------------------------------------------------!
     313
     314 SUBROUTINE time_mdh_indices(daytype_mdh,mo, dd, hh, index_mm, index_dd, index_hh)
     315
     316    USE indices
     317
     318    IMPLICIT NONE
     319
     320    !> IN/OUTPUT
     321    INTEGER, INTENT(INOUT) :: mo          !> Month of year
     322    INTEGER, INTENT(INOUT) :: dd          !> Day of month
     323    INTEGER, INTENT(INOUT) :: hh          !> Hour of day
     324    INTEGER, INTENT(INOUT) :: index_mm    !> Index Month
     325    INTEGER, INTENT(INOUT) :: index_dd    !> Index Day
     326    INTEGER, INTENT(INOUT) :: index_hh    !> Index Hour
     327
     328    CHARACTER(len=80), INTENT(INOUT) :: daytype_mdh !> type of the day in mdh mode: one of 1-WORKDAY
     329                                                    !                                      2-WEEKEND
     330                                                    !                                      3-HOLIDAY
     331
     332    REAL(wp)                         :: frac_day=0 
     333
     334    !> ------------------------------------------------------------------------
     335
     336    INTEGER                          :: weekday
     337
     338    !> CONSTANTS
     339    INTEGER, PARAMETER               :: nmonth = 12
     340    INTEGER, PARAMETER               :: nday = 7
     341    INTEGER, PARAMETER               :: nhour = 24
     342
     343    frac_day= (dd-1)/nday    !> indicates the week of the month, supposing the month starts on monday
     344
     345   ! 1:7      1:31  7                   (0:30)/7
     346    weekday = dd-( nday * (INT( CEILING( frac_day ) ) ) ) ! for now we let the year start on Monday.
     347
     348    !TBD: set weekday correct based on date
     349    index_mm = mo
     350    index_dd = nmonth + weekday  !> Index of the days in the mdh mode (13:20)
     351
     352    SELECT CASE(TRIM(daytype_mdh))
     353
     354                   CASE ("workday")
     355               
     356                   index_hh = nmonth+ nday + hh
     357
     358                   CASE ("weekend")
     359               
     360                   index_hh = nmonth+ nday + nhour + hh
     361
     362                   CASE ("holiday")
     363               
     364                   index_hh = nmonth+ nday + 2*nhour + hh
     365    END SELECT
     366
     367
     368 END SUBROUTINE time_mdh_indices
     369
     370!------------------------------------------------------------------------------!
     371! Description:
     372! ------------
     373!> This routine determines the time factor index in the HOURLY case of the DEFAULT emissions mode.
     374!------------------------------------------------------------------------------!
     375
     376 SUBROUTINE time_hour_indices(mo,dd,hh,index_hh)
     377
     378    USE indices
     379
     380    IMPLICIT NONE
     381
     382    !> IN/OUTPUT
     383    INTEGER, INTENT(INOUT)              :: mo          !> Month
     384    INTEGER, INTENT(INOUT)              :: hh          !> Hour
     385    INTEGER, INTENT(INOUT)              :: dd          !> Day
     386    INTEGER, INTENT(INOUT)              :: index_hh    !> Index Hour
     387 
     388    !> Additional Variables for calculateing indices
     389    INTEGER                             :: index_mm    !> Index Month
     390    INTEGER                             :: index_dd    !> Index Day
     391    INTEGER                             :: i_mon       !> Index for going through the different months
     392    INTEGER                             :: sum_dd      !> Sum days
     393
     394    !> CONSTANTS
     395    INTEGER, PARAMETER                  :: nmonth=12
     396    INTEGER, PARAMETER                  :: nday = 7
     397    INTEGER, PARAMETER                  :: nhour = 24
     398    INTEGER, PARAMETER, DIMENSION(12)   :: days = (/31,28,31,30,31,30,31,31,30,31,30,31/) ! no leap year
     399   
     400
     401    index_mm = mo-1
     402    index_dd = dd-1
     403    sum_dd=0
     404
     405    IF (mo == 1) THEN
     406
     407       index_hh=(index_dd*nhour)+hh
     408
     409    ELSE
     410
     411        DO i_mon=1,index_mm
    95412       
    96 
    97     END SUBROUTINE calc_date_and_time
    98 
    99 
    100 
    101  END MODULE date_and_time_mod
     413            sum_dd=sum_dd+days(i_mon)
     414
     415        ENDDO
     416     
     417    index_hh=(sum_dd*nhour)+(index_dd*nhour)+(hh)
     418
     419    ENDIF
     420 
     421
     422 END SUBROUTINE time_hour_indices
     423
     424
     425END MODULE date_and_time_mod
Note: See TracChangeset for help on using the changeset viewer.