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

Last change on this file since 1938 was 1938, checked in by hellstea, 8 years ago

dependency errors corrected in Makefile

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