source: palm/tags/release-3.10/SOURCE/lpm_pack_arrays.f90 @ 3901

Last change on this file since 3901 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.9 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lpm_pack_arrays.f90 1037 2012-10-22 14:10:22Z suehring $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 849 2012-03-15 10:35:09Z raasch
32! initial revision (former part of advec_particles)
33!
34!
35! Description:
36! ------------
37! Pack particle and tail arrays, which means eliminate those elements marked for
38! deletion and move data with higher index values to these free indices.
39! Determine the new number of particles.
40!------------------------------------------------------------------------------!
41
42    USE particle_attributes
43
44    IMPLICIT NONE
45
46    INTEGER ::  n, nd, nn
47
48
49!
50!-- Find out elements marked for deletion and move data with higher index
51!-- values to these free indices
52    nn = 0
53    nd = 0
54
55    DO  n = 1, number_of_particles
56
57       IF ( particle_mask(n) )  THEN
58          nn = nn + 1
59          particles(nn) = particles(n)
60       ELSE
61          nd = nd + 1
62       ENDIF
63
64    ENDDO
65!
66!-- The number of deleted particles has been determined in routines
67!-- lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
68    number_of_particles = number_of_particles - deleted_particles
69
70!
71!-- Handle tail array in the same way, store the new tail ids and re-assign it
72!-- to the respective particles
73    IF ( use_particle_tails )  THEN
74
75       nn = 0
76       nd = 0
77
78       DO  n = 1, number_of_tails
79
80          IF ( tail_mask(n) )  THEN
81             nn = nn + 1
82             particle_tail_coordinates(:,:,nn) = &
83                                                particle_tail_coordinates(:,:,n)
84             new_tail_id(n) = nn
85          ELSE
86             nd = nd + 1
87          ENDIF
88
89       ENDDO
90
91       DO  n = 1, number_of_particles
92          IF ( particles(n)%tail_id /= 0 )  THEN
93             particles(n)%tail_id = new_tail_id(particles(n)%tail_id)
94          ENDIF
95       ENDDO
96
97    ENDIF
98
99!
100!-- The number of deleted tails has been determined in routines
101!-- lpm_boundary_conds and lpm_exchange_horiz
102    number_of_tails = number_of_tails - deleted_tails
103
104
105 END SUBROUTINE lpm_pack_arrays
Note: See TracBrowser for help on using the repository browser.