Ignore:
Timestamp:
Sep 16, 2020 10:20:34 AM (4 years ago)
Author:
gronemeier
Message:

Add option to fix date and time of the simulation; renamed set_reference_date_time to init_date_time (palm_date_time_mod, init_3d_model, modules, parin)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/palm_date_time_mod.f90

    r4360 r4680  
    11!> @file palm_date_time_mod.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! ------------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! Add option to fix date and time; renamed set_reference_date_time to init_date_time
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2729! Add days of northward- and southward equinox
    28 ! 
     30!
    2931! 4227 2019-09-10 18:04:34Z gronemeier
    3032! Complete rework of module date_and_time_mod:
     
    4850!>
    4951!> @todo Consider leap seconds
    50 !> @note Time_zone only supports full-hour time zones, i.e., time zones like
    51 !>       Australian Central Standard Time (UTC+9.5) are not possible
    52 !------------------------------------------------------------------------------!
     52!> @note Time_zone only supports full-hour time zones, i.e., time zones like Australian Central
     53!>       Standard Time (UTC+9.5) are not possible
     54!--------------------------------------------------------------------------------------------------!
    5355 MODULE palm_date_time_mod
    5456
    55     USE control_parameters,                                                    &
     57    USE control_parameters,                                                                        &
    5658         ONLY:  message_string
    5759
     
    6870    INTEGER(iwp), PARAMETER ::  months_per_year    = 12_iwp                                 !< months in a year
    6971!
    70 !-- Definition of mean northward and southward equinox (summer and winter half year)
    71 !-- in days of year. For simplicity, March 21 and September 21 is assumed.
    72     INTEGER(iwp), PARAMETER ::  northward_equinox  = 80_iwp
    73     INTEGER(iwp), PARAMETER ::  southward_equinox  = 264_iwp
     72!-- Day of year of the mean northward and southward equinox (summer and winter half year)
     73    INTEGER(iwp), PARAMETER ::  northward_equinox  = 80_iwp                                 !< Mar 21 (leap year: Mar 20)
     74    INTEGER(iwp), PARAMETER ::  southward_equinox  = 264_iwp                                !< Sep 21 (leap year: Sep 20)
    7475
    7576    REAL(wp),     PARAMETER ::  seconds_per_minute = 60.0_wp                                !< seconds in a minute
     
    124125!
    125126!-- Variable Declaration
     127    LOGICAL              ::  date_is_fixed              = .FALSE.  !< if true, date is fixed (time can still change)
    126128    LOGICAL              ::  reference_date_time_is_set = .FALSE.  !< true if reference_date_time is set
     129    LOGICAL              ::  time_is_fixed              = .FALSE.  !< if true, time does not change at all
    127130
    128131    TYPE(date_time_type) ::  reference_date_time                   !< reference date-time
     
    133136!
    134137!-- Set reference date and time
    135     INTERFACE set_reference_date_time
    136         MODULE PROCEDURE set_reference_date_time
    137     END INTERFACE set_reference_date_time
     138    INTERFACE init_date_time
     139        MODULE PROCEDURE init_date_time
     140    END INTERFACE init_date_time
    138141!
    139142!-- Return date and time information
     
    145148    PUBLIC &
    146149       get_date_time, &
    147        set_reference_date_time
     150       init_date_time
    148151!
    149152!-- Public variables
     
    167170! Description:
    168171! ------------
    169 !> Set reference date-time.
     172!> Initialize date-time setting by defining a global reference date-time and choosing a variable or
     173!> fixed date.
    170174!> Only a single call is allowed to this routine during execution.
    171175!--------------------------------------------------------------------------------------------------!
    172  SUBROUTINE set_reference_date_time( date_time_str )
     176 SUBROUTINE init_date_time( date_time_str, use_fixed_date, use_fixed_time )
    173177
    174178    CHARACTER(LEN=date_time_str_len), INTENT(IN) ::  date_time_str  !< string containing date-time information
    175179
     180    LOGICAL, INTENT(IN), OPTIONAL ::  use_fixed_date  !< flag to fix date
     181    LOGICAL, INTENT(IN), OPTIONAL ::  use_fixed_time  !< flag to fix time
    176182!
    177183!-- Check if date and time are already set
     
    179185       !> @note This error should never be observed by a user.
    180186       !>       It can only appear if the code was modified.
    181        WRITE( message_string, * ) 'Multiple calls to set_reference_date_time detected.&' //  &
    182                                   'The reference date-time must be set only once.'
    183        CALL message( 'set_reference_date_time', 'PA0680', 2, 2, 0, 6, 0 )
     187       WRITE( message_string, * ) 'Multiple calls to init_date_time detected.&' //  &
     188                                  'This routine must not be called more than once.'
     189       CALL message( 'init_date_time', 'PA0680', 2, 2, 0, 6, 0 )
    184190       RETURN
    185191
     
    190196       reference_date_time_is_set = .TRUE.
    191197
    192     ENDIF
    193 
    194  END SUBROUTINE set_reference_date_time
     198       IF ( PRESENT( use_fixed_date ) )  date_is_fixed = use_fixed_date
     199       IF ( PRESENT( use_fixed_time ) )  time_is_fixed = use_fixed_time
     200
     201    ENDIF
     202
     203 END SUBROUTINE init_date_time
    195204
    196205
     
    201210!> An alternative reference date-time string can be specified via 'reference_date_time_str'.
    202211!> Call to this routine is only possible if a reference time is either specified in the call itself
    203 !> via 'reference_date_time_str' or previously set by calling routine 'set_reference_date_time'.
     212!> via 'reference_date_time_str' or previously set by calling routine 'init_date_time'.
    204213!--------------------------------------------------------------------------------------------------!
    205214 SUBROUTINE get_date_time( time_since_reference, reference_date_time_str,    &
     
    241250                                  'Returning date-time information is not possible. ' // &
    242251                                  'Either specify reference_date_time_str ' //           &
    243                                   'or set a reference via set_reference_date_time.'
     252                                  'or set a reference via init_date_time.'
    244253       CALL message( 'get_date_time', 'PA0677', 2, 2, 0, 6, 0 )
    245254       RETURN
     
    252261       internal_reference_date_time = reference_date_time
    253262    ENDIF
    254 !
    255 !-- Add time to reference time
    256     date_time = add_date_time( time_since_reference, internal_reference_date_time )
     263
     264    IF ( time_is_fixed )  THEN
     265!
     266!--    If time shall not change, set new time to reference time
     267       date_time = internal_reference_date_time
     268    ELSE
     269!
     270!--    Add time to reference time
     271       date_time = add_date_time( time_since_reference, internal_reference_date_time )
     272!
     273!--    If date shall be fixed, revert it to the reference date if changed
     274       IF ( date_is_fixed )  THEN
     275          IF ( date_time%year /= internal_reference_date_time%year  .OR.                          &
     276               get_day_of_year( date_time ) /= get_day_of_year( internal_reference_date_time ) )  &
     277          THEN
     278
     279             date_time%year           = internal_reference_date_time%year
     280             date_time%month          = internal_reference_date_time%month
     281             date_time%day            = internal_reference_date_time%day
     282
     283             date_time = update_leapyear_setting( date_time )
     284
     285             date_time%second_of_year = get_second_of_year( date_time )
     286
     287          ENDIF
     288       ENDIF
     289    ENDIF
    257290!
    258291!-- Set requested return values
Note: See TracChangeset for help on using the changeset viewer.