Ignore:
Timestamp:
Aug 2, 2019 11:06:18 AM (5 years ago)
Author:
monakurppa
Message:

Several changes in the salsa aerosol module:

  • Add "salsa_" before each salsa output variable
  • Add a possibility to output the number (salsa_N_UFP) and mass concentration (salsa_PM0.1) of ultrafine particles, i.e. particles with a diameter smaller than 100 nm
  • Implement aerosol emission mode "parameterized" which is based on the street type (similar to the chemistry module).
  • Remove unnecessary nucleation subroutines.
  • Add the z-dimension for gaseous emissions to correspond the implementation in the chemistry module
File:
1 edited

Legend:

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

    r4039 r4131  
    2525! -----------------
    2626! $Id$
     27! Allow profile output for salsa variables.
     28!
     29! 4039 2019-06-18 10:32:41Z suehring
    2730! Correct conversion to kinematic scalar fluxes in case of pw-scheme and
    2831! statistic regions
     
    335338                simulated_time, simulated_time_at_begin,                       &
    336339                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
    337                 ws_scheme_mom, ws_scheme_sca
     340                ws_scheme_mom, ws_scheme_sca, salsa, max_pr_salsa
    338341
    339342    USE cpulog,                                                                &
     
    19541957                ENDIF
    19551958             ENDIF
     1959             IF ( salsa )  THEN
     1960                IF ( max_pr_cs > 0 )  THEN
     1961                   sums_l(:,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0) =    &
     1962                      sums_l(:,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0) + &
     1963                      sums_l(:,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,i)
     1964
     1965                ENDIF
     1966             ENDIF
    19561967          ENDDO
    19571968       ENDIF
     
    19741985                CALL MPI_ALLREDUCE( sums_l(nzb,pr_palm+max_pr_user+i,0),       &
    19751986                                    sums(nzb,pr_palm+max_pr_user+i),           &
     1987                                    nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d, ierr )
     1988             ENDDO
     1989       ENDIF
     1990
     1991       IF ( salsa  .AND.  max_pr_salsa > 0 )  THEN
     1992          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     1993             DO  i = 1, max_pr_salsa
     1994                CALL MPI_ALLREDUCE( sums_l(nzb,pr_palm+max_pr_user+max_pr_cs+i,0),                 &
     1995                                    sums(nzb,pr_palm+max_pr_user+max_pr_user+i),                   &
    19761996                                    nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d, ierr )
    19771997             ENDDO
     
    20512071                                 sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) / &
    20522072                                 ngp_2dh_s_inner(k,sr)
     2073             ENDDO
     2074          ENDIF 
     2075       ENDIF
     2076
     2077       IF ( salsa ) THEN
     2078          IF ( max_pr_salsa > 0 )  THEN
     2079             DO k = nzb, nzt+1
     2080                sums(k,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa) = &
     2081                  sums(k,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa) &
     2082                  / ngp_2dh_s_inner(k,sr)
    20532083             ENDDO
    20542084          ENDIF 
     
    22022232          ENDIF
    22032233       ENDIF
     2234
     2235       IF ( salsa )  THEN
     2236          IF ( max_pr_salsa > 0 )  THEN    ! salsa profiles
     2237             hom(:,1,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa, sr) = &
     2238                  sums(:,pr_palm+max_pr_user+max_pr_cs+1:pr_palm+max_pr_user+max_pr_cs+max_pr_salsa)
     2239          ENDIF
     2240       ENDIF
    22042241!
    22052242!--    Determine the boundary layer height using two different schemes.
Note: See TracChangeset for help on using the changeset viewer.