Ignore:
Timestamp:
May 13, 2019 11:04:01 AM (5 years ago)
Author:
suehring
Message:

Updates from chemistriy branched merged into trunk: code cleaning and formatting, code structure optimizations

File:
1 edited

Legend:

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

    r3885 r3968  
    2727! -----------------
    2828! $Id$
     29! - in subroutine chem_emissions_match replace all decision structures relating to
     30!   mode_emis to emiss_lod
     31! - in subroutine chem_check_parameters replace emt%nspec with emt%n_emiss_species
     32! - spring cleaning (E.C. Chan)
     33!
     34! 3885 2019-04-11 11:29:34Z kanani
    2935! Changes related to global restructuring of location messages and introduction
    3036! of additional debug messages
     
    3642! Removed unused variables from chem_emissions_mod
    3743!
    38 !3772 2019-02-28 15:51:57Z suehring
     44! 3772 2019-02-28 15:51:57Z suehring
    3945! - In case of parametrized emissions, assure that emissions are only on natural
    4046!   surfaces (i.e. streets) and not on urban surfaces.
    4147! - some unnecessary if clauses removed
    4248!
    43 !3685 2019 -01-21 01:02:11Z knoop
     49! 3685 2019 -01-21 01:02:11Z knoop
    4450! Some interface calls moved to module_interface + cleanup
    4551!
     
    172178    REAL(wp), PARAMETER ::  r_cp    = 0.286_wp               !< R / cp (exponent for potential temperature)
    173179
    174 
    175180    SAVE
    176 
    177181
    178182!   
     
    196200       MODULE PROCEDURE chem_emissions_setup
    197201    END INTERFACE chem_emissions_setup
    198 
    199 
    200202   
    201203    PUBLIC chem_emissions_init, chem_emissions_match, chem_emissions_setup
     
    213215 SUBROUTINE chem_emissions_check_parameters
    214216
    215 
    216217    IMPLICIT NONE
    217218
    218219    TYPE(chem_emis_att_type) ::  emt
    219220
    220     !
    221     !-- Check Emission Species Number equal to number of passed names for the chemistry species:
    222     IF ( SIZE(emt%species_name) /= emt%nspec  )  THEN
     221!
     222!-- Check if species count matches the number of names
     223!-- passed for the chemiscal species
     224
     225    IF  ( SIZE(emt%species_name) /= emt%n_emiss_species  )  THEN
     226!    IF  ( SIZE(emt%species_name) /= emt%nspec  )  THEN
    223227
    224228       message_string = 'Numbers of input emission species names and number of species'     //      &
     
    227231           
    228232    ENDIF
    229    
    230233
    231234 END SUBROUTINE chem_emissions_check_parameters
     235
    232236
    233237!------------------------------------------------------------------------------!
    234238! Description:
    235239! ------------
    236 !> Matching the chemical species indices. The routine checks what are the indices of the emission input species
    237 !> and the corresponding ones of the model species. The routine gives as output a vector containing the number
    238 !> of common species: it is important to note that while the model species are distinct, their values could be
    239 !> given to a single species in input: for example, in the case of NO2 and NO, values may be passed in input as
    240 !> NOx values.
     240!> Matching the chemical species indices. The routine checks what are the
     241!> indices of the emission input species and the corresponding ones of the
     242!> model species. The routine gives as output a vector containing the number
     243!> of common species: it is important to note that while the model species
     244!> are distinct, their values could be given to a single species in input.
     245!> For example, in the case of NO2 and NO, values may be passed in input as
     246!> NOX values.
    241247!------------------------------------------------------------------------------!
     248
    242249SUBROUTINE chem_emissions_match( emt_att,len_index )   
    243250
    244251
    245     INTEGER(iwp), INTENT(INOUT)             ::  len_index   !< Variable where to store the number of common species between the input dataset and the model species   
    246 
    247     TYPE(chem_emis_att_type), INTENT(INOUT) ::  emt_att     !< Chemistry Emission Array containing information for all the input chemical emission species
    248    
    249     INTEGER(iwp) ::  ind_mod, ind_inp                       !< Parameters for cycling through chemical model and input species
    250     INTEGER(iwp) ::  nspec_emis_inp                         !< Variable where to store the number of the emission species in input
    251     INTEGER(iwp) ::  ind_voc                                !< Indices to check whether a split for voc should be done
    252     INTEGER(iwp) ::  ispec                                  !< index for cycle over effective number of emission species
    253 
    254 
    255     IF ( debug_output )  CALL debug_message( 'chem_emissions_match', 'start' )
    256 
    257     !
    258     !-- Number of input emission species.
    259     nspec_emis_inp=emt_att%nspec
    260 
    261     !
    262     !-- Check the emission mode: DEFAULT, PRE-PROCESSED or PARAMETERIZED
    263     SELECT CASE( TRIM( mode_emis ) )
    264 
    265        !
    266        !-- PRE-PROCESSED mode
    267        CASE ( "PRE-PROCESSED" )
     252
     253    INTEGER(iwp)  ::  ind_inp                    !< Parameters for cycling through chemical input species
     254    INTEGER(iwp)  ::  ind_mod                    !< Parameters for cycling through chemical model species
     255    INTEGER(iwp)  ::  ind_voc                    !< Indices to check whether a split for voc should be done
     256    INTEGER(iwp)  ::  ispec                      !< index for cycle over effective number of emission species
     257    INTEGER(iwp)  ::  nspec_emis_inp             !< Variable where to store # of emission species in input
     258
     259    INTEGER(iwp), INTENT(INOUT)  ::  len_index   !< number of common species between input dataset & model species
     260
     261    TYPE(chem_emis_att_type), INTENT(INOUT) ::  emt_att     !< Chemistry Emission Array (decl. netcdf_data_input.f90)
     262
     263
     264    IF  ( debug_output )  CALL debug_message( 'chem_emissions_match', 'start' )
     265
     266!
     267!-- Number of input emission species
     268
     269    nspec_emis_inp = emt_att%n_emiss_species
     270!    nspec_emis_inp=emt_att%nspec
     271
     272!
     273!-- Check the emission LOD: 0 (PARAMETERIZED), 1 (DEFAULT), 2 (PRE-PROCESSED)
     274!
     275    SELECT CASE (emiss_lod)
     276
     277!
     278!-- LOD 0 (PARAMETERIZED mode)
     279
     280       CASE (0)
    268281
    269282          len_index = 0
    270           len_index_voc = 0
    271 
    272           IF ( nvar > 0 .AND. (nspec_emis_inp > 0) )  THEN
    273              !
    274              !-- Cycle over model species
    275              DO ind_mod = 1,  nvar
    276                 !
    277                 !-- Cycle over input species 
    278                 DO ind_inp = 1, nspec_emis_inp
    279 
    280                    !
    281                    !-- Check for VOC Species 
    282                    IF ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN       
    283                       DO ind_voc = 1, emt_att%nvoc
    284              
    285                          IF ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    286                             len_index = len_index + 1
    287                             len_index_voc = len_index_voc + 1
    288                          ENDIF
    289                       END DO
    290                    ENDIF
    291                    !
    292                    !-- Other Species
    293                    IF ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    294                       len_index = len_index + 1
    295                    ENDIF
    296                 ENDDO
    297              ENDDO
    298 
    299              !
    300              !-- Allocate array for storing the indices of the matched species
    301              IF ( len_index > 0 )  THEN
    302  
    303                 ALLOCATE( match_spec_input(len_index) )
    304  
    305                 ALLOCATE( match_spec_model(len_index) )
    306 
    307                 IF ( len_index_voc > 0 )  THEN
    308                    !
    309                    !-- contains indices of the VOC model species
    310                    ALLOCATE( match_spec_voc_model(len_index_voc) )
    311                    !
    312                    !-- contains the indices of different values of VOC composition of input variable VOC_composition
    313                    ALLOCATE( match_spec_voc_input(len_index_voc) )
    314 
    315                 ENDIF
    316 
    317                 !
    318                 !-- pass the species indices to declared arrays
    319                 len_index = 0
    320 
    321                 !
    322                 !-- Cycle over model species
    323                 DO ind_mod = 1, nvar
    324                    !
    325                    !-- Cycle over Input species 
    326                    DO ind_inp = 1, nspec_emis_inp
    327                       !
    328                       !-- VOCs
    329                       IF ( TRIM(emt_att%species_name(ind_inp) ) == "VOC" .AND.    &
    330                            ALLOCATED(match_spec_voc_input) )  THEN
    331                          
    332                          DO ind_voc= 1, emt_att%nvoc
    333                             IF ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    334                                len_index = len_index + 1
    335                                len_index_voc = len_index_voc + 1
    336                        
    337                                match_spec_input(len_index) = ind_inp
    338                                match_spec_model(len_index) = ind_mod
    339 
    340                                match_spec_voc_input(len_index_voc) = ind_voc
    341                                match_spec_voc_model(len_index_voc) = ind_mod                         
    342                             ENDIF
    343                          END DO
    344                       ENDIF
    345 
    346                       !
    347                       !-- Other Species
    348                       IF ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    349                          len_index = len_index + 1
    350                          match_spec_input(len_index) = ind_inp
    351                          match_spec_model(len_index) = ind_mod
    352                       ENDIF
    353                    END DO
    354                 END DO
    355 
    356              ELSE
    357                 !
    358                 !-- in case there are no species matching
    359                 message_string = 'Non of given emission species'            //         &
    360                                  ' matches'                                //          &
    361                                  ' model chemical species:'                //          &
    362                                  ' Emission routine is not called' 
    363                 CALL message( 'chem_emissions_matching', 'CM0438', 0, 0, 0, 6, 0 )
    364              ENDIF
    365  
    366           ELSE
    367 
    368              !
    369              !-- either spc_names is zero or nspec_emis_inp is not allocated
    370              message_string = 'Array of Emission species not allocated:'             //          &
    371                               ' Either no emission species are provided as input or'  //         &
    372                               ' no chemical species are used by PALM:'                //         &
    373                               ' Emission routine is not called'                 
    374              CALL message( 'chem_emissions_matching', 'CM0439', 0, 2, 0, 6, 0 )
    375 
    376           ENDIF
    377 
    378        !
    379        !-- DEFAULT mode
    380        CASE ("DEFAULT")
    381 
    382           len_index = 0          !<  index for TOTAL number of species   
    383           len_index_voc = 0      !<  index for TOTAL number of VOCs
    384           len_index_pm = 3       !<  index for TOTAL number of PMs: PM1, PM2.5, PM10.
    385  
    386           IF ( nvar > 0 .AND. nspec_emis_inp > 0 )  THEN
    387 
    388              !
    389              !-- Cycle over model species
    390              DO ind_mod = 1, nvar
    391                 !
    392                 !-- Cycle over input species
    393                 DO ind_inp = 1, nspec_emis_inp
    394 
    395                    !
    396                    !-- Check for VOC Species 
    397                    IF ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN
    398                       DO ind_voc= 1, emt_att%nvoc
    399                        
    400                          IF ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    401                             len_index = len_index + 1
    402                             len_index_voc = len_index_voc + 1
    403                          ENDIF
    404                          
    405                       END DO
    406                    ENDIF
    407 
    408                    !
    409                    !-- PMs: There is one input species name for all PM
    410                    !-- This variable has 3 dimensions, one for PM1, PM2.5 and PM10
    411                    IF ( TRIM( emt_att%species_name(ind_inp) ) == "PM" )  THEN
    412                       !
    413                       !-- PM1
    414                       IF ( TRIM( spc_names(ind_mod) ) == "PM1" )  THEN
    415                          len_index = len_index + 1
    416                       !
    417                       !-- PM2.5
    418                       ELSEIF ( TRIM( spc_names(ind_mod) ) == "PM25" )  THEN
    419                          len_index = len_index + 1
    420                       !
    421                       !-- PM10
    422                       ELSEIF ( TRIM( spc_names(ind_mod) ) == "PM10" )  THEN
    423                          len_index = len_index + 1
    424                       ENDIF
    425                    ENDIF
    426 
    427                    !
    428                    !-- NOx: NO2 and NO   
    429                    IF ( TRIM( emt_att%species_name(ind_inp) ) == "NOx" )  THEN
    430                       !
    431                       !-- NO
    432                       IF ( TRIM( spc_names(ind_mod) ) == "NO" )  THEN
    433                          len_index = len_index + 1
    434                       !
    435                       !-- NO2
    436                       ELSEIF ( TRIM( spc_names(ind_mod) ) == "NO2" )  THEN
    437                          len_index = len_index + 1
    438                       ENDIF
    439                    ENDIF
    440 
    441                    !
    442                    !-- SOx: SO2 and SO4
    443                    IF ( TRIM( emt_att%species_name(ind_inp) ) == "SOx" )  THEN
    444                       !
    445                       !-- SO2
    446                       IF ( TRIM( spc_names(ind_mod) ) == "SO2" )  THEN
    447                          len_index = len_index + 1
    448                       !
    449                       !-- SO4
    450                       ELSEIF ( TRIM( spc_names(ind_mod) ) == "SO4" )  THEN
    451                          len_index = len_index + 1
    452                       ENDIF
    453                    ENDIF
    454 
    455                    !
    456                    !-- Other Species
    457                    IF ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    458                       len_index = len_index + 1
    459                    ENDIF
    460                 END DO
    461              END DO
    462 
    463 
    464              !
    465              !-- Allocate arrays
    466              IF ( len_index > 0 )  THEN
    467 
    468                 ALLOCATE( match_spec_input(len_index) )
    469                 ALLOCATE( match_spec_model(len_index) )
    470 
    471                 IF ( len_index_voc > 0 )  THEN
    472                    !
    473                    !-- Contains indices of the VOC model species
    474                    ALLOCATE( match_spec_voc_model(len_index_voc) )
    475                    !
    476                    !-- Contains the indices of different values of VOC composition
    477                    !-- of input variable VOC_composition
    478                    ALLOCATE( match_spec_voc_input(len_index_voc) )                                                 
    479                 ENDIF
    480 
    481                 !
    482                 !-- Pass the species indices to declared arrays
    483                 len_index = 0
    484                 len_index_voc = 0
    485                
    486                 DO ind_mod = 1, nvar
    487                    DO ind_inp = 1, nspec_emis_inp
    488 
    489                       !
    490                       !-- VOCs
    491                       IF ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" .AND.   &
    492                          ALLOCATED(match_spec_voc_input) )  THEN     
    493                          DO ind_voc= 1, emt_att%nvoc
    494                             IF ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
    495                                len_index = len_index + 1
    496                                len_index_voc = len_index_voc + 1
    497                        
    498                                match_spec_input(len_index) = ind_inp
    499                                match_spec_model(len_index) = ind_mod
    500 
    501                                match_spec_voc_input(len_index_voc) = ind_voc
    502                                match_spec_voc_model(len_index_voc) = ind_mod                         
    503                             ENDIF
    504                          END DO
    505                       ENDIF
    506 
    507                       !
    508                       !-- PMs
    509                       IF ( TRIM( emt_att%species_name(ind_inp) ) == "PM" )  THEN
    510                          !
    511                          !-- PM1
    512                          IF ( TRIM( spc_names(ind_mod) ) == "PM1" )  THEN
    513                             len_index = len_index + 1
    514 
    515                             match_spec_input(len_index) = ind_inp
    516                             match_spec_model(len_index) = ind_mod
    517                          !
    518                          !-- PM2.5
    519                          ELSEIF ( TRIM( spc_names(ind_mod) ) == "PM25" )  THEN
    520                             len_index = len_index + 1
    521 
    522                             match_spec_input(len_index) = ind_inp
    523                             match_spec_model(len_index) = ind_mod
    524                          !
    525                          !-- PM10
    526                          ELSEIF ( TRIM( spc_names(ind_mod) ) == "PM10" )  THEN
    527                             len_index = len_index + 1
    528    
    529                             match_spec_input(len_index) = ind_inp
    530                             match_spec_model(len_index) = ind_mod
    531  
    532                          ENDIF
    533                       ENDIF
    534 
    535                       !
    536                       !-- NOx
    537                       IF ( TRIM( emt_att%species_name(ind_inp) ) == "NOx" )  THEN
    538                          !
    539                          !-- NO
    540                          IF ( TRIM( spc_names(ind_mod) ) == "NO" )  THEN
    541                             len_index = len_index + 1
    542 
    543                             match_spec_input(len_index) = ind_inp
    544                             match_spec_model(len_index) = ind_mod
    545                          !
    546                          !-- NO2
    547                          ELSEIF ( TRIM( spc_names(ind_mod) ) == "NO2" )  THEN
    548                             len_index = len_index + 1
    549 
    550                             match_spec_input(len_index) = ind_inp
    551                             match_spec_model(len_index) = ind_mod
    552  
    553                          ENDIF
    554                       ENDIF
    555 
    556                       !
    557                       !-- SOx
    558                       IF ( TRIM( emt_att%species_name(ind_inp) ) == "SOx" ) THEN
    559                          !
    560                          !-- SO2
    561                          IF ( TRIM( spc_names(ind_mod) ) == "SO2" )  THEN
    562                             len_index = len_index + 1
    563 
    564                             match_spec_input(len_index) = ind_inp
    565                             match_spec_model(len_index) = ind_mod
    566  
    567                          !
    568                          !-- SO4
    569                          ELSEIF ( TRIM( spc_names(ind_mod) ) == "SO4" )  THEN
    570                             len_index = len_index + 1
    571 
    572                             match_spec_input(len_index) = ind_inp
    573                             match_spec_model(len_index) = ind_mod
    574  
    575                          ENDIF
    576                       ENDIF
    577 
    578                       !
    579                       !-- Other Species
    580                       IF ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    581                          len_index = len_index + 1
    582                            
    583                          match_spec_input(len_index) = ind_inp
    584                          match_spec_model(len_index) = ind_mod
    585                       ENDIF
    586                    END DO
    587                 END DO
    588 
    589              ELSE
    590 
    591                 message_string = 'Non of given Emission Species'            //         &
    592                                  ' matches'                                //          &
    593                                  ' model chemical species'                 //          &
    594                                  ' Emission routine is not called'         
    595                 CALL message( 'chem_emissions_matching', 'CM0440', 0, 0, 0, 6, 0 )
    596 
    597              ENDIF
    598 
    599           ELSE
    600 
    601              message_string = 'Array of Emission species not allocated: '            //          &
    602                               ' Either no emission species are provided as input or'  //         &
    603                               ' no chemical species are used by PALM:'                //         &
    604                               ' Emission routine is not called'                                   
    605              CALL message( 'chem_emissions_matching', 'CM0441', 0, 2, 0, 6, 0 )
    606  
    607           ENDIF
    608  
    609        !
    610        !-- PARAMETERIZED mode
    611        CASE ("PARAMETERIZED")
    612 
    613           len_index = 0
    614 
    615           IF ( nvar > 0 .AND. nspec_emis_inp > 0 )  THEN
    616 
    617              !
    618              !-- Cycle over model species
     283
     284          IF  ( nvar > 0 .AND. nspec_emis_inp > 0 )  THEN
     285
     286!
     287!-- Cycle over model species
     288
    619289             DO ind_mod = 1, nvar
    620290                ind_inp = 1
    621291                DO WHILE ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )    !< 'novalue' is the default 
    622                    IF ( TRIM( surface_csflux_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
     292                   IF  ( TRIM( surface_csflux_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
    623293                      len_index = len_index + 1
    624294                   ENDIF
     
    627297             ENDDO
    628298
    629              IF ( len_index > 0 )  THEN
    630 
    631                 !
    632                 !-- Allocation of Arrays of the matched species
    633                 ALLOCATE( match_spec_input(len_index) )
    634  
    635                 ALLOCATE( match_spec_model(len_index) )
    636 
    637                 !
    638                 !-- Pass the species indices to declared arrays   
     299             IF  ( len_index > 0 )  THEN
     300
     301!
     302!-- Allocation of Arrays of the matched species
     303
     304                ALLOCATE ( match_spec_input(len_index) )
     305                ALLOCATE ( match_spec_model(len_index) )
     306
     307!
     308!-- Pass species indices to declared arrays
     309
    639310                len_index = 0
    640311
    641312                DO ind_mod = 1, nvar 
    642313                   ind_inp = 1
    643                    DO WHILE ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )     
    644                       IF ( TRIM( surface_csflux_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
     314                   DO WHILE  ( TRIM( surface_csflux_name(ind_inp) ) /= 'novalue' )
     315                      IF  ( TRIM(surface_csflux_name(ind_inp)) ==          &
     316                            TRIM(spc_names(ind_mod))            )  THEN
    645317                         len_index = len_index + 1
    646318                         match_spec_input(len_index) = ind_inp
     
    651323                END DO
    652324
    653                 !
    654                 !-- Check
     325!
     326!-- Check
     327
    655328                DO ispec = 1, len_index
    656329
    657                    IF ( emiss_factor_main(match_spec_input(ispec) ) < 0 .AND.    &
     330                   IF  ( emiss_factor_main(match_spec_input(ispec) ) < 0 .AND.    &
    658331                        emiss_factor_side(match_spec_input(ispec) ) < 0 )  THEN
    659332
    660                       message_string = 'PARAMETERIZED emissions mode selected:'            //           &
     333                      message_string = 'PARAMETERIZED emissions mode selected:'             //          &
    661334                                       ' EMISSIONS POSSIBLE ONLY ON STREET SURFACES'        //          &
    662335                                       ' but values of scaling factors for street types'    //          &
     
    665338                                       ' or not provided at all: PLEASE set a finite value' //          &
    666339                                       ' for these parameters in the chemistry namelist'         
    667                       CALL message( 'chem_emissions_matching', 'CM0442', 2, 2, 0, 6, 0 )
     340                      CALL message( 'chem_emissions_matching', 'CM0442', 2, 2, 0, 6, 0 )
     341 
    668342                   ENDIF
     343
    669344                END DO
    670345
     
    672347             ELSE
    673348               
    674                 message_string = 'Non of given Emission Species'            //          &
     349                message_string = 'Non of given Emission Species'           //           &
    675350                                 ' matches'                                //           &
    676351                                 ' model chemical species'                 //           &
    677352                                 ' Emission routine is not called'         
    678                 CALL message( 'chem_emissions_matching', 'CM0443', 0, 0, 0, 6, 0 )
     353                CALL message( 'chem_emissions_matching', 'CM0443', 0, 0, 0, 6, 0 )
     354 
    679355             ENDIF
    680356
    681357          ELSE
    682358     
    683              message_string = 'Array of Emission species not allocated: '            //           &
     359             message_string = 'Array of Emission species not allocated: '             //          &
    684360                              ' Either no emission species are provided as input or'  //          &
    685361                              ' no chemical species are used by PALM.'                //          &
     
    687363             CALL message( 'chem_emissions_matching', 'CM0444', 0, 2, 0, 6, 0 )
    688364 
    689           ENDIF             
    690 
    691 
    692        !
    693        !-- If emission module is switched on but mode_emis is not specified or it is given the wrong name
     365          ENDIF
     366
     367!
     368!-- LOD 1 (DEFAULT mode)
     369
     370       CASE (1)
     371
     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
     377
     378!
     379!-- Cycle over model species
     380             DO ind_mod = 1, nvar
     381
     382!
     383!-- Cycle over input species
     384
     385                DO ind_inp = 1, nspec_emis_inp
     386
     387!
     388!-- Check for VOC Species
     389
     390                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN
     391                      DO ind_voc= 1, emt_att%nvoc
     392                       
     393                         IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
     394                            len_index = len_index + 1
     395                            len_index_voc = len_index_voc + 1
     396                         ENDIF
     397                         
     398                      END DO
     399                   ENDIF
     400
     401!
     402!-- PMs: There is one input species name for all PM
     403!-- This variable has 3 dimensions, one for PM1, PM2.5 and PM10
     404
     405                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "PM" )  THEN
     406
     407                      IF      ( TRIM( spc_names(ind_mod) ) == "PM1" )   THEN
     408                         len_index = len_index + 1
     409                      ELSEIF  ( TRIM( spc_names(ind_mod) ) == "PM25" )  THEN
     410                         len_index = len_index + 1
     411                      ELSEIF  ( TRIM( spc_names(ind_mod) ) == "PM10" )  THEN
     412                         len_index = len_index + 1
     413                      ENDIF
     414
     415                   ENDIF
     416
     417!
     418!-- NOX: NO2 and NO
     419
     420                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "NOX" )  THEN
     421
     422                      IF     ( TRIM( spc_names(ind_mod) ) == "NO"  )  THEN
     423                         len_index = len_index + 1
     424                      ELSEIF  ( TRIM( spc_names(ind_mod) ) == "NO2" )  THEN
     425                         len_index = len_index + 1
     426                      ENDIF
     427
     428                   ENDIF
     429
     430!
     431!-- SOX: SO2 and SO4
     432
     433                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "SOX" )  THEN
     434
     435                      IF      ( TRIM( spc_names(ind_mod) ) == "SO2" )  THEN
     436                         len_index = len_index + 1
     437                      ELSEIF  ( TRIM( spc_names(ind_mod) ) == "SO4" )  THEN
     438                         len_index = len_index + 1
     439                      ENDIF
     440
     441                   ENDIF
     442
     443!
     444!-- Other Species
     445
     446                   IF  ( TRIM( emt_att%species_name(ind_inp) ) ==             &
     447                        TRIM( spc_names(ind_mod) ) )  THEN
     448                      len_index = len_index + 1
     449                   ENDIF
     450
     451                END DO  ! ind_inp ...
     452
     453             END DO  ! ind_mod ...
     454
     455
     456!
     457!-- Allocate arrays
     458
     459             IF  ( len_index > 0 )  THEN
     460
     461                ALLOCATE ( match_spec_input(len_index) )
     462                ALLOCATE ( match_spec_model(len_index) )
     463
     464                IF  ( len_index_voc > 0 )  THEN
     465
     466!
     467!-- Contains indices of the VOC model species
     468
     469                   ALLOCATE( match_spec_voc_model(len_index_voc) )
     470
     471!
     472!-- Contains the indices of different values of VOC composition
     473!-- of input variable VOC_composition
     474
     475                   ALLOCATE( match_spec_voc_input(len_index_voc) )
     476
     477                ENDIF
     478
     479!
     480!-- Pass the species indices to declared arrays
     481
     482                len_index = 0
     483                len_index_voc = 0
     484               
     485                DO ind_mod = 1, nvar
     486                   DO ind_inp = 1, nspec_emis_inp
     487
     488!
     489!-- VOCs
     490
     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
     495
     496                            IF  ( TRIM( emt_att%voc_name(ind_voc) ) ==                  &
     497                                 TRIM( spc_names(ind_mod) ) )  THEN
     498
     499                               len_index     = len_index + 1
     500                               len_index_voc = len_index_voc + 1
     501                       
     502                               match_spec_input(len_index) = ind_inp
     503                               match_spec_model(len_index) = ind_mod
     504
     505                               match_spec_voc_input(len_index_voc) = ind_voc
     506                               match_spec_voc_model(len_index_voc) = ind_mod
     507
     508                            ENDIF
     509
     510                         END DO
     511
     512                      ENDIF
     513
     514!
     515!-- PMs
     516
     517                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == "PM" )  THEN
     518
     519                         IF      ( TRIM( spc_names(ind_mod) ) == "PM1"  )  THEN
     520                            len_index = len_index + 1
     521                            match_spec_input(len_index) = ind_inp
     522                            match_spec_model(len_index) = ind_mod
     523                         ELSEIF  ( TRIM( spc_names(ind_mod) ) == "PM25" )  THEN
     524                            len_index = len_index + 1
     525                            match_spec_input(len_index) = ind_inp
     526                            match_spec_model(len_index) = ind_mod
     527                         ELSEIF  ( TRIM( spc_names(ind_mod) ) == "PM10" )  THEN
     528                            len_index = len_index + 1
     529                            match_spec_input(len_index) = ind_inp
     530                            match_spec_model(len_index) = ind_mod
     531                         ENDIF
     532
     533                      ENDIF
     534
     535!
     536!-- NOX
     537                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == "NOX" )  THEN
     538
     539                         IF      ( TRIM( spc_names(ind_mod) ) == "NO"  )  THEN
     540                            len_index = len_index + 1
     541
     542                            match_spec_input(len_index) = ind_inp
     543                            match_spec_model(len_index) = ind_mod
     544
     545                         ELSEIF  ( TRIM( spc_names(ind_mod) ) == "NO2" )  THEN
     546                            len_index = len_index + 1
     547
     548                            match_spec_input(len_index) = ind_inp
     549                            match_spec_model(len_index) = ind_mod
     550 
     551                         ENDIF
     552
     553                      ENDIF
     554
     555
     556!
     557!-- SOX
     558
     559                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == "SOX" ) THEN
     560
     561                         IF  ( TRIM( spc_names(ind_mod) ) == "SO2" )  THEN
     562                            len_index = len_index + 1
     563                            match_spec_input(len_index) = ind_inp
     564                            match_spec_model(len_index) = ind_mod
     565                         ELSEIF  ( TRIM( spc_names(ind_mod) ) == "SO4" )  THEN
     566                            len_index = len_index + 1
     567                            match_spec_input(len_index) = ind_inp
     568                            match_spec_model(len_index) = ind_mod
     569                         ENDIF
     570
     571                      ENDIF
     572
     573!
     574!-- Other Species
     575
     576                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
     577                         len_index = len_index + 1
     578                         match_spec_input(len_index) = ind_inp
     579                         match_spec_model(len_index) = ind_mod
     580                      ENDIF
     581
     582                   END DO  ! inp_ind
     583
     584                END DO     ! inp_mod
     585
     586!
     587!-- Error reporting (no matching)
     588
     589             ELSE
     590
     591                message_string = 'None of given Emission Species matches'           //   &
     592                                 ' model chemical species'                          //   &
     593                                 ' Emission routine is not called'         
     594                CALL message( 'chem_emissions_matching', 'CM0440', 0, 0, 0, 6, 0 )
     595
     596             ENDIF
     597
     598!
     599!-- Error reporting (no species)
     600
     601          ELSE
     602
     603             message_string = 'Array of Emission species not allocated: '             // &
     604                              ' Either no emission species are provided as input or'  // &
     605                              ' no chemical species are used by PALM:'                // &
     606                              ' Emission routine is not called'                                   
     607             CALL message( 'chem_emissions_matching', 'CM0441', 0, 2, 0, 6, 0 )
     608 
     609          ENDIF
     610
     611!
     612!-- LOD 2 (PRE-PROCESSED mode)
     613
     614       CASE (2)
     615
     616          len_index = 0
     617          len_index_voc = 0
     618
     619          IF  ( nvar > 0 .AND. (nspec_emis_inp > 0) )  THEN
     620!
     621!-- Cycle over model species
     622             DO ind_mod = 1, nvar
     623
     624!
     625!-- Cycle over input species 
     626                DO ind_inp = 1, nspec_emis_inp
     627
     628!
     629!-- Check for VOC Species
     630
     631                   IF  ( TRIM( emt_att%species_name(ind_inp) ) == "VOC" )  THEN       
     632                      DO ind_voc = 1, emt_att%nvoc
     633                         IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
     634                            len_index     = len_index + 1
     635                            len_index_voc = len_index_voc + 1
     636                         ENDIF
     637                      END DO
     638                   ENDIF
     639
     640!
     641!-- Other Species
     642
     643                   IF  ( TRIM(emt_att%species_name(ind_inp)) == TRIM(spc_names(ind_mod)) )  THEN
     644                      len_index = len_index + 1
     645                   ENDIF
     646                ENDDO
     647             ENDDO
     648
     649!
     650!-- Allocate array for storing the indices of the matched species
     651
     652             IF  ( len_index > 0 )  THEN
     653 
     654                ALLOCATE ( match_spec_input(len_index) )
     655 
     656                ALLOCATE ( match_spec_model(len_index) )
     657
     658                IF  ( len_index_voc > 0 )  THEN
     659!
     660!-- contains indices of the VOC model species
     661                   ALLOCATE( match_spec_voc_model(len_index_voc) )
     662!
     663!-- contains the indices of different values of VOC composition of input variable VOC_composition
     664                   ALLOCATE( match_spec_voc_input(len_index_voc) )
     665
     666                ENDIF
     667
     668!
     669!-- pass the species indices to declared arrays
     670
     671                len_index = 0
     672
     673!
     674!-- Cycle over model species
     675
     676                DO ind_mod = 1, nvar
     677 
     678!
     679!-- Cycle over Input species 
     680
     681                   DO ind_inp = 1, nspec_emis_inp
     682
     683!
     684!-- VOCs
     685
     686                      IF  ( TRIM(emt_att%species_name(ind_inp) ) == "VOC" .AND.    &
     687                           ALLOCATED(match_spec_voc_input) )  THEN
     688                         
     689                         DO ind_voc= 1, emt_att%nvoc
     690                            IF  ( TRIM( emt_att%voc_name(ind_voc) ) == TRIM( spc_names(ind_mod) ) )  THEN
     691                               len_index = len_index + 1
     692                               len_index_voc = len_index_voc + 1
     693                       
     694                               match_spec_input(len_index) = ind_inp
     695                               match_spec_model(len_index) = ind_mod
     696
     697                               match_spec_voc_input(len_index_voc) = ind_voc
     698                               match_spec_voc_model(len_index_voc) = ind_mod                         
     699                            ENDIF
     700                         END DO
     701                      ENDIF
     702
     703!
     704!-- Other Species
     705
     706                      IF  ( TRIM( emt_att%species_name(ind_inp) ) == TRIM( spc_names(ind_mod) ) )  THEN
     707                         len_index = len_index + 1
     708                         match_spec_input(len_index) = ind_inp
     709                         match_spec_model(len_index) = ind_mod
     710                      ENDIF
     711
     712                   END DO  ! ind_inp
     713                END DO     ! ind_mod
     714
     715             ELSE  ! if len_index_voc .le. 0
     716
     717!
     718!-- in case there are no species matching
     719
     720                message_string = 'Non of given emission species'            //         &
     721                                 ' matches'                                //          &
     722                                 ' model chemical species:'                //          &
     723                                 ' Emission routine is not called' 
     724                CALL message( 'chem_emissions_matching', 'CM0438', 0, 0, 0, 6, 0 )
     725             ENDIF
     726
     727!
     728!-- Error check (no matching)
     729 
     730          ELSE
     731
     732!
     733!-- either spc_names is zero or nspec_emis_inp is not allocated
     734             message_string = 'Array of Emission species not allocated:'              // &
     735                              ' Either no emission species are provided as input or'  // &
     736                              ' no chemical species are used by PALM:'                // &
     737                              ' Emission routine is not called'                 
     738             CALL message( 'chem_emissions_matching', 'CM0439', 0, 2, 0, 6, 0 )
     739
     740          ENDIF 
     741
     742!
     743!-- If emission module is switched on but mode_emis is not specified or it is given the wrong name
     744
     745!
     746!-- Error check (no species)
     747
    694748       CASE DEFAULT
    695749
    696           message_string = 'Emission Module switched ON, but'            //                         &
    697                            ' either no emission mode specified or incorrectly given :'  //          &
     750          message_string = 'Emission Module switched ON, but'                           //         &
     751                           ' either no emission mode specified or incorrectly given :'  //         &
    698752                           ' please, pass the correct value to the namelist parameter "mode_emis"'                 
    699753          CALL message( 'chem_emissions_matching', 'CM0445', 2, 2, 0, 6, 0 )             
     
    701755       END SELECT
    702756
    703        IF ( debug_output )  CALL debug_message( 'chem_emissions_match', 'end' )
     757       IF  ( debug_output )  CALL debug_message( 'chem_emissions_match', 'end' )
    704758
    705759 END SUBROUTINE chem_emissions_match
     
    724778!   
    725779!-- Actions for initial runs
    726 !  IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     780!  IF  (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    727781!--    ...
    728782!   
     
    735789
    736790
    737   IF ( debug_output )  CALL debug_message( 'chem_emissions_init', 'start' )
    738 
    739   !
    740   !-- Matching
    741   CALL  chem_emissions_match( chem_emis_att, nspec_out )
    742  
    743   IF ( nspec_out == 0 )  THEN
     791    IF  ( debug_output )  CALL debug_message( 'chem_emissions_init', 'start' )
     792
     793!
     794!-- Matching
     795
     796    CALL  chem_emissions_match( chem_emis_att, n_matched_vars )
     797 
     798    IF  ( n_matched_vars == 0 )  THEN
    744799 
    745      emission_output_required = .FALSE.
    746 
    747   ELSE
    748 
    749      emission_output_required = .TRUE.
    750 
    751 
    752      !
    753      !-- Set molecule masses'
    754      ALLOCATE( chem_emis_att%xm(nspec_out) )
    755 
    756      DO ispec = 1, nspec_out
    757         SELECT CASE ( TRIM( spc_names(match_spec_model(ispec)) ) )
    758            CASE ( 'SO2' ); chem_emis_att%xm(ispec) = xm_S + xm_O * 2        !< kg/mole
    759            CASE ( 'SO4' ); chem_emis_att%xm(ispec) = xm_S + xm_O * 4        !< kg/mole
    760            CASE ( 'NO' ); chem_emis_att%xm(ispec) = xm_N + xm_O             !< kg/mole
    761            CASE ( 'NO2' ); chem_emis_att%xm(ispec) = xm_N + xm_O * 2        !< kg/mole   
    762            CASE ( 'NH3' ); chem_emis_att%xm(ispec) = xm_N + xm_H * 3        !< kg/mole
    763            CASE ( 'CO'  ); chem_emis_att%xm(ispec) = xm_C + xm_O            !< kg/mole
    764            CASE ( 'CO2' ); chem_emis_att%xm(ispec) = xm_C + xm_O * 2        !< kg/mole
    765            CASE ( 'CH4' ); chem_emis_att%xm(ispec) = xm_C + xm_H * 4        !< kg/mole     
    766            CASE ( 'HNO3' ); chem_emis_att%xm(ispec) = xm_H + xm_N + xm_O*3  !< kg/mole 
    767            CASE DEFAULT
    768               chem_emis_att%xm(ispec) = 1.0_wp
    769         END SELECT
    770      ENDDO
     800       emission_output_required = .FALSE.
     801
     802    ELSE
     803
     804       emission_output_required = .TRUE.
     805
     806
     807!
     808!-- Set molecule masses  (in kg/mol)
     809
     810       ALLOCATE( chem_emis_att%xm(n_matched_vars) )
     811
     812       DO ispec = 1, n_matched_vars
     813          SELECT CASE ( TRIM( spc_names(match_spec_model(ispec)) ) )
     814             CASE ( 'SO2'  );  chem_emis_att%xm(ispec) = xm_S + xm_O * 2
     815             CASE ( 'SO4'  );  chem_emis_att%xm(ispec) = xm_S + xm_O * 4
     816             CASE ( 'NO'   );  chem_emis_att%xm(ispec) = xm_N + xm_O
     817             CASE ( 'NO2'  );  chem_emis_att%xm(ispec) = xm_N + xm_O * 2
     818             CASE ( 'NH3'  );  chem_emis_att%xm(ispec) = xm_N + xm_H * 3
     819             CASE ( 'CO'   );  chem_emis_att%xm(ispec) = xm_C + xm_O
     820             CASE ( 'CO2'  );  chem_emis_att%xm(ispec) = xm_C + xm_O * 2
     821             CASE ( 'CH4'  );  chem_emis_att%xm(ispec) = xm_C + xm_H * 4
     822             CASE ( 'HNO3' );  chem_emis_att%xm(ispec) = xm_H + xm_N + xm_O*3
     823             CASE DEFAULT
     824                chem_emis_att%xm(ispec) = 1.0_wp
     825          END SELECT
     826       ENDDO
    771827
    772828   
    773      !
    774      !-- assign emission values
    775      SELECT CASE ( TRIM( mode_emis ) )   
    776 
    777 
    778         !
    779         !-- PRE-PROCESSED case
    780         CASE ( "PRE-PROCESSED" )
    781 
    782            IF ( .NOT. ALLOCATED( emis_distribution) ) ALLOCATE( emis_distribution(nzb:nzt+1,0:ny,0:nx,nspec_out) ) 
    783  
    784            !
    785            !-- Get emissions at the first time step
    786            CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out )
    787 
    788         !
    789         !-- Default case
    790         CASE ( "DEFAULT" )
    791 
    792            IF ( .NOT. ALLOCATED( emis_distribution) ) ALLOCATE( emis_distribution(1,0:ny,0:nx,nspec_out) )
    793 
    794            !
    795            !-- Get emissions at the first time step
    796            CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out )
    797 
    798         !
    799         !-- PARAMETERIZED case
    800         CASE ( "PARAMETERIZED" )
    801 
    802            IF ( .NOT. ALLOCATED( emis_distribution) ) ALLOCATE( emis_distribution(1,0:ny,0:nx,nspec_out) )
    803 
    804            !
    805            !-- Get emissions at the first time step
    806            CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out)
    807 
    808      END SELECT
    809 
    810   ENDIF   
    811 
    812   IF ( debug_output )  CALL debug_message( 'chem_emissions_init', 'end' )
     829!
     830!-- Get emissions for the first time step base on LOD (if defined)
     831!-- or emission mode (if no LOD defined)
     832
     833!
     834!-- NOTE - I could use a combined if ( lod = xxx .or. mode = 'XXX' )
     835!--        type of decision structure but I think it is much better
     836!--        to implement it this way (i.e., conditional on lod if it
     837!--        is defined, and mode if not) as we can easily take out
     838!--        the case structure for mode_emis later on.
     839!--        (ecc 20140424)
     840
     841       IF   ( emiss_lod < 0 )  THEN  !-- no LOD defined (not likely)
     842
     843          SELECT CASE ( TRIM( mode_emis ) )   
     844
     845             CASE ( 'PARAMETERIZED' )     ! LOD 0
     846
     847                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     848                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
     849                ENDIF
     850
     851                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars)
     852
     853             CASE ( 'DEFAULT' )           ! LOD 1
     854
     855                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     856                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
     857                ENDIF
     858
     859                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars )
     860
     861             CASE ( 'PRE-PROCESSED' )     ! LOD 2
     862
     863                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     864                   ALLOCATE( emis_distribution(nzb:nzt+1,0:ny,0:nx,n_matched_vars) )
     865                ENDIF
     866 
     867                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars )
     868
     869          END SELECT
     870
     871       ELSE  ! if LOD is defined
     872
     873          SELECT CASE ( emiss_lod )
     874
     875             CASE ( 0 )     ! parameterized mode
     876
     877                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     878                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
     879                ENDIF
     880
     881                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars)
     882
     883             CASE ( 1 )     ! default mode
     884
     885                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     886                   ALLOCATE( emis_distribution(1,0:ny,0:nx,n_matched_vars) )
     887                ENDIF
     888
     889                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars )
     890
     891             CASE ( 2 )     ! pre-processed mode
     892
     893                IF  ( .NOT. ALLOCATED( emis_distribution) )  THEN
     894                   ALLOCATE( emis_distribution(nzb:nzt+1,0:ny,0:nx,n_matched_vars) )
     895                ENDIF
     896 
     897                CALL chem_emissions_setup( chem_emis_att, chem_emis, n_matched_vars )
     898
     899          END SELECT
     900
     901       ENDIF
     902
     903    ENDIF
     904
     905    IF  ( debug_output )  CALL debug_message( 'chem_emissions_init', 'end' )
    813906
    814907 END SUBROUTINE chem_emissions_init
     
    822915!-------------------------------------------------------------------------------!
    823916
    824  SUBROUTINE chem_emissions_setup( emt_att, emt, nspec_out )
     917 SUBROUTINE chem_emissions_setup( emt_att, emt, n_matched_vars )
    825918 
    826919   USE surface_mod,                                                  &
     
    835928 
    836929
    837     TYPE(chem_emis_att_type), INTENT(INOUT) ::  emt_att                         !< variable to store emission information                                                                          
     930    TYPE(chem_emis_att_type), INTENT(INOUT) ::  emt_att                         !< variable to store emission information
    838931
    839932    TYPE(chem_emis_val_type), INTENT(INOUT), ALLOCATABLE, DIMENSION(:) ::  emt  !< variable to store emission input values,
    840933                                                                                !< depending on the considered species
    841934
    842     INTEGER,INTENT(IN) ::  nspec_out                                            !< Output of matching routine with number
     935    INTEGER,INTENT(IN) ::  n_matched_vars                                       !< Output of matching routine with number
    843936                                                                                !< of matched species
    844937
     
    858951
    859952    REAL(wp), DIMENSION(24) :: par_emis_time_factor                             !< time factors for the parameterized mode:
    860                                                                                !< fixed houlry profile for example day
    861     REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  conv_to_ratio          !< factor used for converting input
     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
    862955                                                                                !< to concentration ratio
    863956    REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  tmp_temp
     
    883976    !------------------------------------------------------   
    884977
    885     IF ( emission_output_required )  THEN
     978    IF  ( emission_output_required )  THEN
    886979
    887980       !
    888981       !-- Set emis_dt 
    889        IF ( call_chem_at_all_substeps )  THEN
     982       IF  ( call_chem_at_all_substeps )  THEN
    890983
    891984          dt_emis = dt_3d * weight_pres(intermediate_timestep_count)
     
    897990       ENDIF
    898991
    899 
    900        !
    901        !-- Conversion of units to the ones employed in PALM
    902        !-- In PARAMETERIZED mode no conversion is performed: in this case input units are fixed
    903 
    904         IF ( TRIM( mode_emis ) == "DEFAULT" .OR. TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
     992 !
     993 !-- Conversion of units to the ones employed in PALM
     994 !-- In PARAMETERIZED mode no conversion is performed: in this case input units are fixed
     995
     996        IF  ( TRIM( mode_emis ) == "DEFAULT" .OR. TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
    905997
    906998          SELECT CASE ( TRIM( emt_att%units ) )
    907              !
    908              !-- kilograms
    909              CASE ( 'kg/m2/s', 'KG/M2/S' )
    910                
    911                 con_factor=1
    912 
    913              CASE ('kg/m2/hour', 'KG/M2/HOUR' )
    914 
    915                 con_factor=hour_to_s
    916 
    917              CASE ( 'kg/m2/day', 'KG/M2/DAY' )
    918                
    919                 con_factor=day_to_s
    920 
    921              CASE ( 'kg/m2/year', 'KG/M2/YEAR' )
    922              
    923                 con_factor=year_to_s
    924 
    925              !
    926              !-- Tons
    927              CASE ( 'ton/m2/s', 'TON/M2/S' )
    928                
    929                 con_factor=tons_to_kg
    930 
    931              CASE ( 'ton/m2/hour', 'TON/M2/HOUR' )
    932                
    933                 con_factor=tons_to_kg*hour_to_s
    934 
    935              CASE ( 'ton/m2/year', 'TON/M2/YEAR' )
    936                
    937                 con_factor=tons_to_kg*year_to_s
    938 
    939              !
    940              !-- Grams
    941              CASE ( 'g/m2/s', 'G/M2/S' )
    942          
    943                 con_factor=g_to_kg
    944 
    945              CASE ( 'g/m2/hour', 'G/M2/HOUR' )
    946 
    947                 con_factor=g_to_kg*hour_to_s
    948 
    949              CASE ( 'g/m2/year', 'G/M2/YEAR' )
    950  
    951                 con_factor=g_to_kg*year_to_s
    952 
    953              !
    954              !-- Micrograms
    955              CASE ( 'micrograms/m2/s', 'MICROGRAMS/M2/S' )
    956  
    957                 con_factor=miug_to_kg
    958 
    959              CASE ( 'micrograms/m2/hour', 'MICROGRAMS/M2/HOUR' )
    960  
    961                 con_factor=miug_to_kg*hour_to_s
    962 
    963              CASE ( 'micrograms/m2/year', 'MICROGRAMS/M2/YEAR' )
    964  
    965                 con_factor=miug_to_kg*year_to_s
     999
     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
     1016
     1017!
     1018!-- Error check (need units)
    9661019
    9671020             CASE DEFAULT 
    968                 message_string = 'The Units of the provided emission input' // &
    969                                  ' are not the ones required by PALM-4U: please check '      // &
     1021                message_string = 'The Units of the provided emission input'                 // &
     1022                                 ' are not the ones required by PALM-4U: please check '     // &
    9701023                                 ' emission module documentation.'                                 
    9711024                CALL message( 'chem_emissions_setup', 'CM0446', 2, 2, 0, 6, 0 )
     
    9731026          END SELECT
    9741027
    975          
    9761028       ENDIF
    9771029
    978        !
    979        !-- Conversion factor to convert  kg/m**2/s to ppm/s
     1030!
     1031!-- Conversion factor to convert  kg/m**2/s to ppm/s
     1032
    9801033       DO i = nxl, nxr
    9811034          DO j = nys, nyn
    982              !
    983              !-- Derive Temperature from Potential Temperature
     1035
     1036!
     1037!-- Derive Temperature from Potential Temperature
     1038
    9841039             tmp_temp(nzb:nzt+1,j,i) = pt(nzb:nzt+1,j,i) * ( hyp(nzb:nzt+1) * pref_i )**r_cp
    985              
    986              
    987              !>  We need to pass to cssws <- (ppm/s) * dz
    988              !>  Input is Nmole/(m^2*s)
    989              !>  To go to ppm*dz multiply the input by (m**2/N)*dz
    990              !>  (m**2/N)*dz == V/N
    991              !>  V/N = RT/P
    992              !>  m**3/Nmole               (J/mol)*K^-1           K                      Pa         
     1040 
     1041!           
     1042!-- We need to pass to cssws <- (ppm/s) * dz
     1043!-- Input is Nmole/(m^2*s)
     1044!-- To go to ppm*dz multiply the input by (m**2/N)*dz
     1045!-- (m**2/N)*dz == V/N
     1046!-- V/N = RT/P
     1047
     1048!                   m**3/Nmole               (J/mol)*K^-1           K                      Pa         
    9931049             conv_to_ratio(nzb:nzt+1,j,i) = ( (Rgas * tmp_temp(nzb:nzt+1,j,i)) / ((hyp(nzb:nzt+1))) ) 
     1050
    9941051          ENDDO
    9951052       ENDDO
    9961053
    9971054
    998        !
    999        !-- Initialize
     1055!
     1056!-- Initialize
     1057
    10001058       emis_distribution(:,nys:nyn,nxl:nxr,:) = 0.0_wp
    10011059
    10021060 
    1003        !
    1004        !-- PRE-PROCESSED MODE
    1005        IF ( TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
    1006 
    1007           !
    1008           !-- Update time indices
     1061!
     1062!-- LOD 2 (PRE-PROCESSED MODE)
     1063
     1064       IF  ( emiss_lod == 2 )  THEN
     1065
     1066! for reference (ecc)
     1067!       IF  ( TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
     1068
     1069!
     1070!-- Update time indices
     1071
    10091072          CALL time_preprocessed_indices( index_hh )
    10101073
    1011        ELSEIF ( TRIM( mode_emis ) == "DEFAULT" )  THEN
    1012 
    1013           !
    1014           !-- Allocate array where to store temporary emission values     
    1015           IF ( .NOT. ALLOCATED(emis) ) ALLOCATE( emis(nys:nyn,nxl:nxr) )
    1016           !
    1017           !-- Allocate time factor per category
    1018           ALLOCATE( time_factor(emt_att%ncat) ) 
    1019           !
    1020           !-- Read-in hourly emission time factor
    1021           IF ( TRIM( time_fac_type ) == "HOUR" )  THEN
    1022 
    1023              !
    1024              !-- Update time indices
     1074
     1075!
     1076!-- LOD 1 (DEFAULT MODE)
     1077
     1078        ELSEIF  ( emiss_lod == 1 )  THEN
     1079
     1080! for reference (ecc)
     1081!       ELSEIF  ( TRIM( mode_emis ) == "DEFAULT" )  THEN
     1082
     1083!
     1084!-- Allocate array where to store temporary emission values
     1085
     1086          IF  ( .NOT. ALLOCATED(emis) ) ALLOCATE( emis(nys:nyn,nxl:nxr) )
     1087
     1088!
     1089!-- Allocate time factor per category
     1090
     1091          ALLOCATE( time_factor(emt_att%ncat) )
     1092
     1093!
     1094!-- Read-in hourly emission time factor
     1095
     1096          IF  ( TRIM(time_fac_type) == "HOUR" )  THEN
     1097
     1098!
     1099!-- Update time indices
     1100
    10251101             CALL time_default_indices( month_of_year, day_of_month, hour_of_day, index_hh )
    1026              !
    1027              !-- Check if the index is less or equal to the temporal dimension of HOURLY emission files             
    1028              IF ( index_hh <= SIZE( emt_att%hourly_emis_time_factor(1,:) ) )  THEN
    1029                 !
    1030                 !-- Read-in the correspondant time factor             
     1102
     1103!
     1104!-- Check if the index is less or equal to the temporal dimension of HOURLY emission files
     1105
     1106             IF  ( index_hh <= SIZE( emt_att%hourly_emis_time_factor(1,:) ) )  THEN
     1107
     1108!
     1109!-- Read-in the correspondant time factor
     1110
    10311111                time_factor(:) = emt_att%hourly_emis_time_factor(:,index_hh)     
     1112
     1113!
     1114!-- Error check (time out of range)
    10321115
    10331116             ELSE
     
    10381121
    10391122             ENDIF
    1040           !
    1041           !-- Read-in MDH emissions time factors
    1042           ELSEIF ( TRIM( time_fac_type ) == "MDH" )  THEN
    1043 
    1044              !
    1045              !-- Update time indices     
     1123
     1124!
     1125!-- Read-in MDH emissions time factors
     1126
     1127          ELSEIF  ( TRIM( time_fac_type ) == "MDH" )  THEN
     1128
     1129!
     1130!-- Update time indices
    10461131             CALL time_default_indices( daytype_mdh, month_of_year, day_of_month,     &
    10471132                  hour_of_day, index_mm, index_dd,index_hh )
    10481133
    1049              !
    1050              !-- Check if the index is less or equal to the temporal dimension of MDH emission files             
    1051              IF ( ( index_hh + index_dd + index_mm) <= SIZE( emt_att%mdh_emis_time_factor(1,:) ) )  THEN
    1052                 !
    1053                 !-- Read-in the correspondant time factor             
    1054                 time_factor(:) = emt_att%mdh_emis_time_factor(:,index_mm) * emt_att%mdh_emis_time_factor(:,index_dd) *   &
    1055                                                                          emt_att%mdh_emis_time_factor(:,index_hh)
     1134!
     1135!-- Check if the index is less or equal to the temporal dimension of MDH emission files
     1136
     1137             IF  ( ( index_hh + index_dd + index_mm) <= SIZE( emt_att%mdh_emis_time_factor(1,:) ) )  THEN
     1138
     1139!
     1140!-- Read in corresponding time factor
     1141
     1142                time_factor(:) = emt_att%mdh_emis_time_factor(:,index_mm) *    &
     1143                                 emt_att%mdh_emis_time_factor(:,index_dd) *    &
     1144                                 emt_att%mdh_emis_time_factor(:,index_hh)
     1145
     1146!
     1147!-- Error check (MDH time factor not provided)
    10561148     
    10571149             ELSE
     
    10611153                CALL message( 'chem_emissions_setup', 'CM0449', 2, 2, 0, 6, 0 )
    10621154
    1063              ENDIF
     1155             ENDIF 
     1156
     1157!
     1158!-- Error check (no time factor defined)
    10641159
    10651160          ELSE
     
    10711166          ENDIF
    10721167
    1073        !
    1074        !-- PARAMETERIZED MODE
    1075        ELSEIF ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
     1168!
     1169!-- PARAMETERIZED MODE
     1170
     1171       ELSEIF ( emiss_lod == 0 )  THEN
     1172
     1173
     1174! for reference (ecc)
     1175!       ELSEIF  ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
    10761176       
    1077           !
    1078           !-- assign constant values of time factors, diurnal time profile for traffic sector
    1079           par_emis_time_factor( : ) =  &
    1080             (/ 0.009, 0.004, 0.004, 0.009, 0.029, 0.039, 0.056, 0.053, 0.051, 0.051, 0.052, 0.055,  &
    1081                0.059, 0.061, 0.064, 0.067, 0.069, 0.069, 0.049, 0.039, 0.039, 0.029, 0.024, 0.019 /)
     1177!
     1178!-- assign constant values of time factors, diurnal profile for traffic sector
     1179
     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,      &
     1183                                          0.049, 0.039, 0.039, 0.029, 0.024, 0.019 /)
    10821184         
    1083           IF ( .NOT. ALLOCATED( time_factor ) ) ALLOCATE( time_factor(1) )
    1084 
    1085           !
    1086           !-- Get time-factor for specific hour
     1185          IF  ( .NOT. ALLOCATED (time_factor) )  ALLOCATE (time_factor(1))
     1186
     1187!
     1188!-- Get time-factor for specific hour
     1189
    10871190          index_hh = hour_of_day
    1088 
    10891191          time_factor(1) = par_emis_time_factor(index_hh)
    10901192
    1091        ENDIF
     1193       ENDIF  ! emiss_lod
    10921194
    10931195       
    1094        !
    1095        !--  Emission distribution calculation
    1096 
    1097        !
    1098        !-- PARAMETERIZED case
    1099        IF ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
    1100 
    1101           DO ispec = 1, nspec_out
    1102 
    1103              !
    1104              !-- Units are micromoles/m**2*day (or kilograms/m**2*day for PMs)
    1105              emis_distribution(1,nys:nyn,nxl:nxr,ispec) = surface_csflux(match_spec_input(ispec)) *  &
    1106                                                            time_factor(1) * hour_to_s
     1196!
     1197!--  Emission distribution calculation
     1198
     1199!
     1200!-- LOD 0 (PARAMETERIZED mode)
     1201
     1202       IF  ( emiss_lod == 0 )  THEN
     1203
     1204! for reference (ecc)
     1205!       IF  ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
     1206
     1207          DO ispec = 1, n_matched_vars
     1208
     1209!
     1210!-- Units are micromoles/m**2*day (or kilograms/m**2*day for PMs)
     1211
     1212             emis_distribution(1,nys:nyn,nxl:nxr,ispec) =            &
     1213                       surface_csflux(match_spec_input(ispec)) *     &
     1214                       time_factor(1) * hour_to_s
    11071215
    11081216          ENDDO
    11091217
    1110        !
    1111        !-- PRE-PROCESSED case
    1112        ELSEIF ( TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
    1113 
    1114           !
    1115           !-- Cycle over species:
    1116           !-- nspec_out represents the number of species in common between the emission input data
    1117           !-- and the chemistry mechanism used
    1118           DO ispec=1,nspec_out 
    1119    
    1120              emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emt(match_spec_input(ispec))%                                 &
    1121                                                             preproc_emission_data(index_hh,1,nys+1:nyn+1,nxl+1:nxr+1) * &
    1122                                                                 con_factor
    11231218         
    1124           ENDDO
    1125          
    1126        !
    1127        !-- DEFAULT case
    1128        ELSEIF ( TRIM( mode_emis ) == "DEFAULT" )  THEN
    1129 
    1130           !
    1131           !-- Allocate array for the emission value corresponding to a specific category and time factor
    1132           ALLOCATE( delta_emis(nys:nyn,nxl:nxr) ) 
    1133 
    1134           !
    1135           !-- Cycle over categories
     1219!
     1220!-- LOD 1 (DEFAULT mode)
     1221
     1222
     1223       ELSEIF  ( emiss_lod == 1 )  THEN
     1224
     1225! for referene (ecc)
     1226!       ELSEIF  ( TRIM( mode_emis ) == "DEFAULT" )  THEN
     1227
     1228!
     1229!-- Allocate array for the emission value corresponding to a specific category and time factor
     1230
     1231          ALLOCATE (delta_emis(nys:nyn,nxl:nxr))
     1232
     1233!
     1234!-- Cycle over categories
     1235
    11361236          DO icat = 1, emt_att%ncat
    11371237 
    1138              !
    1139              !-- Cycle over Species
    1140              !-- nspec_out represents the number of species in common between the emission input data
    1141              !-- and the chemistry mechanism used
    1142              DO ispec = 1, nspec_out
    1143 
    1144                 emis(nys:nyn,nxl:nxr) = emt(match_spec_input(ispec))%default_emission_data(icat,nys+1:nyn+1,nxl+1:nxr+1)
    1145 
    1146 
    1147                 !
    1148                 !-- NOx
    1149                 IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "NO" )  THEN
     1238!
     1239!-- Cycle over Species:  n_matched_vars represents the number of species
     1240!-- in common between the emission input data and the chemistry mechanism used
     1241
     1242             DO ispec = 1, n_matched_vars
     1243
     1244                emis(nys:nyn,nxl:nxr) =                    &
     1245                       emt(match_spec_input(ispec))%       &
     1246                           default_emission_data(icat,nys+1:nyn+1,nxl+1:nxr+1)
     1247
     1248!
     1249!-- NO
     1250
     1251                IF  ( TRIM(spc_names(match_spec_model(ispec))) == "NO" )  THEN
    11501252               
    1151                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &                 !<  kg/m2*s
    1152                                                   emt_att%nox_comp(icat,1) * con_factor * hour_per_day
    1153 
    1154                    emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1155                                                                  delta_emis(nys:nyn,nxl:nxr)
    1156 
    1157                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "NO2" )  THEN
    1158 
    1159                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &                 !<  kg/m2*s
    1160                                                   emt_att%nox_comp(icat,2) * con_factor * hour_per_day
    1161 
    1162                    emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1163                                                                  delta_emis(nys:nyn,nxl:nxr)
    1164  
    1165                 !
    1166                 !-- SOx
    1167                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "SO2" )  THEN
     1253                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *       &         ! kg/m2/s
     1254                                                 time_factor(icat) *           &
     1255                                                 emt_att%nox_comp(icat,1) *    &
     1256                                                 con_factor * hour_per_day
     1257
     1258                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     1259                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +    &
     1260                               delta_emis(nys:nyn,nxl:nxr)
     1261!
     1262!-- NO2
     1263
     1264                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "NO2" )  THEN
     1265
     1266                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *       &         ! kg/m2/s
     1267                                                 time_factor(icat) *           &
     1268                                                 emt_att%nox_comp(icat,2) *    &
     1269                                                 con_factor * hour_per_day
     1270
     1271                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     1272                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +    &
     1273                               delta_emis(nys:nyn,nxl:nxr)
     1274 
     1275!
     1276!-- SO2
     1277                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "SO2" )  THEN
    11681278                 
    1169                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &                 !<  kg/m2*s
    1170                                                  emt_att%sox_comp(icat,1) * con_factor * hour_per_day
    1171 
    1172                    emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1173                                                                  delta_emis(nys:nyn,nxl:nxr)
    1174 
    1175                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "SO4" )  THEN
     1279                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *       &         ! kg/m2/s
     1280                                                 time_factor(icat) *           &
     1281                                                 emt_att%sox_comp(icat,1) *    &
     1282                                                 con_factor * hour_per_day
     1283
     1284                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     1285                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +    &
     1286                               delta_emis(nys:nyn,nxl:nxr)
     1287
     1288!
     1289!-- SO4
     1290
     1291                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "SO4" )  THEN
     1292
    11761293                 
    1177                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &                 !<  kg/m2*s
    1178                                                  emt_att%sox_comp(icat,2) * con_factor * hour_per_day
    1179 
    1180                    emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1181                                                                  delta_emis(nys:nyn,nxl:nxr)
    1182  
    1183 
    1184                 !
    1185                 !-- PMs
    1186                 !-- PM1
    1187                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1" )  THEN
    1188 
    1189                    !
    1190                    !-- Cycle over PM1 components
    1191                    DO i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,1) )
    1192 
    1193                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &               !<  kg/m2*s
    1194                                                      emt_att%pm_comp(icat,i_pm_comp,1) * con_factor * hour_per_day
    1195 
    1196                       emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1197                                                                     delta_emis(nys:nyn,nxl:nxr)
     1294                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *       &         ! kg/m2/s
     1295                                                 time_factor(icat) *           &
     1296                                                 emt_att%sox_comp(icat,2) *    &
     1297                                                 con_factor * hour_per_day
     1298
     1299                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                &
     1300                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +    &
     1301                               delta_emis(nys:nyn,nxl:nxr)
     1302 
     1303
     1304!
     1305!-- PM1
     1306
     1307                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1" )  THEN
     1308
     1309                   DO  i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,1) )   ! cycle through components
     1310
     1311                      delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *              &     ! kg/m2/s
     1312                                                    time_factor(icat) *                  &
     1313                                                    emt_att%pm_comp(icat,i_pm_comp,1) *  &
     1314                                                    con_factor * hour_per_day
     1315
     1316                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     1317                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +              &
     1318                               delta_emis(nys:nyn,nxl:nxr)
     1319
    11981320                   ENDDO
    11991321
    1200                 !
    1201                 !-- PM2.5
    1202                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM25" )  THEN
    1203 
    1204                    !
    1205                    !-- Cycle over PM2.5 components
    1206                    DO i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,2) )
    1207 
    1208                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &               !<  kg/m2*s
    1209                                                      emt_att%pm_comp(icat,i_pm_comp,2) * con_factor * hour_per_day
    1210 
    1211                       emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1212                                                                     delta_emis(nys:nyn,nxl:nxr)
     1322!
     1323!-- PM2.5
     1324
     1325                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM25" )  THEN
     1326
     1327                   DO  i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,2) )   ! cycle through components
     1328
     1329                      delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *              &     ! kg/m2/s
     1330                                                    time_factor(icat) *                  &
     1331                                                    emt_att%pm_comp(icat,i_pm_comp,2) *  &
     1332                                                    con_factor * hour_per_day
     1333
     1334                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     1335                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +              &
     1336                               delta_emis(nys:nyn,nxl:nxr)
    12131337 
    12141338                   ENDDO
    12151339
    1216                 !
    1217                 !-- PM10
    1218                 ELSEIF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM10" )  THEN
    1219 
    1220                    !
    1221                    !-- Cycle over PM10 components
    1222                    DO i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,3) ) 
    1223 
    1224                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &               !<  kg/m2*s
    1225                                                      emt_att%pm_comp(icat,i_pm_comp,3) * con_factor * hour_per_day
    1226 
    1227                       emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+ &
    1228                                                                  delta_emis(nys:nyn,nxl:nxr)
     1340!
     1341!-- PM10
     1342
     1343                ELSEIF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
     1344
     1345                   DO  i_pm_comp = 1, SIZE( emt_att%pm_comp(1,:,3) )   ! cycle through components
     1346
     1347                      delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *              &     ! kg/m2/s
     1348                                                    time_factor(icat)     *              &
     1349                                                    emt_att%pm_comp(icat,i_pm_comp,3) *  &
     1350                                                    con_factor * hour_per_day
     1351
     1352                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                       &
     1353                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +              &
     1354                               delta_emis(nys:nyn,nxl:nxr)
    12291355
    12301356                   ENDDO
    12311357
    1232                 !
    1233                 !-- VOCs
    1234                 ELSEIF ( SIZE( match_spec_voc_input ) > 0 )  THEN
    1235 
    1236                    DO ivoc = 1, SIZE( match_spec_voc_input )
    1237 
    1238                       IF ( TRIM( spc_names(match_spec_model(ispec)) ) == TRIM( emt_att%voc_name(ivoc) ) )  THEN   
    1239 
    1240                          delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &
    1241                                                         emt_att%voc_comp(icat,match_spec_voc_input(ivoc)) * &
    1242                                                          con_factor * hour_per_day
    1243 
    1244                          emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1245                                                                        delta_emis(nys:nyn,nxl:nxr)
     1358!
     1359!-- VOCs
     1360
     1361                ELSEIF  ( SIZE( match_spec_voc_input ) > 0 )  THEN
     1362
     1363                   DO  ivoc = 1, SIZE( match_spec_voc_input )          ! cycle through components
     1364
     1365                      IF  ( TRIM(spc_names(match_spec_model(ispec))) ==                &
     1366                            TRIM(emt_att%voc_name(ivoc)) )  THEN   
     1367
     1368                         delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *           &
     1369                                                       time_factor(icat) *               &
     1370                                                       emt_att%voc_comp(icat,match_spec_voc_input(ivoc)) *   &
     1371                                                       con_factor * hour_per_day
     1372
     1373                         emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                    &
     1374                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +              &
     1375                               delta_emis(nys:nyn,nxl:nxr)
    12461376
    12471377                      ENDIF                       
     
    12491379                   ENDDO
    12501380               
    1251                 !
    1252                 !-- any other species
     1381!
     1382!-- any other species
     1383
    12531384                ELSE
    12541385
    1255                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) * time_factor(icat) * &
    1256                                                   con_factor * hour_per_day
    1257  
    1258                    emis_distribution(1,nys:nyn,nxl:nxr,ispec) = emis_distribution(1,nys:nyn,nxl:nxr,ispec) + &
    1259                                                                  delta_emis(nys:nyn,nxl:nxr)
    1260 
    1261                 ENDIF
     1386                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr) *                 &
     1387                                                 time_factor(icat) *                     &
     1388                                                 con_factor * hour_per_day
     1389 
     1390                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                          &
     1391                               emis_distribution(1,nys:nyn,nxl:nxr,ispec) +              &
     1392                               delta_emis(nys:nyn,nxl:nxr)
     1393
     1394                ENDIF  ! TRIM spc_names
    12621395               
    12631396                emis(:,:)= 0
     
    12691402          ENDDO
    12701403
    1271        ENDIF
     1404!
     1405!-- LOD 2 (PRE-PROCESSED mode)
     1406
     1407       ELSEIF  ( emiss_lod == 2 )  THEN
     1408
     1409! for reference (ecc)
     1410!       ELSEIF  ( TRIM( mode_emis ) == "PRE-PROCESSED" )  THEN
     1411
     1412!
     1413!-- Cycle over species: n_matched_vars represents the number of species
     1414!-- in common between the emission input data and the chemistry mechanism used
     1415
     1416          DO ispec = 1, n_matched_vars 
     1417 
     1418! (ecc)   
     1419             emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                &
     1420                       emt(match_spec_input(ispec))%                                     &
     1421                           preproc_emission_data(index_hh,1,nys+1:nyn+1,nxl+1:nxr+1) *   &
     1422                       con_factor
     1423
     1424
     1425!             emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                &
     1426!                       emt(match_spec_input(ispec))%                                     &
     1427!                           preproc_emission_data(index_hh,1,:,:) *   &
     1428!                       con_factor
     1429          ENDDO
     1430
     1431       ENDIF  ! emiss_lod
    12721432
    12731433       
    12741434!
    12751435!-- Cycle to transform x,y coordinates to the one of surface_mod and to assign emission values to cssws
    1276 !
    1277 !-- PARAMETERIZED mode
    1278        !
    1279        !-- Units of inputs are micromoles/(m**2*s)
    1280        IF ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
    1281 
    1282           IF ( street_type_f%from_file )  THEN
    1283 
    1284 !
    1285 !--          Streets are lsm surfaces, hence, no usm surface treatment required.
    1286 !--          However, urban surface may be initialized via default initialization
    1287 !--          in surface_mod, e.g. at horizontal urban walls that are at k == 0
    1288 !--          (building is lower than the first grid point). Hence, in order to
    1289 !--          have only emissions at streets, set the surfaces emissions to zero
    1290 !--          at urban walls.
    1291              IF ( surf_usm_h%ns >=1 )  surf_usm_h%cssws = 0.0_wp
    1292 !
    1293 !--          Now, treat land-surfaces.
     1436
     1437!
     1438!-- LOD 0 (PARAMETERIZED mode)
     1439!-- Units of inputs are micromoles/m2/s
     1440
     1441       IF  ( emiss_lod == 0 )  THEN
     1442! for reference (ecc)
     1443!       IF  ( TRIM( mode_emis ) == "PARAMETERIZED" )  THEN
     1444
     1445          IF  (street_type_f%from_file)  THEN
     1446
     1447!
     1448!-- Streets are lsm surfaces, hence, no usm surface treatment required.
     1449!-- However, urban surface may be initialized via default initialization
     1450!-- in surface_mod, e.g. at horizontal urban walls that are at k == 0
     1451!-- (building is lower than the first grid point). Hence, in order to
     1452!-- have only emissions at streets, set the surfaces emissions to zero
     1453!-- at urban walls.
     1454 
     1455             IF  ( surf_usm_h%ns >=1 )  surf_usm_h%cssws = 0.0_wp
     1456
     1457!
     1458!-- Treat land-surfaces.
     1459
    12941460             DO  m = 1, surf_lsm_h%ns
     1461
    12951462                i = surf_lsm_h%i(m)
    12961463                j = surf_lsm_h%j(m)
    12971464                k = surf_lsm_h%k(m)
    12981465
    1299                 IF ( street_type_f%var(j,i) >= main_street_id  .AND. street_type_f%var(j,i) < max_street_id )  THEN
    1300 
    1301                    !
    1302                    !-- Cycle over matched species
    1303                    DO  ispec = 1, nspec_out
    1304 
    1305                       !
    1306                       !-- PMs are already in kilograms
    1307                       IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1 "  &
    1308                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM25"  &
    1309                           .OR. TRIM( spc_names(match_spec_model(ispec)) )=="PM10")  THEN
    1310 
    1311                          !
    1312                          !--           kg/(m^2*s) * kg/m^3
    1313                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_main(match_spec_input(ispec)) * &
    1314                                                                         emis_distribution(1,j,i,ispec) *            &  !< in kg/(m^2*s)
    1315                                                                          rho_air(k)                                    !< in kg/m^3
     1466                IF  ( street_type_f%var(j,i) >= main_street_id    .AND.                  &
     1467                      street_type_f%var(j,i) < max_street_id   )  THEN
     1468
     1469!
     1470!-- Cycle over matched species
     1471
     1472                   DO  ispec = 1, n_matched_vars
     1473
     1474!
     1475!-- PMs are already in kilograms
     1476
     1477                      IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR. &
     1478                            TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR. &
     1479                            TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
     1480
     1481!
     1482!-- kg/(m^2*s) * kg/m^3
     1483                         surf_lsm_h%cssws(match_spec_model(ispec),m) =                   &
     1484                                   emiss_factor_main(match_spec_input(ispec)) *          &
     1485                                   emis_distribution(1,j,i,ispec) *                      &     ! kg/(m^2*s)
     1486                                   rho_air(k)                                                  ! kg/m^3
    13161487                         
    1317                       !
    1318                       !-- Other Species
    1319                       !-- Inputs are micromoles
     1488!
     1489!-- Other Species
     1490!-- Inputs are micromoles
     1491
    13201492                      ELSE
    13211493
    1322                          !   
    1323                          !--             ppm/s *m *kg/m^3               
    1324                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_main(match_spec_input(ispec)) * &
    1325                                                                         emis_distribution(1,j,i,ispec) *            &  !< in micromoles/(m^2*s)
    1326                                                                          conv_to_ratio(k,j,i) *                     &  !< in m^3/Nmole     
    1327                                                                           rho_air(k)                                   !< in kg/m^3
     1494!   
     1495!-- ppm/s *m *kg/m^3               
     1496                         surf_lsm_h%cssws(match_spec_model(ispec),m) =                   &
     1497                                   emiss_factor_main(match_spec_input(ispec)) *          &
     1498                                   emis_distribution(1,j,i,ispec) *                      &     ! micromoles/(m^2*s)
     1499                                   conv_to_ratio(k,j,i) *                                &     ! m^3/Nmole     
     1500                                   rho_air(k)                                                  ! kg/m^3
    13281501
    13291502                      ENDIF
    13301503
    1331                    ENDDO
    1332 
    1333 
    1334                 ELSEIF ( street_type_f%var(j,i) >= side_street_id  .AND. street_type_f%var(j,i) < main_street_id )  THEN
    1335 
    1336                    !
    1337                    !-- Cycle over matched species
    1338                    DO  ispec = 1, nspec_out
    1339 
    1340                       !
    1341                       !-- PMs are already in kilograms
    1342                       IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1"  &
    1343                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM25"  &
    1344                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM10" )  THEN
    1345 
    1346                          !
    1347                          !--           kg/(m^2*s) * kg/m^3
    1348                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_side(match_spec_input(ispec)) * &
    1349                                                                         emis_distribution(1,j,i,ispec) *            &  !< in kg/(m^2*s)
    1350                                                                          rho_air(k)                                    !< in kg/m^3   
    1351                       !
    1352                       !-- Other species
    1353                       !-- Inputs are micromoles
     1504                   ENDDO  ! ispec
     1505
     1506
     1507                ELSEIF  ( street_type_f%var(j,i) >= side_street_id   .AND.               &
     1508                          street_type_f%var(j,i) < main_street_id )  THEN
     1509
     1510!
     1511!-- Cycle over matched species
     1512
     1513                   DO  ispec = 1, n_matched_vars
     1514
     1515!
     1516!-- PMs are already in kilograms
     1517
     1518                      IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR. &
     1519                            TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR. &
     1520                            TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
     1521
     1522!
     1523!-- kg/(m^2*s) * kg/m^3
     1524                         surf_lsm_h%cssws(match_spec_model(ispec),m) =                   &
     1525                                   emiss_factor_side(match_spec_input(ispec)) *          &
     1526                                   emis_distribution(1,j,i,ispec) *                      &     ! kg/(m^2*s)
     1527                                   rho_air(k)                                                  ! kg/m^3   
     1528!
     1529!-- Other species
     1530!-- Inputs are micromoles
     1531
    13541532                      ELSE
    1355                    
    1356                          !   
    1357                          !--             ppm/s *m *kg/m^3     
    1358                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_side(match_spec_input(ispec)) * &
    1359                                                                         emis_distribution(1,j,i,ispec) *            &  !< in micromoles/(m^2*s)
    1360                                                                          conv_to_ratio(k,j,i) *                     &  !< in m^3/Nmole       
    1361                                                                           rho_air(k)                                   !< in kg/m^3   
     1533
     1534!   
     1535!-- ppm/s *m *kg/m^3
     1536
     1537                         surf_lsm_h%cssws(match_spec_model(ispec),m) =                   &
     1538                                   emiss_factor_side(match_spec_input(ispec)) *          &
     1539                                   emis_distribution(1,j,i,ispec) *                      &  ! micromoles/(m^2*s)
     1540                                   conv_to_ratio(k,j,i) *                                &  ! m^3/Nmole       
     1541                                   rho_air(k)                                               ! kg/m^3   
     1542
    13621543                      ENDIF
    13631544
    1364                    ENDDO
     1545                   ENDDO  ! ispec
     1546
     1547!
     1548!-- If no street type is defined, then assign zero emission to all the species
    13651549
    13661550                ELSE
    13671551
    1368                    !
    1369                    !-- If no street type is defined, then assign zero emission to all the species
    13701552                   surf_lsm_h%cssws(:,m) = 0.0_wp
    13711553
    1372                 ENDIF
    1373 
    1374              ENDDO
    1375 
    1376           ENDIF
    1377 
    1378        !
    1379        !-- For both DEFAULT and PRE-PROCESSED mode
     1554                ENDIF  ! street type
     1555
     1556             ENDDO  ! m
     1557
     1558          ENDIF  ! street_type_f%from_file
     1559
     1560
     1561!
     1562!-- LOD 1 (DEFAULT) and LOD 2 (PRE-PROCESSED)
     1563
     1564
    13801565       ELSE   
    13811566       
    13821567
    1383           DO ispec = 1, nspec_out
     1568          DO ispec = 1, n_matched_vars
    13841569                   
    13851570!
    13861571!--          Default surfaces
     1572
    13871573             DO  m = 1, surf_def_h(0)%ns
    13881574
     
    13901576                j = surf_def_h(0)%j(m)
    13911577
    1392                 IF ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
    1393 
    1394                    !
    1395                    !-- PMs
    1396                    IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1"  &
    1397                         .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM25"  &
    1398                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM10" )  THEN
     1578                IF  ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
     1579
     1580!
     1581!-- PMs
     1582                   IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR.    &
     1583                         TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR.    &
     1584                         TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
    13991585               
    1400                       !
    1401                       !--            kg/(m^2*s) *kg/m^3                         kg/(m^2*s)                 
    1402                       surf_def_h(0)%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec)*  &
    1403                                                                         rho_air(nzb)                           !< in kg/m^3 
    1404  
     1586                      surf_def_h(0)%cssws(match_spec_model(ispec),m) =         &     ! kg/m2/s * kg/m3
     1587                               emis_distribution(1,j,i,ispec)*                 &     ! kg/m2/s
     1588                               rho_air(nzb)                                          ! kg/m^3 
    14051589 
    14061590                   ELSE
    14071591
    1408                       !
    1409                       !-- VOCs
    1410                       IF ( len_index_voc > 0 .AND. emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
    1411                          !
    1412                          !--           (ppm/s) * m * kg/m^3                        mole/(m^2/s)   
    1413                          surf_def_h(0)%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &
    1414                                                                            conv_to_ratio(nzb,j,i) *         &  !< in m^3/mole
    1415                                                                             ratio2ppm *                     &  !< in ppm
    1416                                                                              rho_air(nzb)                      !< in kg/m^3 
    1417 
    1418 
    1419                       !
    1420                       !-- Other species
     1592!
     1593!-- VOCs
     1594                      IF  ( len_index_voc > 0                                           .AND.      &
     1595                            emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
     1596
     1597                         surf_def_h(0)%cssws(match_spec_model(ispec),m) =      &  ! ppm/s * m * kg/m3
     1598                               emis_distribution(1,j,i,ispec) *                &  ! mole/m2/s
     1599                               conv_to_ratio(nzb,j,i) *                        &  ! m^3/mole
     1600                               ratio2ppm *                                     &  ! ppm
     1601                               rho_air(nzb)                                       ! kg/m^3 
     1602
     1603
     1604!
     1605!-- Other species
     1606
    14211607                      ELSE
    14221608
    1423                          !
    1424                          !--           (ppm/s) * m  * kg/m^3                    kg/(m^2/s)
    1425                          surf_def_h(0)%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &       
    1426                                                                            ( 1.0_wp / emt_att%xm(ispec) ) * &  !< in mole/kg
    1427                                                                              conv_to_ratio(nzb,j,i) *       &  !< in m^3/mole 
    1428                                                                               ratio2ppm *                   &  !< in ppm
    1429                                                                                rho_air(nzb)                    !< in  kg/m^3 
     1609                         surf_def_h(0)%cssws(match_spec_model(ispec),m) =      &   ! ppm/s * m * kg/m3
     1610                               emis_distribution(1,j,i,ispec) *                &   ! kg/m2/s
     1611                               ( 1.0_wp / emt_att%xm(ispec) ) *                &   ! mole/kg
     1612                               conv_to_ratio(nzb,j,i) *                        &   ! m^3/mole 
     1613                               ratio2ppm *                                     &   ! ppm
     1614                               rho_air(nzb)                                        !  kg/m^3 
    14301615 
    1431 
    1432                       ENDIF
    1433 
    1434                    ENDIF
    1435 
    1436                 ENDIF
    1437 
    1438              ENDDO
     1616                      ENDIF  ! VOC
     1617
     1618                   ENDIF  ! PM
     1619
     1620                ENDIF  ! emis_distribution > 0
     1621
     1622             ENDDO  ! m
    14391623         
    14401624!
    1441 !--          LSM surfaces
    1442              DO m = 1, surf_lsm_h%ns
     1625!-- LSM surfaces
     1626
     1627             DO  m = 1, surf_lsm_h%ns
    14431628
    14441629                i = surf_lsm_h%i(m)
     
    14461631                k = surf_lsm_h%k(m)
    14471632
    1448                 IF ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
    1449 
    1450                    !
    1451                    !-- PMs
    1452                    IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1"  &
    1453                         .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM25"  &
    1454                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM10" )  THEN
    1455    
    1456                       !
    1457                       !--         kg/(m^2*s) * kg/m^3                           kg/(m^2*s)           
    1458                       surf_lsm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &
    1459                                                                      rho_air(k)                                !< in kg/m^3
     1633                IF  ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
     1634
     1635!
     1636!-- PMs
     1637                   IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR.    &
     1638                         TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR.    &
     1639                         TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
     1640
     1641                      surf_lsm_h%cssws(match_spec_model(ispec),m) =            &    ! kg/m2/s * kg/m3
     1642                               emis_distribution(1,j,i,ispec) *                &    ! kg/m2/s
     1643                               rho_air(k)                                           ! kg/m^3
    14601644 
    14611645                   ELSE
    14621646
    1463                       !
    1464                       !-- VOCs
    1465                       IF ( len_index_voc > 0 .AND. emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
    1466                          !
    1467                          !--          (ppm/s) * m * kg/m^3                        mole/(m^2/s)   
    1468                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &     
    1469                                                                         conv_to_ratio(k,j,i) *           &     !< in m^3/mole
    1470                                                                          ratio2ppm *                     &     !< in ppm
    1471                                                                           rho_air(k)                           !< in kg/m^3 
    1472 
    1473                       !
    1474                       !-- Other species
     1647!
     1648!-- VOCs
     1649
     1650                      IF  ( len_index_voc > 0                                           .AND.      &
     1651                            emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
     1652
     1653                         surf_lsm_h%cssws(match_spec_model(ispec),m) =         &   ! ppm/s * m * kg/m3
     1654                               emis_distribution(1,j,i,ispec) *                &   ! mole/m2/s 
     1655                               conv_to_ratio(k,j,i) *                          &   ! m^3/mole
     1656                               ratio2ppm *                                     &   ! ppm
     1657                               rho_air(k)                                          ! kg/m^3 
     1658
     1659!
     1660!-- Other species
     1661
    14751662                      ELSE
    1476                          !
    1477                          !--           (ppm/s) * m  * kg/m^3                    kg/(m^2/s)
    1478                          surf_lsm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &
    1479                                                                         ( 1.0_wp / emt_att%xm(ispec) ) * &     !< in mole/kg
    1480                                                                          conv_to_ratio(k,j,i) *          &     !< in m^3/mole
    1481                                                                           ratio2ppm *                    &     !< in ppm
    1482                                                                            rho_air(k)                          !< in kg/m^3     
     1663
     1664                         surf_lsm_h%cssws(match_spec_model(ispec),m) =         &   ! ppm/s * m * kg/m3
     1665                               emis_distribution(1,j,i,ispec) *                &   ! kg/m2/s
     1666                               ( 1.0_wp / emt_att%xm(ispec) ) *                &   ! mole/kg
     1667                               conv_to_ratio(k,j,i) *                          &   ! m^3/mole
     1668                               ratio2ppm *                                     &   ! ppm
     1669                               rho_air(k)                                          ! kg/m^3     
    14831670                                                   
    1484                       ENDIF
    1485 
    1486                    ENDIF
    1487 
    1488                 ENDIF
    1489 
    1490              ENDDO
    1491 
    1492 !
    1493 !--          USM surfaces
    1494              DO m = 1, surf_usm_h%ns
     1671                      ENDIF  ! VOC
     1672
     1673                   ENDIF  ! PM
     1674
     1675                ENDIF  ! emis_distribution
     1676
     1677             ENDDO  ! m
     1678
     1679!
     1680!-- USM surfaces
     1681
     1682             DO  m = 1, surf_usm_h%ns
    14951683
    14961684                i = surf_usm_h%i(m)
     
    14981686                k = surf_usm_h%k(m)
    14991687
    1500                 IF ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
    1501 
    1502                    !
    1503                    !-- PMs
    1504                    IF ( TRIM( spc_names(match_spec_model(ispec)) ) == "PM1" &
    1505                         .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM25"  &
    1506                           .OR. TRIM( spc_names(match_spec_model(ispec)) ) == "PM10" )  THEN
     1688                IF  ( emis_distribution(1,j,i,ispec) > 0.0_wp )  THEN
     1689
     1690!
     1691!-- PMs
     1692                   IF  ( TRIM(spc_names(match_spec_model(ispec))) == "PM1"     .OR.    &
     1693                         TRIM(spc_names(match_spec_model(ispec))) == "PM25"    .OR.    &
     1694                         TRIM(spc_names(match_spec_model(ispec))) == "PM10" )  THEN
    15071695                   
    1508                       !
    1509                       !--          kg/(m^2*s) *kg/m^3                             kg/(m^2*s)                     
    1510                       surf_usm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec)*  &
    1511                                                                      rho_air(k)                                !< in kg/m^3
    1512 
    1513  
     1696                      surf_usm_h%cssws(match_spec_model(ispec),m) =            &    ! kg/m2/s * kg/m3
     1697                               emis_distribution(1,j,i,ispec)*                 &    ! kg/m2/s
     1698                               rho_air(k)                                           ! kg/m^3
     1699
    15141700                   ELSE
    15151701                     
    1516                       !
    1517                       !-- VOCs
    1518                       IF ( len_index_voc > 0 .AND. emt_att%species_name(match_spec_input(ispec)) == "VOC" ) THEN
    1519                          !
    1520                          !--          (ppm/s) * m * kg/m^3                        mole/(m^2/s)   
    1521                          surf_usm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &
    1522                                                                         conv_to_ratio(k,j,i) *           &     !< in m^3/mole
    1523                                                                          ratio2ppm *                     &     !< in ppm
    1524                                                                           rho_air(k)                           !< in kg/m^3   
    1525 
    1526                       !
    1527                       !-- Other species
     1702!
     1703!-- VOCs
     1704                      IF  ( len_index_voc > 0                                           .AND.      &
     1705                            emt_att%species_name(match_spec_input(ispec)) == "VOC" )  THEN
     1706
     1707                         surf_usm_h%cssws(match_spec_model(ispec),m) =         &   ! ppm/s * m * kg/m3
     1708                               emis_distribution(1,j,i,ispec) *                &   ! m2/s
     1709                               conv_to_ratio(k,j,i) *                          &   ! m^3/mole
     1710                               ratio2ppm *                                     &   ! ppm
     1711                               rho_air(k)                                          ! kg/m^3   
     1712
     1713!
     1714!-- Other species
    15281715                      ELSE
    15291716
    1530                          !
    1531                          !--          (ppm/s) * m * kg/m^3                        kg/(m^2/s)                     
    1532                          surf_usm_h%cssws(match_spec_model(ispec),m) = emis_distribution(1,j,i,ispec) *  &   
    1533                                                                         ( 1.0_wp / emt_att%xm(ispec) ) * &     !< in mole/kg
    1534                                                                          conv_to_ratio(k,j,i) *          &     !< in m^3/mole
    1535                                                                           ratio2ppm*                     &     !< in ppm
    1536                                                                            rho_air(k)                          !< in kg/m^3   
    1537 
    1538 
    1539                       ENDIF
    1540 
    1541                    ENDIF
    1542 
    1543                 ENDIF
    1544  
    1545              ENDDO
     1717                         surf_usm_h%cssws(match_spec_model(ispec),m) =         &   ! ppm/s * m * kg/m3
     1718                               emis_distribution(1,j,i,ispec) *                &   ! kg/m2/s
     1719                               ( 1.0_wp / emt_att%xm(ispec) ) *                &   ! mole/kg
     1720                               conv_to_ratio(k,j,i) *                          &   ! m^3/mole
     1721                               ratio2ppm*                                      &   ! ppm
     1722                               rho_air(k)                                          ! kg/m^3   
     1723
     1724
     1725                      ENDIF  ! VOC
     1726
     1727                   ENDIF  ! PM
     1728
     1729                ENDIF  ! emis_distribution
     1730 
     1731             ENDDO  ! m
    15461732
    15471733          ENDDO
     
    15491735       ENDIF
    15501736
    1551        !
    1552        !-- Deallocate time_factor in case of DEFAULT mode)
    1553        IF ( ALLOCATED ( time_factor ) ) DEALLOCATE( time_factor )
     1737!
     1738!-- Deallocate time_factor in case of DEFAULT mode)
     1739
     1740       IF  ( ALLOCATED (time_factor) )  DEALLOCATE (time_factor)
    15541741
    15551742   ENDIF
Note: See TracChangeset for help on using the changeset viewer.