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

Last change on this file since 4058 was 3962, checked in by suehring, 5 years ago

Bugfixes in initial settings of child and parent communication patterns

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