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

Last change on this file since 4186 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 7.0 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-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: mod_particle_attributes.f90 4182 2019-08-22 15:20:23Z suehring $
27! Corrected "Former revisions" section
28!
29! 4043 2019-06-18 16:59:00Z schwenkel
30! Remove min_nr_particle
31!
32! 4017 2019-06-06 12:16:46Z schwenkel
33! interoperable C datatypes introduced in particle type to avoid compiler warnings
34!
35! 3720 2019-02-06 13:19:55Z knoop
36! time_prel replaced by last_particle_release_time
37! 1359 2014-04-11 17:15:14Z hoffmann
38! new module containing all particle related variables
39! -dt_sort_particles
40!
41! Description:
42! ------------
43!> Definition of variables used to compute particle transport
44!------------------------------------------------------------------------------!
45MODULE particle_attributes
46
47    USE, INTRINSIC ::  ISO_C_BINDING
48
49    USE kinds
50
51    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
52    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
53    INTEGER(iwp) ::  ibc_par_lr                                   !< particle left/right boundary condition dummy
54    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
55    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
56    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
57    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
58
59    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
60
61    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
62   
63    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
64    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)   
65    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
66
67    REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
68    REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
69
70!
71!-- WARNING: For compatibility of derived types, the BIND attribute is required, and interoperable C
72!-- datatypes must be used. These type are hard wired here! So changes in working precision (wp, iwp)
73!-- will not affect the particle_type!
74!-- The main reason for introducing the interoperable datatypes was to avoid compiler warnings of
75!-- the gfortran compiler.
76!-- The BIND attribite is required because of C_F_POINTER usage in the pmc particle interface.
77    TYPE, BIND(C) ::  particle_type
78        REAL(C_DOUBLE) ::  aux1          !< auxiliary multi-purpose feature
79        REAL(C_DOUBLE) ::  aux2          !< auxiliary multi-purpose feature
80        REAL(C_DOUBLE) ::  radius        !< radius of particle
81        REAL(C_DOUBLE) ::  age           !< age of particle
82        REAL(C_DOUBLE) ::  age_m         !<
83        REAL(C_DOUBLE) ::  dt_sum        !<
84        REAL(C_DOUBLE) ::  e_m           !< interpolated sgs tke
85        REAL(C_DOUBLE) ::  origin_x      !< origin x-position of particle (changed cyclic bc)
86        REAL(C_DOUBLE) ::  origin_y      !< origin y-position of particle (changed cyclic bc)
87        REAL(C_DOUBLE) ::  origin_z      !< origin z-position of particle (changed cyclic bc)
88        REAL(C_DOUBLE) ::  rvar1         !<
89        REAL(C_DOUBLE) ::  rvar2         !<
90        REAL(C_DOUBLE) ::  rvar3         !<
91        REAL(C_DOUBLE) ::  speed_x       !< speed of particle in x
92        REAL(C_DOUBLE) ::  speed_y       !< speed of particle in y
93        REAL(C_DOUBLE) ::  speed_z       !< speed of particle in z
94        REAL(C_DOUBLE) ::  weight_factor !< weighting factor
95        REAL(C_DOUBLE) ::  x             !< x-position
96        REAL(C_DOUBLE) ::  y             !< y-position
97        REAL(C_DOUBLE) ::  z             !< z-position
98        INTEGER(C_INT) ::  class         !< radius class needed for collision
99        INTEGER(C_INT) ::  group         !< number of particle group
100        INTEGER(C_LONG_LONG) ::  id            !< particle ID (64 bit integer)
101        LOGICAL(C_BOOL) ::  particle_mask !< if this parameter is set to false the particle will be deleted
102        INTEGER(C_INT) ::  block_nr      !< number for sorting (removable?)
103    END TYPE particle_type
104
105    TYPE(particle_type), DIMENSION(:), POINTER ::  particles       !< Particle array for this grid cell
106    TYPE(particle_type)                        ::  zero_particle   !< zero particle to avoid weird thinge
107
108    TYPE particle_groups_type
109        SEQUENCE
110        REAL(wp) ::  density_ratio  !< density ratio of the fluid and the particles
111        REAL(wp) ::  radius         !< radius of particle
112        REAL(wp) ::  exp_arg        !< exponential term of particle inertia
113        REAL(wp) ::  exp_term       !< exponential term of particle inertia
114    END TYPE particle_groups_type
115
116    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
117       particle_groups
118
119    TYPE  grid_particle_def
120        INTEGER(iwp), DIMENSION(0:7)               ::  start_index        !< start particle index for current block
121        INTEGER(iwp), DIMENSION(0:7)               ::  end_index          !< end particle index for current block
122        INTEGER(iwp)                               ::  id_counter         !< particle id counter
123        LOGICAL                                    ::  time_loop_done     !< timestep loop for particle advection
124        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles          !< Particle array for this grid cell
125    END TYPE grid_particle_def
126
127    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
128
129    TYPE block_offset_def          !<
130        INTEGER(iwp) ::  i_off     !<
131        INTEGER(iwp) ::  j_off     !<
132        INTEGER(iwp) ::  k_off     !<
133    END TYPE block_offset_def
134
135    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
136
137    SAVE
138
139
140END MODULE particle_attributes
Note: See TracBrowser for help on using the repository browser.