Ignore:
Timestamp:
Aug 29, 2017 2:10:28 PM (7 years ago)
Author:
schwenkel
Message:

improved aerosol initialization for bulk microphysics

File:
1 edited

Legend:

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

    r2346 r2375  
    2525! -----------------
    2626! $Id$
     27! Initialization of chemical aerosol composition
     28!
     29! 2346 2017-08-09 16:39:17Z suehring
    2730! Bugfix, correct determination of topography top index
    2831!
     
    970973
    971974    USE cloud_parameters,                                                      &
    972         ONLY: l_d_rv, rho_l, r_v
     975        ONLY: l_d_rv, molecular_weight_of_solute,                              &
     976              molecular_weight_of_water, rho_l, r_v, rho_s, vanthoff
    973977
    974978    USE constants,                                                             &
     
    978982
    979983    USE particle_attributes,                                                   &
    980         ONLY: aero_type, aero_weight, log_sigma, molecular_weight_of_solute,   &
    981               molecular_weight_of_water, na, rho_s, rm, vanthoff
     984        ONLY: aero_species, aero_type, aero_weight, log_sigma, na, rm
    982985
    983986    IMPLICIT NONE
     
    10031006    INTEGER(iwp)  :: kp             !<
    10041007
     1008!
     1009!-- Set constants for different aerosol species
     1010    IF ( TRIM(aero_species) .EQ. 'nacl' ) THEN
     1011       molecular_weight_of_solute = 0.05844_wp
     1012       rho_s                      = 2165.0_wp
     1013       vanthoff                   = 2.0_wp
     1014    ELSEIF ( TRIM(aero_species) .EQ. 'c3h4o4' ) THEN
     1015       molecular_weight_of_solute = 0.10406_wp
     1016       rho_s                      = 1600.0_wp
     1017       vanthoff                   = 1.37_wp
     1018    ELSEIF ( TRIM(aero_species) .EQ. 'nh4o3' ) THEN
     1019       molecular_weight_of_solute = 0.08004_wp
     1020       rho_s                      = 1720.0_wp
     1021       vanthoff                   = 2.31_wp
     1022    ELSE
     1023       WRITE( message_string, * ) 'unknown aerosol species ',   &
     1024                                'aero_species = "', TRIM( aero_species ), '"'
     1025       CALL message( 'lpm_init', 'PA0470', 1, 2, 0, 6, 0 )
     1026    ENDIF
    10051027!
    10061028!-- The following typical aerosol spectra are taken from Jaenicke (1993):
Note: See TracChangeset for help on using the changeset viewer.