source: palm/trunk/SOURCE/mod_particle_attributes.f90 @ 4677

Last change on this file since 4677 was 4677, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

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