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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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