Ignore:
Timestamp:
Apr 22, 2016 8:52:11 AM (8 years ago)
Author:
hoffmann
Message:

improvements for the consideration of aerosols in the LCM

File:
1 edited

Legend:

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

    r1874 r1890  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Initialization of aerosol equilibrium radius not possible in supersaturated
     22! environments. Therefore, a maximum supersaturation of -1 % is assumed during
     23! initialization.
    2224!
    2325! Former revisions:
     
    811813    REAL(wp)  :: weight_sum         !< sum of all weighting factors
    812814
    813     INTEGER(iwp), DIMENSION(:,:,:), INTENT(IN) ::  local_start !<
     815    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg), INTENT(IN) ::  local_start !<
    814816
    815817    INTEGER(iwp)  :: n              !<
     
    980982
    981983!
    982 !--          The formula is only valid for subsaturated environments. In (super-)
    983 !--          saturated air, the inital radius is used.
    984              IF ( e_a / e_s < 1.0_wp )  THEN
     984!--          The formula is only valid for subsaturated environments. For
     985!--          supersaturations higher than -1 %, the supersaturation is set to -1%.
     986             IF ( e_a / e_s < 0.99_wp )  THEN
    985987
    986988                DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
     
    995997                ENDDO
    996998
     999             ELSE
     1000
     1001                DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
     1002
     1003                   bfactor             = vanthoff * molecular_weight_of_water *    &
     1004                                         rho_s * particles(n)%rvar2**3 /           &
     1005                                         ( molecular_weight_of_solute * rho_l )
     1006                   particles(n)%radius = particles(n)%rvar2 * ( bfactor /          &
     1007                                         particles(n)%rvar2**3 )**(1.0_wp/3.0_wp) *&
     1008                                         0.01_wp**(-1.0_wp/3.0_wp)
     1009
     1010                ENDDO
     1011
    9971012             ENDIF
    9981013
Note: See TracChangeset for help on using the changeset viewer.