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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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