Ignore:
Timestamp:
Jun 6, 2019 12:16:46 PM (5 years ago)
Author:
schwenkel
Message:

Modularization of all lagrangian particle model code components

File:
1 edited

Legend:

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

    r3786 r4017  
    115115    USE kinds
    116116
    117     CHARACTER(LEN=15) ::  aero_species = 'nacl'                    !< aerosol species
    118     CHARACTER(LEN=15) ::  aero_type    = 'maritime'                !< aerosol type
    119     CHARACTER(LEN=15) ::  bc_par_lr    = 'cyclic'                  !< left/right boundary condition
    120     CHARACTER(LEN=15) ::  bc_par_ns    = 'cyclic'                  !< north/south boundary condition
    121     CHARACTER(LEN=15) ::  bc_par_b     = 'reflect'                 !< bottom boundary condition
    122     CHARACTER(LEN=15) ::  bc_par_t     = 'absorb'                  !< top boundary condition
    123     CHARACTER(LEN=15) ::  collision_kernel   = 'none'              !< collision kernel
    124     CHARACTER(LEN=5)  ::  splitting_function = 'gamma'             !< function for calculation critical weighting factor
    125     CHARACTER(LEN=5)  ::  splitting_mode     = 'const'             !< splitting mode
    126 
    127     INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step
    128117    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
    129118    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
     
    131120    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
    132121    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
    133     INTEGER(iwp) ::  iran_part = -1234567                         !< number for random generator
    134     INTEGER(iwp) ::  isf                                          !< dummy for splitting function
    135     INTEGER(iwp) ::  i_splitting_mode                             !< dummy for splitting mode
    136     INTEGER(iwp) ::  max_number_particles_per_gridbox = 100       !< namelist parameter (see documentation)
    137     INTEGER(iwp) ::  merge_drp = 0                                !< number of merged droplets
    138122    INTEGER(iwp) ::  min_nr_particle = 50                         !< namelist parameter (see documentation)
    139     INTEGER(iwp) ::  new_particles = 0                            !< number of new particles
    140     INTEGER(iwp) ::  n_max = 100                                  !< number of radii bin for splitting functions
    141123    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
    142124    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
    143     INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level
    144     INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< namelist parameter (see documentation)
    145     INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset
    146     INTEGER(iwp) ::  offset_ocean_nzt_m1 = 0                      !< in case of oceans runs, the vertical index calculations need an offset
    147     INTEGER(iwp) ::  particles_per_point = 1                      !< namelist parameter (see documentation)
    148     INTEGER(iwp) ::  radius_classes = 20                          !< namelist parameter (see documentation)
    149     INTEGER(iwp) ::  sort_count = 0                               !< counter for sorting particles
    150     INTEGER(iwp) ::  splitting_factor = 2                         !< namelist parameter (see documentation)
    151     INTEGER(iwp) ::  splitting_factor_max = 5                     !< namelist parameter (see documentation)
    152     INTEGER(iwp) ::  step_dealloc = 100                           !< namelist parameter (see documentation)
    153     INTEGER(iwp) ::  sum_merge_drp = 0                            !< sum of merged super droplets
    154     INTEGER(iwp) ::  sum_new_particles = 0                        !< sum of created particles (in splitting algorithm)
    155     INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain
    156     INTEGER(iwp) ::  trlp_count_sum                               !< parameter for particle exchange of PEs
    157     INTEGER(iwp) ::  trlp_count_recv_sum                          !< parameter for particle exchange of PEs
    158     INTEGER(iwp) ::  trrp_count_sum                               !< parameter for particle exchange of PEs
    159     INTEGER(iwp) ::  trrp_count_recv_sum                          !< parameter for particle exchange of PEs
    160     INTEGER(iwp) ::  trsp_count_sum                               !< parameter for particle exchange of PEs
    161     INTEGER(iwp) ::  trsp_count_recv_sum                          !< parameter for particle exchange of PEs
    162     INTEGER(iwp) ::  trnp_count_sum                               !< parameter for particle exchange of PEs
    163     INTEGER(iwp) ::  trnp_count_recv_sum                          !< parameter for particle exchange of PEs
    164125
    165126    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
    166127
    167128    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
    168 
    169     LOGICAL ::  curvature_solution_effects = .FALSE.      !< namelist parameter (see documentation)
    170     LOGICAL ::  deallocate_memory = .TRUE.                !< namelist parameter (see documentation)
    171     LOGICAL ::  hall_kernel = .FALSE.                     !< flag for collision kernel
    172     LOGICAL ::  merging = .FALSE.                         !< namelist parameter (see documentation)
     129   
    173130    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
    174     LOGICAL ::  random_start_position = .FALSE.           !< namelist parameter (see documentation)
    175     LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< namelist parameter (see documentation)
    176     LOGICAL ::  seed_follows_topography = .FALSE.         !< namelist parameter (see documentation)
    177     LOGICAL ::  splitting = .FALSE.                       !< namelist parameter (see documentation)
    178     LOGICAL ::  use_kernel_tables = .FALSE.               !< parameter, which turns on the use of precalculated collision kernels
    179     LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)
     131    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)   
    180132    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
    181     LOGICAL ::  write_particle_statistics = .FALSE.       !< namelist parameter (see documentation)
    182 
    183     LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
    184                 vertical_particle_advection = .TRUE.              !< Switch on/off vertical particle transport
    185 
    186     REAL(wp) ::  aero_weight = 1.0_wp                      !< namelist parameter (see documentation)
     133
    187134    REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
    188     REAL(wp) ::  c_0 = 3.0_wp                              !< parameter for lagrangian timescale
    189     REAL(wp) ::  dt_min_part = 0.0002_wp                   !< minimum particle time step when SGS velocities are used (s)
    190     REAL(wp) ::  dt_prel = 9999999.9_wp                    !< namelist parameter (see documentation)
    191     REAL(wp) ::  dt_write_particle_data = 9999999.9_wp     !< namelist parameter (see documentation)
    192     REAL(wp) ::  end_time_prel = 9999999.9_wp              !< namelist parameter (see documentation)
    193     REAL(wp) ::  initial_weighting_factor = 1.0_wp         !< namelist parameter (see documentation)
    194     REAL(wp) ::  last_particle_release_time = 0.0_wp       !< last time of particle release
    195     REAL(wp) ::  log_sigma(3) = 1.0_wp                     !< namelist parameter (see documentation)
    196     REAL(wp) ::  na(3) = 0.0_wp                            !< namelist parameter (see documentation)
    197     REAL(wp) ::  number_concentration = -1.0_wp            !< namelist parameter (see documentation)
    198135    REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
    199     REAL(wp) ::  radius_merge = 1.0E-7_wp                  !< namelist parameter (see documentation)
    200     REAL(wp) ::  radius_split = 40.0E-6_wp                 !< namelist parameter (see documentation)
    201     REAL(wp) ::  rm(3) = 1.0E-6_wp                         !< namelist parameter (see documentation)
    202     REAL(wp) ::  sgs_wf_part                               !< parameter for sgs
    203     REAL(wp) ::  time_write_particle_data = 0.0_wp         !< write particle data at current time on file
    204     REAL(wp) ::  weight_factor_merge = -1.0_wp             !< namelist parameter (see documentation)
    205     REAL(wp) ::  weight_factor_split = -1.0_wp             !< namelist parameter (see documentation)
    206     REAL(wp) ::  z0_av_global                              !< horizontal mean value of z0
    207 
    208     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  density_ratio = 9999999.9_wp  !< namelist parameter (see documentation)
    209     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdx = 9999999.9_wp            !< namelist parameter (see documentation)
    210     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdy = 9999999.9_wp            !< namelist parameter (see documentation)
    211     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdz = 9999999.9_wp            !< namelist parameter (see documentation)
    212     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psb = 9999999.9_wp            !< namelist parameter (see documentation)
    213     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psl = 9999999.9_wp            !< namelist parameter (see documentation)
    214     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psn = 9999999.9_wp            !< namelist parameter (see documentation)
    215     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psr = 9999999.9_wp            !< namelist parameter (see documentation)
    216     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pss = 9999999.9_wp            !< namelist parameter (see documentation)
    217     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pst = 9999999.9_wp            !< namelist parameter (see documentation).
    218     REAL(wp), DIMENSION(max_number_of_particle_groups) ::  radius = 9999999.9_wp         !< namelist parameter (see documentation)
    219 
    220     REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0)
    221136
    222137!
Note: See TracChangeset for help on using the changeset viewer.