source: palm/trunk/SOURCE/pmc_particle_interface.f90 @ 2967

Last change on this file since 2967 was 2967, checked in by raasch, 6 years ago

bugfix: missing parallel cpp-directives added

  • Property svn:keywords set to Id
File size: 44.1 KB
Line 
1MODULE pmc_particle_interface
2
3!------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the
7! terms of the GNU General Public License as published by the Free Software
8! Foundation, either version 3 of the License, or (at your option) any later
9! version.
10!
11! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
12! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
13! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
14!
15! You should have received a copy of the GNU General Public License along with
16! PALM. If not, see <http://www.gnu.org/licenses/>.
17!
18! Copyright 1997-2018 Leibniz Universitaet Hannover
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! ------------------
23!
24!
25! Former revisions:
26! -----------------!
27! $Id: pmc_particle_interface.f90 2967 2018-04-13 11:22:08Z raasch $
28! bugfix: missing parallel cpp-directives added
29!
30! 2884 2018-03-14 08:33:20Z scharf
31! B: corrected KIND of variable "parsize" for some MPI calls
32!
33! 2841 2018-02-27 15:02:57Z knoop
34! Bugfix: wrong placement of include 'mpif.h' corrected
35!
36! 2809 2018-02-15 09:55:58Z schwenkel
37! Bugfix for gfortran: Replace the function C_SIZEOF with STORAGE_SIZE.
38
39!
40! Initial Version (by Klaus Ketelsen)
41!
42!
43! Description:
44! ------------
45! Introduce particle transfer in nested models.
46! Interface to palm lpm model to handel particle transfer between parent and
47! child model.
48!------------------------------------------------------------------------------!
49
50   USE, INTRINSIC ::  ISO_C_BINDING
51
52#if defined( __parallel )  &&  !defined( __mpifh )
53   USE MPI
54#endif
55
56   USE kinds
57
58   USE pegrid,                                                                 &
59       ONLY: myidx,myidy
60
61   USE indices,                                                                &
62       ONLY: nx, ny, nxl, nxr, nys, nyn, nzb, nzt, nxlg, nxrg, nysg, nyng, nbgp
63
64   USE grid_variables,                                                         &
65       ONLY:  dx, dy
66
67   USE arrays_3d,                                                              &
68        ONLY: zw
69
70   USE control_parameters,                                                     &
71       ONLY:  message_string
72
73   USE particle_attributes,                                                    &
74       ONLY:  prt_count, particles, grid_particles,                            &
75              particle_type, number_of_particles, zero_particle,               &
76              ibc_par_t, ibc_par_lr, ibc_par_ns, alloc_factor
77
78   USE lpm_pack_and_sort_mod
79
80   USE lpm_exchange_horiz_mod,                                                 &
81       ONLY: realloc_particles_array
82
83#if defined( __parallel )
84   USE pmc_general,                                                            &
85       ONLY: pedef
86
87   USE pmc_parent,                                                             &
88       ONLY: children, pmc_s_fillbuffer, pmc_s_getdata_from_buffer,            &
89             pmc_s_get_child_npes
90
91   USE pmc_child,                                                              &
92       ONLY:  me, pmc_c_getbuffer, pmc_c_putbuffer
93
94   USE pmc_interface,                                                          &
95       ONLY: cpl_id, get_number_of_childs, nr_part,  part_adr, nested_run,     &
96             get_childid, get_child_edges, nr_partc,  part_adrc,               &
97             coarse_bound, coord_x, coord_y, cg,   get_child_gridspacing,      &
98             lower_left_coord_x, lower_left_coord_y
99
100    USE pmc_handle_communicator,                                               &
101        ONLY:  pmc_parent_for_child
102
103   USE pmc_mpi_wrapper,                                                        &
104       ONLY: pmc_send_to_parent, pmc_recv_from_child
105
106#endif
107
108   IMPLICIT NONE
109
110#if defined( __parallel )  &&  defined( __mpifh )
111   INCLUDE "mpif.h"
112#endif
113
114   PRIVATE
115   SAVE
116
117   TYPE  coarse_particle_def
118      INTEGER(iwp) ::  nr_particle
119     
120      TYPE(particle_type),ALLOCATABLE,DIMENSION(:) ::  parent_particles
121   END TYPE  coarse_particle_def
122
123   INTEGER(iwp),PARAMETER ::  Min_particles_per_column = 100      !<
124   INTEGER(iwp),PARAMETER ::  max_nr_particle_in_rma_win = 100000 !<
125
126   INTEGER(iwp) ::  nr_fine_in_coarse  !< Number of fine grid cells in coarse grid (one direction)
127   INTEGER(iwp) ::  particle_win_child !<
128
129   INTEGER(iwp),ALLOCATABLE,DIMENSION(:) ::  particle_win_parent !<
130   
131   TYPE(C_PTR), ALLOCATABLE,DIMENSION(:) ::  buf_ptr !<
132   
133   TYPE(particle_type), DIMENSION(:),POINTER ::  particle_in_win !<
134
135   TYPE(coarse_particle_def),ALLOCATABLE,DIMENSION(:,:) ::  coarse_particles !<
136
137   
138
139   INTERFACE pmcp_g_init
140      MODULE PROCEDURE pmcp_g_init
141   END  INTERFACE pmcp_g_init
142
143   INTERFACE pmcp_g_alloc_win
144      MODULE PROCEDURE pmcp_g_alloc_win
145   END  INTERFACE pmcp_g_alloc_win
146
147   INTERFACE pmcp_c_get_particle_from_parent
148      MODULE PROCEDURE pmcp_c_get_particle_from_parent
149   END  INTERFACE pmcp_c_get_particle_from_parent
150
151   INTERFACE pmcp_c_send_particle_to_parent
152      MODULE PROCEDURE pmcp_c_send_particle_to_parent
153   END  INTERFACE pmcp_c_send_particle_to_parent
154
155   INTERFACE pmcp_p_fill_particle_win
156      MODULE PROCEDURE pmcp_p_fill_particle_win
157   END  INTERFACE pmcp_p_fill_particle_win
158
159   INTERFACE pmcp_p_empty_particle_win
160      MODULE PROCEDURE pmcp_p_empty_particle_win
161   END  INTERFACE pmcp_p_empty_particle_win
162
163   INTERFACE pmcp_g_print_number_of_particles
164      MODULE PROCEDURE pmcp_g_print_number_of_particles
165   END  INTERFACE pmcp_g_print_number_of_particles
166
167   INTERFACE pmcp_p_delete_particles_in_fine_grid_area
168      MODULE PROCEDURE pmcp_p_delete_particles_in_fine_grid_area
169   END  INTERFACE pmcp_p_delete_particles_in_fine_grid_area
170
171   PUBLIC pmcp_g_init, pmcp_g_alloc_win, pmcp_c_get_particle_from_parent
172   PUBLIC pmcp_c_send_particle_to_parent, pmcp_p_fill_particle_win, pmcp_g_print_number_of_particles
173   PUBLIC pmcp_p_empty_particle_win, pmcp_p_delete_particles_in_fine_grid_area
174
175 CONTAINS
176
177!------------------------------------------------------------------------------!
178! Description:
179! ------------
180!> general routine:
181!> Initializing actions of the particle interface
182!> check particle boundary conditions for the child models
183!------------------------------------------------------------------------------!
184 SUBROUTINE pmcp_g_init
185 
186    IMPLICIT NONE
187 
188    INTEGER(iwp) ::  nr_childs !< Number of child models of the current model
189
190#if defined( __parallel )
191
192    nr_childs = get_number_of_childs()
193!
194!-- Check if the current model has child models
195    IF ( nr_childs > 0 )   THEN
196       ALLOCATE( nr_part(nysg:nyng, nxlg:nxrg) )
197       ALLOCATE( part_adr(nysg:nyng, nxlg:nxrg) )
198       nr_part = 0
199       part_adr   = 0
200    ENDIF
201
202!
203!-- Set the boundary conditions to nested for all non root (i.e child) models
204    IF ( cpl_id > 1 )  THEN
205   
206       IF ( ibc_par_t /= 3 )   THEN
207          ibc_par_t  = 3
208          message_string = 'In Child model:  bc_par_t is automatically set to nested '
209          CALL message( 'pmcp_g_init ', 'PA0477', 0, 1, 0, 6, 0 )   ! PA number has to be adjusted
210       ENDIF
211   
212       IF ( ibc_par_lr /= 3 )   THEN
213          ibc_par_lr = 3
214          message_string = 'In Child model:  bc_par_lr is automatically set to nested '
215          CALL message( 'pmcp_g_init ', 'PA0478', 0, 1, 0, 6, 0 )   ! PA number has to be adjusted
216       ENDIF
217       
218       IF ( ibc_par_ns /= 3 )   THEN
219          ibc_par_ns = 3
220          message_string = 'In Child model:  bc_par_ns is automatically set to nested '
221          CALL message( 'pmcp_g_init ', 'PA0479', 0, 1, 0, 6, 0 )   ! PA number has to be adjusted
222       ENDIF
223       
224    ENDIF
225
226#endif
227 END SUBROUTINE pmcp_g_init
228!------------------------------------------------------------------------------!
229! Description:
230! ------------
231!> general routine:
232!> allocate the MPI windows
233!------------------------------------------------------------------------------!
234 SUBROUTINE pmcp_g_alloc_win
235 
236    IMPLICIT NONE
237   
238    INTEGER(iwp) ::  m         !< loop index
239    INTEGER(iwp) ::  ierr      !< error code
240    INTEGER(iwp) ::  icl       !< left boundary in coarse(parent) index space
241    INTEGER(iwp) ::  icr       !< right boundary in coarse(parent) index space
242    INTEGER(iwp) ::  jcs       !< south boundary in coarse(parent) index space
243    INTEGER(iwp) ::  jcn       !< north boundary in coarse(parent) index space
244    INTEGER(iwp) ::  child_id  !< Id of a child model
245    INTEGER(iwp) ::  nr_childs !< Number of child models of the current model
246   
247    INTEGER ::  parsize !<
248    TYPE(C_PTR), SAVE ::  ptr !<
249   
250    TYPE(particle_type),DIMENSION(:),POINTER ::  win_buffer !<
251   
252    INTEGER(iwp),DIMENSION(1) ::  buf_shape !<
253
254#if defined( __parallel )
255    INTEGER(KIND=MPI_ADDRESS_KIND) ::  parsize_mpi_address_kind !<
256    INTEGER(KIND=MPI_ADDRESS_KIND) ::  winsize !<
257
258!
259!-- If the model has a parent model prepare the structures for transfer
260    IF ( cpl_id > 1 )  THEN
261
262       parsize_mpi_address_kind = STORAGE_SIZE(zero_particle)/8
263
264       CALL MPI_ALLOC_MEM( parsize_mpi_address_kind , MPI_INFO_NULL, ptr, ierr )
265       parsize = parsize_mpi_address_kind
266       buf_shape(1) = 1
267       CALL C_F_POINTER( ptr, win_buffer, buf_shape )
268       CALL MPI_WIN_CREATE( win_buffer, parsize_mpi_address_kind, parsize,     &
269                            MPI_INFO_NULL, me%intra_comm, particle_win_child,  &
270                            ierr )
271
272!
273!--    Child domain boundaries in the parent index space
274       icl = coarse_bound(1)
275       icr = coarse_bound(2)
276       jcs = coarse_bound(3)
277       jcn = coarse_bound(4)
278
279       ALLOCATE( coarse_particles(jcs:jcn, icl:icr) )
280
281       coarse_particles(:,:)%nr_particle = 0
282    ENDIF
283
284!
285!-- If the model has child models prepare the structures for transfer
286    nr_childs = get_number_of_childs()
287    IF ( nr_childs > 0 )   THEN
288       ALLOCATE( particle_win_parent(nr_childs) )
289       ALLOCATE( buf_ptr(nr_childs) )
290       DO  m = 1, nr_childs
291          child_id = get_childid(m)
292          parsize_mpi_address_kind = STORAGE_SIZE(zero_particle)/8
293          parsize = parsize_mpi_address_kind
294
295          winsize = max_nr_particle_in_rma_win * parsize_mpi_address_kind
296          CALL MPI_ALLOC_MEM( winsize , MPI_INFO_NULL, buf_ptr(m), ierr )
297          buf_shape(1) = max_nr_particle_in_rma_win
298          CALL C_F_POINTER( buf_ptr(m), win_buffer, buf_shape )
299          CALL MPI_WIN_CREATE( win_buffer, winsize, parsize, MPI_INFO_NULL,    &
300                               children(child_id)%intra_comm,                  &
301                               particle_win_parent(m), ierr )
302          ENDDO
303    ENDIF
304
305#endif
306 END SUBROUTINE pmcp_g_alloc_win
307
308
309!------------------------------------------------------------------------------!
310! Description:
311! ------------
312!> child routine:
313!> Read/get particles out of the parent MPI window
314!------------------------------------------------------------------------------!
315 SUBROUTINE pmcp_c_get_particle_from_parent
316 
317    IMPLICIT NONE
318
319    INTEGER(iwp) ::  i    !< x grid index
320    INTEGER(iwp) ::  icl  !< left boundary in coarse(parent) index space
321    INTEGER(iwp) ::  ierr !< error code
322    INTEGER(iwp) ::  ij   !< combined xy index for the buffer array
323    INTEGER(iwp) ::  ip   !< loop index (child PEs)
324    INTEGER(iwp) ::  j    !< y grid index
325    INTEGER(iwp) ::  jcs  !< south boundary in coarse(parent) index space
326    INTEGER(iwp) ::  nr   !< number of particles to receive from a parent box
327   
328    INTEGER ::  parsize !<
329
330#if defined( __parallel )
331    TYPE(pedef), POINTER ::  ape !< TO_DO Klaus: give a description and better name of the variable
332
333    INTEGER(KIND=MPI_ADDRESS_KIND) ::  parsize_mpi_address_kind !<
334    INTEGER(KIND=MPI_ADDRESS_KIND) ::  target_disp !<
335
336    IF ( cpl_id > 1 )  THEN
337   
338       CALL pmc_c_getbuffer( particle_transfer = .TRUE. ) !Get number of particle/column and offset in RMA window xx
339
340!
341!--    Wait for buffer to fill.
342!
343!--    The parent side (in pmc_s_fillbuffer) is filling the buffer in the MPI RMA window
344!--    When the filling is complete, a MPI_BARRIER is called.
345!--    The child is not allowd to access the parent-buffer before it is completely filled
346!--    Synchronization is done implicitely in pmc_c_getbuffer and pmc_s_fillbuffer on the parent side
347
348       icl = coarse_bound(1)
349       jcs = coarse_bound(3)
350
351       DO  ip = 1, me%inter_npes
352
353          ape => me%pes(ip)
354
355          DO  ij = 1, ape%nrele
356              j = ape%locind(ij)%j + jcs - 1
357              i = ape%locind(ij)%i + icl - 1
358              nr = nr_partc(j,i)
359              IF ( nr > 0 )  THEN
360
361                 CALL check_and_alloc_coarse_particle (i, j, nr)
362                 parsize_mpi_address_kind = STORAGE_SIZE(zero_particle)/8
363                 parsize = parsize_mpi_address_kind
364                 target_disp = part_adrc(j,i) - 1
365                 CALL MPI_WIN_LOCK( MPI_LOCK_SHARED , ip - 1, 0,               &
366                                    particle_win_child, ierr )
367                 CALL MPI_GET( coarse_particles(j,i)%parent_particles,         &
368                               nr * parsize, MPI_BYTE, ip - 1, target_disp,    &
369                               nr * parsize, MPI_BYTE, particle_win_child, ierr )
370                 CALL MPI_WIN_UNLOCK( ip - 1, particle_win_child, ierr )
371             ENDIF
372             coarse_particles(j,i)%nr_particle = nr
373          ENDDO
374       ENDDO
375
376       CALL c_copy_particle_to_child_grid
377    ENDIF
378
379#endif
380 END SUBROUTINE pmcp_c_get_particle_from_parent
381
382
383!------------------------------------------------------------------------------!
384! Description:
385! ------------
386!> child routine:
387!> Write/put particles into the parent MPI window
388!------------------------------------------------------------------------------!
389  SUBROUTINE pmcp_c_send_particle_to_parent
390 
391    IMPLICIT NONE
392   
393    INTEGER(iwp) ::  disp_offset            !<
394    INTEGER(iwp) ::  i                      !< x loop index
395    INTEGER(iwp) ::  icl                    !< left boundary in coarse(parent) index space
396    INTEGER(iwp) ::  icr                    !< right boundary in coarse(parent) index space
397    INTEGER(iwp) ::  ierr                   !< error code
398    INTEGER(iwp) ::  ij                     !< combined xy index for the buffer array
399    INTEGER(iwp) ::  ip                     !< loop index (child PEs)
400    INTEGER(iwp) ::  j                      !< y loop index
401    INTEGER(iwp) ::  jcs                    !< south boundary in coarse(parent) index space
402    INTEGER(iwp) ::  jcn                    !< north boundary in coarse(parent) index space
403    INTEGER(iwp) ::  max_nr_particle_per_pe !< maximum number of particles per PE (depending on grid apect ratio)
404    INTEGER(iwp) ::  n                      !< shorter variable name for nr_fine_in_coarse
405    INTEGER(iwp) ::  nr                     !< shorter variabel name for nr_partc
406    INTEGER(iwp) ::  pe_offset              !< offset index of the current PE
407   
408    INTEGER ::  parsize !<
409   
410    REAL(wp) ::  eps=0.00001 !< used in calculations to avoid rounding errors
411    REAL(wp) ::  xx          !< number of fine grid cells inside a coarse grid cell in x-direction
412    REAL(wp) ::  yy          !< number of fine grid cells inside a coarse grid cell in y-direction
413
414 !   TYPE(particle_type) ::  dummy_part !< dummy particle (needed for size calculations)
415
416#if defined( __parallel )
417    TYPE(pedef), POINTER ::  ape !< TO_DO Klaus: give a description and better name of the variable
418
419    INTEGER(KIND=MPI_ADDRESS_KIND) ::  parsize_mpi_address_kind !<
420    INTEGER(KIND=MPI_ADDRESS_KIND) ::  target_disp !<
421   
422   
423    IF ( cpl_id > 1 )  THEN
424       CALL c_copy_particle_to_coarse_grid
425
426!
427!--    Child domain boundaries in the parent index space
428
429       icl = coarse_bound(1)
430       icr = coarse_bound(2)
431       jcs = coarse_bound(3)
432       jcn = coarse_bound(4)
433
434       nr_partc = 0
435       
436       DO i = icl, icr
437          DO j = jcs, jcn
438             nr_partc(j,i) = coarse_particles(j,i)%nr_particle
439          ENDDO
440       ENDDO
441       part_adrc = 0
442
443!
444!--    compute number of fine grid cells in coarse grid (one direction)
445       xx = (cg%dx + eps) / dx ! +eps to avoid rounding error
446       yy = (cg%dy + eps) / dy
447       nr_fine_in_coarse = MAX( INT(xx), INT(yy) )
448
449       IF ( MOD( coord_x(0), cg%dx ) /= 0.0 .OR. MOD( coord_y(0), cg%dy ) /= 0.0 ) THEN
450          nr_fine_in_coarse = nr_fine_in_coarse + 1
451       ENDIF
452
453!
454!--    Assign a number to my child PE to select different areas in the RMA window on server side
455!--    With this number a square of child PEs is defined which share the same coarse grid cells
456
457       n           = nr_fine_in_coarse ! local variable n to make folloing statements shorter
458       pe_offset   = MOD( myidx, n ) * n + MOD( myidy, n)
459       max_nr_particle_per_pe = max_nr_particle_in_rma_win / ( n * n )
460       disp_offset            = pe_offset * max_nr_particle_per_pe
461       parsize_mpi_address_kind = STORAGE_SIZE(zero_particle)/8
462       parsize = parsize_mpi_address_kind
463       DO  ip = 1, me%inter_npes
464
465          ape => me%pes(ip)
466
467          target_disp = disp_offset
468          DO ij = 1, ape%nrele
469             j  = ape%locind(ij)%j + jcs - 1
470             i  = ape%locind(ij)%i + icl - 1
471             nr = nr_partc(j,i)
472             IF( nr > 0 ) THEN
473                IF ( target_disp + nr - disp_offset >= max_nr_particle_per_pe ) THEN
474                   WRITE(9,*) 'RMA window too small on child ',                &
475                              target_disp + nr - disp_offset,                  &
476                              max_nr_particle_per_pe, max_nr_particle_in_rma_win
477                   message_string = 'RMA window too small on child'
478                   CALL message( 'pmci_create_child_arrays', 'PA0480', 3, 2, 0, 6, 0 )   ! PA number has to be adjusted
479                ENDIF
480                CALL MPI_WIN_LOCK( MPI_LOCK_SHARED , ip - 1, 0,                &
481                                   particle_win_child, ierr )
482                CALL MPI_PUT( coarse_particles(j,i)%parent_particles,          &
483                              nr * parsize, MPI_BYTE, ip - 1, target_disp,     &
484                              nr * parsize, MPI_BYTE,  particle_win_child, ierr )
485                CALL MPI_WIN_UNLOCK( ip - 1, particle_win_child, ierr )
486                part_adrc(j,i) = target_disp + 1
487                target_disp    = target_disp + nr
488             ENDIF
489          ENDDO
490       ENDDO
491
492       CALL pmc_c_putbuffer ( particle_transfer = .TRUE. )   !Send new number of particle/column and offset to parent
493
494    ENDIF
495
496#endif
497 END SUBROUTINE pmcp_c_send_particle_to_parent
498
499
500!------------------------------------------------------------------------------!
501! Description:
502! ------------
503!> parent routine:
504!> write particles into the MPI window
505!------------------------------------------------------------------------------!
506 SUBROUTINE pmcp_p_fill_particle_win
507 
508    IMPLICIT NONE
509
510    LOGICAL      ::  active_particle !< Particles located in the fine/child grid area are marked as active (to be transferred)
511    LOGICAL,SAVE ::  lfirst = .TRUE. !<
512   
513    INTEGER(iwp) ::  child_id            !< id of the child model
514    INTEGER(iwp) ::  i                   !< x grid box index
515    INTEGER(iwp) ::  ierr                !< error code
516    INTEGER(iwp) ::  ij                  !< combined xy index for the buffer array
517    INTEGER(iwp) ::  ip                  !< loop index (child PEs)
518    INTEGER(iwp) ::  j                   !< y grid box index
519    INTEGER(iwp) ::  k                   !< z grid box index
520    INTEGER(iwp) ::  m                   !< loop index (number of childs)
521    INTEGER(iwp) ::  n                   !< loop index (number of particles)
522    INTEGER(iwp) ::  nr_part_col         !< Number of particles to transfer per column
523    INTEGER(iwp) ::  number_of_particles !<
524    INTEGER(iwp) ::  pindex              !<
525    INTEGER(iwp) ::  tot_particle_count  !< Total number of particles per child
526   
527    REAL(wp) ::  dx_child   !< child grid spacing
528    REAL(wp) ::  dy_child   !< child grid spacing
529    REAL(wp) ::  dz_child   !< child grid spacing
530    REAL(wp) ::  ny_coord   !< north coordinate of child grid
531    REAL(wp) ::  ny_coord_b !< north coordinate of child grid boundary
532    REAL(wp) ::  lx_coord   !< left coordinate of child grid
533    REAL(wp) ::  lx_coord_b !< left coordinate of child grid boundary
534    REAL(wp) ::  rx_coord   !< right coordinate of child grid
535    REAL(wp) ::  rx_coord_b !< right coordinate of child grid boundary
536    REAL(wp) ::  sy_coord   !< south coordinate of child grid
537    REAL(wp) ::  sy_coord_b !< south coordinate of child grid boundary
538    REAL(wp) ::  uz_coord   !< upper coordinate of child grid
539    REAL(wp) ::  uz_coord_b !< upper coordinate of child grid boundary
540    REAL(wp) ::  x          !< particle position
541    REAL(wp) ::  xo         !< origin of particle
542    REAL(wp) ::  y          !< particle position
543    REAL(wp) ::  yo         !< origin of particle
544    REAL(wp) ::  z          !< particle position
545   
546    INTEGER(iwp),DIMENSION(1) ::  buf_shape !<
547   
548#if defined( __parallel )
549    TYPE(pedef), POINTER ::  ape !< TO_DO Klaus: give a description and better name of the variable
550
551    DO  m = 1, get_number_of_childs()
552
553       child_id = get_childid(m)
554
555       CALL get_child_edges( m, lx_coord, lx_coord_b, rx_coord, rx_coord_b,    &
556                                sy_coord, sy_coord_b, ny_coord, ny_coord_b,    &
557                                uz_coord, uz_coord_b) 
558
559       CALL get_child_gridspacing( m, dx_child, dy_child, dz_child )
560
561       IF ( lfirst )   THEN
562          WRITE(9,'(a,5f10.2)') 'edges          ',lx_coord,rx_coord,sy_coord,ny_coord,uz_coord
563          WRITE(9,'(a,5f10.2)') 'edges boundary ',lx_coord_b,rx_coord_b,sy_coord_b,ny_coord_b,uz_coord_b
564          WRITE(9,'(a,5f10.2)') 'child spacing  ',dx_child, dy_child, dz_child,lower_left_coord_x,lower_left_coord_y
565       ENDIF
566!
567!--    reset values for every child
568       tot_particle_count = 0 
569       nr_part  = 0           
570       part_adr = 0
571       pindex   = 1
572
573       buf_shape(1) = max_nr_particle_in_rma_win
574       CALL C_F_POINTER( buf_ptr(m), particle_in_win , buf_shape )
575
576       DO  ip = 1, children(child_id)%inter_npes
577
578          ape => children(child_id)%pes(ip)
579
580          nr_part_col   = 0 
581         
582          DO  ij = 1, ape%nrele
583             
584!
585!--          Inside the PMC adressing of 3d arrays starts with 1
586             i = ape%locind(ij)%i + nxl - nbgp - 1
587             j = ape%locind(ij)%j + nys - nbgp - 1
588             nr_part_col = 0 ! Number of particles to transfer per column
589             part_adr(j,i) = pindex
590             
591             DO  k = nzb + 1, nzt
592                number_of_particles = prt_count(k,j,i)
593               
594                IF ( number_of_particles <= 0 )  CYCLE
595               
596                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
597
598                ! Select particles within boundary area
599
600                DO n = 1, number_of_particles
601                   x = particles(n)%x
602                   y = particles(n)%y
603                   z = particles(n)%z
604!
605!--                check if the particle is located in the fine grid area
606                   active_particle = ((x > lx_coord .AND. x < rx_coord) .AND.  & 
607                                      (y > sy_coord .AND. y < ny_coord) .AND.  &
608                                      (z > 0.000000001 .AND. z < uz_coord))
609                   IF ( active_particle .AND. particles(n)%particle_mask )  THEN
610                     
611                      particle_in_win(pindex) = particles(n)
612!
613!--                   Change particle positions and origin relative to global origin
614                      particle_in_win(pindex)%x = particle_in_win(pindex)%x + lower_left_coord_x
615                      particle_in_win(pindex)%y = particle_in_win(pindex)%y + lower_left_coord_y
616                      particle_in_win(pindex)%origin_x = particle_in_win(pindex)%origin_x + lower_left_coord_x
617                      particle_in_win(pindex)%origin_y = particle_in_win(pindex)%origin_y + lower_left_coord_y
618
619                      tot_particle_count = tot_particle_count + 1
620                      nr_part_col        = nr_part_col + 1
621                      pindex             = pindex + 1
622                      IF ( pindex > max_nr_particle_in_rma_win ) THEN
623                         WRITE(9,*) 'RMA window too small on parent ',pindex, max_nr_particle_in_rma_win
624                         message_string = 'RMA window too small on parent'
625                         CALL message( 'pmci_create_child_arrays', 'PA0481', 3, 2, 0, 6, 0 )   ! PA number has to be adjusted
626                     ENDIF
627                   END IF
628                ENDDO
629             ENDDO
630             nr_part(j,i) = nr_part_col
631          ENDDO
632       ENDDO
633
634       CALL pmc_s_fillbuffer( child_id, particle_transfer = .TRUE. )
635    ENDDO
636
637    lfirst = .FALSE.
638
639#endif
640 END SUBROUTINE pmcp_p_fill_particle_win
641
642 
643!------------------------------------------------------------------------------!
644! Description:
645! ------------
646!> parent routine:
647!> delete particles from the MPI window
648!------------------------------------------------------------------------------!
649 SUBROUTINE pmcp_p_empty_particle_win
650
651    IMPLICIT NONE
652
653    INTEGER(iwp) ::  child_id           !< model id of the child
654    INTEGER(iwp) ::  ip                 !< loop index (child PEs)
655    INTEGER(iwp) ::  m                  !< loop index (number of childs)
656
657    INTEGER(iwp),DIMENSION(1) ::  buf_shape !<
658
659#if defined( __parallel )
660    DO  m = 1, get_number_of_childs()
661
662       child_id = get_childid(m)
663
664       buf_shape(1) = max_nr_particle_in_rma_win
665       CALL C_F_POINTER( buf_ptr(m), particle_in_win , buf_shape )
666
667!
668!--    In some cells of the coarse grid, there are contributions from more than one child process
669!--    Therfore p_copy_particle_to_org_grid is done for one child process per call
670
671       DO ip = 1, pmc_s_get_child_npes( child_id )
672          nr_part  = 0
673          part_adr = 0
674
675          CALL pmc_s_getdata_from_buffer( child_id, particle_transfer = .TRUE., child_process_nr = ip )
676
677          CALL p_copy_particle_to_org_grid( m, child_id )
678       ENDDO
679
680    ENDDO
681
682#endif
683 END SUBROUTINE pmcp_p_empty_particle_win
684
685
686!------------------------------------------------------------------------------!
687! Description:
688! ------------
689!> parent routine:
690!> After the transfer mark all parent particles that are still inside on of the
691!> child areas for deletion.
692!------------------------------------------------------------------------------!
693 SUBROUTINE pmcp_p_delete_particles_in_fine_grid_area
694
695    IMPLICIT NONE
696
697    LOGICAL ::  to_delete !< particles outside of model domain are marked as to_delete
698   
699    INTEGER(iwp) ::  i !< loop index (x grid)
700    INTEGER(iwp) ::  j !< loop index (y grid)
701    INTEGER(iwp) ::  k !< loop index (z grid)
702    INTEGER(iwp) ::  m !< loop index (number of particles)
703    INTEGER(iwp) ::  n !< loop index (number of childs)
704   
705    REAL(wp) ::  dx_child   !< child grid spacing
706    REAL(wp) ::  dy_child   !< child grid spacing
707    REAL(wp) ::  dz_child   !< child grid spacing
708    REAL(wp) ::  ny_coord   !< north coordinate of child grid
709    REAL(wp) ::  ny_coord_b !< north coordinate of child grid boundary
710    REAL(wp) ::  lx_coord   !< left coordinate of child grid
711    REAL(wp) ::  lx_coord_b !< left coordinate of child grid boundary
712    REAL(wp) ::  rx_coord   !< right coordinate of child grid
713    REAL(wp) ::  rx_coord_b !< right coordinate of child grid boundary
714    REAL(wp) ::  sy_coord   !< south coordinate of child grid
715    REAL(wp) ::  sy_coord_b !< south coordinate of child grid boundary
716    REAL(wp) ::  uz_coord   !< upper coordinate of child grid
717    REAL(wp) ::  uz_coord_b !< upper coordinate of child grid boundary
718    REAL(wp) ::  x          !< particle position
719    REAL(wp) ::  y          !< particle position
720    REAL(wp) ::  z          !< particle position
721   
722#if defined( __parallel )
723    DO  m = 1, get_number_of_childs()
724       CALL get_child_edges( m, lx_coord, lx_coord_b, rx_coord, rx_coord_b,    &
725                                sy_coord, sy_coord_b, ny_coord, ny_coord_b,    &
726                                uz_coord, uz_coord_b )
727
728
729       CALL get_child_gridspacing( m, dx_child, dy_child, dz_child ) 
730
731       DO i = nxl, nxr
732          DO j = nys, nyn
733             DO k = nzb, nzt
734                number_of_particles = prt_count(k,j,i)
735
736                IF ( number_of_particles == 0 ) CYCLE
737
738                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
739
740                DO n = 1, number_of_particles
741                   x = particles(n)%x
742                   y = particles(n)%y
743                   z = particles(n)%z
744
745                   to_delete = ((x > lx_coord .AND. x < rx_coord) .AND.        &
746                                (y > sy_coord .AND. y < ny_coord) .AND.        &
747                                (z > 0.000000001 .AND. z < uz_coord))
748
749                   IF ( to_delete ) THEN
750                      particles(n)%particle_mask = .FALSE.
751                   ENDIF
752                ENDDO
753             ENDDO
754          ENDDO
755       ENDDO
756
757    ENDDO
758
759#endif
760 END SUBROUTINE pmcp_p_delete_particles_in_fine_grid_area
761
762
763!------------------------------------------------------------------------------!
764! Description:
765! ------------
766!> general routine:
767!> print the total number of of the current model and its child models into a file
768!------------------------------------------------------------------------------!
769 SUBROUTINE pmcp_g_print_number_of_particles (my_time,local_nr_particles)
770 
771    USE pegrid,                                                                &
772        ONLY: myid
773 
774    IMPLICIT NONE
775
776    INTEGER(iwp),INTENT(IN) ::  local_nr_particles !<
777   
778    REAL(wp),INTENT(IN) ::  my_time !<
779     
780    LOGICAL, SAVE ::  is_file_open=.FALSE. !<
781   
782    INTEGER(iwp) ::  child_id           !<
783    INTEGER(iwp) ::  child_nr_particles !< total number of particles in all child models
784    INTEGER(iwp) ::  ierr               !< error code
785    INTEGER(iwp) ::  m                  !< loop index (number of childs)
786   
787    CHARACTER(LEN=16) ::  fname !< filename
788   
789    INTEGER(iwp),DIMENSION(2) ::  ivalr !< integer value to be received
790    INTEGER(iwp),DIMENSION(2) ::  ivals !< integer value to be send
791   
792#if defined( __parallel )
793    child_nr_particles = 0
794    IF ( myid == 0 )  THEN
795       IF ( cpl_id > 1 )  THEN
796          ivals(1) = local_nr_particles
797          CALL pmc_send_to_parent( ivals, 1, 0, 400, ierr )
798       ENDIF
799       DO  m = 1, SIZE( pmc_parent_for_child ) - 1
800
801          child_id = pmc_parent_for_child(m)
802          CALL pmc_recv_from_child( child_id, ivalr, 1, 0, 400, ierr )
803          child_nr_particles = child_nr_particles + ivalr(1)
804       ENDDO
805
806       IF ( SIZE( pmc_parent_for_child ) > 1 ) THEN
807          IF ( .NOT. is_file_open )  THEN !kk muss noch auf file_open umgestellt werden
808             WRITE(fname,'(a,i2.2)') 'nr_particles_',cpl_id
809             OPEN (333,file = fname)
810             is_file_open = .true.
811          ENDIF
812          WRITE(333,'(f12.2,3i10)') my_time,local_nr_particles + child_nr_particles,local_nr_particles,child_nr_particles
813       ENDIF
814    ENDIF
815
816#endif
817 END SUBROUTINE pmcp_g_print_number_of_particles
818
819
820!------------------------------------------------------------------------------!
821!------------------------------------------------------------------------------!
822! Private subroutines
823!------------------------------------------------------------------------------!
824!------------------------------------------------------------------------------!
825
826!------------------------------------------------------------------------------!
827! Description:
828! ------------
829!> child routine
830!> update the size of the local buffer (coarse_particles)
831!------------------------------------------------------------------------------!
832 SUBROUTINE check_and_alloc_coarse_particle (ic,jc,nr,with_copy)
833   
834    IMPLICIT NONE
835   
836    INTEGER(iwp),INTENT(IN) ::  ic !< coarse x grid index
837    INTEGER(iwp),INTENT(IN) ::  jc !< coarse y grid index
838    INTEGER(iwp),INTENT(IN) ::  nr !< number of particles to be transferred/stored in local buffer
839   
840    LOGICAL,INTENT(IN),OPTIONAL ::  with_copy !< copy particles in buffer? or reallocate empty buffer
841
842    LOGICAL :: with_copy_lo !< local variable of with copy
843   
844    INTEGER(iwp) ::  new_size !< new size of the local buffer
845    INTEGER(iwp) ::  old_size !< old size of the local buffer
846   
847    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  tmp_particles_d !<
848
849#if defined( __parallel )
850    with_copy_lo = .FALSE.
851    IF ( PRESENT( with_copy ) ) with_copy_lo = with_copy
852
853    IF ( .NOT. ALLOCATED( coarse_particles(jc,ic)%parent_particles ) ) THEN
854       new_size = MAX( nr, Min_particles_per_column )
855       ALLOCATE( coarse_particles(jc,ic)%parent_particles(new_size) )
856    ELSEIF ( nr > SIZE( coarse_particles(jc,ic)%parent_particles ) ) THEN
857
858       old_size = SIZE( coarse_particles(jc,ic)%parent_particles )
859       new_size = old_size * ( 1.0_wp + alloc_factor / 100.0_wp )
860       new_size = MAX( nr, new_size, old_size + Min_particles_per_column )
861
862!
863!--    Copy existing particles to new particle buffer
864       IF ( with_copy_lo ) THEN
865          ALLOCATE( tmp_particles_d(old_size) )
866          tmp_particles_d(1:old_size) = coarse_particles(jc,ic)%parent_particles
867
868          DEALLOCATE( coarse_particles(jc,ic)%parent_particles )
869          ALLOCATE( coarse_particles(jc,ic)%parent_particles(new_size) )
870
871          coarse_particles(jc,ic)%parent_particles(1:old_size)          = tmp_particles_d(1:old_size)
872          coarse_particles(jc,ic)%parent_particles(old_size+1:new_size) = zero_particle
873
874          DEALLOCATE( tmp_particles_d )
875!
876!--    allocate or reallocate an empty buffer
877       ELSE
878          DEALLOCATE( coarse_particles(jc,ic)%parent_particles )
879          ALLOCATE( coarse_particles(jc,ic)%parent_particles(new_size) )
880       ENDIF
881    ENDIF
882
883#endif
884 END SUBROUTINE check_and_alloc_coarse_particle
885
886
887!------------------------------------------------------------------------------!
888! Description:
889! ------------
890!> child routine:
891!> copy/sort particles out of the local buffer into the respective grid boxes
892!------------------------------------------------------------------------------!
893 SUBROUTINE c_copy_particle_to_child_grid
894 
895    IMPLICIT NONE
896 
897    INTEGER(iwp) ::  ic  !< coarse x grid index
898    INTEGER(iwp) ::  icl !< left boundary in coarse(parent) index space
899    INTEGER(iwp) ::  icr !< right boundary in coarse(parent) index space
900    INTEGER(iwp) ::  ip  !< x grid index
901    INTEGER(iwp) ::  jc  !< coarse y grid index
902    INTEGER(iwp) ::  jcn !< north boundary in coarse(parent) index space
903    INTEGER(iwp) ::  jcs !< south boundary in coarse(parent) index space
904    INTEGER(iwp) ::  jp  !< y grid index
905    INTEGER(iwp) ::  kp  !< z grid index
906    INTEGER(iwp) ::  n   !< loop index (number of particles)
907    INTEGER(iwp) ::  nr  !< short variable for name number or particles
908   
909    REAL(wp) ::  xc  !< child x coordinate
910    REAL(wp) ::  xoc !< child x origin
911    REAL(wp) ::  yc  !< child y coordinate
912    REAL(wp) ::  yoc !< child y origin
913    REAL(wp) ::  zc  !< child z coordinate
914
915#if defined( __parallel )
916!
917!-- Child domain boundaries in the parent index space
918    icl = coarse_bound(1)
919    icr = coarse_bound(2)
920    jcs = coarse_bound(3)
921    jcn = coarse_bound(4)
922
923    DO ic = icl, icr
924       DO jc = jcs, jcn
925          nr = coarse_particles(jc,ic)%nr_particle
926
927          IF ( nr > 0 ) THEN
928             DO n = 1, nr
929                xc =  coarse_particles(jc,ic)%parent_particles(n)%x-lower_left_coord_x
930                yc =  coarse_particles(jc,ic)%parent_particles(n)%y-lower_left_coord_y
931                zc =  coarse_particles(jc,ic)%parent_particles(n)%z
932                xoc = coarse_particles(jc,ic)%parent_particles(n)%origin_x-lower_left_coord_x
933                yoc = coarse_particles(jc,ic)%parent_particles(n)%origin_y-lower_left_coord_y
934                ip = xc / dx
935                jp = yc / dy
936                kp = nzt
937                DO WHILE ( zw(kp-1) > zc .AND. kp > nzb + 1 )         ! kk search loop has to be optimzed !!!
938                   kp = kp - 1
939                ENDDO 
940
941                IF ( ip >= nxl .AND. ip <= nxr .AND. jp >= nys .AND. jp <= nyn ) THEN
942                   prt_count(kp,jp,ip) = prt_count(kp,jp,ip) + 1
943                   IF ( prt_count(kp,jp,ip) > SIZE( grid_particles(kp,jp,ip)%particles ) ) THEN
944                      CALL realloc_particles_array( ip, jp, kp )
945                   ENDIF
946                   coarse_particles(jc,ic)%parent_particles(n)%x = xc                   ! Adjust coordinates to child grid
947                   coarse_particles(jc,ic)%parent_particles(n)%y = yc
948                   coarse_particles(jc,ic)%parent_particles(n)%origin_x = xoc           ! Adjust origins to child grid
949                   coarse_particles(jc,ic)%parent_particles(n)%origin_y = yoc
950                   grid_particles(kp,jp,ip)%particles(prt_count(kp,jp,ip)) = coarse_particles(jc,ic)%parent_particles(n)
951                ENDIF
952             ENDDO
953          ENDIF
954       ENDDO
955    ENDDO
956
957#endif
958 END SUBROUTINE c_copy_particle_to_child_grid
959
960
961!------------------------------------------------------------------------------!
962! Description:
963! ------------
964!> child routine:
965!> copy particles which left the model area into the local buffer
966!------------------------------------------------------------------------------!
967 SUBROUTINE c_copy_particle_to_coarse_grid
968 
969    IMPLICIT NONE
970   
971    LOGICAL ::  boundary_particle !<
972   
973    INTEGER(iwp) ::  i    !< loop index (x grid)
974    INTEGER(iwp) ::  ic   !< loop index (coarse x grid)
975    INTEGER(iwp) ::  icl  !< left boundary in coarse(parent) index space
976    INTEGER(iwp) ::  icr  !< left boundary in coarse(parent) index space
977    INTEGER(iwp) ::  ierr !< error code
978    INTEGER(iwp) ::  j    !< loop index (y grid)
979    INTEGER(iwp) ::  jc   !< loop index (coarse y grid)
980    INTEGER(iwp) ::  jcs  !< south boundary in coarse(parent) index space
981    INTEGER(iwp) ::  jcn  !< north boundary in coarse(parent) index space
982    INTEGER(iwp) ::  k    !< loop index (z grid)
983    INTEGER(iwp) ::  n    !< loop index (number of particles)
984   
985    REAL(iwp) ::  x       !< x coordinate
986    REAL(iwp) ::  xo      !< x origin
987    REAL(iwp) ::  x_left  !< absolute left boundary
988    REAL(iwp) ::  x_right !< absolute right boundary
989    REAL(iwp) ::  y       !< left boundary in coarse(parent) index space
990    REAL(iwp) ::  yo      !< y origin
991    REAL(iwp) ::  y_north !< absolute north boundary
992    REAL(iwp) ::  y_south !< absoulte south boundary
993    REAL(iwp) ::  z       !< z coordinate
994
995#if defined( __parallel )
996!
997!-- Child domain boundaries in the parent index space
998
999    icl = coarse_bound(1)
1000    icr = coarse_bound(2)
1001    jcs = coarse_bound(3)
1002    jcn = coarse_bound(4)
1003
1004!
1005!-- absolute coordinates
1006    x_left  = coord_x(0)
1007    x_right = coord_x(nx) + dx
1008    y_south = coord_y(0)
1009    y_north = coord_y(ny) + dy
1010
1011!   Clear Particle Buffer
1012
1013    DO ic = icl, icr
1014       DO jc = jcs, jcn
1015          coarse_particles(jc,ic)%nr_particle = 0
1016       ENDDO
1017    ENDDO
1018
1019!
1020!-- Determine particles which leave the inner area in east or west dirextion
1021!-- Compute only first (nxl) and last (nxr) loop iterration.
1022    DO  i = nxl, nxr
1023       DO  j = nys, nyn
1024          DO  k = nzb + 1, nzt
1025             number_of_particles = prt_count(k,j,i)
1026             IF ( number_of_particles <= 0 )  CYCLE
1027             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
1028             DO  n = 1, number_of_particles
1029                IF ( particles(n)%particle_mask )  THEN
1030                   x =  particles(n)%x+ lower_left_coord_x 
1031                   y =  particles(n)%y+ lower_left_coord_y 
1032                   xo = particles(n)%origin_x + lower_left_coord_x
1033                   yo = particles(n)%origin_y + lower_left_coord_y
1034                   z =  particles(n)%z
1035                   
1036                   boundary_particle = .FALSE.
1037                   boundary_particle = boundary_particle .OR. (x < x_left  .OR. x > x_right)
1038                   boundary_particle = boundary_particle .OR. (y < y_south .OR. y > y_north)
1039                   boundary_particle = boundary_particle .OR. (z > zw(nzt))
1040
1041                   IF ( boundary_particle ) THEN                     
1042                      ic = x / cg%dx                     !TODO anpassen auf Mehrfachnesting
1043                      jc = y / cg%dy
1044
1045                      IF ( ic >= icl .AND. ic <= icr .AND. jc >= jcs .AND. jc <= jcn ) THEN
1046                         coarse_particles(jc,ic)%nr_particle = coarse_particles(jc,ic)%nr_particle + 1
1047                         CALL check_and_alloc_coarse_particle( ic, jc, coarse_particles(jc,ic)%nr_particle, with_copy=.TRUE. )
1048
1049                         coarse_particles(jc,ic)%parent_particles(coarse_particles(jc,ic)%nr_particle)   = particles(n)
1050                         coarse_particles(jc,ic)%parent_particles(coarse_particles(jc,ic)%nr_particle)%x = x   !adapt to global coordinates
1051                         coarse_particles(jc,ic)%parent_particles(coarse_particles(jc,ic)%nr_particle)%y = y
1052                         coarse_particles(jc,ic)%parent_particles(coarse_particles(jc,ic)%nr_particle)%origin_x = xo
1053                         coarse_particles(jc,ic)%parent_particles(coarse_particles(jc,ic)%nr_particle)%origin_y = yo
1054!--                      Mark particle as deleted after copying it to the transfer buffer
1055                         grid_particles(k,j,i)%particles(n)%particle_mask = .FALSE.
1056                      ELSE
1057                         WRITE(9,'(a,10i6)') 'This should not happen ',i,j,k,ic,jc,icl,icr,jcs,jcn
1058                         CALL MPI_Abort( MPI_COMM_WORLD, 9999, ierr )
1059                      ENDIF
1060                   ENDIF
1061                ENDIF
1062             ENDDO
1063          ENDDO
1064       ENDDO
1065    ENDDO
1066
1067!
1068!- Pack particles (eliminate those marked for deletion),
1069!- determine new number of particles
1070   CALL lpm_sort_in_subboxes
1071
1072#endif
1073 END SUBROUTINE c_copy_particle_to_coarse_grid
1074
1075
1076!------------------------------------------------------------------------------!
1077! Description:
1078! ------------
1079!> parent routine:
1080!> copy/sort particles from the MPI window into the respective grid boxes
1081!------------------------------------------------------------------------------!
1082 SUBROUTINE p_copy_particle_to_org_grid( m, child_id )
1083
1084    IMPLICIT NONE
1085
1086    INTEGER(iwp),INTENT(IN) ::  child_id !<
1087    INTEGER(iwp),INTENT(IN) ::  m        !<
1088
1089    INTEGER(iwp) ::  i      !< loop index (x grid)
1090    INTEGER(iwp) ::  j      !< loop index (y grid)
1091    INTEGER(iwp) ::  k      !< loop index (z grid)
1092    INTEGER(iwp) ::  n      !< loop index (nr part)
1093    INTEGER(iwp) ::  nr     !< short variable name for nr_part
1094    INTEGER(iwp) ::  pindex !< short variable name part_adr
1095   
1096    REAL(iwp) ::  x  !< x coordinate
1097    REAL(iwp) ::  xo !< x origin
1098    REAL(iwp) ::  y  !< y coordinate
1099    REAL(iwp) ::  yo !< y origin
1100    REAL(iwp) ::  z  !< z coordinate
1101   
1102    INTEGER(iwp),DIMENSION(1) ::  buf_shape !<
1103
1104#if defined( __parallel )
1105    buf_shape(1) = max_nr_particle_in_rma_win
1106    CALL C_F_POINTER( buf_ptr(m), particle_in_win , buf_shape )
1107
1108    DO i = nxl, nxr
1109       DO j = nys, nyn
1110          nr = nr_part(j,i)
1111          IF ( nr > 0 ) THEN
1112             pindex = part_adr(j,i)
1113             DO n = 1, nr
1114                x = particle_in_win(pindex)%x-lower_left_coord_x
1115                y = particle_in_win(pindex)%y-lower_left_coord_y
1116                z = particle_in_win(pindex)%z
1117                xo = particle_in_win(pindex)%origin_x-lower_left_coord_x
1118                yo = particle_in_win(pindex)%origin_y-lower_left_coord_y
1119                k = nzt + 1
1120                DO WHILE ( zw(k-1) > z .AND. k > nzb + 1 )                               ! kk search loop has to be optimzed !!!
1121                   k = k - 1
1122                END DO
1123
1124                prt_count(k,j,i) = prt_count(k,j,i) + 1
1125                IF ( prt_count(k,j,i) > SIZE( grid_particles(k,j,i)%particles ) ) THEN
1126                   CALL realloc_particles_array( i, j, k )
1127                ENDIF
1128                grid_particles(k,j,i)%particles(prt_count(k,j,i)) = particle_in_win(pindex)
1129               
1130!
1131!--             Update particle positions and origins relative to parent domain
1132                grid_particles(k,j,i)%particles(prt_count(k,j,i))%x = x
1133                grid_particles(k,j,i)%particles(prt_count(k,j,i))%y = y
1134                grid_particles(k,j,i)%particles(prt_count(k,j,i))%origin_x = xo
1135                grid_particles(k,j,i)%particles(prt_count(k,j,i))%origin_y = yo
1136                pindex = pindex + 1
1137             ENDDO
1138          ENDIF
1139       ENDDO
1140    ENDDO
1141
1142#endif
1143 END SUBROUTINE p_copy_particle_to_org_grid
1144
1145
1146END MODULE pmc_particle_interface
Note: See TracBrowser for help on using the repository browser.