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

Last change on this file since 3241 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

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