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

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

code has been put under the GNU General Public License (v3)

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