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

Last change on this file since 2839 was 2809, checked in by schwenkel, 6 years ago

Bugfix for gfortran: Replace the function C_SIZEOF with STORAGE_SIZE

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