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

lpm_droplet_condensation improved, microphysics partially modularized

File:
1 edited

Legend:

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

    r1823 r1849  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! bfactor removed
    2222!
    2323! Former revisions:
     
    8585       
    8686    USE cloud_parameters,                                                      &
    87         ONLY:  bfactor, cp, c_sedimentation, dpirho_l, dt_precipitation,       &
    88                hyrho, k_st, l_d_cp, l_d_r, l_d_rv, l_v, mass_of_solute,  &
    89                molecular_weight_of_solute, molecular_weight_of_water, pirho_l, &
    90                pt_d_t, rho_l, r_d, r_v, sed_qc_const, schmidt, schmidt_p_1d3,  &
    91                sigma_gc, t_d_pt, vanthoff, w_precipitation
    92        
    93     USE constants,                                                             &
    94         ONLY:  pi
    95        
     87        ONLY:  cp, hyrho, l_d_cp, l_d_r, l_d_rv, l_v, pt_d_t, rho_l, r_d, r_v, &
     88               t_d_pt
     89               
    9690    USE control_parameters,                                                    &
    97         ONLY:  g, message_string, microphysics_seifert, pt_surface,            &
    98                rho_surface, surface_pressure
     91        ONLY:  g, message_string, pt_surface, rho_surface, surface_pressure
    9992   
    10093    USE indices,                                                               &
     
    118111    l_d_rv = l_v / r_v
    119112
    120     schmidt_p_1d3 = schmidt**( 1.0_wp / 3.0_wp )
    121 
    122     pirho_l  = pi * rho_l / 6.0_wp
    123     dpirho_l = 1.0_wp / pirho_l
    124 !
    125 !-- constant for the sedimentation of cloud water (2-moment cloud physics)
    126     sed_qc_const = k_st * ( 3.0_wp / ( 4.0_wp * pi * rho_l )                   &
    127                           )**( 2.0_wp / 3.0_wp ) *                             &
    128                    EXP( 5.0_wp * LOG( sigma_gc )**2 )
    129 !
    130 !-- Calculate timestep according to precipitation
    131     IF ( microphysics_seifert )  THEN
    132        dt_precipitation = c_sedimentation * MINVAL( dzu(nzb+2:nzt) ) /         &
    133                           w_precipitation
    134     ENDIF
    135 !
    136 !-- Calculate factor used in equation for droplet growth by condensation
    137     bfactor = 3.0_wp * vanthoff * mass_of_solute * molecular_weight_of_water   &
    138               / ( 4.0_wp * pi * rho_l * molecular_weight_of_solute )
    139113!
    140114!-- Calculate:
Note: See TracChangeset for help on using the changeset viewer.