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

Last change on this file since 1822 was 1822, checked in by hoffmann, 8 years ago

changes in LPM and bulk cloud microphysics

  • Property svn:keywords set to Id
File size: 7.2 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!
[1818]16! Copyright 1997-2016 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[849]19! Current revisions:
20! ------------------
[1822]21! Tails removed. Unused variables removed.
[1686]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: lpm_pack_arrays.f90 1822 2016-04-07 07:49:42Z hoffmann $
26!
[1686]27! 1685 2015-10-08 07:32:13Z raasch
28! bugfix concerning vertical index calculation in case of ocean
29!
[1683]30! 1682 2015-10-07 23:56:08Z knoop
31! Code annotations made doxygen readable
32!
[1360]33! 1359 2014-04-11 17:15:14Z hoffmann
34! New particle structure integrated.
35! Kind definition added to all floating point numbers.
36!
[1321]37! 1320 2014-03-20 08:40:49Z raasch
[1320]38! ONLY-attribute added to USE-statements,
39! kind-parameters added to all INTEGER and REAL declaration statements,
40! kinds are defined in new module kinds,
41! comment fields (!:) to be used for variable explanations added to
42! all variable declaration statements
[849]43!
[1037]44! 1036 2012-10-22 13:43:42Z raasch
45! code put under GPL (PALM 3.9)
46!
[850]47! 849 2012-03-15 10:35:09Z raasch
48! initial revision (former part of advec_particles)
[849]49!
[850]50!
[849]51! Description:
52! ------------
[1822]53!> Pack particle arrays, which means eliminate those elements marked for
[1682]54!> deletion and move data with higher index values to these free indices.
55!> Determine the new number of particles.
[849]56!------------------------------------------------------------------------------!
[1682]57 MODULE lpm_pack_arrays_mod
58 
[849]59
[1320]60    USE particle_attributes,                                                   &
[1822]61        ONLY:  grid_particles, number_of_particles, offset_ocean_nzt,          &
62               particles, particle_type, prt_count
[849]63
[1359]64    PRIVATE
65    PUBLIC lpm_pack_all_arrays, lpm_pack_arrays
[849]66
[1359]67    INTERFACE lpm_pack_all_arrays
68       MODULE PROCEDURE lpm_pack_all_arrays
69    END INTERFACE lpm_pack_all_arrays
[849]70
[1359]71    INTERFACE lpm_pack_arrays
72       MODULE PROCEDURE lpm_pack_arrays
73    END INTERFACE lpm_pack_arrays
74
75CONTAINS
76
[1682]77!------------------------------------------------------------------------------!
78! Description:
79! ------------
80!> @todo Missing subroutine description.
81!------------------------------------------------------------------------------!
[1359]82    SUBROUTINE lpm_pack_all_arrays
83
84       USE cpulog,                                                             &
85           ONLY:  cpu_log, log_point_s
86
87       USE indices,                                                            &
88           ONLY:  nxl, nxr, nys, nyn, nzb, nzt
89
90       USE kinds
91
92       IMPLICIT NONE
93
[1682]94       INTEGER(iwp) ::  i !<
95       INTEGER(iwp) ::  j !<
96       INTEGER(iwp) ::  k !<
[1359]97
98       CALL cpu_log( log_point_s(51), 'lpm_pack_all_arrays', 'start' )
99       DO  i = nxl, nxr
100          DO  j = nys, nyn
101             DO  k = nzb+1, nzt
102                number_of_particles = prt_count(k,j,i)
103                IF ( number_of_particles <= 0 )  CYCLE
104                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
105                CALL lpm_pack_and_sort(i,j,k)
106                prt_count(k,j,i) = number_of_particles
107             ENDDO
108          ENDDO
109       ENDDO
110       CALL cpu_log( log_point_s(51), 'lpm_pack_all_arrays', 'stop' )
111       RETURN
112
113    END SUBROUTINE lpm_pack_all_arrays
114
[1682]115!------------------------------------------------------------------------------!
116! Description:
117! ------------
118!> @todo Missing subroutine description.
119!------------------------------------------------------------------------------!
[1359]120    SUBROUTINE lpm_pack_arrays
121
122       USE kinds
123
124       IMPLICIT NONE
125
[1682]126       INTEGER(iwp) ::  n       !<
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
[1359]157    END SUBROUTINE lpm_pack_arrays
158
[1682]159!------------------------------------------------------------------------------!
160! Description:
161! ------------
162!> @todo Missing subroutine description.
163!------------------------------------------------------------------------------!
[1359]164    SUBROUTINE lpm_pack_and_sort (ip,jp,kp)
165
166      USE control_parameters,                                                  &
[1685]167          ONLY: dz
[1359]168
169      USE kinds
170
171      USE grid_variables,                                                      &
172          ONLY: ddx, ddy
173
174      IMPLICIT NONE
175
[1685]176      INTEGER(iwp), INTENT(IN) :: ip
177      INTEGER(iwp), INTENT(IN) :: jp
178      INTEGER(iwp), INTENT(IN) :: kp
[1359]179
[1685]180      INTEGER(iwp)             :: i
181      INTEGER(iwp)             :: is
182      INTEGER(iwp)             :: j
183      INTEGER(iwp)             :: k
184      INTEGER(iwp)             :: n
185      INTEGER(iwp)             :: nn
186      INTEGER(iwp)             :: m
187      INTEGER(iwp)             :: sort_index
[1359]188
[1685]189      INTEGER(iwp), DIMENSION(0:7) :: sort_count
[1359]190
191      TYPE(particle_type), DIMENSION(number_of_particles,0:7) :: sort_particles
192
[849]193       nn = 0
[1359]194       sort_count = 0
[849]195
[1359]196       DO  n = 1, number_of_particles
197          sort_index = 0
[849]198
[1359]199          IF ( particles(n)%particle_mask )  THEN
[849]200             nn = nn + 1
[1359]201             i = particles(n)%x * ddx
202             j = particles(n)%y * ddy
[1685]203             k = ( particles(n)%z + 0.5_wp * dz ) / dz + offset_ocean_nzt
[1359]204             IF ( i == ip )  sort_index = sort_index+4
205             IF ( j == jp )  sort_index = sort_index+2
206             IF ( k == kp )  sort_index = sort_index+1
207             sort_count(sort_index) = sort_count(sort_index)+1
208             m = sort_count(sort_index)
209             sort_particles(m,sort_index) = particles(n)
210             sort_particles(m,sort_index)%block_nr = sort_index
[849]211          ENDIF
212
213       ENDDO
214
[1359]215       nn = 0
216
217       DO is = 0,7
218          grid_particles(kp,jp,ip)%start_index(is) = nn + 1
219          DO n = 1,sort_count(is)
220             nn = nn+1
221             particles(nn) = sort_particles(n,is)
222          ENDDO
223          grid_particles(kp,jp,ip)%end_index(is) = nn
[849]224       ENDDO
225
[1359]226       number_of_particles = nn
227       RETURN
[849]228
[1359]229    END SUBROUTINE lpm_pack_and_sort
[849]230
231
[1359]232 END module lpm_pack_arrays_mod
Note: See TracBrowser for help on using the repository browser.