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

Last change on this file since 4828 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

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