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

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

extensions required for MPI-I/O of particle data to restart files

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