Ignore:
Timestamp:
Aug 29, 2017 2:10:28 PM (7 years ago)
Author:
schwenkel
Message:

improved aerosol initialization for bulk microphysics

File:
1 edited

Legend:

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

    r2318 r2375  
    2525! -----------------
    2626! $Id$
     27! Improved aerosol initilization and some minor bugfixes
     28! for droplet sedimenation
     29!
     30! 2318 2017-07-20 17:27:44Z suehring
    2731! Get topography top index via Function call
    2832!
     
    188192    REAL(wp) ::  xrmax = 5.0E-6_wp         !< maximum rain drop site (kg)
    189193
    190     REAL(wp) ::  c_sedimentation = 2.0_wp  !< Courant number of sedimentation process
    191     REAL(wp) ::  dpirho_l                  !< 6.0 / ( pi * rho_l )
    192     REAL(wp) ::  dt_micro                  !< microphysics time step
    193     REAL(wp) ::  na_init = 100.0E6_wp      !< Total particle/aerosol concentration (cm-3)
    194     REAL(wp) ::  nc_const = 70.0E6_wp      !< cloud droplet concentration
    195     REAL(wp) ::  dt_precipitation = 100.0_wp !< timestep precipitation (s)
    196     REAL(wp) ::  sed_qc_const              !< const. for sedimentation of cloud water
    197     REAL(wp) ::  pirho_l                   !< pi * rho_l / 6.0;
     194    REAL(wp) ::  c_sedimentation = 2.0_wp        !< Courant number of sedimentation process
     195    REAL(wp) ::  dpirho_l                        !< 6.0 / ( pi * rho_l )
     196    REAL(wp) ::  dry_aerosol_radius = 0.05E-6_wp !< dry aerosol radius
     197    REAL(wp) ::  dt_micro                        !< microphysics time step
     198    REAL(wp) ::  sigma_bulk = 2.0_wp             !< width of aerosol spectrum
     199    REAL(wp) ::  na_init = 100.0E6_wp            !< Total particle/aerosol concentration (cm-3)
     200    REAL(wp) ::  nc_const = 70.0E6_wp            !< cloud droplet concentration
     201    REAL(wp) ::  dt_precipitation = 100.0_wp     !< timestep precipitation (s)
     202    REAL(wp) ::  sed_qc_const                    !< const. for sedimentation of cloud water
     203    REAL(wp) ::  pirho_l                         !< pi * rho_l / 6.0;
    198204
    199205    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nc_1d  !<
     
    210216
    211217    PUBLIC cloud_water_sedimentation, collision_turbulence,                    &
    212            curvature_solution_effects_bulk, c_sedimentation, dt_precipitation, &
    213            limiter_sedimentation, na_init, nc_const, sigma_gc,                 &
     218           curvature_solution_effects_bulk, c_sedimentation,                   &
     219           dry_aerosol_radius, dt_precipitation,                               &
     220           limiter_sedimentation, na_init, nc_const, sigma_gc, sigma_bulk,     &
    214221           ventilation_effect
    215222
     
    290297
    291298       USE cloud_parameters,                                                   &
    292            ONLY:  rho_l
     299           ONLY:  molecular_weight_of_solute, rho_l, rho_s, vanthoff
    293300
    294301       USE control_parameters,                                                 &
    295            ONLY:  microphysics_morrison, microphysics_seifert
     302           ONLY:  aerosol_nacl, aerosol_c3h4o4 , aerosol_nh4no3,               &
     303                  microphysics_morrison, microphysics_seifert
    296304
    297305       USE indices,                                                            &
     
    313321       ENDIF
    314322
     323!
     324!--    Set constants for certain aerosol type
     325       IF ( microphysics_morrison )  THEN
     326          IF ( aerosol_nacl ) THEN
     327             molecular_weight_of_solute = 0.05844_wp
     328             rho_s                      = 2165.0_wp
     329             vanthoff                   = 2.0_wp
     330          ELSEIF ( aerosol_c3h4o4 ) THEN
     331             molecular_weight_of_solute = 0.10406_wp
     332             rho_s                      = 1600.0_wp
     333             vanthoff                   = 1.37_wp
     334          ELSEIF ( aerosol_nh4no3 ) THEN
     335             molecular_weight_of_solute = 0.08004_wp
     336             rho_s                      = 1720.0_wp
     337             vanthoff                   = 2.31_wp
     338          ENDIF
     339       ENDIF
     340 
    315341!
    316342!--    Pre-calculate frequently calculated fractions of pi and rho_l
     
    509535
    510536       USE cloud_parameters,                                                   &
    511            ONLY:  hyrho, l_d_cp, l_d_r, l_v, rho_l, r_v, t_d_pt
     537           ONLY:  hyrho, l_d_cp, l_d_r, l_v, molecular_weight_of_solute,       &
     538                  molecular_weight_of_water, rho_l, rho_s, r_v, t_d_pt,        &
     539                  vanthoff
    512540
    513541       USE constants,                                                          &
     
    524552       USE control_parameters,                                                 &
    525553          ONLY: simulated_time
    526 
    527        USE particle_attributes,                                                &
    528           ONLY:  molecular_weight_of_solute, molecular_weight_of_water, rho_s, &
    529               log_sigma, vanthoff
    530554
    531555       IMPLICIT NONE
     
    545569       REAL(wp)     ::  n_ccn             !<
    546570       REAL(wp)     ::  q_s               !<
    547        REAL(wp)     ::  rd0               !<
    548571       REAL(wp)     ::  s_0               !<
    549572       REAL(wp)     ::  sat               !<
    550573       REAL(wp)     ::  sat_max           !<
    551574       REAL(wp)     ::  sigma             !<
     575       REAL(wp)     ::  sigma_act         !<
    552576       REAL(wp)     ::  t_int             !<
    553577       REAL(wp)     ::  t_l               !<
     
    616640!
    617641!--                Prescribe power index that describes the soluble fraction
    618 !--                of an aerosol particle (beta) and mean geometric radius of
    619 !--                dry aerosol spectrum
     642!--                of an aerosol particle (beta)
    620643!--                (see: Morrison + Grabowski, 2007, JAS, 64)
    621                    beta_act = 0.5_wp
    622                    rd0      = 0.05E-6_wp
     644                   beta_act  = 0.5_wp
     645                   sigma_act = sigma_bulk**( 1.0_wp + beta_act )
    623646!
    624647!--                Calculate mean geometric supersaturation (s_0) with
    625648!--                parameterization by Khvorostyanov and Curry (2006)
    626                    s_0   = rd0 **(- ( 1.0_wp + beta_act ) ) *                  &
     649                   s_0   = dry_aerosol_radius **(- ( 1.0_wp + beta_act ) ) *    &
    627650                       ( 4.0_wp * afactor**3 / ( 27.0_wp * bfactor ) )**0.5_wp
    628651
     
    632655!--                (see: Khvorostyanov + Curry, 2006, J. Geo. Res., 111)
    633656                   n_ccn = ( na_init / 2.0_wp ) * ( 1.0_wp - ERF(              &
    634                       LOG( s_0 / sat ) / ( SQRT(2.0_wp) * log_sigma(1) ) ) )
     657                      LOG( s_0 / sat ) / ( SQRT(2.0_wp) * LOG(sigma_act) ) ) )
    635658                   activ = MAX( ( n_ccn - nc(k,j,i) ) / dt_micro, 0.0_wp )
    636659                ENDIF
     
    13571380
    13581381       sed_qc(nzt+1) = 0.0_wp
     1382       sed_nc(nzt+1) = 0.0_wp
    13591383
    13601384       DO  i = nxlg, nxrg
     
    13861410                ENDIF
    13871411
    1388                 IF ( qc(k,j,i) > eps_sb )  THEN
     1412                IF ( qc(k,j,i) > eps_sb .AND.  nc_sedi > eps_mr )  THEN
    13891413                   sed_qc(k) = sed_qc_const * nc_sedi**( -2.0_wp / 3.0_wp ) *  &
    13901414                               ( qc(k,j,i) * hyrho(k) )**( 5.0_wp / 3.0_wp ) * &
     
    19481972
    19491973       USE cloud_parameters,                                                   &
    1950            ONLY:  hyrho, l_d_cp, l_d_r, l_v, rho_l, r_v, t_d_pt
     1974           ONLY:  hyrho, l_d_cp, l_d_r, l_v, molecular_weight_of_solute,       &
     1975                  molecular_weight_of_water, rho_l, rho_s, r_v, t_d_pt,        &
     1976                  vanthoff
    19511977
    19521978       USE constants,                                                          &
     
    19631989       USE control_parameters,                                                 &
    19641990          ONLY: simulated_time
    1965 
    1966        USE particle_attributes,                                                &
    1967           ONLY:  molecular_weight_of_solute, molecular_weight_of_water, rho_s, &
    1968               log_sigma, vanthoff
    19691991
    19701992       IMPLICIT NONE
     
    19842006       REAL(wp)     ::  n_ccn             !<
    19852007       REAL(wp)     ::  q_s               !<
    1986        REAL(wp)     ::  rd0               !<
    19872008       REAL(wp)     ::  s_0               !<
    19882009       REAL(wp)     ::  sat               !<
    19892010       REAL(wp)     ::  sat_max           !<
    19902011       REAL(wp)     ::  sigma             !<
     2012       REAL(wp)     ::  sigma_act         !<
    19912013       REAL(wp)     ::  t_int             !<
    19922014       REAL(wp)     ::  t_l               !<
     
    20522074!
    20532075!--          Prescribe power index that describes the soluble fraction
    2054 !--          of an aerosol particle (beta) and mean geometric radius of
    2055 !--          dry aerosol spectrum
     2076!--          of an aerosol particle (beta).
    20562077!--          (see: Morrison + Grabowski, 2007, JAS, 64)
    2057              beta_act = 0.5_wp
    2058              rd0      = 0.05E-6_wp
     2078             beta_act  = 0.5_wp
     2079             sigma_act = sigma_bulk**( 1.0_wp + beta_act )
    20592080!
    20602081!--          Calculate mean geometric supersaturation (s_0) with
    20612082!--          parameterization by Khvorostyanov and Curry (2006)
    2062              s_0   = rd0 **(- ( 1.0_wp + beta_act ) ) *                        &
     2083             s_0   = dry_aerosol_radius **(- ( 1.0_wp + beta_act ) ) *         &
    20632084               ( 4.0_wp * afactor**3 / ( 27.0_wp * bfactor ) )**0.5_wp
    20642085
     
    20672088!--          supersaturation and taking Koehler theory into account
    20682089!--          (see: Khvorostyanov + Curry, 2006, J. Geo. Res., 111)
    2069              n_ccn = ( na_init / 2.0_wp ) * ( 1.0_wp - ERF(                     &
    2070                 LOG( s_0 / sat ) / ( SQRT(2.0_wp) * log_sigma(1) ) ) )
     2090             n_ccn = ( na_init / 2.0_wp ) * ( 1.0_wp - ERF(                    &
     2091                LOG( s_0 / sat ) / ( SQRT(2.0_wp) * LOG(sigma_act) ) ) )
    20712092             activ = MAX( ( n_ccn ) / dt_micro, 0.0_wp )
    20722093
     
    27092730
    27102731       sed_qc(nzt+1) = 0.0_wp
     2732       sed_nc(nzt+1) = 0.0_wp
     2733
    27112734
    27122735       DO  k = nzt, nzb+1, -1
     
    27352758          ENDIF
    27362759
    2737           IF ( qc_1d(k) > eps_sb )  THEN
     2760          IF ( qc_1d(k) > eps_sb  .AND.  nc_sedi > eps_mr )  THEN
    27382761             sed_qc(k) = sed_qc_const * nc_sedi**( -2.0_wp / 3.0_wp ) *        &
    27392762                         ( qc_1d(k) * hyrho(k) )**( 5.0_wp / 3.0_wp )  * flag
Note: See TracChangeset for help on using the changeset viewer.