Ignore:
Timestamp:
Oct 30, 2018 7:05:21 PM (5 years ago)
Author:
suehring
Message:

Branch salsa @3446 re-integrated into trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/chem_emissions_mod.f90

    r3458 r3467  
    2727! -----------------
    2828! $Id$
     29! Enabled PARAMETRIZED mode for default surfaces when LSM is not applied but
     30! salsa is used
     31!
     32! 3458 2018-10-30 14:51:23Z kanani
    2933! from chemistry branch r3443, banzhafs, Russo:
    3034! Additional correction for index of input file of pre-processed mode
     
    885889   USE indices,                                                               &
    886890       ONLY: nnx,nny,nnz
     891   USE salsa_mod,                                                             &
     892       ONLY:  salsa
    887893   USE surface_mod,                                                           &
    888894       ONLY:  surf_lsm_h,surf_def_h,surf_usm_h
     
    13661372
    13671373       !> Streets are lsm surfaces, hence, no usm surface treatment required
    1368              IF (surf_lsm_h%ns .GT. 0) THEN
     1374             IF (surf_lsm_h%ns .GT. 0 ) THEN
    13691375                DO  m = 1, surf_lsm_h%ns
    13701376                   i = surf_lsm_h%i(m)
     
    14421448                   !> If no street type is defined, then assign null emissions to all the species
    14431449                      surf_lsm_h%cssws(:,m) = 0.0_wp
     1450
     1451                   ENDIF
     1452
     1453                ENDDO
     1454             ELSEIF ( salsa ) THEN
     1455                DO  m = 1, surf_def_h(0)%ns
     1456                   i = surf_def_h(0)%i(m)
     1457                   j = surf_def_h(0)%j(m)
     1458                   k = surf_def_h(0)%k(m)
     1459
     1460
     1461                   IF ( street_type_f%var(j,i) >= main_street_id  .AND.        &
     1462                        street_type_f%var(j,i) < max_street_id )               &
     1463                   THEN
     1464
     1465                      !> Cycle over already matched species
     1466                      DO  ispec=1,nspec_out
     1467
     1468                         !> PMs are already in mass units:micrograms: have to be converted to kilograms
     1469                         IF ( TRIM(spc_names(match_spec_model(ispec)))=="PM1"       &
     1470                              .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25" &
     1471                              .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10")&
     1472                         THEN
     1473                                 
     1474                            surf_def_h(0)%cssws(match_spec_model(ispec),m) =   &
     1475                                  emiss_factor_main(match_spec_input(ispec)) * &
     1476                                  emis_distribution(1,j,i,ispec) * rho_air(k) /&
     1477                                  time_factor(1)
     1478                         ELSE
     1479
     1480                         !> Other Species: inputs are micromoles: have to be converted             
     1481                            surf_def_h(0)%cssws(match_spec_model(ispec),m) =   &
     1482                               emiss_factor_main(match_spec_input(ispec)) *    &
     1483                               emis_distribution(1,j,i,ispec) *                &
     1484                               conv_to_ratio(k,j,i) *  rho_air(k) / time_factor(1)
     1485                         ENDIF
     1486                      ENDDO
     1487
     1488                   ELSEIF ( street_type_f%var(j,i) >= side_street_id  .AND.    &
     1489                            street_type_f%var(j,i) < main_street_id )          &
     1490                   THEN
     1491
     1492                   !> Cycle over already matched species
     1493                      DO  ispec=1,nspec_out
     1494
     1495                         !> PMs are already in mass units: micrograms
     1496                         IF ( TRIM(spc_names(match_spec_model(ispec)))=="PM1"   &
     1497                              .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM25" &
     1498                              .OR. TRIM(spc_names(match_spec_model(ispec)))=="PM10")&
     1499                         THEN
     1500
     1501                            surf_def_h(0)%cssws(match_spec_model(ispec),m) =   &
     1502                               emiss_factor_side(match_spec_input(ispec)) *    &
     1503                               emis_distribution(1,j,i,ispec) * rho_air(k) /   &
     1504                               time_factor(1) 
     1505                         ELSE
     1506               
     1507                            surf_def_h(0)%cssws(match_spec_model(ispec),m) =   &
     1508                               emiss_factor_side(match_spec_input(ispec)) *    &
     1509                               emis_distribution(1,j,i,ispec) *                &
     1510                               conv_to_ratio(k,j,i) * rho_air(k) / time_factor(1)
     1511                         ENDIF
     1512
     1513                      ENDDO
     1514
     1515                   ELSE
     1516
     1517                   !> If no street type is defined, then assign null emissions to all the species
     1518                      surf_def_h(0)%cssws(:,m) = 0.0_wp
    14441519
    14451520                   ENDIF
Note: See TracChangeset for help on using the changeset viewer.