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

Last change on this file since 1612 was 1576, checked in by raasch, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 7.5 KB
Line 
1MODULE particle_attributes
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014  Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: mod_particle_attributes.f90 1576 2015-03-27 10:23:30Z maronga $
27!
28! 1575 2015-03-27 09:56:27Z raasch
29! +seed_follows_topography
30!
31! 1359 2014-04-11 17:15:14Z hoffmann
32! new module containing all particle related variables
33! -dt_sort_particles
34!
35! Description:
36! ------------
37! Definition of variables used to compute particle transport
38!------------------------------------------------------------------------------!
39
40    USE kinds
41
42    CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic',  bc_par_ns = 'cyclic',         &
43                          bc_par_b  = 'reflect', bc_par_t  = 'absorb',         &
44                          collision_kernel = 'none'
45
46    INTEGER(iwp) ::  deleted_particles = 0, deleted_tails = 0,                 &
47                     dissipation_classes = 10, ibc_par_lr,                     &
48                     ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,   &
49                     maximum_number_of_particles = 0,                          &
50                     maximum_number_of_tailpoints = 100,                       &
51                     maximum_number_of_tails = 0,                              &
52                     min_nr_particle = 50,                                     &
53                     mpi_particle_type,                                        &
54                     number_of_particles = 0,                                  &
55                     number_of_particle_groups = 1, number_of_tails = 0,       &
56                     number_of_initial_tails = 0, number_of_sublayers = 20,    &
57                     offset_ocean_nzt = 0,                                     &
58                     offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
59                     particle_file_count = 0, radius_classes = 20,             &
60                     skip_particles_for_tail = 100, sort_count = 0,            &
61                     total_number_of_particles, total_number_of_tails = 0,     &
62                     trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
63                     trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum, &
64                     trnp_count_sum, trnp_count_recv_sum
65
66    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10
67
68    INTEGER(iwp), DIMENSION(:), ALLOCATABLE     ::  new_tail_id
69    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
70
71    LOGICAL ::  hall_kernel = .FALSE., palm_kernel = .FALSE.,                  &
72                particle_advection = .FALSE., random_start_position = .FALSE., &
73                read_particles_from_restartfile = .TRUE.,                      &
74                seed_follows_topography = .FALSE.,                             &
75                uniform_particles = .TRUE., use_kernel_tables = .FALSE.,       &
76                use_particle_tails = .FALSE., use_sgs_for_particles = .FALSE., &
77                wang_kernel = .FALSE., write_particle_statistics = .FALSE.
78
79    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
80                vertical_particle_advection = .TRUE.
81
82    LOGICAL, DIMENSION(:), ALLOCATABLE ::  tail_mask
83
84    REAL(wp) ::  alloc_factor = 20.0_wp, c_0 = 3.0_wp,                         &
85                 dt_min_part = 0.0002_wp, dt_prel = 9999999.9_wp,              &
86                 dt_write_particle_data = 9999999.9_wp,                        &
87                 dvrp_psize = 9999999.9_wp, end_time_prel = 9999999.9_wp,      &
88                 initial_weighting_factor = 1.0_wp,                            &
89                 maximum_tailpoint_age = 100000.0_wp,                          &
90                 minimum_tailpoint_distance = 0.0_wp,                          &
91                 particle_advection_start = 0.0_wp,                            &
92                 sgs_wfu_part = 0.3333333_wp, sgs_wfv_part = 0.3333333_wp,     &
93                 sgs_wfw_part = 0.3333333_wp, time_prel = 0.0_wp,              &
94                 time_sort_particles = 0.0_wp,                                 &
95                 time_write_particle_data = 0.0_wp, z0_av_global
96
97    REAL(wp), DIMENSION(max_number_of_particle_groups) ::                      &
98                 density_ratio = 9999999.9_wp, pdx = 9999999.9_wp,             &
99                 pdy = 9999999.9_wp, pdz = 9999999.9_wp, psb = 9999999.9_wp,   &
100                 psl = 9999999.9_wp, psn = 9999999.9_wp, psr = 9999999.9_wp,   &
101                 pss = 9999999.9_wp, pst = 9999999.9_wp, radius = 9999999.9_wp
102
103    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  particle_tail_coordinates
104
105    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
106
107    TYPE particle_type
108        SEQUENCE
109#if defined( __twocachelines )
110        REAL(wp)     ::  radius
111        REAL(sp)     ::  x, y, z, speed_x, speed_y, speed_z
112        REAL(wp)     ::  weight_factor, rvar1, dt_sum
113        INTEGER(iwp) ::  class
114        LOGICAL      ::  particle_mask
115
116        REAL(wp)     ::  dvrp_psize, rvar2, rvar3
117        REAL(sp)     ::  age, origin_x, origin_y, origin_z, e_m, age_m
118        INTEGER(iwp) ::  group, tailpoints, tail_id, block_nr
119#else
120        REAL(wp)     ::  radius, age, age_m, dt_sum, dvrp_psize, e_m,          &
121                         origin_x, origin_y, origin_z, rvar1, rvar2, rvar3,    &
122                         speed_x, speed_y, speed_z, weight_factor, x, y, z
123        INTEGER(iwp) ::  class, group, tailpoints, tail_id
124        LOGICAL      ::  particle_mask
125        INTEGER(iwp) ::  block_nr
126#endif                                                      !One 32 Bit word for 64 Bit alignment in Type declaration
127    END TYPE particle_type
128
129    TYPE(particle_type), DIMENSION(:), POINTER             ::  particles
130    TYPE(particle_type)                                    ::  zero_particle
131
132    TYPE particle_groups_type
133        SEQUENCE
134        REAL(wp) ::  density_ratio, radius, exp_arg, exp_term
135    END TYPE particle_groups_type
136
137    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
138       particle_groups
139
140    TYPE  grid_particle_def
141        INTEGER(iwp), DIMENSION(0:7)               ::  start_index
142        INTEGER(iwp), DIMENSION(0:7)               ::  end_index
143        LOGICAL                                    ::  time_loop_done
144        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles                !Particle array for this grid cell
145    END TYPE grid_particle_def
146
147    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
148
149    TYPE block_offset_def
150        INTEGER(iwp) ::  i_off
151        INTEGER(iwp) ::  j_off
152        INTEGER(iwp) ::  k_off
153    END TYPE block_offset_def
154
155    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
156
157    SAVE
158
159
160END MODULE particle_attributes
161
Note: See TracBrowser for help on using the repository browser.