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

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

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

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