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

Last change on this file since 2609 was 2609, checked in by schwenkel, 6 years ago

Integrated subroutine pack_and_sort into lpm_sort_in_subboxes

  • Property svn:keywords set to Id
File size: 12.8 KB
RevLine 
[1682]1!> @file lpm_pack_arrays.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1036]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!
[2101]17! Copyright 1997-2017 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[849]20! Current revisions:
21! ------------------
[2001]22!
23!
[1321]24! Former revisions:
25! -----------------
26! $Id: lpm_pack_arrays.f90 2609 2017-11-14 14:14:44Z schwenkel $
[2609]27! Integrated subroutine pack_and_sort into lpm_sort_in_subboxes
28!
29! 2606 2017-11-10 10:36:31Z schwenkel
[2606]30! Changed particle box locations: center of particle box now coincides
31! with scalar grid point of same index.
32! Renamed module and subroutines: lpm_pack_arrays_mod -> lpm_pack_and_sort_mod
33! lpm_pack_all_arrays -> lpm_sort_in_subboxes, lpm_pack_arrays -> lpm_pack
34! lpm_sort -> lpm_sort_timeloop_done
35!
36! 2417 2017-09-06 15:22:27Z suehring
[2417]37! New routine which sorts particles into particles that completed and not
38! completed the LES timestep.
39!
40! 2101 2017-01-05 16:42:31Z suehring
[1321]41!
[2001]42! 2000 2016-08-20 18:09:15Z knoop
43! Forced header and separation lines into 80 columns
44!
[1823]45! 1822 2016-04-07 07:49:42Z hoffmann
46! Tails removed. Unused variables removed.
47!
[1686]48! 1685 2015-10-08 07:32:13Z raasch
49! bugfix concerning vertical index calculation in case of ocean
50!
[1683]51! 1682 2015-10-07 23:56:08Z knoop
52! Code annotations made doxygen readable
53!
[1360]54! 1359 2014-04-11 17:15:14Z hoffmann
55! New particle structure integrated.
56! Kind definition added to all floating point numbers.
57!
[1321]58! 1320 2014-03-20 08:40:49Z raasch
[1320]59! ONLY-attribute added to USE-statements,
60! kind-parameters added to all INTEGER and REAL declaration statements,
61! kinds are defined in new module kinds,
62! comment fields (!:) to be used for variable explanations added to
63! all variable declaration statements
[849]64!
[1037]65! 1036 2012-10-22 13:43:42Z raasch
66! code put under GPL (PALM 3.9)
67!
[850]68! 849 2012-03-15 10:35:09Z raasch
69! initial revision (former part of advec_particles)
[849]70!
[850]71!
[849]72! Description:
73! ------------
[1822]74!> Pack particle arrays, which means eliminate those elements marked for
[1682]75!> deletion and move data with higher index values to these free indices.
76!> Determine the new number of particles.
[2417]77!> Moreover, particles are also sorted into groups finished and not finished
78!> its timestep.
[849]79!------------------------------------------------------------------------------!
[2606]80 MODULE lpm_pack_and_sort_mod
[1682]81 
[849]82
[1320]83    USE particle_attributes,                                                   &
[1822]84        ONLY:  grid_particles, number_of_particles, offset_ocean_nzt,          &
85               particles, particle_type, prt_count
[849]86
[1359]87    PRIVATE
[2606]88    PUBLIC lpm_sort_in_subboxes, lpm_pack, lpm_sort_timeloop_done
[849]89
[2606]90    INTERFACE lpm_sort_in_subboxes
91       MODULE PROCEDURE lpm_sort_in_subboxes
92    END INTERFACE lpm_sort_in_subboxes
[849]93
[2606]94    INTERFACE lpm_pack
95       MODULE PROCEDURE lpm_pack
96    END INTERFACE lpm_pack
[1359]97
[2606]98    INTERFACE lpm_sort_timeloop_done
99       MODULE PROCEDURE lpm_sort_timeloop_done
100    END INTERFACE lpm_sort_timeloop_done
[1359]101
[2417]102
103 CONTAINS
104
[1682]105!------------------------------------------------------------------------------!
106! Description:
[2606]107! -----------
108!> Routine for the whole processor
109!> Sort all particles into the 8 respective subgrid boxes
[1682]110!------------------------------------------------------------------------------!
[2606]111    SUBROUTINE lpm_sort_in_subboxes
[1359]112
[2606]113       USE cpulog,                                                              &
[1359]114           ONLY:  cpu_log, log_point_s
115
[2606]116       USE indices,                                                             &
[1359]117           ONLY:  nxl, nxr, nys, nyn, nzb, nzt
118
119       USE kinds
120
[2606]121       USE control_parameters,                                                  &
122           ONLY: dz
123       
124       USE grid_variables,                                                      &
125           ONLY: dx,dy,ddx, ddy
126         
[1359]127       IMPLICIT NONE
128
[2609]129       INTEGER(iwp) ::  i  !<
[2606]130       INTEGER(iwp) ::  ip !<
[2609]131       INTEGER(iwp) ::  is !<
132       INTEGER(iwp) ::  j  !<
[2606]133       INTEGER(iwp) ::  jp !<
[2609]134       INTEGER(iwp) ::  k  !<
[2606]135       INTEGER(iwp) ::  kp !<
[2609]136       INTEGER(iwp) ::  m  !<
137       INTEGER(iwp) ::  n  !<
138       INTEGER(iwp) ::  nn !<
139       INTEGER(iwp) ::  sort_index  !<
[1359]140
[2609]141       INTEGER(iwp), DIMENSION(0:7) ::  sort_count  !<
142
143       TYPE(particle_type), DIMENSION(:,:), ALLOCATABLE ::  sort_particles  !<
144
[2606]145       CALL cpu_log( log_point_s(51), 'lpm_sort_in_subboxes', 'start' )
146       DO  ip = nxl, nxr
147          DO  jp = nys, nyn
148             DO  kp = nzb+1, nzt
149                number_of_particles = prt_count(kp,jp,ip)
[1359]150                IF ( number_of_particles <= 0 )  CYCLE
[2606]151                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
[2609]152                     
153                nn = 0
154                sort_count = 0
155                ALLOCATE( sort_particles(number_of_particles, 0:7) )
[2606]156               
[2609]157                DO  n = 1, number_of_particles
158                   sort_index = 0
159
160                   IF ( particles(n)%particle_mask )  THEN
161                      nn = nn + 1
162!
163!--                   Sorting particles with a binary scheme
164!--                   sort_index=111_2=7_10 -> particle at the left,south,bottom subgridbox
165!--                   sort_index=000_2=0_10 -> particle at the right,north,top subgridbox
166!--                   For this the center of the gridbox is calculated
167                      i = (particles(n)%x + 0.5_wp * dx) * ddx
168                      j = (particles(n)%y + 0.5_wp * dy) * ddy
169                      k = ( particles(n)%z+ 0.5_wp *dz ) / dz+1 + offset_ocean_nzt
170                     
171                      IF ( i == ip )  sort_index = sort_index + 4 
172                      IF ( j == jp )  sort_index = sort_index + 2
173                      IF ( k == kp )  sort_index = sort_index + 1
174                     
175                      sort_count(sort_index) = sort_count(sort_index) + 1
176                      m = sort_count(sort_index)
177                      sort_particles(m,sort_index) = particles(n)
178                      sort_particles(m,sort_index)%block_nr = sort_index
179                   ENDIF
180                ENDDO
181
182                nn = 0
183                DO is = 0,7
184                   grid_particles(kp,jp,ip)%start_index(is) = nn + 1
185                   DO n = 1,sort_count(is)
186                      nn = nn + 1
187                      particles(nn) = sort_particles(n,is)
188                   ENDDO
189                   grid_particles(kp,jp,ip)%end_index(is) = nn
190                ENDDO
191
192                number_of_particles = nn   
[2606]193                prt_count(kp,jp,ip) = number_of_particles
[2609]194                DEALLOCATE(sort_particles)
[1359]195             ENDDO
196          ENDDO
197       ENDDO
[2606]198       CALL cpu_log( log_point_s(51), 'lpm_sort_in_subboxes', 'stop' )
[1359]199       RETURN
200
[2606]201    END SUBROUTINE lpm_sort_in_subboxes
[1359]202
[1682]203!------------------------------------------------------------------------------!
204! Description:
205! ------------
[2606]206!> Move all particles not marked for deletion to lowest indices (packing)
[1682]207!------------------------------------------------------------------------------!
[2606]208    SUBROUTINE lpm_pack
[1359]209
210       USE kinds
211
212       IMPLICIT NONE
213
[1682]214       INTEGER(iwp) ::  n       !<
215       INTEGER(iwp) ::  nn      !<
[849]216!
[1359]217!--    Find out elements marked for deletion and move data from highest index
218!--    values to these free indices
219       nn = number_of_particles
[849]220
[1359]221       DO WHILE ( .NOT. particles(nn)%particle_mask )
222          nn = nn-1
223          IF ( nn == 0 )  EXIT
224       ENDDO
[849]225
[1359]226       IF ( nn > 0 )  THEN
227          DO  n = 1, number_of_particles
228             IF ( .NOT. particles(n)%particle_mask )  THEN
229                particles(n) = particles(nn)
230                nn = nn - 1
231                DO WHILE ( .NOT. particles(nn)%particle_mask )
232                   nn = nn-1
233                   IF ( n == nn )  EXIT
234                ENDDO
235             ENDIF
236             IF ( n == nn )  EXIT
237          ENDDO
[849]238       ENDIF
239
240!
[1359]241!--    The number of deleted particles has been determined in routines
242!--    lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
243       number_of_particles = nn
[849]244
[2606]245    END SUBROUTINE lpm_pack 
246               
[2417]247!------------------------------------------------------------------------------!
248! Description:
249! ------------
250!> Sort particles in each sub-grid box into two groups: particles that already
251!> completed the LES timestep, and particles that need further timestepping to
252!> complete the LES timestep.
253!------------------------------------------------------------------------------!
[2606]254    SUBROUTINE lpm_sort_timeloop_done
[849]255
[2417]256       USE control_parameters,                                                 &
257           ONLY:  dt_3d
258
259       USE indices,                                                            &
260           ONLY: nxl, nxr, nys, nyn, nzb, nzt
261
262       USE kinds
263
264       IMPLICIT NONE
265
266       INTEGER(iwp) :: end_index     !< particle end index for each sub-box
267       INTEGER(iwp) :: i             !< index of particle grid box in x-direction
268       INTEGER(iwp) :: j             !< index of particle grid box in y-direction
269       INTEGER(iwp) :: k             !< index of particle grid box in z-direction
270       INTEGER(iwp) :: n             !< running index for number of particles
271       INTEGER(iwp) :: nb            !< index of subgrid boux
272       INTEGER(iwp) :: nf            !< indices for particles in each sub-box that already finalized their substeps
273       INTEGER(iwp) :: nnf           !< indices for particles in each sub-box that need further treatment
274       INTEGER(iwp) :: num_finalized !< number of particles in each sub-box that already finalized their substeps
275       INTEGER(iwp) :: start_index   !< particle start index for each sub-box
276
277       TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: sort_particles  !< temporary particle array
278
279       DO  i = nxl, nxr
280          DO  j = nys, nyn
281             DO  k = nzb+1, nzt
282
283                number_of_particles = prt_count(k,j,i)
284                IF ( number_of_particles <= 0 )  CYCLE
285
286                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
287
288                DO  nb = 0, 7
289!
290!--                Obtain start and end index for each subgrid box
291                   start_index = grid_particles(k,j,i)%start_index(nb)
292                   end_index   = grid_particles(k,j,i)%end_index(nb)
293!
294!--                Allocate temporary array used for sorting.
295                   ALLOCATE( sort_particles(start_index:end_index) )
296!
297!--                Determine number of particles already completed the LES
298!--                timestep, and write them into a temporary array.
299                   nf = start_index
300                   num_finalized = 0
301                   DO  n = start_index, end_index
302                      IF ( dt_3d - particles(n)%dt_sum < 1E-8_wp )  THEN
303                         sort_particles(nf) = particles(n)
304                         nf                 = nf + 1
305                         num_finalized      = num_finalized + 1
306                      ENDIF
307                   ENDDO
308!
309!--                Determine number of particles that not completed the LES
310!--                timestep, and write them into a temporary array.
311                   nnf = nf
312                   DO  n = start_index, end_index
313                      IF ( dt_3d - particles(n)%dt_sum > 1E-8_wp )  THEN
314                         sort_particles(nnf) = particles(n)
315                         nnf                 = nnf + 1
316                      ENDIF
317                   ENDDO
318!
319!--                Write back sorted particles
320                   particles(start_index:end_index) =                          &
321                                           sort_particles(start_index:end_index)
322!
323!--                Determine updated start_index, used to masked already
324!--                completed particles.
325                   grid_particles(k,j,i)%start_index(nb) =                     &
326                                      grid_particles(k,j,i)%start_index(nb)    &
327                                    + num_finalized
328!
329!--                Deallocate dummy array
330                   DEALLOCATE ( sort_particles )
331!
332!--                Finally, if number of non-completed particles is non zero
333!--                in any of the sub-boxes, set control flag appropriately.
334                   IF ( nnf > nf )                                             &
335                      grid_particles(k,j,i)%time_loop_done = .FALSE.
336
337                ENDDO
338             ENDDO
339          ENDDO
340       ENDDO
341
[2606]342    END SUBROUTINE lpm_sort_timeloop_done
[2417]343
344
[2606]345 END module lpm_pack_and_sort_mod
Note: See TracBrowser for help on using the repository browser.