Ignore:
Timestamp:
Sep 10, 2019 6:04:34 PM (5 years ago)
Author:
gronemeier
Message:

implement new palm_date_time_mod; replaced namelist parameters time_utc_init and day_of_year_init by origin_date_time

File:
1 edited

Legend:

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

    r4226 r4227  
    2626! -----------------
    2727! $Id$
     28! implement new palm_date_time_mod
     29!
     30! 4226 2019-09-10 17:03:24Z suehring
    2831! Netcdf input routine for dimension length renamed
    2932!
     
    83858388 SUBROUTINE salsa_emission_setup( init )
    83868389
    8387     USE date_and_time_mod,                                                                         &
    8388         ONLY:  day_of_month, hour_of_day, index_dd, index_hh, index_mm, month_of_year,             &
    8389                time_default_indices, time_utc_init
    8390 
    83918390    USE netcdf_data_input_mod,                                                                     &
    83928391        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
     
    83948393               get_dimension_length, open_read_file, street_type_f
    83958394
     8395    USE palm_date_time_mod,                                                                        &
     8396        ONLY:  days_per_week, get_date_time, hours_per_day, months_per_year, seconds_per_hour
     8397
    83968398    USE surface_mod,                                                                               &
    83978399        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     
    84038405    CHARACTER(LEN=25) ::  mod_name             !< name in the input file
    84048406
    8405     INTEGER(iwp) ::  i         !< loop index
    8406     INTEGER(iwp) ::  ib        !< loop index: aerosol number bins
    8407     INTEGER(iwp) ::  ic        !< loop index: aerosol chemical components
    8408     INTEGER(iwp) ::  id_salsa  !< NetCDF id of aerosol emission input file
    8409     INTEGER(iwp) ::  in        !< loop index: emission category
    8410     INTEGER(iwp) ::  inn       !< loop index
    8411     INTEGER(iwp) ::  j         !< loop index
    8412     INTEGER(iwp) ::  ss        !< loop index
     8407    INTEGER(iwp) ::  day_of_month   !< day of the month
     8408    INTEGER(iwp) ::  day_of_week    !< day of the week
     8409    INTEGER(iwp) ::  day_of_year    !< day of the year
     8410    INTEGER(iwp) ::  hour_of_day    !< hour of the day
     8411    INTEGER(iwp) ::  i              !< loop index
     8412    INTEGER(iwp) ::  ib             !< loop index: aerosol number bins
     8413    INTEGER(iwp) ::  ic             !< loop index: aerosol chemical components
     8414    INTEGER(iwp) ::  id_salsa       !< NetCDF id of aerosol emission input file
     8415    INTEGER(iwp) ::  in             !< loop index: emission category
     8416    INTEGER(iwp) ::  index_dd       !< index day
     8417    INTEGER(iwp) ::  index_hh       !< index hour
     8418    INTEGER(iwp) ::  index_mm       !< index month
     8419    INTEGER(iwp) ::  inn            !< loop index
     8420    INTEGER(iwp) ::  j              !< loop index
     8421    INTEGER(iwp) ::  month_of_year  !< month of the year
     8422    INTEGER(iwp) ::  ss             !< loop index
    84138423
    84148424    INTEGER(iwp), DIMENSION(maxspec) ::  cc_i2m   !<
     
    84178427
    84188428    LOGICAL, INTENT(in) ::  init  !< if .TRUE. --> initialisation call
     8429
     8430    REAL(wp) ::  second_of_day    !< second of the day
    84198431
    84208432    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nsect_emission  !< sectional number emission
     
    86628674!
    86638675!--             Next emission update
    8664                 next_aero_emission_update = MOD( time_utc_init, 3600.0_wp ) - 3600.0_wp
     8676                CALL get_date_time( 0.0_wp, second_of_day=second_of_day )
     8677                next_aero_emission_update = MOD( second_of_day, seconds_per_hour ) - seconds_per_hour
    86658678!
    86668679!--             Get chemical composition (i.e. mass fraction of different species) in aerosols
     
    88188831!
    88198832!--             Get the index of the current hour
    8820                 CALL time_default_indices( month_of_year, day_of_month, hour_of_day, index_hh )
     8833                CALL get_date_time( time_since_reference_point, &
     8834                                    day_of_year=day_of_year, hour=hour_of_day )
     8835                index_hh = ( day_of_year - 1_iwp ) * hours_per_day + hour_of_day
    88218836                aero_emission_att%time_factor = aero_emission_att%etf(:,index_hh)
    88228837
     
    88258840!--             Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
    88268841!--             Needs to be calculated.)
    8827                 CALL time_default_indices( daytype, month_of_year, day_of_month, hour_of_day,      &
    8828                                            index_mm, index_dd, index_hh )
     8842                CALL get_date_time( time_since_reference_point, &
     8843                                    month=month_of_year,        &
     8844                                    day=day_of_month,           &
     8845                                    hour=hour_of_day,           &
     8846                                    day_of_week=day_of_week     )
     8847                index_mm = month_of_year
     8848                index_dd = months_per_year + day_of_week
     8849                SELECT CASE(TRIM(daytype))
     8850
     8851                   CASE ("workday")
     8852                      index_hh = months_per_year + days_per_week + hour_of_day
     8853
     8854                   CASE ("weekend")
     8855                      index_hh = months_per_year + days_per_week + hours_per_day + hour_of_day
     8856
     8857                   CASE ("holiday")
     8858                      index_hh = months_per_year + days_per_week + 2*hours_per_day + hour_of_day
     8859
     8860                END SELECT
    88298861                aero_emission_att%time_factor = aero_emission_att%etf(:,index_mm) *                &
    88308862                                                aero_emission_att%etf(:,index_dd) *                &
     
    91199151 SUBROUTINE salsa_gas_emission_setup( init )
    91209152
    9121     USE date_and_time_mod,                                                                         &
    9122         ONLY:  day_of_month, hour_of_day, index_dd, index_hh, index_mm, month_of_year,             &
    9123                time_default_indices, time_utc_init
    9124 
    91259153    USE netcdf_data_input_mod,                                                                     &
    91269154        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
     
    91289156               get_dimension_length, open_read_file
    91299157
     9158    USE palm_date_time_mod,                                                                        &
     9159        ONLY:  days_per_week, get_date_time, hours_per_day, months_per_year, seconds_per_hour
     9160
    91309161    USE surface_mod,                                                                               &
    91319162        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     
    91389169    CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names   !<  variable names in input data
    91399170
     9171
     9172    INTEGER(iwp) ::  day_of_month   !< day of the month
     9173    INTEGER(iwp) ::  day_of_week    !< day of the week
     9174    INTEGER(iwp) ::  day_of_year    !< day of the year
     9175    INTEGER(iwp) ::  hour_of_day    !< hour of the day
    91409176    INTEGER(iwp) ::  id_chem        !< NetCDF id of chemistry emission file
    91419177    INTEGER(iwp) ::  i              !< loop index
    91429178    INTEGER(iwp) ::  ig             !< loop index
    91439179    INTEGER(iwp) ::  in             !< running index for emission categories
     9180    INTEGER(iwp) ::  index_dd       !< index day
     9181    INTEGER(iwp) ::  index_hh       !< index hour
     9182    INTEGER(iwp) ::  index_mm       !< index month
    91449183    INTEGER(iwp) ::  j              !< loop index
     9184    INTEGER(iwp) ::  month_of_year  !< month of the year
    91459185    INTEGER(iwp) ::  num_vars       !< number of variables
    91469186
     
    91489188
    91499189    LOGICAL, INTENT(in) ::  init          !< if .TRUE. --> initialisation call
     9190
     9191    REAL(wp) ::  second_of_day    !< second of the day
    91509192
    91519193    REAL(wp), DIMENSION(:), ALLOCATABLE ::  time_factor  !< emission time factor
     
    92589300!
    92599301!--       Next emission update
    9260           next_gas_emission_update = MOD( time_utc_init, 3600.0_wp ) - 3600.0_wp
     9302          CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
     9303          next_gas_emission_update = MOD( second_of_day, seconds_per_hour ) - seconds_per_hour
    92619304!
    92629305!--       Allocate and read surface emission data (in total PM) (NOTE that "preprocessed" input data
     
    93039346!
    93049347!--       Get the index of the current hour
    9305           CALL time_default_indices( month_of_year, day_of_month, hour_of_day, index_hh )
     9348          CALL get_date_time( time_since_reference_point, &
     9349                              day_of_year=day_of_year, hour=hour_of_day )
     9350          index_hh = ( day_of_year - 1_iwp ) * hours_per_day + hour_of_day
    93069351          time_factor = chem_emission_att%hourly_emis_time_factor(:,index_hh)
    93079352
     
    93109355!--       Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
    93119356!--       Needs to be calculated.)
    9312           CALL time_default_indices( daytype, month_of_year, day_of_month, hour_of_day,            &
    9313                                      index_mm, index_dd, index_hh )
     9357          CALL get_date_time( time_since_reference_point, &
     9358                              month=month_of_year,        &
     9359                              day=day_of_month,           &
     9360                              hour=hour_of_day,           &
     9361                              day_of_week=day_of_week     )
     9362          index_mm = month_of_year
     9363          index_dd = months_per_year + day_of_week
     9364          SELECT CASE(TRIM(daytype))
     9365
     9366             CASE ("workday")
     9367                index_hh = months_per_year + days_per_week + hour_of_day
     9368
     9369             CASE ("weekend")
     9370                index_hh = months_per_year + days_per_week + hours_per_day + hour_of_day
     9371
     9372             CASE ("holiday")
     9373                index_hh = months_per_year + days_per_week + 2*hours_per_day + hour_of_day
     9374
     9375          END SELECT
    93149376          time_factor = chem_emission_att%mdh_emis_time_factor(:,index_mm) *                       &
    93159377                        chem_emission_att%mdh_emis_time_factor(:,index_dd) *                       &
Note: See TracChangeset for help on using the changeset viewer.