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

Last change on this file since 1002 was 850, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.1 KB
Line 
1 SUBROUTINE lpm_pack_arrays
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_pack_arrays.f90 850 2012-03-15 12:09:25Z raasch $
11!
12! 849 2012-03-15 10:35:09Z raasch
13! initial revision (former part of advec_particles)
14!
15!
16! Description:
17! ------------
18! Pack particle and tail arrays, which means eliminate those elements marked for
19! deletion and move data with higher index values to these free indices.
20! Determine the new number of particles.
21!------------------------------------------------------------------------------!
22
23    USE particle_attributes
24
25    IMPLICIT NONE
26
27    INTEGER ::  n, nd, nn
28
29
30!
31!-- Find out elements marked for deletion and move data with higher index
32!-- values to these free indices
33    nn = 0
34    nd = 0
35
36    DO  n = 1, number_of_particles
37
38       IF ( particle_mask(n) )  THEN
39          nn = nn + 1
40          particles(nn) = particles(n)
41       ELSE
42          nd = nd + 1
43       ENDIF
44
45    ENDDO
46!
47!-- The number of deleted particles has been determined in routines
48!-- lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
49    number_of_particles = number_of_particles - deleted_particles
50
51!
52!-- Handle tail array in the same way, store the new tail ids and re-assign it
53!-- to the respective particles
54    IF ( use_particle_tails )  THEN
55
56       nn = 0
57       nd = 0
58
59       DO  n = 1, number_of_tails
60
61          IF ( tail_mask(n) )  THEN
62             nn = nn + 1
63             particle_tail_coordinates(:,:,nn) = &
64                                                particle_tail_coordinates(:,:,n)
65             new_tail_id(n) = nn
66          ELSE
67             nd = nd + 1
68          ENDIF
69
70       ENDDO
71
72       DO  n = 1, number_of_particles
73          IF ( particles(n)%tail_id /= 0 )  THEN
74             particles(n)%tail_id = new_tail_id(particles(n)%tail_id)
75          ENDIF
76       ENDDO
77
78    ENDIF
79
80!
81!-- The number of deleted tails has been determined in routines
82!-- lpm_boundary_conds and lpm_exchange_horiz
83    number_of_tails = number_of_tails - deleted_tails
84
85
86 END SUBROUTINE lpm_pack_arrays
Note: See TracBrowser for help on using the repository browser.