Changeset 4364


Ignore:
Timestamp:
Jan 8, 2020 2:12:31 AM (4 years ago)
Author:
monakurppa
Message:

Time in the input data set relative to the start of the simulation

Location:
palm/trunk
Files:
4 edited

Legend:

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

    r4360 r4364  
    2626! -----------------
    2727! $Id$
     28! Set time coordinate in the input data relative to origin_time rather than to
     29! 00:00:00 UTC
     30!
     31! 4360 2020-01-07 11:25:50Z suehring
    2832! Introduction of wall_flags_total_0, which currently sets bits based on static
    2933! topography information used in wall_flags_static_0
     
    526530    REAL(wp) ::  ocsv_init = nclim                   !< Init value for semi-volatile organic gases
    527531    REAL(wp) ::  rhlim = 1.20_wp                     !< RH limit in %/100. Prevents unrealistical RH
    528     REAL(wp) ::  time_utc_init                       !< time in seconds-of-day of origin_date_time
    529532    REAL(wp) ::  skip_time_do_salsa = 0.0_wp         !< Starting time of SALSA (s)
    530533!
     
    85798582 SUBROUTINE salsa_emission_update
    85808583
    8581     USE palm_date_time_mod,                                                                        &
    8582         ONLY:  get_date_time
    8583 
    85848584    IMPLICIT NONE
    85858585
     
    85878587
    85888588       IF ( time_since_reference_point >= skip_time_do_salsa  )  THEN
    8589 !
    8590 !--       Get time_utc_init from origin_date_time
    8591           CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
    85928589
    85938590          IF ( next_aero_emission_update <=                                                        &
    8594                MAX( time_since_reference_point, 0.0_wp ) + time_utc_init )  THEN
     8591               MAX( time_since_reference_point, 0.0_wp ) )  THEN
    85958592             CALL salsa_emission_setup( .FALSE. )
    85968593          ENDIF
    85978594
    85988595          IF ( next_gas_emission_update <=                                                         &
    8599                MAX( time_since_reference_point, 0.0_wp ) + time_utc_init )  THEN
     8596               MAX( time_since_reference_point, 0.0_wp ) )  THEN
    86008597             IF ( salsa_emission_mode == 'read_from_file'  .AND.  .NOT. salsa_gases_from_chem )    &
    86018598             THEN
     
    91439140          ELSEIF ( aero_emission_att%lod == 2 )  THEN
    91449141!
    9145 !--          Get time_utc_init from origin_date_time
    9146              CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
    9147 !
    9148 !--          Obtain time index for current point in time. Note, the time coordinate in the input
    9149 !--          file is relative to time_utc_init.
    9150              aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time - (                      &
    9151                                                    time_utc_init + MAX( time_since_reference_point,&
    9152                                                                         0.0_wp) ) ), DIM = 1 ) - 1
     9142!--          Obtain time index for current point in time.
     9143             aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time -                        &
     9144                                                   MAX( time_since_reference_point, 0.0_wp ) ),    &
     9145                                              DIM = 1 ) - 1
    91539146!
    91549147!--          Allocate the data input array always before reading in the data and deallocate after
     
    96539646    ELSEIF ( lod_gas_emissions == 2 )  THEN
    96549647!
    9655 !--    Get time_utc_init from origin_date_time
    9656        CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
    9657 !
    9658 !--    Obtain time index for current point in time. Note, the time coordinate in the input file is
    9659 !--    relative to time_utc_init.
    9660        chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time - ( time_utc_init +               &
    9661                                          MAX( time_since_reference_point, 0.0_wp) ) ), DIM = 1 ) - 1
     9648!--    Obtain time index for current point in time.
     9649       chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time -                                 &
     9650                                          MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1
    96629651!
    96639652!--    Allocate the data input array always before reading in the data and deallocate after (NOTE
     
    1224512234!-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed
    1224612235!-- time(tind_p) before boundary data is updated again.
    12247     fac_dt = ( time_utc_init + time_since_reference_point -                                        &
    12248                salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) /                              &
     12236    fac_dt = ( time_since_reference_point - salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) / &
    1224912237             ( salsa_nest_offl%time(salsa_nest_offl%tind_p) -                                      &
    1225012238               salsa_nest_offl%time(salsa_nest_offl%tind) )
     
    1253212520    nmass_bins = nbins_aerosol * ncomponents_mass
    1253312521!
    12534 !-- Get time_utc_init from origin_date_time
    12535     CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
    12536 !
    1253712522!-- Allocate arrays for reading boundary values. Arrays will incorporate 2 time levels in order to
    1253812523!-- interpolate in between.
     
    1258012565!--    input is only required for the 3D simulation, not for the soil/wall spinup. However, as the
    1258112566!--    spinup time is added to the end_time, this must be considered here.
    12582        IF ( end_time - spinup_time >                                           &
    12583             salsa_nest_offl%time(salsa_nest_offl%nt-1) - time_utc_init )  THEN
     12567       IF ( end_time - spinup_time > salsa_nest_offl%time(salsa_nest_offl%nt-1) )  THEN
    1258412568          message_string = 'end_time of the simulation exceeds the time dimension in the dynamic'//&
    1258512569                           ' input file.'
     
    1258712571       ENDIF
    1258812572
    12589        IF ( salsa_nest_offl%time(0) /= time_utc_init )  THEN
    12590           message_string = 'Offline nesting: time dimension must start at time_utc_init.'
     12573       IF ( salsa_nest_offl%time(0) /= 0.0_wp )  THEN
     12574          message_string = 'Offline nesting: time dimension must start at 0.0.'
    1259112575          CALL message( 'salsa_nesting_offl_init', 'PA0691', 1, 2, 0, 6, 0 )
    1259212576       ENDIF
     
    1275612740!-- Check if dynamic driver data input is required.
    1275712741    IF ( salsa_nest_offl%time(salsa_nest_offl%tind_p) <= MAX( time_since_reference_point, 0.0_wp)  &
    12758          + time_utc_init  .OR.  .NOT.  salsa_nest_offl%init )  THEN
     12742         .OR.  .NOT.  salsa_nest_offl%init )  THEN
    1275912743       CONTINUE
    1276012744!
     
    1276512749!
    1276612750!-- Obtain time index for current point in time.
    12767     salsa_nest_offl%tind = MINLOC( ABS( salsa_nest_offl%time - ( time_utc_init +                   &
    12768                                         MAX( time_since_reference_point, 0.0_wp) ) ), DIM = 1 ) - 1
     12751    salsa_nest_offl%tind = MINLOC( ABS( salsa_nest_offl%time -                                     &
     12752                                   MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1
    1276912753    salsa_nest_offl%tind_p = salsa_nest_offl%tind + 1
    1277012754!
  • palm/trunk/TESTS/cases/urban_environment_salsa/MONITORING/urban_environment_salsa_rc

    r4347 r4364  
    11
    22 ******************************    --------------------------------------------
    3  * PALM 6.0  Rev: 3915M       *    atmosphere - run without 1D - prerun
     3 * PALM 6.0  Rev: 4363M       *    atmosphere - run without 1D - prerun
    44 ******************************    --------------------------------------------
    55
    6  Date:               2019-12-18    Run:       urban_environment_salsa__gfortran_
    7  Time:                 13:56:13    Run-No.:   00
    8  Run on host:        gfortran_d
    9  Number of PEs:               2    Processor grid (x,y): (   1,   2) calculated
    10                                    A 1d-decomposition along y is used
     6 Date:               2020-01-07    Run:       urban_environment_salsa           
     7 Time:                 21:00:12    Run-No.:   00
     8 Run on host:           default
     9 Number of PEs:               4    Processor grid (x,y): (   2,   2) calculated
    1110 ------------------------------------------------------------------------------
    1211
     
    4645
    4746 Number of gridpoints (x,y,z):  (0:  19, 0:  19, 0:  61)
    48  Subdomain size (x,y,z):        (    20,     10,     62)
     47 Subdomain size (x,y,z):        (    10,     10,     62)
    4948
    5049
Note: See TracChangeset for help on using the changeset viewer.