Changeset 4055 for palm/trunk/SOURCE


Ignore:
Timestamp:
Jun 27, 2019 9:47:29 AM (5 years ago)
Author:
suehring
Message:

chem_emissions_mod: Formatting adjustments; initialization of arrays fixed; univsersal gas constant moved to basic_constants_and_equations_mod.f90

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r3655 r4055  
    2525! -----------------
    2626! $Id$
     27! Added rgas_univ (universal gas constant) (E.C. Chan)
     28!
     29!
     30! 3655 2019-01-07 16:51:22Z knoop
    2731! OpenACC port for SPEC
    2832!
     
    6266    REAL(wp), PARAMETER ::  pi = 3.141592654_wp                       !< PI
    6367    !$ACC DECLARE COPYIN(pi)
     68    REAL(wp), PARAMETER ::  rgas_univ = 8.31446261815324_wp           !< universal gas constant (J K-1 mol-1)
    6469    REAL(wp), PARAMETER ::  rho_l = 1.0E3_wp                          !< density of water (kg m-3)
    6570    REAL(wp), PARAMETER ::  rho_nacl = 2165.0_wp                      !< density of NaCl (kg m-3)
  • palm/trunk/SOURCE/chem_emissions_mod.f90

    r3968 r4055  
    2727! -----------------
    2828! $Id$
     29! - replaced local thermo. constants w/ module definitions in
     30!   basic_constants_and_equations_mod (rgas_univ, p_0, r_d_cp)
     31! - initialize array emis_distribution immediately following allocation
     32! - lots of minor formatting changes based on review sesson in 20190325
     33!   (E.C. Chan)
     34!
     35! 3968 2019-05-13 11:04:01Z suehring
    2936! - in subroutine chem_emissions_match replace all decision structures relating to
    3037!   mode_emis to emiss_lod
     
    5461! removed unnecessary informative messsages/location
    5562! messages and corrected comments on PM units from to kg 
    56 ! bug fix: spcs_name replaced by nvar in DO loops
     63! bug fix: spcs_name replaced by nvar in DO  loops
    5764!
    5865! 3591 2018-11-30 17:37:32Z suehring
     
    118125 MODULE chem_emissions_mod
    119126
    120     USE arrays_3d,                                                             &
     127    USE arrays_3d,                                                          &
    121128        ONLY:  rho_air
    122129
    123     USE control_parameters,                                                    &
    124         ONLY:  debug_output,                                                   &
    125                end_time, message_string, initializing_actions,                 &
     130    USE basic_constants_and_equations_mod,                                  &
     131        ONLY:  rgas_univ, p_0, rd_d_cp
     132
     133    USE control_parameters,                                                 &
     134        ONLY:  debug_output,                                                &
     135               end_time, message_string, initializing_actions,              &
    126136               intermediate_timestep_count, dt_3d
    127137 
     
    134144#endif
    135145
    136     USE netcdf_data_input_mod,                                                  &
     146    USE netcdf_data_input_mod,                                               &
    137147        ONLY: chem_emis_att_type, chem_emis_val_type
    138148
    139     USE date_and_time_mod,                                                      &
    140         ONLY: day_of_month, hour_of_day,                                        &
    141              index_mm, index_dd, index_hh,                                      &
    142              month_of_year, hour_of_day,                                        &
     149    USE date_and_time_mod,                                                   &
     150        ONLY: day_of_month, hour_of_day,                                     &
     151             index_mm, index_dd, index_hh,                                   &
     152             month_of_year, hour_of_day,                                     &
    143153             time_default_indices, time_preprocessed_indices
    144154   
    145     USE chem_gasphase_mod,                                                      &
     155    USE chem_gasphase_mod,                                                   &
    146156        ONLY: nvar, spc_names
    147157 
    148158    USE chem_modules
    149159
    150     USE statistics,                                                             &   
     160    USE statistics,                                                          &   
    151161        ONLY:  weight_pres
    152162
     
    159169    CHARACTER (LEN=80) ::  filename_emis             !< Variable for the name of the netcdf input file
    160170
     171    INTEGER(iwp) ::  dt_emis                         !< Time Step Emissions
    161172    INTEGER(iwp) ::  i                               !< index 1st selected dimension (some dims are not spatial)
    162173    INTEGER(iwp) ::  j                               !< index 2nd selected dimension
     
    165176    INTEGER(iwp) ::  j_start                         !< Index to start read variable from netcdf in additional dims
    166177    INTEGER(iwp) ::  j_end                           !< Index to end read variable from netcdf in additional dims
     178    INTEGER(iwp) ::  len_index                       !< length of index (used for several indices)
     179    INTEGER(iwp) ::  len_index_pm                    !< length of PMs index
     180    INTEGER(iwp) ::  len_index_voc                   !< length of voc index
    167181    INTEGER(iwp) ::  z_start                         !< Index to start read variable from netcdf in additional dims
    168182    INTEGER(iwp) ::  z_end                           !< Index to end read variable from netcdf in additional dims
    169     INTEGER(iwp) ::  dt_emis                         !< Time Step Emissions
    170     INTEGER(iwp) ::  len_index                       !< length of index (used for several indices)
    171     INTEGER(iwp) ::  len_index_voc                   !< length of voc index
    172     INTEGER(iwp) ::  len_index_pm                    !< length of PMs index
    173 
    174     REAL(wp) ::  con_factor                          !< Units Conversion Factor
    175                            
    176     REAL(wp), PARAMETER ::  Rgas = 8.3144                    !< gas constant in J/mol/K           
    177     REAL(wp), PARAMETER ::  pref_i  = 1.0_wp / 100000.0_wp   !< Inverse Reference Pressure (1/Pa)
    178     REAL(wp), PARAMETER ::  r_cp    = 0.286_wp               !< R / cp (exponent for potential temperature)
     183
     184    REAL(wp) ::  conversion_factor                   !< Units Conversion Factor
    179185
    180186    SAVE
     
    204210!
    205211!-- Public Variables
    206     PUBLIC con_factor, len_index, len_index_pm, len_index_voc
     212    PUBLIC conversion_factor, len_index, len_index_pm, len_index_voc
    207213
    208214 CONTAINS
     
    249255SUBROUTINE chem_emissions_match( emt_att,len_index )   
    250256
    251 
    252 
    253257    INTEGER(iwp)  ::  ind_inp                    !< Parameters for cycling through chemical input species
    254258    INTEGER(iwp)  ::  ind_mod                    !< Parameters for cycling through chemical model species
     
    282286          len_index = 0
    283287
    284           IF  ( nvar > 0 .AND. nspec_emis_inp > 0 )  THEN
     288! number of species and number of matched species can be different
     289! but call is only made if both are greater than zero
     290
     291          IF  ( nvar > 0  .AND.  nspec_emis_inp > 0 )  THEN
    285292
    286293!
    287294!-- Cycle over model species
    288295
    289              DO ind_mod = 1, nvar
     296             DO  ind_mod = 1, nvar
    290297                ind_inp = 1
    291                 DO WHILE ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )    !< 'novalue' is the default 
     298                DO  WHILE ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )    !< 'novalue' is the default 
    292299                   IF  ( TRIM( surface_csflux_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    293300                      len_index = len_index + 1
     
    310317                len_index = 0
    311318
    312                 DO ind_mod = 1, nvar 
     319                DO  ind_mod = 1, nvar 
    313320                   ind_inp = 1
    314                    DO WHILE  ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )
     321                   DO  WHILE  ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )
    315322                      IF  ( TRIM(surface_csflux_name(ind_inp)) ==          &
    316323                            TRIM(spc_names(ind_mod))            )  THEN
     
    326333!-- Check
    327334
    328                 DO ispec = 1, len_index
    329 
    330                    IF  ( emiss_factor_main(match_spec_input(ispec) ) < 0 .AND.    &
    331                         emiss_factor_side(match_spec_input(ispec) ) < 0 )  THEN
     335                DO  ispec = 1, len_index
     336
     337                   IF  ( emiss_factor_main(match_spec_input(ispec) ) < 0    .AND.     &
     338                         emiss_factor_side(match_spec_input(ispec) ) < 0 )  THEN
    332339
    333340                      message_string = 'PARAMETERIZED emissions mode selected:'             //          &
     
    370377       CASE (1)
    371378
    372           len_index = 0          ! TOTAL number of species (to be accumulated) 
    373           len_index_voc = 0      ! TOTAL number of VOCs (to be accumulated)
    374           len_index_pm = 3       ! TOTAL number of PMs: PM1, PM2.5, PM10.
    375  
    376           IF  ( nvar > 0 .AND. nspec_emis_inp > 0 )  THEN
     379          len_index = 0          ! total number of species (to be accumulated) 
     380          len_index_voc = 0      ! total number of VOCs (to be accumulated)
     381          len_index_pm = 3       ! total number of PMs: PM1, PM2.5, PM10.
     382
     383!
     384!-- number of model species and input species could be different
     385!-- but process this only when both are non-zero
     386 
     387          IF  ( nvar > 0  .AND.  nspec_emis_inp > 0 )  THEN
    377388
    378389!
    379390!-- Cycle over model species
    380              DO ind_mod = 1, nvar
     391             DO  ind_mod = 1, nvar
    381392
    382393!
    383394!-- Cycle over input species
    384395
    385                 DO ind_inp = 1, nspec_emis_inp
     396                DO  ind_inp = 1, nspec_emis_inp
    386397
    387398!
     
    389400
    390401                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN
    391                       DO ind_voc= 1, emt_att%nvoc
     402                      DO  ind_voc= 1, emt_att%nvoc
    392403                       
    393404                         IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
     
    483494                len_index_voc = 0
    484495               
    485                 DO ind_mod = 1, nvar
    486                    DO ind_inp = 1, nspec_emis_inp
     496                DO  ind_mod = 1, nvar
     497                   DO  ind_inp = 1, nspec_emis_inp
    487498
    488499!
    489500!-- VOCs
    490501
    491                       IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" .AND.       &
    492                            ALLOCATED (match_spec_voc_input) )  THEN
    493 
    494                          DO ind_voc = 1, emt_att%nvoc
     502                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC"  .AND.        &
     503                            ALLOCATED (match_spec_voc_input) )  THEN
     504
     505                         DO  ind_voc = 1, emt_att%nvoc
    495506
    496507                            IF  ( TRIM( emt_att%voc_name(ind_voc) ) ==                  &
     
    617628          len_index_voc = 0
    618629
    619           IF  ( nvar > 0 .AND. (nspec_emis_inp > 0) )  THEN
     630          IF  ( nvar > 0  .AND.  nspec_emis_inp > 0 )  THEN
    620631!
    621632!-- Cycle over model species
    622              DO ind_mod = 1, nvar
     633             DO  ind_mod = 1, nvar
    623634
    624635!
    625636!-- Cycle over input species 
    626                 DO ind_inp = 1, nspec_emis_inp
     637                DO  ind_inp = 1, nspec_emis_inp
    627638
    628639!
     
    630641
    631642                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN       
    632                       DO ind_voc = 1, emt_att%nvoc
     643                      DO  ind_voc = 1, emt_att%nvoc
    633644                         IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    634645                            len_index     = len_index + 1
     
    674685!-- Cycle over model species
    675686
    676                 DO ind_mod = 1, nvar
     687                DO  ind_mod = 1, nvar
    677688 
    678689!
    679690!-- Cycle over Input species 
    680691
    681                    DO ind_inp = 1, nspec_emis_inp
     692                   DO  ind_inp = 1, nspec_emis_inp
    682693
    683694!
    684695!-- VOCs
    685696
    686                       IF  ( TRIM(emt_att%species_name(ind_inp) ) == "VOC" .AND.    &
     697                      IF  ( TRIM(emt_att%species_name(ind_inp) ) == "VOC"  .AND.     &
    687698                           ALLOCATED(match_spec_voc_input) )  THEN
    688699                         
    689                          DO ind_voc= 1, emt_att%nvoc
     700                         DO  ind_voc= 1, emt_att%nvoc
    690701                            IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    691702                               len_index = len_index + 1
     
    716727
    717728!
    718 !-- in case there are no species matching
     729!-- in case there are no species matching (just informational message)
    719730
    720731                message_string = 'Non of given emission species'            //         &
     
    767778!> fluxes at timestep 0
    768779!------------------------------------------------------------------------------!
     780
    769781 SUBROUTINE chem_emissions_init
    770782
    771     USE netcdf_data_input_mod,                                                 &
     783    USE netcdf_data_input_mod,                                              &
    772784        ONLY:  chem_emis, chem_emis_att
    773785   
    774786    IMPLICIT NONE
    775787 
    776     INTEGER(iwp)                :: ispec                                            !< running index
     788    INTEGER(iwp) :: ispec                        !< running index
    777789
    778790!   
     
    810822       ALLOCATE( chem_emis_att%xm(n_matched_vars) )
    811823
    812        DO ispec = 1, n_matched_vars
     824       DO  ispec = 1, n_matched_vars
    813825          SELECT CASE ( TRIM( spc_names(match_spec_model(ispec)) ) )
    814826             CASE ( 'SO2'  );  chem_emis_att%xm(ispec) = xm_S + xm_O * 2
     
    837849!--        is defined, and mode if not) as we can easily take out
    838850!--        the case structure for mode_emis later on.
    839 !--        (ecc 20140424)
    840851
    841852       IF   ( emiss_lod < 0 )  THEN  !-- no LOD defined (not likely)
     
    845856             CASE ( 'PARAMETERIZED' )     ! LOD 0
    846857
    847                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     858                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    848859                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
    849860                ENDIF
     
    853864             CASE ( 'DEFAULT' )           ! LOD 1
    854865
    855                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     866                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    856867                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
    857868                ENDIF
     
    861872             CASE ( 'PRE-PROCESSED' )     ! LOD 2
    862873
    863                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     874                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    864875                   ALLOCATE( emis_distribution(nzb:nzt+1,0:ny,0:nx,n_matched_vars) )
    865876                ENDIF
     
    875886             CASE ( 0 )     ! parameterized mode
    876887
    877                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     888                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    878889                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
    879890                ENDIF
     
    883894             CASE ( 1 )     ! default mode
    884895
    885                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     896                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    886897                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
    887898                ENDIF
     
    891902             CASE ( 2 )     ! pre-processed mode
    892903
    893                 IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     904                IF  (  .NOT. ALLOCATED( emis_distribution) )  THEN
    894905                   ALLOCATE( emis_distribution(nzb:nzt+1,0:ny,0:nx,n_matched_vars) )
    895906                ENDIF
     
    900911
    901912       ENDIF
     913
     914!
     915! -- initialize
     916
     917       emis_distribution = 0.0_wp
    902918
    903919    ENDIF
     
    917933 SUBROUTINE chem_emissions_setup( emt_att, emt, n_matched_vars )
    918934 
    919    USE surface_mod,                                                  &
     935   USE surface_mod,                                               &
    920936       ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
    921    USE netcdf_data_input_mod,                                        &
     937
     938   USE netcdf_data_input_mod,                                     &
    922939       ONLY:  street_type_f
    923    USE arrays_3d,                                                    &       
     940
     941   USE arrays_3d,                                                 &       
    924942       ONLY: hyp, pt
    925943
     
    937955
    938956    INTEGER(iwp) ::  i                                                          !< running index for grid in x-direction
     957    INTEGER(iwp) ::  i_pm_comp                                                  !< index for number of PM components
     958    INTEGER(iwp) ::  icat                                                       !< Index for number of categories
     959    INTEGER(iwp) ::  ispec                                                      !< index for number of species
     960    INTEGER(iwp) ::  ivoc                                                       !< Index for number of VOCs
    939961    INTEGER(iwp) ::  j                                                          !< running index for grid in y-direction
    940962    INTEGER(iwp) ::  k                                                          !< running index for grid in z-direction
    941963    INTEGER(iwp) ::  m                                                          !< running index for horizontal surfaces
    942    
    943     INTEGER(iwp) ::  icat                                                       !< Index for number of categories
    944     INTEGER(iwp) ::  ispec                                                      !< index for number of species
    945     INTEGER(iwp) ::  i_pm_comp                                                  !< index for number of PM components
    946     INTEGER(iwp) ::  ivoc                                                       !< Index for number of VOCs
    947 
    948     REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::  delta_emis                       
    949     REAL(wp), ALLOCATABLE, DIMENSION(:)   ::  time_factor                       !< factor for time scaling of emissions
    950     REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::  emis
    951 
    952     REAL(wp), DIMENSION(24) :: par_emis_time_factor                             !< time factors for the parameterized mode:
    953                                                                                 !< fixed houlry profile for example day
    954     REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  conv_to_ratio            !< factor used for converting input
    955                                                                                 !< to concentration ratio
    956     REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  tmp_temp
    957964
    958965    !
    959966    !-- CONVERSION FACTORS: TIME 
    960     REAL(wp), PARAMETER ::  s_per_hour = 3600.0                       !< number of sec per hour (s)/(hour)   
    961     REAL(wp), PARAMETER ::  s_per_day = 86400.0                       !< number of sec per day (s)/(day) 
    962     REAL(wp), PARAMETER ::  hour_per_year = 8760.0                    !< number of hours in a year of 365 days 
    963     REAL(wp), PARAMETER ::  hour_per_day = 24.0                       !< number of hours in a day
    964    
    965     REAL(wp), PARAMETER ::  hour_to_s = 1/s_per_hour                  !< conversion from hours to seconds (s/hour) ~ 0.2777778     
    966     REAL(wp), PARAMETER ::  day_to_s = 1/s_per_day                    !< conversion from day to seconds (s/day) ~ 1.157407e-05
    967     REAL(wp), PARAMETER ::  year_to_s = 1/(s_per_hour*hour_per_year)  !< conversion from year to sec (s/year) ~ 3.170979e-08
     967    REAL(wp), PARAMETER ::  hour_per_year =  8760.0_wp  !< number of hours in a year of 365 days 
     968    REAL(wp), PARAMETER ::  hour_per_day  =    24.0_wp  !< number of hours in a day
     969    REAL(wp), PARAMETER ::  s_per_hour    =  3600.0_wp  !< number of sec per hour (s)/(hour)   
     970    REAL(wp), PARAMETER ::  s_per_day     = 86400.0_wp  !< number of sec per day (s)/(day) 
     971
     972    REAL(wp), PARAMETER ::  day_to_s      = 1.0_wp/s_per_day                   !< conversion day   -> sec
     973    REAL(wp), PARAMETER ::  hour_to_s     = 1.0_wp/s_per_hour                  !< conversion hours -> sec
     974    REAL(wp), PARAMETER ::  year_to_s     = 1.0_wp/(s_per_hour*hour_per_year)  !< conversion year  -> sec
    968975    !
    969     !-- CONVERSION FACTORS: WEIGHT 
    970     REAL(wp), PARAMETER ::  tons_to_kg = 100                          !< Conversion from tons to kg (kg/tons)   
    971     REAL(wp), PARAMETER ::  g_to_kg = 0.001                           !< Conversion from g to kg (kg/g)
    972     REAL(wp), PARAMETER ::  miug_to_kg = 0.000000001                  !< Conversion from g to kg (kg/g)
     976    !-- CONVERSION FACTORS: MASS
     977    REAL(wp), PARAMETER ::  g_to_kg       = 1.0E-03_wp     !< Conversion from g to kg (kg/g)
     978    REAL(wp), PARAMETER ::  miug_to_kg    = 1.0E-09_wp     !< Conversion from g to kg (kg/g)
     979    REAL(wp), PARAMETER ::  tons_to_kg    = 100.0_wp       !< Conversion from tons to kg (kg/tons)   
    973980    !
    974     !-- CONVERSION FACTORS: fraction to ppm
    975     REAL(wp), PARAMETER ::  ratio2ppm  = 1.0e06 
    976     !------------------------------------------------------   
     981    !-- CONVERSION FACTORS: PPM
     982    REAL(wp), PARAMETER ::  ratio2ppm     = 1.0E+06_wp
     983 
     984    REAL(wp), DIMENSION(24)                        ::  par_emis_time_factor    !< time factors for the parameterized mode:
     985                                                                               !< fixed houlry profile for example day
     986    REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  conv_to_ratio           !< factor used for converting input
     987                                                                               !< to concentration ratio
     988    REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  tmp_temp                !< temporary variable for abs. temperature
     989
     990    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  delta_emis   !< incremental emission factor                     
     991    REAL(wp), DIMENSION(:),   ALLOCATABLE ::  time_factor  !< factor for time scaling of emissions
     992    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  emis         !< emission factor
    977993
    978994    IF  ( emission_output_required )  THEN
    979995
    980        !
    981        !-- Set emis_dt 
     996!
     997!-- Set emis_dt to be used - since chemistry ODEs can be stiff, the option
     998!-- to solve them at every RK substep is present to help improve stability
     999!-- should the need arises
     1000 
    9821001       IF  ( call_chem_at_all_substeps )  THEN
    9831002
     
    9941013 !-- In PARAMETERIZED mode no conversion is performed: in this case input units are fixed
    9951014
    996         IF  ( TRIM( mode_emis ) == "DEFAULT" .OR. TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
     1015        IF  ( TRIM( mode_emis ) == "DEFAULT"  .OR. TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
    9971016
    9981017          SELECT CASE ( TRIM( emt_att%units ) )
    9991018
    1000              CASE ( 'kg/m2/s',    'KG/M2/S'    );  con_factor = 1.0_wp                   ! kg
    1001              CASE ( 'kg/m2/hour', 'KG/M2/HOUR' );  con_factor = hour_to_s
    1002              CASE ( 'kg/m2/day',  'KG/M2/DAY'  );  con_factor = day_to_s
    1003              CASE ( 'kg/m2/year', 'KG/M2/YEAR' );  con_factor = year_to_s
    1004 
    1005              CASE ( 'ton/m2/s',    'TON/M2/S'    );  con_factor = tons_to_kg             ! tonnes
    1006              CASE ( 'ton/m2/hour', 'TON/M2/HOUR' );  con_factor = tons_to_kg*hour_to_s
    1007              CASE ( 'ton/m2/year', 'TON/M2/YEAR' );  con_factor = tons_to_kg*year_to_s
    1008 
    1009              CASE ( 'g/m2/s',    'G/M2/S'    );  con_factor = g_to_kg                    ! grams
    1010              CASE ( 'g/m2/hour', 'G/M2/HOUR' );  con_factor = g_to_kg*hour_to_s
    1011              CASE ( 'g/m2/year', 'G/M2/YEAR' );  con_factor = g_to_kg*year_to_s
    1012 
    1013              CASE ( 'micrograms/m2/s',    'MICROGRAMS/M2/S'    );  con_factor = miug_to_kg            ! ug
    1014              CASE ( 'micrograms/m2/hour', 'MICROGRAMS/M2/HOUR' );  con_factor = miug_to_kg*hour_to_s
    1015              CASE ( 'micrograms/m2/year', 'MICROGRAMS/M2/YEAR' );  con_factor = miug_to_kg*year_to_s
     1019             CASE ( 'kg/m2/s', 'KG/M2/S'    );     conversion_factor = 1.0_wp                   ! kg
     1020             CASE ( 'kg/m2/hour', 'KG/M2/HOUR' );  conversion_factor = hour_to_s
     1021             CASE ( 'kg/m2/day', 'KG/M2/DAY'  );   conversion_factor = day_to_s
     1022             CASE ( 'kg/m2/year', 'KG/M2/YEAR' );  conversion_factor = year_to_s
     1023
     1024             CASE ( 'ton/m2/s', 'TON/M2/S'    );     conversion_factor = tons_to_kg             ! tonnes
     1025             CASE ( 'ton/m2/hour', 'TON/M2/HOUR' );  conversion_factor = tons_to_kg*hour_to_s
     1026             CASE ( 'ton/m2/year', 'TON/M2/YEAR' );  conversion_factor = tons_to_kg*year_to_s
     1027
     1028             CASE ( 'g/m2/s', 'G/M2/S'    );     conversion_factor = g_to_kg                    ! grams
     1029             CASE ( 'g/m2/hour', 'G/M2/HOUR' );  conversion_factor = g_to_kg*hour_to_s
     1030             CASE ( 'g/m2/year', 'G/M2/YEAR' );  conversion_factor = g_to_kg*year_to_s
     1031
     1032             CASE ( 'micrograms/m2/s', 'MICROGRAMS/M2/S'    );     conversion_factor = miug_to_kg            ! ug
     1033             CASE ( 'micrograms/m2/hour', 'MICROGRAMS/M2/HOUR' );  conversion_factor = miug_to_kg*hour_to_s
     1034             CASE ( 'micrograms/m2/year', 'MICROGRAMS/M2/YEAR' );  conversion_factor = miug_to_kg*year_to_s
    10161035
    10171036!
     
    10311050!-- Conversion factor to convert  kg/m**2/s to ppm/s
    10321051
    1033        DO i = nxl, nxr
    1034           DO j = nys, nyn
     1052       DO  i = nxl, nxr
     1053          DO  j = nys, nyn
    10351054
    10361055!
    10371056!-- Derive Temperature from Potential Temperature
    10381057
    1039              tmp_temp(nzb:nzt+1,j,i) = pt(nzb:nzt+1,j,i) * ( hyp(nzb:nzt+1) * pref_i )**r_cp
     1058             tmp_temp(nzb:nzt+1,j,i) = pt(nzb:nzt+1,j,i) *                     &
     1059                                       ( hyp(nzb:nzt+1) / p_0 )**rd_d_cp
    10401060 
    10411061!           
     
    10461066!-- V/N = RT/P
    10471067
     1068             conv_to_ratio(nzb:nzt+1,j,i) =  rgas_univ *                       &  ! J K-1 mol-1
     1069                                             tmp_temp(nzb:nzt+1,j,i) /         &  ! K
     1070                                             hyp(nzb:nzt+1)                       ! Pa
     1071
     1072! (ecc) for reference
    10481073!                   m**3/Nmole               (J/mol)*K^-1           K                      Pa         
    1049              conv_to_ratio(nzb:nzt+1,j,i) = ( (Rgas * tmp_temp(nzb:nzt+1,j,i)) / ((hyp(nzb:nzt+1))) ) 
     1074!             conv_to_ratio(nzb:nzt+1,j,i) = ( (Rgas * tmp_temp(nzb:nzt+1,j,i)) / ((hyp(nzb:nzt+1))) ) 
    10501075
    10511076          ENDDO
     
    10531078
    10541079
     1080! (ecc) moved initialization immediately after allocation
    10551081!
    10561082!-- Initialize
    10571083
    1058        emis_distribution(:,nys:nyn,nxl:nxr,:) = 0.0_wp
     1084!       emis_distribution(:,nys:nyn,nxl:nxr,:) = 0.0_wp
    10591085
    10601086 
     
    10841110!-- Allocate array where to store temporary emission values
    10851111
    1086           IF  ( .NOT. ALLOCATED(emis) ) ALLOCATE( emis(nys:nyn,nxl:nxr) )
     1112          IF  (  .NOT. ALLOCATED(emis) ) ALLOCATE( emis(nys:nyn,nxl:nxr) )
    10871113
    10881114!
     
    11291155!
    11301156!-- Update time indices
    1131              CALL time_default_indices( daytype_mdh, month_of_year, day_of_month,     &
     1157             CALL time_default_indices( daytype_mdh, month_of_year, day_of_month,  &
    11321158                  hour_of_day, index_mm, index_dd,index_hh )
    11331159
     
    11781204!-- assign constant values of time factors, diurnal profile for traffic sector
    11791205
    1180           par_emis_time_factor( : ) =  (/ 0.009, 0.004, 0.004, 0.009, 0.029, 0.039,      &
    1181                                           0.056, 0.053, 0.051, 0.051, 0.052, 0.055,      &
    1182                                           0.059, 0.061, 0.064, 0.067, 0.069, 0.069,      &
     1206          par_emis_time_factor( : ) =  (/ 0.009, 0.004, 0.004, 0.009, 0.029, 0.039,   &
     1207                                          0.056, 0.053, 0.051, 0.051, 0.052, 0.055,   &
     1208                                          0.059, 0.061, 0.064, 0.067, 0.069, 0.069,   &
    11831209                                          0.049, 0.039, 0.039, 0.029, 0.024, 0.019 /)
    11841210         
    1185           IF  ( .NOT. ALLOCATED (time_factor) )  ALLOCATE (time_factor(1))
     1211          IF  (  .NOT. ALLOCATED (time_factor) )  ALLOCATE (time_factor(1))
    11861212
    11871213!
     
    12051231!       IF  ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
    12061232
    1207           DO ispec = 1, n_matched_vars
     1233          DO  ispec = 1, n_matched_vars
    12081234
    12091235!
     
    12141240                       time_factor(1) * hour_to_s
    12151241
    1216           ENDDO
     1242          ENDDO  
    12171243
    12181244         
     
    12341260!-- Cycle over categories
    12351261
    1236           DO icat = 1, emt_att%ncat
     1262          DO  icat = 1, emt_att%ncat
    12371263 
    12381264!
     
    12401266!-- in common between the emission input data and the chemistry mechanism used
    12411267
    1242              DO ispec = 1, n_matched_vars
     1268             DO  ispec = 1, n_matched_vars
    12431269
    12441270                emis(nys:nyn,nxl:nxr) =                    &
     
    12541280                                                 time_factor(icat) *           &
    12551281                                                 emt_att%nox_comp(icat,1) *    &
    1256                                                  con_factor * hour_per_day
     1282                                                 conversion_factor * hour_per_day
    12571283
    12581284                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     
    12671293                                                 time_factor(icat) *           &
    12681294                                                 emt_att%nox_comp(icat,2) *    &
    1269                                                  con_factor * hour_per_day
     1295                                                 conversion_factor * hour_per_day
    12701296
    12711297                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     
    12801306                                                 time_factor(icat) *           &
    12811307                                                 emt_att%sox_comp(icat,1) *    &
    1282                                                  con_factor * hour_per_day
     1308                                                 conversion_factor * hour_per_day
    12831309
    12841310                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     
    12951321                                                 time_factor(icat) *           &
    12961322                                                 emt_att%sox_comp(icat,2) *    &
    1297                                                  con_factor * hour_per_day
     1323                                                 conversion_factor * hour_per_day
    12981324
    12991325                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     
    13121338                                                    time_factor(icat) *                  &
    13131339                                                    emt_att%pm_comp(icat,i_pm_comp,1) *  &
    1314                                                     con_factor * hour_per_day
     1340                                                    conversion_factor * hour_per_day
    13151341
    13161342                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     
    13301356                                                    time_factor(icat) *                  &
    13311357                                                    emt_att%pm_comp(icat,i_pm_comp,2) *  &
    1332                                                     con_factor * hour_per_day
     1358                                                    conversion_factor * hour_per_day
    13331359
    13341360                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     
    13481374                                                    time_factor(icat)     *              &
    13491375                                                    emt_att%pm_comp(icat,i_pm_comp,3) *  &
    1350                                                     con_factor * hour_per_day
     1376                                                    conversion_factor * hour_per_day
    13511377
    13521378                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     
    13691395                                                       time_factor(icat) *               &
    13701396                                                       emt_att%voc_comp(icat,match_spec_voc_input(ivoc)) *   &
    1371                                                        con_factor * hour_per_day
     1397                                                       conversion_factor * hour_per_day
    13721398
    13731399                         emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                    &
     
    13861412                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *                 &
    13871413                                                 time_factor(icat) *                     &
    1388                                                  con_factor * hour_per_day
     1414                                                 conversion_factor * hour_per_day
    13891415 
    13901416                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                          &
     
    13941420                ENDIF  ! TRIM spc_names
    13951421               
    1396                 emis(:,:)= 0
     1422                emis = 0
    13971423               
    13981424             ENDDO
    13991425             
    1400              delta_emis(:,:)=0
     1426             delta_emis = 0
    14011427         
    14021428          ENDDO
     
    14141440!-- in common between the emission input data and the chemistry mechanism used
    14151441
    1416           DO ispec = 1, n_matched_vars 
     1442          DO  ispec = 1, n_matched_vars 
    14171443 
    14181444! (ecc)   
     
    14201446                       emt(match_spec_input(ispec))%                                     &
    14211447                           preproc_emission_data(index_hh,1,nys+1:nyn+1,nxl+1:nxr+1) *   &
    1422                        con_factor
     1448                       conversion_factor
    14231449
    14241450
     
    14261452!                       emt(match_spec_input(ispec))%                                     &
    14271453!                           preproc_emission_data(index_hh,1,:,:) *   &
    1428 !                       con_factor
     1454!                       conversion_factor
    14291455          ENDDO
    14301456
     
    14641490                k = surf_lsm_h%k(m)
    14651491
     1492!
     1493!-- set everything to zero then reassign according to street type
     1494
     1495                surf_lsm_h%cssws(:,m) = 0.0_wp
     1496
    14661497                IF  ( street_type_f%var(j,i) >= main_street_id    .AND.                  &
    14671498                      street_type_f%var(j,i) < max_street_id   )  THEN
     
    14751506!-- PMs are already in kilograms
    14761507
    1477                       IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR. &
    1478                             TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR. &
     1508                      IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR.  &
     1509                            TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR.  &
    14791510                            TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
    14801511
     
    15161547!-- PMs are already in kilograms
    15171548
    1518                       IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR. &
    1519                             TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR. &
     1549                      IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"      .OR. &
     1550                            TRIM(spc_names(match_spec_model(ispec))) == "PM25"     .OR. &
    15201551                            TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
    15211552
     
    15481579!-- If no street type is defined, then assign zero emission to all the species
    15491580
    1550                 ELSE
    1551 
    1552                    surf_lsm_h%cssws(:,m) = 0.0_wp
     1581! (ecc) moved to front (for reference)
     1582!                ELSE
     1583!
     1584!                   surf_lsm_h%cssws(:,m) = 0.0_wp
    15531585
    15541586                ENDIF  ! street type
     
    15661598       
    15671599
    1568           DO ispec = 1, n_matched_vars
     1600          DO  ispec = 1, n_matched_vars
    15691601                   
    15701602!
     
    17021734!
    17031735!-- VOCs
    1704                       IF  ( len_index_voc > 0                                           .AND.      &
     1736                      IF  ( len_index_voc > 0                                         .AND.      &
    17051737                            emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
    17061738
Note: See TracChangeset for help on using the changeset viewer.