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

Last change on this file since 3655 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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