Ignore:
Timestamp:
Apr 15, 2016 11:46:09 AM (8 years ago)
Author:
hoffmann
Message:

initialization of aerosol spectra added

File:
1 edited

Legend:

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

    r1852 r1871  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Initialization of aerosols added.
    2222!
    2323! Former revisions:
     
    119119    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
    120120
    121 !
    122 !-- Lagrangian cloud model constants
    123     REAL(wp) ::  mass_of_solute = 1.0E-17_wp                !< soluted NaCl (kg)
    124     REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp    !< mol. m. NaCl (kg mol-1)
    125     REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp  !< mol. m. H2O (kg mol-1)
    126     REAL(wp) ::  vanthoff = 2.0_wp                          !< van't Hoff factor for NaCl
    127 
    128121    TYPE particle_type
    129122        SEQUENCE
     
    164157    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
    165158
     159!
     160!-- Lagrangian cloud model constants (especially for steering aerosols)
     161    REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp    !< mol. m. NaCl (kg mol-1)
     162    REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp  !< mol. m. H2O (kg mol-1)
     163    REAL(wp) ::  rho_s = 2165.0_wp                          !< density of NaCl (kg m-3)
     164    REAL(wp) ::  vanthoff = 2.0_wp                          !< van't Hoff factor for NaCl
     165
     166    REAL(wp) ::  n1 = 100.0_wp, s1 = 2.0_wp, rm1 = 0.05E-6_wp, &
     167                 n2 =   0.0_wp, s2 = 2.0_wp, rm2 = 0.05E-6_wp, &
     168                 n3 =   0.0_wp, s3 = 2.0_wp, rm3 = 0.05E-6_wp
     169
     170    LOGICAL  ::  monodisperse_aerosols      = .FALSE.       !< initialize monodisperse aerosols
     171    LOGICAL  ::  init_aerosol_probabilistic = .FALSE.       !< how to initialize aerosol spectra
     172
    166173    SAVE
    167174
Note: See TracChangeset for help on using the changeset viewer.