source: palm/trunk/SOURCE/lpm_pack_arrays.f90 @ 1343

Last change on this file since 1343 was 1321, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.5 KB
Line 
1 SUBROUTINE lpm_pack_arrays
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: lpm_pack_arrays.f90 1321 2014-03-20 09:40:40Z kanani $
27!
28! 1320 2014-03-20 08:40:49Z raasch
29! ONLY-attribute added to USE-statements,
30! kind-parameters added to all INTEGER and REAL declaration statements,
31! kinds are defined in new module kinds,
32! comment fields (!:) to be used for variable explanations added to
33! all variable declaration statements
34!
35! 1036 2012-10-22 13:43:42Z raasch
36! code put under GPL (PALM 3.9)
37!
38! 849 2012-03-15 10:35:09Z raasch
39! initial revision (former part of advec_particles)
40!
41!
42! Description:
43! ------------
44! Pack particle and tail arrays, which means eliminate those elements marked for
45! deletion and move data with higher index values to these free indices.
46! Determine the new number of particles.
47!------------------------------------------------------------------------------!
48
49    USE kinds
50
51    USE particle_attributes,                                                   &
52        ONLY:  deleted_particles, deleted_tails, new_tail_id,                  &
53               number_of_particles, number_of_tails, particles, particle_mask, &
54               particle_tail_coordinates, tail_mask, use_particle_tails
55
56
57    IMPLICIT NONE
58
59    INTEGER(iwp) ::  n       !:
60    INTEGER(iwp) ::  nd      !:
61    INTEGER(iwp) ::  nn      !:
62!
63!-- Find out elements marked for deletion and move data with higher index
64!-- values to these free indices
65    nn = 0
66    nd = 0
67
68    DO  n = 1, number_of_particles
69
70       IF ( particle_mask(n) )  THEN
71          nn = nn + 1
72          particles(nn) = particles(n)
73       ELSE
74          nd = nd + 1
75       ENDIF
76
77    ENDDO
78!
79!-- The number of deleted particles has been determined in routines
80!-- lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
81    number_of_particles = number_of_particles - deleted_particles
82
83!
84!-- Handle tail array in the same way, store the new tail ids and re-assign it
85!-- to the respective particles
86    IF ( use_particle_tails )  THEN
87
88       nn = 0
89       nd = 0
90
91       DO  n = 1, number_of_tails
92
93          IF ( tail_mask(n) )  THEN
94             nn = nn + 1
95             particle_tail_coordinates(:,:,nn) = &
96                                                particle_tail_coordinates(:,:,n)
97             new_tail_id(n) = nn
98          ELSE
99             nd = nd + 1
100          ENDIF
101
102       ENDDO
103
104       DO  n = 1, number_of_particles
105          IF ( particles(n)%tail_id /= 0 )  THEN
106             particles(n)%tail_id = new_tail_id(particles(n)%tail_id)
107          ENDIF
108       ENDDO
109
110    ENDIF
111
112!
113!-- The number of deleted tails has been determined in routines
114!-- lpm_boundary_conds and lpm_exchange_horiz
115    number_of_tails = number_of_tails - deleted_tails
116
117
118 END SUBROUTINE lpm_pack_arrays
Note: See TracBrowser for help on using the repository browser.