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

Last change on this file since 3130 was 3049, checked in by Giersch, 6 years ago

Revision history corrected

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