source: palm/trunk/SOURCE/mod_particle_attributes.f90

Last change on this file was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 7.8 KB
Line 
1!> @file mod_particle_attributes.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2021 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! ------------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: mod_particle_attributes.f90 4828 2021-01-05 11:21:41Z banzhafs $
26! variables for particle output renamed, id counter removed from particle type
27!
28! 4677 2020-09-14 07:55:28Z raasch
29! file re-formatted to follow the PALM coding standard
30!
31! 4628 2020-07-29 07:23:03Z raasch
32! extensions required for MPI-I/O of particle data to restart files
33!
34! 4360 2020-01-07 11:25:50Z suehring
35! Corrected "Former revisions" section
36!
37! 4043 2019-06-18 16:59:00Z schwenkel
38! Remove min_nr_particle
39!
40! 4017 2019-06-06 12:16:46Z schwenkel
41! interoperable C datatypes introduced in particle type to avoid compiler warnings
42!
43! 3720 2019-02-06 13:19:55Z knoop
44! time_prel replaced by last_particle_release_time
45!
46! 1359 2014-04-11 17:15:14Z hoffmann
47! new module containing all particle related variables
48! -dt_sort_particles
49!
50! Description:
51! ------------
52!> Definition of variables used to compute particle transport
53!--------------------------------------------------------------------------------------------------!
54 MODULE particle_attributes
55
56    USE, INTRINSIC ::  ISO_C_BINDING
57
58    USE control_parameters,                                                                        &
59        ONLY: varnamelength
60
61    USE kinds
62
63    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
64
65    CHARACTER(LEN=64)                           ::  pts_id_file = ''  !< namelist parameter
66    CHARACTER(LEN=varnamelength), DIMENSION(50) ::  data_output_pts = ''    !< namelist parameter
67
68    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
69    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
70    INTEGER(iwp) ::  ibc_par_lr                                   !< particle left/right boundary condition dummy
71    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
72    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
73    INTEGER(iwp) ::  number_of_output_particles = 0               !< number of output particles
74    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on
75                                                                  !< prt_count)
76    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
77    INTEGER(iwp) ::  pts_increment = 1                            !< increment of particles in output file
78
79    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
80
81    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
82    LOGICAL ::  unlimited_dimension = .TRUE.              !< umlimited dimension for particle output
83    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)
84    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
85
86    REAL(wp) ::  alloc_factor = 20.0_wp                   !< namelist parameter (see documentation)
87    REAL(wp) ::  oversize = 100.0_wp                      !< reserve spare particles in output file (in % relative to initial
88                                                          !< number)
89    REAL(wp) ::  particle_advection_start = 0.0_wp        !< namelist parameter (see documentation)
90    REAL(wp) ::  pts_percentage = 100.0_wp                !< percentage of particles in output file
91
92    TYPE, PUBLIC ::  particle_type
93        REAL(wp)     ::  aux1             !< auxiliary multi-purpose feature
94        REAL(wp)     ::  aux2             !< auxiliary multi-purpose feature
95        REAL(wp)     ::  radius           !< radius of particle
96        REAL(wp)     ::  age              !< age of particle
97        REAL(wp)     ::  age_m            !<
98        REAL(wp)     ::  dt_sum           !<
99        REAL(wp)     ::  e_m              !< interpolated sgs tke
100        REAL(wp)     ::  origin_x         !< origin x-position of particle (changed cyclic bc)
101        REAL(wp)     ::  origin_y         !< origin y-position of particle (changed cyclic bc)
102        REAL(wp)     ::  origin_z         !< origin z-position of particle (changed cyclic bc)
103        REAL(wp)     ::  rvar1            !<
104        REAL(wp)     ::  rvar2            !<
105        REAL(wp)     ::  rvar3            !<
106        REAL(wp)     ::  speed_x          !< speed of particle in x
107        REAL(wp)     ::  speed_y          !< speed of particle in y
108        REAL(wp)     ::  speed_z          !< speed of particle in z
109        REAL(wp)     ::  weight_factor    !< weighting factor
110        REAL(wp)     ::  x                !< x-position
111        REAL(wp)     ::  y                !< y-position
112        REAL(wp)     ::  z                !< z-position
113        INTEGER(iwp) ::  class            !< radius class needed for collision
114        INTEGER(iwp) ::  group            !< number of particle group
115        INTEGER(idp) ::  id               !< particle ID (64 bit integer)
116        LOGICAL      ::  particle_mask    !< if this parameter is set to false the particle will be deleted
117        INTEGER(iwp) ::  block_nr         !< number for sorting (removable?)
118        INTEGER(iwp) ::  particle_nr=-1   !< particle number for particle IO (increment one
119    END TYPE particle_type
120
121    TYPE(particle_type), DIMENSION(:), POINTER ::  particles      !< Particle array for this grid cell
122    TYPE(particle_type)                        ::  zero_particle  !< zero particle to avoid weird things
123
124    TYPE particle_groups_type
125        SEQUENCE
126        REAL(wp) ::  density_ratio  !< density ratio of the fluid and the particles
127        REAL(wp) ::  radius         !< radius of particle
128        REAL(wp) ::  exp_arg        !< exponential term of particle inertia
129        REAL(wp) ::  exp_term       !< exponential term of particle inertia
130    END TYPE particle_groups_type
131
132    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::  particle_groups
133
134    TYPE  grid_particle_def
135        INTEGER(iwp), DIMENSION(0:7)               ::  start_index     !< start particle index for current block
136        INTEGER(iwp), DIMENSION(0:7)               ::  end_index       !< end particle index for current block
137        LOGICAL                                    ::  time_loop_done  !< timestep loop for particle advection
138        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles       !< Particle array for this grid cell
139    END TYPE grid_particle_def
140
141    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
142
143    TYPE block_offset_def          !<
144        INTEGER(iwp) ::  i_off     !<
145        INTEGER(iwp) ::  j_off     !<
146        INTEGER(iwp) ::  k_off     !<
147    END TYPE block_offset_def
148
149    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
150
151    SAVE
152
153
154 END MODULE particle_attributes
Note: See TracBrowser for help on using the repository browser.