Ignore:
Timestamp:
Feb 17, 2012 9:09:57 AM (12 years ago)
Author:
raasch
Message:

preliminary checkin of new curvature/solution effects on droplet growth

File:
1 edited

Legend:

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

    r810 r824  
    44! Current revisions:
    55! -----------------
    6 !
     6! +bfactor, curvature_solution_effects, eps_ros, molecular_weight_of_water,
     7! vanthoff, -b_cond in cloud_parameters,
     8! dopts_num increased to 27, particle attributes speed_x|y|z_sgs renamed
     9! rvar1|2|3
    710!
    811! Former revisions:
     
    332335    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  rif_wall
    333336
    334     REAL, DIMENSION(:,:,:), ALLOCATABLE :: var_x, var_y, var_z, gamma_x,        &
     337    REAL, DIMENSION(:,:,:), ALLOCATABLE :: var_x, var_y, var_z, gamma_x,       &
    335338                                           gamma_y, gamma_z
    336339
     
    369372!------------------------------------------------------------------------------!
    370373
    371     REAL  ::  b_cond, cp = 1005.0, diff_coeff_l = 0.23E-4,                     &
    372               effective_coll_efficiency, l_d_cp, l_d_r, l_d_rv, l_v = 2.5E+06, &
    373               mass_of_solute, molecular_weight_of_solute,                      &
     374    LOGICAL ::  curvature_solution_effects = .FALSE.
     375
     376    REAL  ::  bfactor, cp = 1005.0, diff_coeff_l = 0.23E-4,                    &
     377              effective_coll_efficiency,                                       &
     378              eps_ros = 1.0E-4,             &  ! accuracy of Rosenbrock method
     379              l_d_cp, l_d_r, l_d_rv, l_v = 2.5E+06,                            &
     380              mass_of_solute = 1.0E-17,              & ! soluted NaCl in kg
     381              molecular_weight_of_solute = 0.05844,  & ! mol. mass NaCl (kg/mol)
     382              molecular_weight_of_water = 0.01801528,& ! mol. mass H2O (kg/mol)
    374383              prec_time_const = 0.001, ql_crit = 0.0005, rho_l = 1.0E3,        &
    375               r_d = 287.0, r_v = 461.51, thermal_conductivity_l = 2.43E-2
     384              r_d = 287.0, r_v = 461.51, thermal_conductivity_l = 2.43E-2,     &
     385              vanthoff = 2.0                        ! van't Hoff factor (NaCl)
    376386
    377387    REAL, DIMENSION(:), ALLOCATABLE   ::  pt_d_t, t_d_pt
     
    10371047#endif
    10381048
    1039     INTEGER, PARAMETER ::  dopr_norm_num = 7, dopts_num = 26, dots_max = 100
     1049    INTEGER, PARAMETER ::  dopr_norm_num = 7, dopts_num = 27, dots_max = 100
    10401050
    10411051    INTEGER ::  dots_num = 23
     
    10521062          (/ 'tnpt   ', 'x_     ', 'y_     ', 'z_     ', 'z_abs  ', 'u      ', &
    10531063             'v      ', 'w      ', 'u"     ', 'v"     ', 'w"     ', 'npt_up ', &
    1054              'w_up   ', 'w_down ', 'npt_max', 'npt_min', 'x*2    ', 'y*2    ', &
    1055              'z*2    ', 'u*2    ', 'v*2    ', 'w*2    ', 'u"2    ', 'v"2    ', &
    1056              'w"2    ', 'npt*2  ' /)
     1064             'w_up   ', 'w_down ', 'radius ', 'npt_max', 'npt_min', 'x*2    ', &
     1065             'y*2    ', 'z*2    ', 'u*2    ', 'v*2    ', 'w*2    ', 'u"2    ', &
     1066             'v"2    ', 'w"2    ', 'npt*2  ' /)
    10571067
    10581068    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_unit = &
    10591069          (/ 'number ', 'm      ', 'm      ', 'm      ', 'm      ', 'm/s    ', &
    10601070             'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'number ', &
    1061              'm/s    ', 'm/s    ', 'number ', 'number ', 'm2    ', 'm2     ', &
    1062              'm2     ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', &
    1063              'm2/s2  ', 'number2' /)
     1071             'm/s    ', 'm/s    ', 'm      ', 'number ', 'number ', 'm2     ', &
     1072             'm2     ', 'm2     ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', &
     1073             'm2/s2  ', 'm2/s2  ', 'number2' /)
    10641074
    10651075    CHARACTER (LEN=7), DIMENSION(dots_max) :: dots_label = &
     
    12301240       SEQUENCE
    12311241       REAL    ::  age, age_m, dt_sum, dvrp_psize, e_m, origin_x, origin_y, &
    1232                    origin_z, radius, speed_x, speed_x_sgs, speed_y,        &
    1233                    speed_y_sgs, speed_z, speed_z_sgs, weight_factor, x, y, z
     1242                   origin_z, radius, rvar1, rvar2, rvar3, speed_x, speed_y, &
     1243                   speed_z, weight_factor, x, y, z
    12341244       INTEGER ::  color, group, tailpoints, tail_id
    12351245    END TYPE particle_type
Note: See TracChangeset for help on using the changeset viewer.