source: palm/trunk/SOURCE/pmc_parent_mod.f90 @ 4339

Last change on this file since 4339 was 4246, checked in by pavelkrc, 4 years ago

Convert CRLF line endings to LF

  • Property svn:keywords set to Id
File size: 34.4 KB
Line 
1 MODULE pmc_parent
2
3!------------------------------------------------------------------------------!
4! This file is part of the PALM model system.
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-2019 Leibniz Universitaet Hannover
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! ------------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: pmc_parent_mod.f90 4246 2019-09-30 09:27:52Z suehring $
28!
29!
30! 4213 2019-09-02 14:25:56Z suehring
31! Allocate array for index_list_2d also for zero-size arrays, in order to 
32! avoid errors when array bound checks are enabled
33!
34! 4212 2019-09-02 14:23:05Z suehring
35! Corrected "Former revisions" section
36!
37! 3962 2019-05-08 19:40:33Z suehring
38! Bugfixes in initial settings of child and parent communication patterns.
39!
40! 3655 2019-01-07 16:51:22Z knoop
41! explicit kind settings
42!
43! 1762 2016-02-25 12:31:13Z hellstea
44! Initial revision by K. Ketelsen
45!
46! Description:
47! ------------
48!> Parent part of Palm Model Coupler
49!------------------------------------------------------------------------------!
50
51#if defined( __parallel )
52    USE, INTRINSIC ::  ISO_C_BINDING
53
54#if !defined( __mpifh )
55    USE MPI
56#endif
57    USE kinds
58    USE pmc_general,                                                           &
59        ONLY: arraydef, childdef, da_namedef, da_namelen, pedef,               &
60              pmc_g_setname, pmc_max_array, pmc_max_models, pmc_sort
61
62    USE pmc_handle_communicator,                                               &
63        ONLY: m_model_comm,m_model_rank,m_model_npes, m_to_child_comm,         &
64              m_world_rank, pmc_parent_for_child
65
66    USE pmc_mpi_wrapper,                                                       &
67        ONLY: pmc_alloc_mem, pmc_bcast, pmc_time
68
69   IMPLICIT NONE
70
71#if defined( __mpifh )
72   INCLUDE "mpif.h"
73#endif
74
75   PRIVATE
76   SAVE
77
78   TYPE childindexdef
79      INTEGER                              ::  nrpoints       !<
80      INTEGER, DIMENSION(:,:), ALLOCATABLE ::  index_list_2d  !<
81   END TYPE childindexdef
82
83   TYPE(childdef), DIMENSION(pmc_max_models),PUBLIC   ::  children     !<
84   TYPE(childindexdef), DIMENSION(pmc_max_models)     ::  indchildren  !<
85
86   INTEGER ::  next_array_in_list = 0  !<
87
88
89   PUBLIC pmc_parent_for_child
90
91
92   INTERFACE pmc_parentinit
93      MODULE PROCEDURE  pmc_parentinit
94   END INTERFACE pmc_parentinit
95
96    INTERFACE pmc_s_set_2d_index_list
97        MODULE PROCEDURE pmc_s_set_2d_index_list
98    END INTERFACE pmc_s_set_2d_index_list
99
100    INTERFACE pmc_s_clear_next_array_list
101        MODULE PROCEDURE pmc_s_clear_next_array_list
102    END INTERFACE pmc_s_clear_next_array_list
103
104    INTERFACE pmc_s_getnextarray
105        MODULE PROCEDURE pmc_s_getnextarray
106    END INTERFACE pmc_s_getnextarray
107
108    INTERFACE pmc_s_set_dataarray
109        MODULE PROCEDURE pmc_s_set_dataarray_2d
110        MODULE PROCEDURE pmc_s_set_dataarray_3d
111        MODULE PROCEDURE pmc_s_set_dataarray_ip2d
112    END INTERFACE pmc_s_set_dataarray
113
114    INTERFACE pmc_s_setind_and_allocmem
115        MODULE PROCEDURE pmc_s_setind_and_allocmem
116    END INTERFACE pmc_s_setind_and_allocmem
117
118    INTERFACE pmc_s_fillbuffer
119        MODULE PROCEDURE pmc_s_fillbuffer
120    END INTERFACE pmc_s_fillbuffer
121
122    INTERFACE pmc_s_getdata_from_buffer
123        MODULE PROCEDURE pmc_s_getdata_from_buffer
124    END INTERFACE pmc_s_getdata_from_buffer
125
126    INTERFACE pmc_s_set_active_data_array
127        MODULE PROCEDURE pmc_s_set_active_data_array
128    END INTERFACE pmc_s_set_active_data_array
129
130    INTERFACE pmc_s_get_child_npes
131        MODULE PROCEDURE pmc_s_get_child_npes
132    END INTERFACE pmc_s_get_child_npes
133
134    PUBLIC pmc_parentinit, pmc_s_clear_next_array_list, pmc_s_fillbuffer,      &
135           pmc_s_getdata_from_buffer, pmc_s_getnextarray,                      &
136           pmc_s_setind_and_allocmem, pmc_s_set_active_data_array,             &
137           pmc_s_set_dataarray, pmc_s_set_2d_index_list,                       &
138           pmc_s_get_child_npes
139
140 CONTAINS
141
142
143 SUBROUTINE pmc_parentinit
144
145    IMPLICIT NONE
146
147    INTEGER(iwp) ::  childid   !<
148    INTEGER(iwp) ::  i         !<
149    INTEGER(iwp) ::  j         !<
150    INTEGER(iwp) ::  istat     !<
151
152    DO  i = 1, SIZE( pmc_parent_for_child )-1
153
154       childid = pmc_parent_for_child( i )
155
156       children(childid)%model_comm = m_model_comm
157       children(childid)%inter_comm = m_to_child_comm(childid)
158
159!
160!--    Get rank and size
161       CALL MPI_COMM_RANK( children(childid)%model_comm,                       &
162                           children(childid)%model_rank, istat )
163       CALL MPI_COMM_SIZE( children(childid)%model_comm,                       &
164                           children(childid)%model_npes, istat )
165       CALL MPI_COMM_REMOTE_SIZE( children(childid)%inter_comm,                &
166                                  children(childid)%inter_npes, istat )
167!
168!--    Intra communicator is used for MPI_GET
169       CALL MPI_INTERCOMM_MERGE( children(childid)%inter_comm, .FALSE.,        &
170                                 children(childid)%intra_comm, istat )
171       CALL MPI_COMM_RANK( children(childid)%intra_comm,                       &
172                           children(childid)%intra_rank, istat )
173
174       ALLOCATE( children(childid)%pes(children(childid)%inter_npes))
175!
176!--    Allocate array of TYPE arraydef for all child PEs to store information
177!--    of the transfer array
178       DO  j = 1, children(childid)%inter_npes
179         ALLOCATE( children(childid)%pes(j)%array_list(pmc_max_array) )
180       ENDDO
181
182       CALL get_da_names_from_child (childid)
183
184    ENDDO
185
186 END SUBROUTINE pmc_parentinit
187
188
189
190 SUBROUTINE pmc_s_set_2d_index_list( childid, index_list )
191
192     IMPLICIT NONE
193
194     INTEGER(iwp), INTENT(IN)                    :: childid     !<
195     INTEGER(iwp), DIMENSION(:,:), INTENT(INOUT) :: index_list  !<
196
197     INTEGER(iwp) ::  ian    !<
198     INTEGER(iwp) ::  ie     !<
199     INTEGER(iwp) ::  ip     !<
200     INTEGER(iwp) ::  is     !<
201     INTEGER(iwp) ::  istat  !<
202
203
204     IF ( m_model_rank == 0 )  THEN
205!
206!--     Sort to ascending parent process order
207        CALL pmc_sort( index_list, 6 )
208        is = 1
209        DO  ip = 0, m_model_npes-1
210!
211!--        Split into parent processes
212           ie = is - 1
213!
214!--        There may be no entry for this process
215           IF ( is <= SIZE( index_list,2 )  .AND.  ie >= 0 )  THEN
216              DO WHILE ( index_list(6,ie+1 ) == ip )
217                 ie = ie + 1
218                 IF ( ie == SIZE( index_list,2 ) )  EXIT
219              ENDDO
220              ian = ie - is + 1
221           ELSE
222              is  = -1
223              ie  = -2
224              ian =  0
225           ENDIF
226!
227!--        Send data to other parent processes
228           IF ( ip == 0 )  THEN
229              indchildren(childid)%nrpoints = ian
230!
231!--           Allocate array for index_list_2d. Note, the array will also be
232!--           allocated in case ian=0, in order to avoid errors when
233!--           array bounds are checked.
234              ALLOCATE( indchildren(childid)%index_list_2d(6,1:ian) )
235              IF ( ian > 0)  THEN
236                  indchildren(childid)%index_list_2d(:,1:ian) =                &
237                                                             index_list(:,is:ie)
238              ENDIF
239           ELSE
240              CALL MPI_SEND( ian, 1, MPI_INTEGER, ip, 1000, m_model_comm,      &
241                             istat )
242              IF ( ian > 0)  THEN
243                  CALL MPI_SEND( index_list(1,is), 6*ian, MPI_INTEGER, ip,     &
244                                 1001, m_model_comm, istat )
245              ENDIF
246           ENDIF
247           is = ie + 1
248        ENDDO
249     ELSE
250        CALL MPI_RECV( indchildren(childid)%nrpoints, 1, MPI_INTEGER, 0, 1000, &
251                       m_model_comm, MPI_STATUS_IGNORE, istat )
252        ian = indchildren(childid)%nrpoints
253!
254!--     Allocate array for index_list_2d. Note, the array will also be
255!--     allocated in case ian=0, in order to avoid errors when
256!--     array bounds are checked.
257        ALLOCATE( indchildren(childid)%index_list_2d(6,1:ian) )
258        IF ( ian > 0 )  THEN
259           CALL MPI_RECV( indchildren(childid)%index_list_2d, 6*ian,           &
260                          MPI_INTEGER, 0, 1001, m_model_comm,                  &
261                          MPI_STATUS_IGNORE, istat)
262        ENDIF
263     ENDIF
264     CALL set_pe_index_list( children(childid),                                &
265                             indchildren(childid)%index_list_2d,               &
266                             indchildren(childid)%nrpoints )
267
268 END SUBROUTINE pmc_s_set_2d_index_list
269
270
271
272 SUBROUTINE pmc_s_clear_next_array_list
273
274    IMPLICIT NONE
275
276    next_array_in_list = 0
277
278 END SUBROUTINE pmc_s_clear_next_array_list
279
280
281
282 LOGICAL FUNCTION pmc_s_getnextarray( childid, myname )
283
284!
285!-- Althoug there are no linked lists any more in PMC, this call still looks like working with a list
286
287    CHARACTER(LEN=*), INTENT(OUT) ::  myname    !<
288    INTEGER(iwp), INTENT(IN)      ::  childid   !<
289
290    TYPE(arraydef), POINTER :: ar
291    TYPE(pedef), POINTER    :: ape
292
293    next_array_in_list = next_array_in_list + 1
294!
295!-- Array names are the same on all children processes, so take first
296!-- process to get the name
297    ape => children(childid)%pes(1)
298
299    IF ( next_array_in_list > ape%nr_arrays )  THEN
300!
301!--    All arrays are done
302       pmc_s_getnextarray = .FALSE.
303       RETURN
304    ENDIF
305
306    ar => ape%array_list(next_array_in_list)
307    myname = ar%name
308!
309!-- Return true if there is still an array in the list
310
311    pmc_s_getnextarray = .TRUE.
312
313 END FUNCTION pmc_s_getnextarray
314
315
316
317 SUBROUTINE pmc_s_set_dataarray_2d( childid, array, array_2 )
318
319    IMPLICIT NONE
320
321    INTEGER(iwp), INTENT(IN) ::  childid   !<
322
323    REAL(wp), INTENT(IN), DIMENSION(:,:), POINTER           ::  array    !<
324    REAL(wp), INTENT(IN), DIMENSION(:,:), POINTER, OPTIONAL ::  array_2  !<
325
326    INTEGER(iwp)               ::  nrdims      !<
327    INTEGER(iwp), DIMENSION(4) ::  dims        !<
328    TYPE(C_PTR)           ::  array_adr   !<
329    TYPE(C_PTR)           ::  second_adr  !<
330
331
332    dims      = 1
333    nrdims    = 2
334    dims(1)   = SIZE( array,1 )
335    dims(2)   = SIZE( array,2 )
336    array_adr = C_LOC( array )
337
338    IF ( PRESENT( array_2 ) )  THEN
339       second_adr = C_LOC(array_2)
340       CALL pmc_s_setarray( childid, nrdims, dims, array_adr,                  &
341                            second_adr = second_adr)
342    ELSE
343       CALL pmc_s_setarray( childid, nrdims, dims, array_adr )
344    ENDIF
345
346 END SUBROUTINE pmc_s_set_dataarray_2d
347
348 SUBROUTINE pmc_s_set_dataarray_ip2d( childid, array )
349
350    IMPLICIT NONE
351
352    INTEGER(iwp),INTENT(IN) ::  childid   !<
353
354    INTEGER(idp), INTENT(IN), DIMENSION(:,:), POINTER           ::  array    !<
355
356    INTEGER(iwp)               ::  nrdims      !<
357    INTEGER(iwp), DIMENSION(4) ::  dims        !<
358    TYPE(C_PTR)           ::  array_adr   !<
359
360
361    dims      = 1
362    nrdims    = 2
363    dims(1)   = SIZE( array,1 )
364    dims(2)   = SIZE( array,2 )
365    array_adr = C_LOC( array )
366
367    CALL pmc_s_setarray( childid, nrdims, dims, array_adr , dimkey=22)
368
369 END SUBROUTINE pmc_s_set_dataarray_ip2d
370
371
372 SUBROUTINE pmc_s_set_dataarray_3d( childid, array, nz_cl, nz, array_2 )
373
374    IMPLICIT NONE
375
376    INTEGER(iwp), INTENT(IN) ::  childid   !<
377    INTEGER(iwp), INTENT(IN) ::  nz        !<
378    INTEGER(iwp), INTENT(IN) ::  nz_cl     !<
379
380    REAL(wp), INTENT(IN), DIMENSION(:,:,:), POINTER           ::  array    !<
381    REAL(wp), INTENT(IN), DIMENSION(:,:,:), POINTER, OPTIONAL ::  array_2  !<
382
383    INTEGER(iwp)               ::  nrdims      !<
384    INTEGER(iwp), DIMENSION(4) ::  dims        !<
385    TYPE(C_PTR)           ::  array_adr   !<
386    TYPE(C_PTR)           ::  second_adr  !<
387
388    nrdims    = 3
389    dims(1)   = SIZE( array,1 )
390    dims(2)   = SIZE( array,2 )
391    dims(3)   = SIZE( array,3 )
392    dims(4)   = nz_cl+dims(1)-nz  ! works for first dimension 1:nz and 0:nz+1
393
394    array_adr = C_LOC(array)
395!
396!-- In PALM's pointer version, two indices have to be stored internally.
397!-- The active address of the data array is set in swap_timelevel.
398    IF ( PRESENT( array_2 ) )  THEN
399      second_adr = C_LOC( array_2 )
400      CALL pmc_s_setarray( childid, nrdims, dims, array_adr,                   &
401                           second_adr = second_adr)
402    ELSE
403       CALL pmc_s_setarray( childid, nrdims, dims, array_adr )
404    ENDIF
405
406 END SUBROUTINE pmc_s_set_dataarray_3d
407
408
409
410 SUBROUTINE pmc_s_setind_and_allocmem( childid )
411
412    USE control_parameters,                                                    &
413        ONLY:  message_string
414
415    IMPLICIT NONE
416
417!
418!-- Naming convention for appendices:   _pc  -> parent to child transfer
419!--                                     _cp  -> child to parent transfer
420!--                                     send -> parent to child transfer
421!--                                     recv -> child to parent transfer
422    INTEGER(iwp), INTENT(IN) ::  childid   !<
423
424    INTEGER(iwp)                   ::  arlen       !<
425    INTEGER(iwp)                   ::  i           !<
426    INTEGER(iwp)                   ::  ierr        !<
427    INTEGER(iwp)                   ::  j           !<
428    INTEGER(iwp)                   ::  lo_nr_arrays !< store number of arrays in  local variiab le
429    INTEGER(iwp)                   ::  myindex     !<
430    INTEGER(iwp)                   ::  total_npes  !< Total Number of PEs Parent and Child
431
432    INTEGER(idp)                   ::  bufsize  !< size of MPI data window
433    INTEGER(KIND=MPI_ADDRESS_KIND) ::  winsize  !<
434   
435    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  myindex_s
436    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  myindex_r
437
438    TYPE(C_PTR)             ::  base_ptr  !<
439    TYPE(pedef), POINTER    ::  ape       !<
440    TYPE(arraydef), POINTER ::  ar        !<
441
442    REAL(wp),DIMENSION(:), POINTER, SAVE ::  base_array_pc  !< base array for parent to child transfer
443    REAL(wp),DIMENSION(:), POINTER, SAVE ::  base_array_cp  !< base array for child to parent transfer
444
445    call MPI_COMM_SIZE (children(childid)%intra_comm, total_npes, ierr)
446!
447!-- Parent to child direction
448    myindex = 1
449    bufsize = 8
450!
451!-- All Child processes get the same number of arrays
452!-- Therfore the number of arrays form the first Child process can be used for Dimension.
453    lo_nr_arrays = children(childid)%pes(1)%nr_arrays
454
455    ALLOCATE( myindex_s(lo_nr_arrays,0:total_npes-1) )
456    ALLOCATE( myindex_r(lo_nr_arrays,0:total_npes-1) )
457
458    myindex_s = 0
459
460!
461!-- First stride: compute size and set index
462    DO  i = 1, children(childid)%inter_npes
463
464       ape => children(childid)%pes(i)
465
466       DO  j = 1, ape%nr_arrays
467
468          ar  => ape%array_list(j)
469          IF ( ar%nrdims == 2 )  THEN
470             arlen = ape%nrele
471          ELSEIF ( ar%nrdims == 3 )  THEN
472             arlen = ape%nrele * ar%a_dim(4)
473          ELSE
474             arlen = -1
475          ENDIF
476          ar%sendindex = myindex
477!
478!         Using intra communicator for MPU_Alltoall, the numbers of the child processes are after the paremt ones
479
480          myindex_s(j,i-1+children(childid)%model_npes) = myindex
481
482          myindex = myindex + arlen
483          bufsize = bufsize + arlen
484          ar%sendsize = arlen
485       ENDDO
486
487    ENDDO
488!
489!-- Using MPI_Alltoall to send indices from  Parent to Child
490!-- The data comming back from the child processes are ignored.
491
492    CALL MPI_ALLTOALL( myindex_s, lo_nr_arrays, MPI_INTEGER,                   &
493                       myindex_r, lo_nr_arrays, MPI_INTEGER,                   &
494                       children(childid)%intra_comm, ierr )
495
496!
497!-- Using MPI_Alltoall to receive indices from Child
498    myindex_s = 0
499    myindex_r = 0
500
501    CALL MPI_ALLTOALL( myindex_s, lo_nr_arrays, MPI_INTEGER,                   &
502                       myindex_r, lo_nr_arrays, MPI_INTEGER,                   &
503                       children(childid)%intra_comm, ierr )
504!
505!-- Create RMA (One Sided Communication) window for data buffer parent to
506!-- child transfer.
507!-- The buffer of MPI_GET (counterpart of transfer) can be PE-local, i.e.
508!-- it can but must not be part of the MPI RMA window. Only one RMA window is
509!-- required to prepare the data for
510!--                       parent -> child transfer on the parent side
511!-- and for
512!--                       child -> parent transfer on the child side
513    CALL pmc_alloc_mem( base_array_pc, bufsize )
514    children(childid)%totalbuffersize = bufsize * wp
515
516    winsize = bufsize * wp
517    CALL MPI_WIN_CREATE( base_array_pc, winsize, wp, MPI_INFO_NULL,            &
518                         children(childid)%intra_comm,                         &
519                         children(childid)%win_parent_child, ierr )
520!
521!-- Open window to set data
522    CALL MPI_WIN_FENCE( 0, children(childid)%win_parent_child, ierr )
523!
524!-- Second stride: set buffer pointer
525    DO  i = 1, children(childid)%inter_npes
526
527       ape => children(childid)%pes(i)
528
529       DO  j = 1, ape%nr_arrays
530
531          ar => ape%array_list(j)
532          ar%sendbuf = C_LOC( base_array_pc(ar%sendindex) )
533
534          IF ( ar%sendindex + ar%sendsize > bufsize )  THEN             
535             WRITE( message_string, '(a,i4,4i7,1x,a)' )                        &
536                    'parent buffer too small ',i,                              &
537                    ar%sendindex,ar%sendsize,ar%sendindex+ar%sendsize,         &
538                    bufsize,trim(ar%name)
539             CALL message( 'pmc_s_setind_and_allocmem', 'PA0429', 3, 2, 0, 6, 0 )
540          ENDIF
541       ENDDO
542    ENDDO
543!
544!-- Child to parent direction
545    bufsize = 8
546!
547!-- First stride: compute size and set index
548    DO  i = 1, children(childid)%inter_npes
549       ape => children(childid)%pes(i)
550       DO  j = 1, ape%nr_arrays
551          ar => ape%array_list(j)
552!
553!--       Receive index from child
554          IF ( ar%nrdims == 3 )  THEN
555             bufsize = MAX( bufsize,                                           &
556                            INT( ape%nrele * ar%a_dim(4), MPI_ADDRESS_KIND ) )
557          ELSE
558             bufsize = MAX( bufsize, INT( ape%nrele, MPI_ADDRESS_KIND ) )
559          ENDIF
560          ar%recvindex = myindex_r(j,i-1+children(childid)%model_npes)
561        ENDDO
562    ENDDO
563
564    DEALLOCATE( myindex_s )
565    DEALLOCATE( myindex_r )
566
567!
568!-- Create RMA (one sided communication, RMA = Remote Memory Access) data buffer.
569!-- The buffer for MPI_GET can be PE local, i.e. it can but must not be part of
570!-- the MPI RMA window
571    CALL pmc_alloc_mem( base_array_cp, bufsize, base_ptr )
572    children(childid)%totalbuffersize = bufsize * wp
573
574    CALL MPI_BARRIER( children(childid)%intra_comm, ierr )
575!
576!-- Second stride: set buffer pointer
577    DO  i = 1, children(childid)%inter_npes
578       ape => children(childid)%pes(i)
579       DO  j = 1, ape%nr_arrays
580          ar => ape%array_list(j)
581          ar%recvbuf = base_ptr
582       ENDDO
583    ENDDO
584
585 END SUBROUTINE pmc_s_setind_and_allocmem
586
587
588
589 SUBROUTINE pmc_s_fillbuffer( childid, waittime, particle_transfer )
590
591    IMPLICIT NONE
592
593    INTEGER(iwp), INTENT(IN)             ::  childid   !<
594
595    REAL(wp), INTENT(OUT), OPTIONAL ::  waittime  !<
596    LOGICAL, INTENT(IN), OPTIONAL   ::  particle_transfer  !<
597
598
599    INTEGER(iwp)               ::  ierr     !<
600    INTEGER(iwp)               ::  ij       !<
601    INTEGER(iwp)               ::  ip       !<
602    INTEGER(iwp)               ::  j        !<
603    INTEGER(iwp)               ::  myindex  !<
604   
605    LOGICAL                    ::  lo_ptrans
606
607    INTEGER(iwp), DIMENSION(1) ::  buf_shape
608
609    REAL(wp)                            ::  t1       !<
610    REAL(wp)                            ::  t2       !<
611    REAL(wp), POINTER, DIMENSION(:)     ::  buf      !<
612    REAL(wp), POINTER, DIMENSION(:,:)   ::  data_2d  !<
613    REAL(wp), POINTER, DIMENSION(:,:,:) ::  data_3d  !<
614    INTEGER(idp), POINTER, DIMENSION(:)     ::  ibuf      !<
615    INTEGER(idp), POINTER, DIMENSION(:,:)   ::  idata_2d  !<
616
617    TYPE(pedef), POINTER    ::  ape  !<
618    TYPE(arraydef), POINTER ::  ar   !<
619
620!
621!-- Synchronization of the model is done in pmci_synchronize.
622!-- Therefor the RMA window can be filled without
623!-- sychronization at this point and a barrier is not necessary.
624!-- Please note that waittime has to be set in pmc_s_fillbuffer AND
625!-- pmc_c_getbuffer
626    IF ( PRESENT( waittime) )  THEN
627      t1 = pmc_time()
628      CALL MPI_BARRIER( children(childid)%intra_comm, ierr )
629      t2 = pmc_time()
630      waittime = t2- t1
631    ENDIF
632
633    lo_ptrans = .FALSE.
634    IF ( PRESENT( particle_transfer))    lo_ptrans = particle_transfer
635
636    DO  ip = 1, children(childid)%inter_npes
637       ape => children(childid)%pes(ip)
638       DO  j = 1, ape%nr_arrays
639          ar => ape%array_list(j)
640          myindex = 1
641
642          IF ( ar%dimkey == 2 .AND. .NOT.lo_ptrans  )  THEN                            ! PALM 2D REAL*8 Array
643
644             buf_shape(1) = ape%nrele
645             CALL C_F_POINTER( ar%sendbuf, buf, buf_shape )
646             CALL C_F_POINTER( ar%data, data_2d, ar%a_dim(1:2) )
647             DO  ij = 1, ape%nrele
648                buf(myindex) = data_2d(ape%locind(ij)%j,ape%locind(ij)%i)
649                myindex = myindex + 1
650             ENDDO
651
652          ELSEIF ( ar%dimkey == 3  .AND. .NOT.lo_ptrans  )  THEN                       ! PALM 3D REAL*8 Array
653
654             buf_shape(1) = ape%nrele*ar%a_dim(4)
655             CALL C_F_POINTER( ar%sendbuf, buf, buf_shape )
656             CALL C_F_POINTER( ar%data, data_3d, ar%a_dim(1:3) )
657             DO  ij = 1, ape%nrele
658                buf(myindex:myindex+ar%a_dim(4)-1) =                            &
659                        data_3d(1:ar%a_dim(4),ape%locind(ij)%j,ape%locind(ij)%i)
660                myindex = myindex + ar%a_dim(4)
661             ENDDO
662          ELSEIF ( ar%dimkey == 22 .AND. lo_ptrans  )  THEN                           ! 2D INTEGER*8 Array for particle Transfer
663
664             buf_shape(1) = ape%nrele
665             CALL C_F_POINTER( ar%sendbuf, ibuf, buf_shape )
666             CALL C_F_POINTER( ar%data, idata_2d, ar%a_dim(1:2) )
667             DO  ij = 1, ape%nrele
668                ibuf(myindex) = idata_2d(ape%locind(ij)%j,ape%locind(ij)%i)
669                myindex = myindex + 1
670             ENDDO
671          ENDIF
672        ENDDO
673    ENDDO
674!
675!-- Buffer is filled
676    CALL MPI_BARRIER( children(childid)%intra_comm, ierr )
677
678 END SUBROUTINE pmc_s_fillbuffer
679
680
681
682 SUBROUTINE pmc_s_getdata_from_buffer( childid, waittime , particle_transfer, child_process_nr )
683
684    IMPLICIT NONE
685
686    INTEGER(iwp), INTENT(IN)             ::  childid      !<
687    REAL(wp), INTENT(OUT), OPTIONAL ::  waittime     !<
688    LOGICAL, INTENT(IN), OPTIONAL   ::  particle_transfer     !<
689    INTEGER(iwp), INTENT(IN), OPTIONAL   ::  child_process_nr      !<
690
691    INTEGER(iwp)                        ::  ierr          !<
692    INTEGER(iwp)                   ::  ij            !<
693    INTEGER(iwp)                   ::  ip            !<
694    INTEGER(iwp)                   ::  ip_start      !<
695    INTEGER(iwp)                   ::  ip_end        !<
696    INTEGER(iwp)                   ::  j             !<
697    INTEGER(iwp)                   ::  myindex       !<
698    INTEGER(iwp)                   ::  nr            !<
699    INTEGER(iwp)                   ::  target_pe     !<
700    INTEGER(KIND=MPI_ADDRESS_KIND) ::  target_disp   !<
701   
702    LOGICAL                        ::  lo_ptrans
703
704    INTEGER(iwp), DIMENSION(1)          ::  buf_shape     !<
705
706    REAL(wp)                                ::  t1       !<
707    REAL(wp)                                ::  t2       !<
708    REAL(wp), POINTER, DIMENSION(:)         ::  buf      !<
709    REAL(wp), POINTER, DIMENSION(:,:)       ::  data_2d  !<
710    REAL(wp), POINTER, DIMENSION(:,:,:)     ::  data_3d  !<
711    INTEGER(idp), POINTER, DIMENSION(:)     ::  ibuf      !<
712    INTEGER(idp), POINTER, DIMENSION(:,:)   ::  idata_2d  !<
713
714    TYPE(pedef), POINTER                    ::  ape  !<
715    TYPE(arraydef), POINTER                 ::  ar   !<
716
717
718    t1 = pmc_time()
719
720    IF(PRESENT(child_process_nr)) then
721       ip_start = child_process_nr
722       ip_end   = child_process_nr
723    ELSE
724       ip_start = 1
725       ip_end   = children(childid)%inter_npes
726    END IF
727
728    lo_ptrans = .FALSE.
729    IF ( PRESENT( particle_transfer))    lo_ptrans = particle_transfer
730
731    IF(ip_start == 1)   THEN
732!
733!--    Wait for child to fill buffer
734       CALL MPI_BARRIER( children(childid)%intra_comm, ierr )
735       t2 = pmc_time() - t1
736       IF ( PRESENT( waittime ) )  waittime = t2
737
738       CALL MPI_BARRIER( children(childid)%intra_comm, ierr )
739    ENDIF
740
741    DO  ip = ip_start,ip_end
742       ape => children(childid)%pes(ip)
743       DO  j = 1, ape%nr_arrays
744          ar => ape%array_list(j)
745         
746          IF ( ar%recvindex < 0 )  CYCLE
747
748          IF ( ar%dimkey == 2  .AND. .NOT.lo_ptrans  )  THEN
749             nr = ape%nrele
750          ELSEIF ( ar%dimkey == 3  .AND. .NOT.lo_ptrans  )  THEN
751             nr = ape%nrele * ar%a_dim(4)
752          ELSE IF ( ar%dimkey == 22 .AND. lo_ptrans)  THEN
753             nr = ape%nrele
754          ELSE
755             CYCLE                                        !particle array are not transfered here
756          ENDIF
757          buf_shape(1) = nr
758          IF(lo_ptrans)   THEN
759             CALL C_F_POINTER( ar%recvbuf, ibuf, buf_shape )
760          ELSE
761             CALL C_F_POINTER( ar%recvbuf, buf, buf_shape )
762          ENDIF
763
764!
765!--       MPI passive target RMA
766          IF ( nr > 0 )  THEN
767             target_disp = ar%recvindex - 1
768!
769!--          Child processes are located behind parent process
770             target_pe = ip - 1 + m_model_npes
771             CALL MPI_WIN_LOCK( MPI_LOCK_SHARED, target_pe, 0,                      &
772                                children(childid)%win_parent_child, ierr )
773             IF(lo_ptrans)   THEN
774                CALL MPI_GET( ibuf, nr*8, MPI_BYTE, target_pe, target_disp, nr*8,    &              !There is no MPI_INTEGER8 datatype
775                              MPI_BYTE, children(childid)%win_parent_child, ierr )
776             ELSE
777                CALL MPI_GET( buf, nr, MPI_REAL, target_pe, target_disp, nr,        &
778                              MPI_REAL, children(childid)%win_parent_child, ierr )
779             ENDIF
780             CALL MPI_WIN_UNLOCK( target_pe,                                        &
781                                  children(childid)%win_parent_child, ierr )
782          ENDIF
783          myindex = 1
784          IF ( ar%dimkey == 2  .AND. .NOT.lo_ptrans  )  THEN
785
786             CALL C_F_POINTER( ar%data, data_2d, ar%a_dim(1:2) )
787             DO  ij = 1, ape%nrele
788                data_2d(ape%locind(ij)%j,ape%locind(ij)%i) = buf(myindex)
789                myindex = myindex + 1
790             ENDDO
791
792          ELSEIF ( ar%dimkey == 3  .AND. .NOT.lo_ptrans  )  THEN
793
794             CALL C_F_POINTER( ar%data, data_3d, ar%a_dim(1:3))
795             DO  ij = 1, ape%nrele
796                data_3d(1:ar%a_dim(4),ape%locind(ij)%j,ape%locind(ij)%i) =     &
797                                              buf(myindex:myindex+ar%a_dim(4)-1)
798                myindex = myindex + ar%a_dim(4)
799             ENDDO
800
801          ELSE IF ( ar%dimkey == 22 .AND. lo_ptrans)  THEN
802
803             CALL C_F_POINTER( ar%data, idata_2d, ar%a_dim(1:2) )
804             DO  ij = 1, ape%nrele
805                idata_2d(ape%locind(ij)%j,ape%locind(ij)%i) = ibuf(myindex)
806                myindex = myindex + 1
807             ENDDO
808
809          ENDIF
810       ENDDO
811    ENDDO
812
813 END SUBROUTINE pmc_s_getdata_from_buffer
814
815
816
817 SUBROUTINE get_da_names_from_child( childid )
818
819!
820!-- Get data array description and name from child
821    IMPLICIT NONE
822
823    INTEGER(iwp), INTENT(IN) ::  childid  !<
824
825    TYPE(da_namedef) ::  myname  !<
826
827    DO
828       CALL pmc_bcast( myname%couple_index, 0, comm=m_to_child_comm(childid) )
829
830       IF ( myname%couple_index == -1 )  EXIT
831
832       CALL pmc_bcast( myname%parentdesc,   0, comm=m_to_child_comm(childid) )
833       CALL pmc_bcast( myname%nameonparent, 0, comm=m_to_child_comm(childid) )
834       CALL pmc_bcast( myname%childdesc,    0, comm=m_to_child_comm(childid) )
835       CALL pmc_bcast( myname%nameonchild,  0, comm=m_to_child_comm(childid) )
836
837       CALL pmc_g_setname( children(childid), myname%couple_index,             &
838                           myname%nameonparent )
839   ENDDO
840
841 END SUBROUTINE get_da_names_from_child
842
843
844
845 SUBROUTINE pmc_s_setarray(childid, nrdims, dims, array_adr, second_adr, dimkey )
846
847!
848!-- Set array for child inter process 0
849    IMPLICIT NONE
850
851    INTEGER(iwp), INTENT(IN)               :: childid    !<
852    INTEGER(iwp), INTENT(IN)               :: nrdims     !<
853    INTEGER(iwp), INTENT(IN), DIMENSION(:) :: dims       !<
854
855    TYPE(C_PTR), INTENT(IN)           :: array_adr  !<
856    TYPE(C_PTR), INTENT(IN), OPTIONAL :: second_adr !<
857    INTEGER(iwp), INTENT(IN), OPTIONAL     :: dimkey     !<
858
859    INTEGER(iwp) ::  i  !< local counter
860
861    TYPE(pedef), POINTER    ::  ape  !<
862    TYPE(arraydef), POINTER ::  ar   !<
863
864
865    DO  i = 1, children(childid)%inter_npes
866       ape => children(childid)%pes(i)
867       ar  => ape%array_list(next_array_in_list)
868       ar%nrdims = nrdims
869       ar%dimkey = nrdims
870       IF(PRESENT(dimkey)) ar%dimkey = dimkey
871       ar%a_dim  = dims
872       ar%data   = array_adr
873       IF ( PRESENT( second_adr ) )  THEN
874          ar%po_data(1) = array_adr
875          ar%po_data(2) = second_adr
876       ELSE
877          ar%po_data(1) = C_NULL_PTR
878          ar%po_data(2) = C_NULL_PTR
879       ENDIF
880    ENDDO
881
882 END SUBROUTINE pmc_s_setarray
883
884
885
886 SUBROUTINE pmc_s_set_active_data_array( childid, iactive )
887
888    IMPLICIT NONE
889
890    INTEGER(iwp), INTENT(IN) ::  childid   !<
891    INTEGER(iwp), INTENT(IN) ::  iactive   !<
892
893    INTEGER(iwp) :: ip  !<
894    INTEGER(iwp) :: j   !<
895
896    TYPE(pedef), POINTER    ::  ape  !<
897    TYPE(arraydef), POINTER ::  ar   !<
898
899    DO  ip = 1, children(childid)%inter_npes
900       ape => children(childid)%pes(ip)
901       DO  j = 1, ape%nr_arrays
902          ar => ape%array_list(j)
903          if(mod(ar%dimkey,10) == 2) CYCLE           !Not for 2D array
904          IF ( iactive == 1  .OR.  iactive == 2 )  THEN
905             ar%data = ar%po_data(iactive)
906          ENDIF
907       ENDDO
908    ENDDO
909
910 END SUBROUTINE pmc_s_set_active_data_array
911
912 INTEGER FUNCTION pmc_s_get_child_npes (child_id)
913   IMPLICIT NONE
914
915   INTEGER(iwp),INTENT(IN)                 :: child_id
916
917   pmc_s_get_child_npes = children(child_id)%inter_npes
918
919   RETURN
920 END FUNCTION pmc_s_get_child_npes
921
922
923 SUBROUTINE set_pe_index_list( mychild, index_list, nrp )
924
925    IMPLICIT NONE
926
927    INTEGER(iwp), INTENT(IN), DIMENSION(:,:) ::  index_list  !<
928    INTEGER(iwp), INTENT(IN)                 ::  nrp         !<
929
930    TYPE(childdef), INTENT(INOUT)       ::  mychild     !<
931
932    INTEGER(iwp)                            :: i        !<
933    INTEGER(iwp)                            :: ierr     !<
934    INTEGER(iwp)                            :: ind      !<
935    INTEGER(iwp)                            :: indwin   !<
936    INTEGER(iwp)                            :: indwin2  !<
937    INTEGER(iwp)                            :: i2       !<
938    INTEGER(iwp)                            :: j        !<
939    INTEGER(iwp)                            :: rempe    !<
940    INTEGER(KIND=MPI_ADDRESS_KIND)          :: winsize  !<
941
942    INTEGER(iwp), DIMENSION(mychild%inter_npes)  :: remind   !<
943
944    INTEGER(iwp), DIMENSION(:), POINTER          :: remindw  !<
945    INTEGER(iwp), DIMENSION(:), POINTER          :: rldef    !<
946
947    TYPE(pedef), POINTER                    :: ape      !<
948
949!
950!-- First, count entries for every remote child process
951    DO  i = 1, mychild%inter_npes
952       ape => mychild%pes(i)
953       ape%nrele = 0
954    ENDDO
955!
956!-- Loop over number of coarse grid cells
957    DO  j = 1, nrp
958       rempe = index_list(5,j) + 1   ! process number on remote process
959       ape => mychild%pes(rempe)
960       ape%nrele = ape%nrele + 1     ! Increment number of elements for this child process
961    ENDDO
962
963    DO  i = 1, mychild%inter_npes
964       ape => mychild%pes(i)
965       ALLOCATE( ape%locind(ape%nrele) )
966    ENDDO
967
968    remind = 0
969!
970!-- Second, create lists
971!-- Loop over number of coarse grid cells
972    DO  j = 1, nrp
973       rempe = index_list(5,j) + 1
974       ape => mychild%pes(rempe)
975       remind(rempe)     = remind(rempe)+1
976       ind               = remind(rempe)
977       ape%locind(ind)%i = index_list(1,j)
978       ape%locind(ind)%j = index_list(2,j)
979    ENDDO
980!
981!-- Prepare number of elements for children processes
982    CALL pmc_alloc_mem( rldef, mychild%inter_npes*2 )
983!
984!-- Number of child processes * size of INTEGER (i just arbitrary INTEGER)
985    winsize = mychild%inter_npes*STORAGE_SIZE(i)/8*2
986
987    CALL MPI_WIN_CREATE( rldef, winsize, iwp, MPI_INFO_NULL,                   &
988                         mychild%intra_comm, indwin, ierr )
989!
990!-- Open window to set data
991    CALL MPI_WIN_FENCE( 0, indwin, ierr )
992
993    rldef(1) = 0            ! index on remote process 0
994    rldef(2) = remind(1)    ! number of elements on remote process 0
995!
996!-- Reserve buffer for index array
997    DO  i = 2, mychild%inter_npes
998       i2          = (i-1) * 2 + 1
999       rldef(i2)   = rldef(i2-2) + rldef(i2-1) * 2  ! index on remote process
1000       rldef(i2+1) = remind(i)                      ! number of elements on remote process
1001    ENDDO
1002!
1003!-- Close window to allow child to access data
1004    CALL MPI_WIN_FENCE( 0, indwin, ierr )
1005!
1006!-- Child has retrieved data
1007    CALL MPI_WIN_FENCE( 0, indwin, ierr )
1008
1009    i2 = 2 * mychild%inter_npes - 1
1010    winsize = ( rldef(i2) + rldef(i2+1) ) * 2
1011!
1012!-- Make sure, MPI_ALLOC_MEM works
1013    winsize = MAX( winsize, INT( 1, MPI_ADDRESS_KIND ) )
1014
1015    CALL pmc_alloc_mem( remindw, INT( winsize ) )
1016
1017    CALL MPI_BARRIER( m_model_comm, ierr )
1018    CALL MPI_WIN_CREATE( remindw, winsize*STORAGE_SIZE(i)/8, iwp, MPI_INFO_NULL,     &
1019                         mychild%intra_comm, indwin2, ierr )
1020!
1021!-- Open window to set data
1022    CALL MPI_WIN_FENCE( 0, indwin2, ierr )
1023!
1024!-- Create the 2D index list
1025    DO  j = 1, nrp
1026       rempe = index_list(5,j) + 1    ! process number on remote process
1027       ape => mychild%pes(rempe)
1028       i2    = rempe * 2 - 1
1029       ind   = rldef(i2) + 1
1030       remindw(ind)   = index_list(3,j)
1031       remindw(ind+1) = index_list(4,j)
1032       rldef(i2)      = rldef(i2)+2
1033    ENDDO
1034!
1035!-- All data are set
1036    CALL MPI_WIN_FENCE( 0, indwin2, ierr )
1037!
1038!-- Don't know why, but this barrier is necessary before windows can be freed
1039!-- TODO: find out why this is required
1040    CALL MPI_BARRIER( mychild%intra_comm, ierr )
1041
1042    CALL MPI_WIN_FREE( indwin, ierr )
1043    CALL MPI_WIN_FREE( indwin2, ierr )
1044
1045!
1046!-- TODO: check if the following idea needs to be done
1047!-- Sollte funktionieren, Problem mit MPI implementation
1048!-- https://www.lrz.de/services/software/parallel/mpi/onesided
1049!-- CALL MPI_Free_mem (remindw, ierr)
1050
1051 END SUBROUTINE set_pe_index_list
1052
1053#endif
1054 END MODULE pmc_parent
Note: See TracBrowser for help on using the repository browser.