Ignore:
Timestamp:
Mar 15, 2012 10:35:09 AM (12 years ago)
Author:
raasch
Message:

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

File:
1 edited

Legend:

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

    r829 r849  
    44! Current revisions:
    55! -----------------
    6 !
     6! +deleted_particles, deleted_tails, tr.._count_sum, tr.._count_recv_sum in
     7! particle_attributes,
     8! +de_dx, de_dy, de_dz in arrays_3d,
     9! first_call_advec_particles renamed first_call_lpm
    710!
    811! Former revisions:
     
    323326
    324327    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
    325           canopy_heat_flux, cdc, d, diss, lad_s, lad_u, lad_v, lad_w, lai,     &
    326           l_wall, p_loc, sec, sls, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l,    &
    327           v_m_n, v_m_r, v_m_s, w_m_l, w_m_n, w_m_r, w_m_s, flux_l_pt,          &
    328           diss_l_pt, flux_l_e, diss_l_e, flux_l_q, diss_l_q, flux_l_sa,        &
    329           diss_l_sa, flux_l_u, flux_l_v, flux_l_w, diss_l_u, diss_l_v, diss_l_w
     328          canopy_heat_flux, cdc, d, de_dx, de_dy, de_dz, diss, lad_s, lad_u,   &
     329          lad_v, lad_w, lai, l_wall, p_loc, sec, sls, tend, u_m_l, u_m_n,      &
     330          u_m_r, u_m_s, v_m_l, v_m_n, v_m_r, v_m_s, w_m_l, w_m_n, w_m_r,       &
     331          w_m_s, flux_l_pt, diss_l_pt, flux_l_e, diss_l_e, flux_l_q, diss_l_q, &
     332          flux_l_sa, diss_l_sa, flux_l_u, flux_l_v, flux_l_w, diss_l_u,        &
     333          diss_l_v, diss_l_w
    330334
    331335    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
     
    569573                cut_spline_overshoot = .TRUE., &
    570574                data_output_2d_on_each_pe = .TRUE., &
    571                 dissipation_control = .FALSE., do2d_at_begin = .FALSE., &
    572                 do3d_at_begin = .FALSE., do3d_compress = .FALSE., &
    573                 do_sum = .FALSE., dp_external = .FALSE., dp_smooth = .FALSE., &
     575                dissipation_control = .FALSE., disturbance_created = .FALSE., &
     576                do2d_at_begin = .FALSE., do3d_at_begin = .FALSE., &
     577                do3d_compress = .FALSE., do_sum = .FALSE., &
     578                dp_external = .FALSE., dp_smooth = .FALSE., &
    574579                dt_changed = .FALSE., dt_fixed = .FALSE., &
    575                 disturbance_created = .FALSE., &
    576                 exchange_mg = .FALSE., &
    577                 first_call_advec_particles = .TRUE., &
     580                dt_3d_reached, dt_3d_reached_l, exchange_mg = .FALSE., &
     581                first_call_lpm = .TRUE., &
    578582                force_print_header = .FALSE., galilei_transformation = .FALSE.,&
    579583                humidity = .FALSE., humidity_remote = .FALSE., &
     
    627631             dt_do2d_xy = 9999999.9, dt_do2d_xz = 9999999.9, &
    628632             dt_do2d_yz = 9999999.9, dt_do3d = 9999999.9, dt_dvrp = 9999999.9, &
    629              dt_max = 20.0, dt_prel = 9999999.9, dt_restart = 9999999.9, &
     633             dt_max = 20.0, dt_restart = 9999999.9, &
    630634             dt_run_control = 60.0, dt_3d = -1.0, dz = -1.0, &
    631635             dz_max = 9999999.9, dz_stretch_factor = 1.08, &
     
    667671             time_do2d_xz = 0.0, time_do2d_yz = 0.0, time_do3d = 0.0, &
    668672             time_do_av = 0.0, time_do_sla = 0.0, time_dvrp = 0.0, &
    669              time_prel = 0.0, time_restart = 9999999.9, time_run_control = 0.0,&
     673             time_restart = 9999999.9, time_run_control = 0.0,&
    670674             time_since_reference_point, top_heatflux = 9999999.9, &
    671675             top_momentumflux_u = 9999999.9, &
     
    11991203    INTEGER ::  mpi_particle_type
    12001204#endif
    1201     INTEGER ::  dissipation_classes = 10, ibc_par_lr, ibc_par_ns, ibc_par_b,   &
    1202                 ibc_par_t, iran_part = -1234567,                               &
     1205    INTEGER ::  deleted_particles = 0, deleted_tails = 0,                      &
     1206                dissipation_classes = 10, ibc_par_lr,                          &
     1207                ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,        &
    12031208                maximum_number_of_particles = 1000,                            &
    12041209                maximum_number_of_tailpoints = 100,                            &
     
    12101215                particle_file_count = 0, radius_classes = 20,                  &
    12111216                skip_particles_for_tail = 100, sort_count = 0,                 &
    1212                 total_number_of_particles, total_number_of_tails = 0
     1217                total_number_of_particles, total_number_of_tails = 0,          &
     1218                trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,           &
     1219                trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum,      &
     1220                trnp_count_sum, trnp_count_recv_sum
    12131221
    12141222    INTEGER, PARAMETER ::  max_number_of_particle_groups = 10
     
    12291237    LOGICAL, DIMENSION(:), ALLOCATABLE ::  particle_mask, tail_mask
    12301238
    1231     REAL    ::  c_0 = 3.0, dt_min_part = 0.0002, dt_sort_particles = 0.0,      &
    1232                 dt_write_particle_data = 9999999.9, dvrp_psize = 9999999.9,    &
    1233                 end_time_prel = 9999999.9, initial_weighting_factor = 1.0,     &
     1239    REAL    ::  c_0 = 3.0, dt_min_part = 0.0002, dt_prel = 9999999.9,          &
     1240                dt_sort_particles = 0.0, dt_write_particle_data = 9999999.9,   &
     1241                dvrp_psize = 9999999.9, end_time_prel = 9999999.9,             &
     1242                initial_weighting_factor = 1.0,                                &
    12341243                maximum_tailpoint_age = 100000.0,                              &
    12351244                minimum_tailpoint_distance = 0.0,                              &
    12361245                particle_advection_start = 0.0, sgs_wfu_part = 0.3333333,      &
    12371246                sgs_wfv_part = 0.3333333, sgs_wfw_part = 0.3333333,            &
    1238                 time_sort_particles = 0.0, time_write_particle_data = 0.0
     1247                time_prel = 0.0, time_sort_particles = 0.0,                    &
     1248                time_write_particle_data = 0.0
    12391249
    12401250    REAL, DIMENSION(max_number_of_particle_groups) ::  &
Note: See TracChangeset for help on using the changeset viewer.