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

Last change on this file since 1683 was 1683, checked in by knoop, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 8.6 KB
RevLine 
[1682]1!> @file lpm_pack_arrays.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1310]16! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[849]19! Current revisions:
20! ------------------
[1360]21!
[1683]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: lpm_pack_arrays.f90 1683 2015-10-07 23:57:51Z knoop $
26!
[1683]27! 1682 2015-10-07 23:56:08Z knoop
28! Code annotations made doxygen readable
29!
[1360]30! 1359 2014-04-11 17:15:14Z hoffmann
31! New particle structure integrated.
32! Kind definition added to all floating point numbers.
33!
[1321]34! 1320 2014-03-20 08:40:49Z raasch
[1320]35! ONLY-attribute added to USE-statements,
36! kind-parameters added to all INTEGER and REAL declaration statements,
37! kinds are defined in new module kinds,
38! comment fields (!:) to be used for variable explanations added to
39! all variable declaration statements
[849]40!
[1037]41! 1036 2012-10-22 13:43:42Z raasch
42! code put under GPL (PALM 3.9)
43!
[850]44! 849 2012-03-15 10:35:09Z raasch
45! initial revision (former part of advec_particles)
[849]46!
[850]47!
[849]48! Description:
49! ------------
[1682]50!> Pack particle and tail arrays, which means eliminate those elements marked for
51!> deletion and move data with higher index values to these free indices.
52!> Determine the new number of particles.
[849]53!------------------------------------------------------------------------------!
[1682]54 MODULE lpm_pack_arrays_mod
55 
[849]56
[1320]57    USE particle_attributes,                                                   &
[1359]58        ONLY:  deleted_tails, grid_particles, new_tail_id,                     &
59               number_of_particles, number_of_tails, offset_ocean_nzt,         &
60               offset_ocean_nzt_m1, particles, particle_type, prt_count,       &
[1320]61               particle_tail_coordinates, tail_mask, use_particle_tails
[849]62
[1359]63    PRIVATE
64    PUBLIC lpm_pack_all_arrays, lpm_pack_arrays
[849]65
[1359]66    INTERFACE lpm_pack_all_arrays
67       MODULE PROCEDURE lpm_pack_all_arrays
68    END INTERFACE lpm_pack_all_arrays
[849]69
[1359]70    INTERFACE lpm_pack_arrays
71       MODULE PROCEDURE lpm_pack_arrays
72    END INTERFACE lpm_pack_arrays
73
74CONTAINS
75
[1682]76!------------------------------------------------------------------------------!
77! Description:
78! ------------
79!> @todo Missing subroutine description.
80!------------------------------------------------------------------------------!
[1359]81    SUBROUTINE lpm_pack_all_arrays
82
83       USE cpulog,                                                             &
84           ONLY:  cpu_log, log_point_s
85
86       USE indices,                                                            &
87           ONLY:  nxl, nxr, nys, nyn, nzb, nzt
88
89       USE kinds
90
91       IMPLICIT NONE
92
[1682]93       INTEGER(iwp) ::  i !<
94       INTEGER(iwp) ::  j !<
95       INTEGER(iwp) ::  k !<
[1359]96
97       CALL cpu_log( log_point_s(51), 'lpm_pack_all_arrays', 'start' )
98       DO  i = nxl, nxr
99          DO  j = nys, nyn
100             DO  k = nzb+1, nzt
101                number_of_particles = prt_count(k,j,i)
102                IF ( number_of_particles <= 0 )  CYCLE
103                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
104                CALL lpm_pack_and_sort(i,j,k)
105                prt_count(k,j,i) = number_of_particles
106             ENDDO
107          ENDDO
108       ENDDO
109       CALL cpu_log( log_point_s(51), 'lpm_pack_all_arrays', 'stop' )
110       RETURN
111
112    END SUBROUTINE lpm_pack_all_arrays
113
[1682]114!------------------------------------------------------------------------------!
115! Description:
116! ------------
117!> @todo Missing subroutine description.
118!------------------------------------------------------------------------------!
[1359]119    SUBROUTINE lpm_pack_arrays
120
121       USE kinds
122
123       IMPLICIT NONE
124
[1682]125       INTEGER(iwp) ::  n       !<
126       INTEGER(iwp) ::  nd      !<
127       INTEGER(iwp) ::  nn      !<
[849]128!
[1359]129!--    Find out elements marked for deletion and move data from highest index
130!--    values to these free indices
131       nn = number_of_particles
[849]132
[1359]133       DO WHILE ( .NOT. particles(nn)%particle_mask )
134          nn = nn-1
135          IF ( nn == 0 )  EXIT
136       ENDDO
[849]137
[1359]138       IF ( nn > 0 )  THEN
139          DO  n = 1, number_of_particles
140             IF ( .NOT. particles(n)%particle_mask )  THEN
141                particles(n) = particles(nn)
142                nn = nn - 1
143                DO WHILE ( .NOT. particles(nn)%particle_mask )
144                   nn = nn-1
145                   IF ( n == nn )  EXIT
146                ENDDO
147             ENDIF
148             IF ( n == nn )  EXIT
149          ENDDO
[849]150       ENDIF
151
152!
[1359]153!--    The number of deleted particles has been determined in routines
154!--    lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
155       number_of_particles = nn
[849]156
157!
[1359]158!-- particle tails are currently not available
159!
[849]160!-- Handle tail array in the same way, store the new tail ids and re-assign it
161!-- to the respective particles
[1359]162!    IF ( use_particle_tails )  THEN
163!
164!       nn = 0
165!       nd = 0
166!
167!       DO  n = 1, number_of_tails
168!
169!          IF ( tail_mask(n) )  THEN
170!             nn = nn + 1
171!             particle_tail_coordinates(:,:,nn) = &
172!                                                particle_tail_coordinates(:,:,n)
173!             new_tail_id(n) = nn
174!          ELSE
175!             nd = nd + 1
176!          ENDIF
177!
178!       ENDDO
179!
180!       DO  n = 1, number_of_particles
181!          IF ( particles(n)%tail_id /= 0 )  THEN
182!             particles(n)%tail_id = new_tail_id(particles(n)%tail_id)
183!          ENDIF
184!       ENDDO
185!
186!    ENDIF
[849]187
[1359]188!
189!-- The number of deleted tails has been determined in routines
190!-- lpm_boundary_conds and lpm_exchange_horiz
191!   number_of_tails = number_of_tails - deleted_tails
192
193
194    END SUBROUTINE lpm_pack_arrays
195
[1682]196!------------------------------------------------------------------------------!
197! Description:
198! ------------
199!> @todo Missing subroutine description.
200!------------------------------------------------------------------------------!
[1359]201    SUBROUTINE lpm_pack_and_sort (ip,jp,kp)
202
203      USE control_parameters,                                                  &
204          ONLY: dz,  atmos_ocean_sign
205
206      USE indices,                                                             &
207          ONLY: nxl, nxr, nys, nyn, nzb, nzt
208
209      USE kinds
210
211      USE grid_variables,                                                      &
212          ONLY: ddx, ddy
213
214      IMPLICIT NONE
215
216      INTEGER(iwp), INTENT(IN)    :: ip
217      INTEGER(iwp), INTENT(IN)    :: jp
218      INTEGER(iwp), INTENT(IN)    :: kp
219
220      INTEGER(iwp)                :: i
221      INTEGER(iwp)                :: j
222      INTEGER(iwp)                :: k
223      INTEGER(iwp)                :: n
224      INTEGER(iwp)                :: nn
225      INTEGER(iwp)                :: m
226      INTEGER(iwp)                :: sort_index
227      INTEGER(iwp)                :: is
228      INTEGER(iwp)                :: kk
229
230      INTEGER(iwp),DIMENSION(0:7) :: sort_count
231
232      TYPE(particle_type), DIMENSION(number_of_particles,0:7) :: sort_particles
233
[849]234       nn = 0
[1359]235       sort_count = 0
[849]236
[1359]237       DO  n = 1, number_of_particles
238          sort_index = 0
[849]239
[1359]240          IF ( particles(n)%particle_mask )  THEN
[849]241             nn = nn + 1
[1359]242             i = particles(n)%x * ddx
243             j = particles(n)%y * ddy
244             k = ( particles(n)%z + 0.5_wp * dz * atmos_ocean_sign ) / dz +    &
245                 offset_ocean_nzt
246             kk= particles(n)%z / dz + 1 + offset_ocean_nzt_m1
247             IF ( i == ip )  sort_index = sort_index+4
248             IF ( j == jp )  sort_index = sort_index+2
249             IF ( k == kp )  sort_index = sort_index+1
250             sort_count(sort_index) = sort_count(sort_index)+1
251             m = sort_count(sort_index)
252             sort_particles(m,sort_index) = particles(n)
253             sort_particles(m,sort_index)%block_nr = sort_index
[849]254          ENDIF
255
256       ENDDO
257
[1359]258       nn = 0
259
260       DO is = 0,7
261          grid_particles(kp,jp,ip)%start_index(is) = nn + 1
262          DO n = 1,sort_count(is)
263             nn = nn+1
264             particles(nn) = sort_particles(n,is)
265          ENDDO
266          grid_particles(kp,jp,ip)%end_index(is) = nn
[849]267       ENDDO
268
[1359]269       number_of_particles = nn
270       RETURN
[849]271
[1359]272    END SUBROUTINE lpm_pack_and_sort
[849]273
274
[1359]275 END module lpm_pack_arrays_mod
Note: See TracBrowser for help on using the repository browser.