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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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