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/lpm_droplet_condensation.f90

    r1852 r1871  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Initialization of aerosols added.
    2222!
    2323! Former revisions:
    2424! -----------------
    2525! $Id$
    26 !
    2726!
    2827! 1849 2016-04-08 11:33:18Z hoffmann
     
    121120
    122121    USE particle_attributes,                                                   &
    123         ONLY:  curvature_solution_effects, hall_kernel, mass_of_solute,        &
     122        ONLY:  curvature_solution_effects, hall_kernel,                        &
    124123               molecular_weight_of_solute, molecular_weight_of_water,          &
    125                number_of_particles, particles, radius_classes,                 &
     124               number_of_particles, particles, radius_classes, rho_s,          &
    126125               use_kernel_tables, vanthoff, wang_kernel
    127126
     
    140139    INTEGER(iwp) :: ros_count                  !<
    141140 
    142     INTEGER(iwp), PARAMETER ::  maxtry = 40    !<
     141    INTEGER(iwp), PARAMETER ::  maxtry = 100   !<
    143142
    144143    LOGICAL ::  repeat                         !<
     
    195194    REAL(wp), PARAMETER ::  e3 = 0.0_wp                !<
    196195    REAL(wp), PARAMETER ::  e4 = 125.0_wp / 108.0_wp   !<
     196    REAL(wp), PARAMETER ::  eps_ros = 1.0E-3_wp        !< accuracy of Rosenbrock method
    197197    REAL(wp), PARAMETER ::  gam = 0.5_wp               !<
    198198    REAL(wp), PARAMETER ::  grow = 1.5_wp              !<
     
    200200    REAL(wp), PARAMETER ::  pshrnk = -1.0_wp /3.0_wp   !<
    201201    REAL(wp), PARAMETER ::  shrnk = 0.5_wp             !<
    202     REAL(wp), PARAMETER ::  eps_ros = 1.0E-4_wp        !< accuracy of Rosenbrock method
    203202
    204203!
     
    311310             afactor = 2.0_wp * sigma / ( rho_l * r_v * t_int )
    312311!
    313 !--          Solute effect (bfactor), mass of solute to be replaced by variable
    314 !--          aerosol radius
    315              bfactor = 3.0_wp * vanthoff * mass_of_solute *                     &
    316                        molecular_weight_of_water / ( 4.0_wp * pi * rho_l *      &
    317                                                      molecular_weight_of_solute &
    318                                                    )
     312!--          Solute effect (bfactor)
     313             bfactor = vanthoff * rho_s * particles(n)%rvar2**3 *              &
     314                       molecular_weight_of_water /                             &
     315                       ( rho_l * molecular_weight_of_solute )
    319316
    320317             r_ros = particles(n)%radius
     
    326323
    327324!
    328 !--          Internal time step should not be > 1.0E-2 in case of evaporation
    329 !--          because larger values may lead to secondary solutions which are
    330 !--          physically unlikely
    331              IF ( dt_ros_next > 1.0E-2_wp  .AND.  e_a / e_s < 1.0_wp )  THEN
     325!--          Internal time step should not be > 1.0E-2 and < 1.0E-6
     326             IF ( dt_ros_next > 1.0E-2_wp )  THEN
    332327                dt_ros_next = 1.0E-3_wp
     328             ELSEIF ( dt_ros_next < 1.0E-6_wp )  THEN
     329                dt_ros_next = 1.0E-6_wp
    333330             ENDIF
     331
    334332!
    335333!--          If calculation of Rosenbrock method is repeated due to unreasonalble
     
    337335!--          reduced
    338336             IF ( ros_count > 1 )  THEN
    339                 dt_ros_next = dt_ros_next - ( 0.2_wp * dt_ros_next )
     337                dt_ros_next = dt_ros_next * 0.1_wp
    340338             ELSEIF ( ros_count > 5 )  THEN
    341339!
     
    349347!--          Internal time step must not be larger than PALM time step
    350348             dt_ros = MIN( dt_ros_next, dt_3d )
     349
    351350!
    352351!--          Integrate growth equation in time unless PALM time step is reached
     
    364363                drdt_ini       = drdt
    365364                dt_ros_sum_ini = dt_ros_sum
    366                 r_ros_ini      = r_ros
     365                r_ros_ini      = MAX( r_ros, particles(n)%rvar2 )
    367366
    368367!
     
    378377
    379378                   IF ( jtry == maxtry+1 )  THEN
    380                       message_string = 'maxtry > 40 in Rosenbrock method'
     379                      message_string = 'maxtry > 100 in Rosenbrock method'
    381380                      CALL message( 'lpm_droplet_condensation', 'PA0347', 2,   &
    382381                                    2, 0, 6, 0 )
     
    385384                   aa    = 1.0_wp / ( gam * dt_ros ) - d2rdtdr
    386385                   g1    = drdt_ini / aa
    387                    r_ros = r_ros_ini + a21 * g1
     386                   r_ros = MAX( r_ros_ini + a21 * g1, particles(n)%rvar2 )
    388387                   drdt  = ddenom * ventilation_effect(n) * ( e_a / e_s - 1.0_wp - &
    389388                                                              afactor / r_ros +    &
     
    393392                   g2    = ( drdt + c21 * g1 / dt_ros )&
    394393                           / aa
    395                    r_ros = r_ros_ini + a31 * g1 + a32 * g2
     394                   r_ros = MAX( r_ros_ini + a31 * g1 + a32 * g2, particles(n)%rvar2 )
    396395                   drdt  = ddenom * ventilation_effect(n) * ( e_a / e_s - 1.0_wp - &
    397396                                                              afactor / r_ros +    &
     
    403402                   g4    = ( drdt +  &
    404403                             ( c41 * g1 + c42 * g2 + c43 * g3 ) / dt_ros ) / aa
    405                    r_ros = r_ros_ini + b1 * g1 + b2 * g2 + b3 * g3 + b4 * g4
     404                   r_ros = MAX( r_ros_ini + b1 * g1 + b2 * g2 + b3 * g3 +      &
     405                                b4 * g4, particles(n)%rvar2 )
    406406
    407407                   dt_ros_sum = dt_ros_sum_ini + dt_ros
     
    451451             particles(n)%rvar1 = dt_ros_next
    452452
    453              new_r(n) = r_ros
    454453!
    455454!--          Radius should not fall below 1E-8 because Rosenbrock method may
    456455!--          lead to errors otherwise
    457              new_r(n) = MAX( new_r(n), 1.0E-8_wp )
     456             new_r(n) = MAX( r_ros, particles(n)%rvar2 )
    458457!
    459458!--          Check if calculated droplet radius change is reasonable since in
Note: See TracChangeset for help on using the changeset viewer.