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

Last change on this file since 3022 was 2841, checked in by knoop, 6 years ago

Bugfix: wrong placement of include 'mpif.h' corrected

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