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

Last change on this file since 2801 was 2801, checked in by thiele, 6 years ago

Introduce particle transfer in nested models

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