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

    r1846 r1849  
    1919! Current revisions:
    2020! ------------------
    21 !
    22 !
     21! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
     22! vanthoff moved to mod_particle_attributes.
     23! dt_micro and several cloud_parameters moved to microphysics_mod.
     24! 1d-microphysics profiles moved to microphysics_mod.
     25!
    2326! Former revisions:
    2427! -----------------
     
    394397          c_u_m, c_u_m_l, c_v_m, c_v_m_l, c_w_m, c_w_m_l, ddzu, ddzu_pres,     &
    395398          dd2zu, dzu, ddzw, dzw, hyp, inflow_damping_factor, l_grid,           &
    396           nc_1d, nr_1d, ptdf_x, ptdf_y, p_surf, pt_surf, pt_1d, pt_init,       &
    397           qsws_surf, q_1d, q_init, q_surf, qc_1d, qr_1d, rdf, rdf_sc,          &
    398           ref_state, sa_init, shf_surf, timenudge, time_surf, time_vert,       &
    399           tmp_tnudge, ug, u_init, u_nzb_p1_for_vfc, vg, v_init,                &
     399          ptdf_x, ptdf_y, p_surf, pt_surf, pt_init, qsws_surf, q_init, q_surf, &
     400          rdf, rdf_sc, ref_state, sa_init, shf_surf, timenudge, time_surf,     &
     401          time_vert, tmp_tnudge, ug, u_init, u_nzb_p1_for_vfc, vg, v_init,     &
    400402          v_nzb_p1_for_vfc, w_subs, zu, zw
    401403
     
    407409          mean_inflow_profiles, nrs, nrsws, nrswst,                            &
    408410          ol,                                                                  & !< Obukhov length
    409           ptnudge, pt_slope_ref,                                               &
     411          precipitation_amount, precipitation_rate, ptnudge, pt_slope_ref,     &
    410412          qnudge, qs, qsws, qswst, qswst_remote, qrs, qrsws, qrswst,           &
    411413          saswsb, saswst, shf, tnudge, td_lsa_lpt, td_lsa_q, td_sub_lpt,       &
     
    421423          diss_l_v, diss_l_w, flux_l_e, flux_l_nr, flux_l_pt, flux_l_q,        &
    422424          flux_l_qr, flux_l_sa, flux_l_u, flux_l_v, flux_l_w, kh, km,          &
    423           l_wall, p_loc, tend, tric,                                           &
     425          l_wall, prr, p_loc, tend, tric,                                      &
    424426          u_m_l, u_m_n, u_m_r, u_m_s, v_m_l, v_m_n, v_m_r, v_m_s, w_m_l,       &
    425427          w_m_n, w_m_r, w_m_s
     
    490492    USE kinds
    491493
    492     LOGICAL ::  cloud_water_sedimentation = .FALSE., & !< cloud water sedimentation in bulk cloud physics
    493                 limiter_sedimentation = .TRUE.,      & !< sedimentation limiter in bulk cloud physics
    494                 collision_turbulence = .FALSE.,      & !< turbulence effects in bulk cloud physics
    495                 ventilation_effect = .TRUE.            !< ventilation effect in bulk cloud physics
    496                
    497 
    498     REAL(wp) ::  a_1 = 8.69E-4_wp,     & !< coef. in turb. parametrization (cm-2 s3)
    499                  a_2 = -7.38E-5_wp,    & !< coef. in turb. parametrization (cm-2 s3)
    500                  a_3 = -1.40E-2_wp,    & !< coef. in turb. parametrization
    501                  a_term = 9.65_wp,     & !< coef. for terminal velocity (m s-1)
    502                  a_vent = 0.78_wp,     & !< coef. for ventilation effect
    503                  b_1 = 11.45E-6_wp,    & !< coef. in turb. parametrization (m)
    504                  b_2 = 9.68E-6_wp,     & !< coef. in turb. parametrization (m)
    505                  b_3 = 0.62_wp,        & !< coef. in turb. parametrization
    506                  b_term = 9.8_wp,      & !< coef. for terminal velocity (m s-1)
    507                  b_vent = 0.308_wp,    & !< coef. for ventilation effect
    508                  beta_cc = 3.09E-4_wp, & !< coef. in turb. parametrization (cm-2 s3)
    509                  bfactor,              & !< solution effect on diffusional growth
    510                  c_1 = 4.82E-6_wp,     & !< coef. in turb. parametrization (m)
    511                  c_2 = 4.8E-6_wp,      & !< coef. in turb. parametrization (m)
    512                  c_3 = 0.76_wp,        & !< coef. in turb. parametrization
    513                  c_const = 0.93_wp,    & !< const. in Taylor-microscale Reynolds number
    514                  c_evap = 0.7_wp,      & !< constant in evaporation
    515                  c_sedimentation = 2.0_wp, & !< Courant number of sedimentation process
    516                  c_term = 600.0_wp,    & !< coef. for terminal velocity (m-1)
    517                  cof(6) = (/ 76.18009172947146_wp,      & !< coefficients in the
    518                              -86.50532032941677_wp,     & !< numerical
    519                              24.01409824083091_wp,      & !< calculation of the
    520                              -1.231739572450155_wp,     & !< gamma function
    521                              0.1208650973866179E-2_wp,  &
    522                              -0.5395239384953E-5_wp /), &
    523                 cp = 1005.0_wp,       & !< heat capacity of dry air (J kg-1 K-1)
    524                 diff_coeff_l = 0.23E-4_wp, & !< diffusivity of water vapor (m2 s-1)
    525                 effective_coll_efficiency, & !< effective collision efficiency
    526                 eps_ros = 1.0E-4_wp,  & !< accuracy of Rosenbrock method
    527                 eps_sb = 1.0E-20_wp,  & !< threshold in two-moments scheme
    528                 k_cc = 9.44E09_wp,    & !< const. cloud-cloud kernel (m3 kg-2 s-1)
    529                 k_cr0 = 4.33_wp,      & !< const. cloud-rain kernel (m3 kg-1 s-1)
    530                 k_rr = 7.12_wp,       & !< const. rain-rain kernel (m3 kg-1 s-1)
    531                 k_br = 1000._wp,      & !< const. in breakup parametrization (m-1)
    532                 k_st = 1.2E8_wp,      & !< const. in drizzle parametrization (m-1 s-1)
    533                 kappa_rr = 60.7_wp,   & !< const. in collision kernel (kg-1/3)
    534                 kin_vis_air = 1.4086E-5_wp, & !< kin. viscosity of air (m2 s-1)
     494    REAL(wp) :: cp = 1005.0_wp,       & !< heat capacity of dry air (J kg-1 K-1)
    535495                l_v = 2.5E+06_wp,     & !< latent heat of vaporization (J kg-1)
    536496                l_d_cp, l_d_r, l_d_rv, & !< l_v / cp, l_v / r_d, l_v / r_v
    537                 mass_of_solute = 1.0E-17_wp, & !< soluted NaCl (kg)
    538                 molecular_weight_of_solute = 0.05844_wp, & !< mol. m. NaCl (kg mol-1)
    539                 molecular_weight_of_water = 0.01801528_wp, & !< mol. m. H2O (kg mol-1)
    540                 nc_const = 70.0E6_wp, & !< cloud droplet concentration
    541                 prec_time_const = 0.001_wp, & !< coef. in Kessler scheme
    542                 pirho_l, dpirho_l, & !< pi * rho_l / 6.0; 6.0 / ( pi * rho_l )
    543497                rho_l = 1.0E3_wp,     & !< density of water (kg m-3)
    544                 ql_crit = 0.0005_wp,  & !< coef. in Kessler scheme
    545498                r_d = 287.0_wp,       & !< sp. gas const. dry air (J kg-1 K-1)
    546                 r_v = 461.51_wp,      & !< sp. gas const. water vapor (J kg-1 K-1)
    547                 schmidt = 0.71_wp,    & !< Schmidt number
    548                 schmidt_p_1d3,        & !< schmidt**( 1.0 / 3.0 )
    549                 sed_qc_const,         & !< const. for sedimentation of cloud water
    550                 sigma_gc = 1.3_wp,    & !< log-normal geometric standard deviation
    551                 stp = 2.5066282746310005_wp, & !< parameter in gamma function
    552                 thermal_conductivity_l = 2.43E-2_wp, & !< therm. cond. air (J m-1 s-1 K-1)
    553                 vanthoff = 2.0_wp,    & !< van't Hoff factor for NaCl
    554                 x0 = 2.6E-10_wp,      & !< separating drop mass (kg)
    555                 xrmin = 2.6E-10_wp,   & !< minimum rain drop size (kg)
    556                 xrmax = 5.0E-6_wp,    & !< maximum rain drop site (kg)
    557                 dt_precipitation = 100.0_wp, & !< timestep precipitation (s)
    558                 w_precipitation = 9.65_wp      !< maximum terminal velocity (m s-1)
     499                r_v = 461.51_wp         !< sp. gas const. water vapor (J kg-1 K-1)
     500
    559501
    560502    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  hyrho, pt_d_t, t_d_pt 
    561 
    562     REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  precipitation_amount, &
    563                                                 precipitation_rate
    564 !
    565 !-- 3D array of precipitation rate
    566     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr
    567503
    568504    SAVE
     
    807743                 dt_do2d_xy = 9999999.9_wp, dt_do2d_xz = 9999999.9_wp, &
    808744                 dt_do2d_yz = 9999999.9_wp, dt_do3d = 9999999.9_wp, dt_dvrp = 9999999.9_wp, &
    809                  dt_max = 20.0_wp, dt_micro = -1.0_wp, &
     745                 dt_max = 20.0_wp, &
    810746                 dt_restart = 9999999.9_wp, &
    811747                 dt_run_control = 60.0_wp, dt_3d = -1.0_wp, dz = -1.0_wp, &
Note: See TracChangeset for help on using the changeset viewer.