Ignore:
Timestamp:
Apr 7, 2016 7:49:42 AM (8 years ago)
Author:
hoffmann
Message:

changes in LPM and bulk cloud microphysics

File:
1 edited

Legend:

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

    r1728 r1822  
    1919! Current revisions:
    2020! ------------------
     21! +collision_algorithm, all_or_nothing, average_impact
    2122!
    22 !
     23! Tails removed.
     24!
    2325! Former revisions:
    2426! -----------------
     
    4749    USE kinds
    4850
    49     CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic',  bc_par_ns = 'cyclic',         &
    50                           bc_par_b  = 'reflect', bc_par_t  = 'absorb',         &
    51                           collision_kernel = 'none'
     51    CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic'                    !< left/right boundary condition
     52    CHARACTER(LEN=15) ::  bc_par_ns = 'cyclic'                    !< north/south boundary condition
     53    CHARACTER(LEN=15) ::  bc_par_b  = 'reflect'                   !< bottom boundary condition
     54    CHARACTER(LEN=15) ::  bc_par_t  = 'absorb'                    !< top boundary condition
     55    CHARACTER(LEN=15) ::  collision_algorithm = 'all_or_nothing'  !< collision algorithm
     56    CHARACTER(LEN=15) ::  collision_kernel = 'none'               !< collision kernel
    5257
    53     INTEGER(iwp) ::  deleted_particles = 0, deleted_tails = 0,                 &
     58    INTEGER(iwp) ::  deleted_particles = 0,                                    &
    5459                     dissipation_classes = 10, ibc_par_lr,                     &
    5560                     ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,   &
    5661                     maximum_number_of_particles = 0,                          &
    57                      maximum_number_of_tailpoints = 100,                       &
    58                      maximum_number_of_tails = 0,                              &
    5962                     min_nr_particle = 50,                                     &
    6063                     mpi_particle_type,                                        &
    6164                     number_of_particles = 0,                                  &
    62                      number_of_particle_groups = 1, number_of_tails = 0,       &
    63                      number_of_initial_tails = 0, number_of_sublayers = 20,    &
     65                     number_of_particle_groups = 1,                            &
     66                     number_of_sublayers = 20,                                 &
    6467                     offset_ocean_nzt = 0,                                     &
    6568                     offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
    6669                     particle_file_count = 0, radius_classes = 20,             &
    67                      skip_particles_for_tail = 100, sort_count = 0,            &
    68                      total_number_of_particles, total_number_of_tails = 0,     &
     70                     sort_count = 0,                                           &
     71                     total_number_of_particles,                                &
    6972                     trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
    7073                     trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum, &
     
    7376    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10
    7477
    75     INTEGER(iwp), DIMENSION(:), ALLOCATABLE     ::  new_tail_id
    7678    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
    7779
    78     LOGICAL ::  hall_kernel = .FALSE., palm_kernel = .FALSE.,                  &
     80    LOGICAL ::  all_or_nothing = .FALSE., average_impact = .FALSE.,            &
     81                hall_kernel = .FALSE., palm_kernel = .FALSE.,                  &
    7982                particle_advection = .FALSE., random_start_position = .FALSE., &
    8083                read_particles_from_restartfile = .TRUE.,                      &
    8184                seed_follows_topography = .FALSE.,                             &
    8285                uniform_particles = .TRUE., use_kernel_tables = .FALSE.,       &
    83                 use_particle_tails = .FALSE., use_sgs_for_particles = .FALSE., &
    84                 wang_kernel = .FALSE., write_particle_statistics = .FALSE.
     86                use_sgs_for_particles = .FALSE., wang_kernel = .FALSE.,        &
     87                write_particle_statistics = .FALSE.
    8588
    8689    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
    8790                vertical_particle_advection = .TRUE.
    8891
    89     LOGICAL, DIMENSION(:), ALLOCATABLE ::  tail_mask
    90 
    9192    REAL(wp) ::  alloc_factor = 20.0_wp, c_0 = 3.0_wp,                         &
    9293                 dt_min_part = 0.0002_wp, dt_prel = 9999999.9_wp,              &
    9394                 dt_write_particle_data = 9999999.9_wp,                        &
    94                  dvrp_psize = 9999999.9_wp, end_time_prel = 9999999.9_wp,      &
     95                 end_time_prel = 9999999.9_wp,                                 &
    9596                 initial_weighting_factor = 1.0_wp,                            &
    96                  maximum_tailpoint_age = 100000.0_wp,                          &
    97                  minimum_tailpoint_distance = 0.0_wp,                          &
    9897                 particle_advection_start = 0.0_wp,                            &
    9998                 sgs_wfu_part = 0.3333333_wp, sgs_wfv_part = 0.3333333_wp,     &
     
    108107                 pss = 9999999.9_wp, pst = 9999999.9_wp, radius = 9999999.9_wp
    109108
    110     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  particle_tail_coordinates
    111 
    112109    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
    113110
    114111    TYPE particle_type
    115112        SEQUENCE
    116 #if defined( __twocachelines )
    117         REAL(wp)     ::  radius
    118         REAL(sp)     ::  x, y, z, speed_x, speed_y, speed_z
    119         REAL(wp)     ::  weight_factor, rvar1, dt_sum
    120         INTEGER(iwp) ::  class
    121         LOGICAL      ::  particle_mask
    122 
    123         REAL(wp)     ::  dvrp_psize, rvar2, rvar3
    124         REAL(sp)     ::  age, origin_x, origin_y, origin_z, e_m, age_m
    125         INTEGER(iwp) ::  group, tailpoints, tail_id, block_nr
    126 #else
    127113        REAL(wp)     ::  radius, age, age_m, dt_sum, dvrp_psize, e_m,          &
    128114                         origin_x, origin_y, origin_z, rvar1, rvar2, rvar3,    &
     
    131117        LOGICAL      ::  particle_mask
    132118        INTEGER(iwp) ::  block_nr
    133 #endif
    134 !-- One 32 Bit word for 64 Bit alignment in Type declaration
    135119    END TYPE particle_type
    136120
    137     TYPE(particle_type), DIMENSION(:), POINTER             ::  particles
    138     TYPE(particle_type)                                    ::  zero_particle
     121    TYPE(particle_type), DIMENSION(:), POINTER ::  particles
     122    TYPE(particle_type)                        ::  zero_particle
    139123
    140124    TYPE particle_groups_type
Note: See TracChangeset for help on using the changeset viewer.