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

Last change on this file since 4181 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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