Ignore:
Timestamp:
Oct 12, 2018 3:17:09 PM (6 years ago)
Author:
kanani
Message:

reintegrate branch resler to trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/chem_emissions_mod.f90

    r3312 r3337  
    2727! -----------------
    2828! $Id$
     29! (from branch resler)
     30! Formatting
     31!
     32! 3312 2018-10-06 14:15:46Z knoop
    2933! Initial revision
    3034!
     
    719723                DO  ispec = 1 , len_index
    720724
    721                    IF ( emiss_factor_main(match_spec_input(ispec)) .LT. 0 .AND. emiss_factor_side(match_spec_input(ispec)) .LT. 0 ) THEN
    722 
    723                       message_string = 'PARAMETERIZED emissions mode selected:'            //          &
     725                   IF ( emiss_factor_main(match_spec_input(ispec)) .LT. 0 .AND.                         &
     726                        emiss_factor_side(match_spec_input(ispec)) .LT. 0 ) THEN
     727
     728                      message_string = 'PARAMETERIZED emissions mode selected:'            //           &
    724729                                       ' EMISSIONS POSSIBLE ONLY ON STREET SURFACES'        //          &
    725730                                       ' but values of scaling factors for street types'    //          &
     
    12461251                IF (TRIM(spc_names(match_spec_model(ispec)))=="NO") THEN
    12471252                !>             Kg/m2                       kg/m2*s                                                   
    1248                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%nox_comp(icat,1)*con_factor
     1253                   delta_emis(nys:nyn,nxl:nxr) =                                                             &
     1254                         emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%nox_comp(icat,1)*con_factor
    12491255                   
    1250                    emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1256                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                              &
     1257                         emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12511258
    12521259                ELSE IF (TRIM(spc_names(match_spec_model(ispec)))=="NO2") THEN
    12531260   
    1254                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%nox_comp(icat,2)*con_factor
    1255 
    1256                    emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1261                   delta_emis(nys:nyn,nxl:nxr) =                                                             &
     1262                         emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%nox_comp(icat,2)*con_factor
     1263
     1264                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                              &
     1265                         emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12571266 
    12581267             !> SOX Compositions
     
    12601269                ELSE IF (TRIM(spc_names(match_spec_model(ispec)))=="SO2") THEN
    12611270                     
    1262                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%sox_comp(icat,1)*con_factor
    1263 
    1264                    emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1271                   delta_emis(nys:nyn,nxl:nxr) =                                                             &
     1272                         emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%sox_comp(icat,1)*con_factor
     1273
     1274                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                              &
     1275                         emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12651276
    12661277                ELSE IF (TRIM(spc_names(match_spec_model(ispec)))=="SO4") THEN
    12671278   
    1268                    delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%sox_comp(icat,2)*con_factor
    1269 
    1270                    emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1279                   delta_emis(nys:nyn,nxl:nxr) =                                                             &
     1280                         emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%sox_comp(icat,2)*con_factor
     1281
     1282                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                              &
     1283                         emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12711284 
    12721285
     
    12781291                   DO i_pm_comp= 1,SIZE(emt_att%pm_comp(1,:,1))
    12791292
    1280                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,1)*con_factor
     1293                      delta_emis(nys:nyn,nxl:nxr) =                                                          &
     1294                            emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,1)*con_factor
    12811295                                                                                         
    12821296
    1283                       emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1297                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                           &
     1298                            emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12841299 
    12851300                   ENDDO
     
    12911306                   DO i_pm_comp= 1,SIZE(emt_att%pm_comp(1,:,2))
    12921307
    1293                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,2)*con_factor
     1308                      delta_emis(nys:nyn,nxl:nxr) =                                                          &
     1309                            emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,2)*con_factor
    12941310                                                                                         
    12951311
    1296                       emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1312                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                           &
     1313                            emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    12971314 
    12981315                   ENDDO
     
    13041321                   DO i_pm_comp= 1,SIZE(emt_att%pm_comp(1,:,3)) 
    13051322                       
    1306                       delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,3)*con_factor
     1323                      delta_emis(nys:nyn,nxl:nxr) =                                                          &
     1324                            emis(nys:nyn,nxl:nxr)*time_factor(icat)*emt_att%pm_comp(icat,i_pm_comp,3)*con_factor
    13071325                                                                                                 
    13081326
    1309                       emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1327                      emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                           &
     1328                            emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    13101329
    13111330                   ENDDO
     
    13191338                      IF (TRIM(spc_names(match_spec_model(ispec)))==TRIM(emt_att%voc_name(ivoc))) THEN   
    13201339
    1321                          delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*                               &
     1340                         delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*               &
    13221341                                                       emt_att%voc_comp(icat,match_spec_voc_input(ivoc))*con_factor
    13231342
    1324                          emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1343                         emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                         &
     1344                               emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    13251345
    13261346                      ENDIF                       
     
    13331353                   delta_emis(nys:nyn,nxl:nxr) = emis(nys:nyn,nxl:nxr)*time_factor(icat)*con_factor
    13341354 
    1335                    emis_distribution(1,nys:nyn,nxl:nxr,ispec)=emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
     1355                   emis_distribution(1,nys:nyn,nxl:nxr,ispec) =                                               &
     1356                         emis_distribution(1,nys:nyn,nxl:nxr,ispec)+delta_emis(nys:nyn,nxl:nxr)
    13361357
    13371358                ENDIF  ! IF (spc_names==)
     
    13751396
    13761397                         !> PMs are already in mass units:micrograms:they have to be converted to kilograms
    1377                          IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1" .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
     1398                         IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1"         &
     1399                             .OR.  TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
    13781400                             .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
    13791401
     
    13891411                         !> Other Species: inputs are micromoles: they have to be converted in moles
    13901412                         !                 ppm/s *m *kg/m^3               
    1391                             surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_main(match_spec_input(ispec))*   &
     1413                            surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_main(match_spec_input(ispec))*  &
    13921414                         !                                                    micromoles/(m^2*s)
    1393                                                                           emis_distribution(1,j,i,ispec) *              &
     1415                                                                          emis_distribution(1,j,i,ispec) *             &
    13941416                         !                                                    m**3/Nmole
    1395                                                                           conv_to_ratio(k,j,i)*                         &       
     1417                                                                          conv_to_ratio(k,j,i)*                        &
    13961418                         !                                                    kg/m^3
    13971419                                                                          rho_air(k)   
     
    14031425
    14041426
    1405                    ELSEIF ( street_type_f%var(j,i) >= side_street_id  .AND. street_type_f%var(j,i) < main_street_id )  THEN
     1427                   ELSEIF ( street_type_f%var(j,i) >= side_street_id  .AND.                                            &
     1428                            street_type_f%var(j,i) < main_street_id )  THEN
    14061429
    14071430                   !> Cycle over already matched species
     
    14091432
    14101433                         !> PMs are already in mass units: micrograms
    1411                          IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1" .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
     1434                         IF (     TRIM(spc_names(match_spec_model(ispec)))=="PM1"   &
     1435                             .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
    14121436                             .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
    14131437
    14141438                            !              kg/(m^2*s) *kg/m^3                               
    1415                             surf_lsm_h%cssws(match_spec_model(ispec),m)= emiss_factor_side(match_spec_input(ispec)) *   &
     1439                            surf_lsm_h%cssws(match_spec_model(ispec),m)= emiss_factor_side(match_spec_input(ispec)) *  &
    14161440                            !                                                       kg/(m^2*s)
    14171441                                                                                emis_distribution(1,j,i,ispec)*        &
     
    14231447                         !>Other Species: inputs are micromoles
    14241448                         !                 ppm/s *m *kg/m^3               
    1425                             surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_side(match_spec_input(ispec)) *   &
     1449                            surf_lsm_h%cssws(match_spec_model(ispec),m) = emiss_factor_side(match_spec_input(ispec)) * &
    14261450                         !                                                    micromoles/(m^2*s)
    1427                                                                           emis_distribution(1,j,i,ispec) *              &
     1451                                                                          emis_distribution(1,j,i,ispec) *             &
    14281452                         !                                                    m**3/Nmole
    1429                                                                           conv_to_ratio(k,j,i)*                         &       
     1453                                                                          conv_to_ratio(k,j,i)*                        &
    14301454                         !                                                    kg/m^3
    14311455                                                                          rho_air(k)   
     
    14661490
    14671491                   !> PMs
    1468                    IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1" .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
    1469                           .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
     1492                   IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1"                                   &
     1493                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"                           &
     1494                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
    14701495                   
    14711496                      !            kg/(m^2*s) *kg/m^3                         kg/(m^2*s)                 
     
    15221547
    15231548                   !> PMs
    1524                    IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1" .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
    1525                           .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
     1549                   IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1"                                            &
     1550                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"                                    &
     1551                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
    15261552
    15271553                      !         kg/(m^2*s) * kg/m^3                           kg/(m^2*s)           
     
    15731599
    15741600                   !> PMs
    1575                    IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1" .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"  &
    1576                           .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
     1601                   IF (TRIM(spc_names(match_spec_model(ispec)))=="PM1"                                     &
     1602                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25"                             &
     1603                         .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10") THEN
    15771604                   
    15781605                      !          kg/(m^2*s) *kg/m^3                             kg/(m^2*s)                     
Note: See TracChangeset for help on using the changeset viewer.