source: palm/trunk/SOURCE/pmc_client_mod.f90 @ 1850

Last change on this file since 1850 was 1850, checked in by maronga, 8 years ago

added _mod string to several filenames to meet the naming convection for modules

  • Property svn:keywords set to Id
File size: 24.8 KB
Line 
1MODULE pmc_client
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2016 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22! Module renamed
23!
24!
25! Former revisions:
26! -----------------
27! $Id: pmc_client_mod.f90 1850 2016-04-08 13:29:27Z maronga $
28!
29! 1833 2016-04-07 14:23:03Z raasch
30! gfortran requires pointer attributes for some array declarations,
31! long line wrapped
32!
33! 1808 2016-04-05 19:44:00Z raasch
34! MPI module used by default on all machines
35!
36! 1797 2016-03-21 16:50:28Z raasch
37! introduction of different datatransfer modes
38!
39! 1791 2016-03-11 10:41:25Z raasch
40! Debug write-statement commented out
41!
42! 1786 2016-03-08 05:49:27Z raasch
43! change in client-server data transfer: server now gets data from client
44! instead that client put's it to the server
45!
46! 1783 2016-03-06 18:36:17Z raasch
47! Bugfix: wrong data-type in MPI_WIN_CREATE replaced
48!
49! 1779 2016-03-03 08:01:28Z raasch
50! kind=dp replaced by wp, dim_order removed
51! array management changed from linked list to sequential loop
52!
53! 1764 2016-02-28 12:45:19Z raasch
54! cpp-statement added (nesting can only be used in parallel mode),
55! all kinds given in PALM style
56!
57! 1762 2016-02-25 12:31:13Z hellstea
58! Initial revision by K. Ketelsen
59!
60! Description:
61! ------------
62!
63! Client part of Palm Model Coupler
64!------------------------------------------------------------------------------!
65
66#if defined( __parallel )
67
68    use, intrinsic :: iso_c_binding
69
70#if defined( __mpifh )
71    INCLUDE "mpif.h"
72#else
73    USE MPI
74#endif
75    USE  kinds
76    USE  PMC_general,   ONLY: ClientDef, DA_NameDef, DA_Namelen, PMC_STATUS_OK, PMC_DA_NAME_ERR, PeDef, ArrayDef, &
77                                         DA_Desclen, DA_Namelen, PMC_G_SetName, PMC_MAX_ARRAY
78    USE  PMC_handle_communicator,   ONLY: m_model_comm,m_model_rank,m_model_npes, m_to_server_comm
79    USE  PMC_MPI_wrapper,           ONLY: PMC_Send_to_Server, PMC_Recv_from_Server, PMC_Time,                     &
80                                              PMC_Bcast, PMC_Inter_Bcast, PMC_Alloc_mem
81    IMPLICIT none
82    PRIVATE
83    SAVE
84
85    Type(ClientDef)                       :: me
86
87    INTEGER                               :: next_array_in_list = 0
88    INTEGER                               :: myIndex = 0                !Counter and unique number for Data Arrays
89
90    ! INTERFACE section
91
92    INTERFACE PMC_ClientInit
93        MODULE procedure PMC_ClientInit
94    END INTERFACE PMC_ClientInit
95
96    INTERFACE PMC_Set_DataArray_Name
97        MODULE procedure PMC_Set_DataArray_Name
98        MODULE procedure PMC_Set_DataArray_Name_LastEntry
99    END INTERFACE PMC_Set_DataArray_Name
100
101    INTERFACE PMC_C_Get_2D_index_list
102        MODULE procedure PMC_C_Get_2D_index_list
103    END INTERFACE PMC_C_Get_2D_index_list
104
105    INTERFACE PMC_C_clear_next_array_list
106        MODULE procedure PMC_C_clear_next_array_list
107    END INTERFACE PMC_C_clear_next_array_list
108
109    INTERFACE PMC_C_GetNextArray
110        MODULE procedure PMC_C_GetNextArray
111    END INTERFACE PMC_C_GetNextArray
112
113    INTERFACE PMC_C_Set_DataArray
114        MODULE procedure PMC_C_Set_DataArray_2d
115        MODULE procedure PMC_C_Set_DataArray_3d
116    END INTERFACE PMC_C_Set_DataArray
117
118    INTERFACE PMC_C_setInd_and_AllocMem
119        MODULE procedure PMC_C_setInd_and_AllocMem
120    END INTERFACE PMC_C_setInd_and_AllocMem
121
122    INTERFACE PMC_C_GetBuffer
123        MODULE procedure PMC_C_GetBuffer
124    END INTERFACE PMC_C_GetBuffer
125
126    INTERFACE PMC_C_PutBuffer
127        MODULE procedure PMC_C_PutBuffer
128    END INTERFACE PMC_C_PutBuffer
129
130    ! Public section
131
132    PUBLIC PMC_ClientInit , PMC_Set_DataArray_Name, PMC_C_Get_2D_index_list
133    PUBLIC PMC_C_GetNextArray, PMC_C_Set_DataArray, PMC_C_clear_next_array_list
134    PUBLIC PMC_C_setInd_and_AllocMem , PMC_C_GetBuffer, PMC_C_PutBuffer
135
136CONTAINS
137
138    SUBROUTINE PMC_ClientInit
139        IMPLICIT none
140
141        INTEGER                       :: i
142        INTEGER                       :: istat
143
144
145        ! Tailor MPI environment
146
147        me%model_comm = m_model_comm
148        me%inter_comm = m_to_server_comm
149
150        ! Get rank and size
151        CALL MPI_Comm_rank (me%model_comm, me%model_rank, istat);
152        CALL MPI_Comm_size (me%model_comm, me%model_npes, istat);
153        CALL MPI_Comm_remote_size (me%inter_comm, me%inter_npes, istat);
154
155        ! intra communicater is used for MPI_Get
156        CALL MPI_Intercomm_merge (me%inter_comm, .true., me%intra_comm, istat);
157        CALL MPI_Comm_rank (me%intra_comm, me%intra_rank, istat);
158        ALLOCATE (me%PEs(me%inter_npes))
159
160!
161!--     Allocate for all Server PEs an array of TYPE ArrayDef to store information of transfer array
162        do i=1,me%inter_npes
163           ALLOCATE(me%PEs(i)%array_list(PMC_MAX_ARRAY))
164        end do
165
166!        if(me%model_rank == 0) write(0,'(a,5i6)') 'PMC_ClientInit ',me%model_rank,me%model_npes,me%inter_npes,me%intra_rank
167
168        return
169    END SUBROUTINE PMC_ClientInit
170
171    SUBROUTINE PMC_Set_DataArray_Name (ServerArrayDesc, ServerArrayName, ClientArrayDesc, ClientArrayName, istat)
172        IMPLICIT none
173        character(len=*),INTENT(IN)           :: ServerArrayName
174        character(len=*),INTENT(IN)           :: ServerArrayDesc
175        character(len=*),INTENT(IN)           :: ClientArrayName
176        character(len=*),INTENT(IN)           :: ClientArrayDesc
177        INTEGER,INTENT(OUT)                   :: istat
178
179        !-- local variables
180        type(DA_NameDef)                      :: myName
181        INTEGER                               :: myPe
182        INTEGER                               :: my_AddiArray=0
183
184        istat = PMC_STATUS_OK
185        if(len(trim(ServerArrayName)) > DA_Namelen .or.                                         &
186            len(trim(ClientArrayName)) > DA_Namelen)  then !Name too long
187            istat = PMC_DA_NAME_ERR
188        end if
189
190        if(m_model_rank == 0) then
191            myIndex = myIndex+1
192            myName%couple_index  = myIndex
193            myName%ServerDesc    = trim(ServerArrayDesc)
194            myName%NameOnServer  = trim(ServerArrayName)
195            myName%ClientDesc    = trim(ClientArrayDesc)
196            myName%NameOnClient  = trim(ClientArrayName)
197        end if
198
199        !   Broadcat to all Client PEs
200
201        CALL PMC_Bcast ( myName%couple_index,  0,   comm=m_model_comm)
202        CALL PMC_Bcast ( myName%ServerDesc, 0,      comm=m_model_comm)
203        CALL PMC_Bcast ( myName%NameOnServer,    0, comm=m_model_comm)
204        CALL PMC_Bcast ( myName%ClientDesc, 0,      comm=m_model_comm)
205        CALL PMC_Bcast ( myName%NameOnClient,    0, comm=m_model_comm)
206
207        !   Broadcat to all Server PEs
208
209        if(m_model_rank == 0) then
210            myPE = MPI_ROOT
211        else
212            myPE = MPI_PROC_NULL
213        endif
214        CALL PMC_Bcast ( myName%couple_index, myPE, comm=m_to_server_comm)
215        CALL PMC_Bcast ( myName%ServerDesc,   myPE, comm=m_to_server_comm)
216        CALL PMC_Bcast ( myName%NameOnServer, myPE, comm=m_to_server_comm)
217        CALL PMC_Bcast ( myName%ClientDesc,   myPE, comm=m_to_server_comm)
218        CALL PMC_Bcast ( myName%NameOnClient, myPE, comm=m_to_server_comm)
219
220        CALL PMC_G_SetName (me, myName%couple_index, myName%NameOnClient)
221
222        return
223    END SUBROUTINE PMC_Set_DataArray_Name
224
225    SUBROUTINE PMC_Set_DataArray_Name_LastEntry (LastEntry)
226        IMPLICIT none
227        LOGICAL,INTENT(IN),optional           :: LastEntry
228
229        !-- local variables
230        type(DA_NameDef)                      :: myName
231        INTEGER                               :: myPe
232
233        myName%couple_index  = -1
234
235        if(m_model_rank == 0) then
236            myPE = MPI_ROOT
237        else
238            myPE = MPI_PROC_NULL
239        endif
240        CALL PMC_Bcast ( myName%couple_index,  myPE, comm=m_to_server_comm)
241
242        return
243    END SUBROUTINE PMC_Set_DataArray_Name_LastEntry
244
245    SUBROUTINE PMC_C_Get_2D_index_list
246       IMPLICIT none
247
248       INTEGER                                 :: i,j,i2,nr,ierr
249       INTEGER                                 :: dummy
250       INTEGER                                 :: indWin          !: MPI window object
251       INTEGER                                 :: indWin2         !: MPI window object
252       INTEGER(KIND=MPI_ADDRESS_KIND)          :: win_size        !: Size of MPI window 1 (in bytes)
253       INTEGER(KIND=MPI_ADDRESS_KIND)          :: disp            !: Displacement Unit (Integer = 4, floating poit = 8
254       INTEGER,DIMENSION(me%inter_npes*2)      :: NrEle           !: Number of Elements of a horizontal slice
255       TYPE(PeDef),POINTER                     :: aPE             !: Pointer to PeDef structure
256       INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize         !: Size of MPI window 2 (in bytes)
257       INTEGER,DIMENSION(:),POINTER            :: myInd
258
259!      CALL PMC_C_CGet_Rem_index_list
260
261       win_size = c_sizeof(dummy)
262       CALL MPI_Win_create (dummy, win_size, iwp, MPI_INFO_NULL, me%intra_comm, indWin, ierr);
263       CALL MPI_Win_fence (0, indWin, ierr)                ! Open Window on Server side
264       CALL MPI_Win_fence (0, indWin, ierr)                ! Close Window on Server Side and opem on Client side
265
266       do i=1,me%inter_npes
267          disp = me%model_rank*2
268          CALL MPI_Get (NrEle((i-1)*2+1),2,MPI_INTEGER,i-1,disp,2,MPI_INTEGER,indWin, ierr)
269       end do
270       CALL MPI_Win_fence (0, indWin, ierr)    ! MPI_get is Non-blocking -> data in NrEle is not available until MPI_fence CALL
271
272       WinSize = 0
273       do i=1,me%inter_npes                         !Allocate memory for index array
274         aPE => me%PEs(i)
275         i2 = (i-1)*2+1
276         nr = NrEle(i2+1)
277         if(nr > 0)  then
278            ALLOCATE(aPE%locInd(nr))
279         else
280            NULLIFY (aPE%locInd)
281         endif
282         WinSize = max(nr,WinSize)                  !Maximum window size
283       end do
284
285       ALLOCATE(myInd(2*WinSize))
286       WinSize = 1
287
288!      local Buffer used in MPI_Get can but must not be inside the MPI Window
289!      Here, we use a dummy for MPI Window because the server PEs do not access the RMA window via MPI_get or MPI_Put
290
291       CALL MPI_Win_create (dummy, WinSize, iwp, MPI_INFO_NULL, me%intra_comm, indWin2, ierr);
292
293       CALL MPI_Win_fence (0, indWin2, ierr)    ! MPI_get is Non-blocking -> data in NrEle is not available until MPI_fence CALL
294       CALL MPI_Win_fence (0, indWin2, ierr)    ! MPI_get is Non-blocking -> data in NrEle is not available until MPI_fence CALL
295
296       do i=1,me%inter_npes
297          aPE => me%PEs(i)
298          nr = NrEle(i*2)
299          if(nr > 0 )  then
300             disp = NrEle(2*(i-1)+1)
301             CALL MPI_Win_lock (MPI_LOCK_SHARED , i-1, 0, indWin2, ierr)
302             CALL MPI_Get (myInd,2*nr,MPI_INTEGER,i-1,disp,2*nr,MPI_INTEGER,indWin2, ierr)
303             CALL MPI_Win_unlock (i-1, indWin2, ierr)
304             do j=1,nr
305                aPE%locInd(j)%i = myInd(2*j-1)
306                aPE%locInd(j)%j = myInd(2*j)
307             end do
308             aPE%NrEle = nr
309          else
310             aPE%NrEle = -1
311          end if
312       end do
313
314       CALL MPI_Barrier(me%intra_comm, ierr)   ! Dont know why, but this barrier is necessary before we can free the windows
315
316       CALL MPI_Win_free(indWin, ierr);
317       CALL MPI_Win_free(indWin2, ierr);
318       DEALLOCATE (myInd)
319
320       return
321    END SUBROUTINE PMC_C_Get_2D_index_list
322
323    SUBROUTINE PMC_C_clear_next_array_list
324       IMPLICIT none
325
326       next_array_in_list = 0
327
328       return
329    END SUBROUTINE PMC_C_clear_next_array_list
330
331!   List handling is still required to get minimal interaction with pmc_interface
332    LOGICAL function PMC_C_GetNextArray (myName)
333        character(len=*),INTENT(OUT)               :: myName
334
335        !-- local variables
336       TYPE(PeDef),POINTER          :: aPE
337       TYPE(ArrayDef),POINTER       :: ar
338
339       next_array_in_list = next_array_in_list+1
340
341!--    Array Names are the same on all client PE, so take first PE to get the name
342       aPE => me%PEs(1)
343
344       if(next_array_in_list > aPE%Nr_arrays) then
345          PMC_C_GetNextArray = .false.             !all arrays done
346          return
347       end if
348
349       ar  => aPE%array_list(next_array_in_list)
350
351       myName = ar%name
352
353       PMC_C_GetNextArray =  .true.                ! Return true if legal array
354       return
355    END function PMC_C_GetNextArray
356
357    SUBROUTINE PMC_C_Set_DataArray_2d (array)
358
359       IMPLICIT none
360
361       REAL(wp), INTENT(IN) ,DIMENSION(:,:), POINTER ::  array
362
363       INTEGER                              :: NrDims
364       INTEGER,DIMENSION (4)                :: dims
365       TYPE(c_ptr)                          :: array_adr
366       INTEGER                              :: i
367       TYPE(PeDef),POINTER                  :: aPE
368       TYPE(ArrayDef),POINTER               :: ar
369
370
371       dims = 1
372
373       NrDims    = 2
374       dims(1)   = size(array,1)
375       dims(2)   = size(array,2)
376
377       array_adr = c_loc(array)
378
379       do i=1,me%inter_npes
380          aPE => me%PEs(i)
381          ar  => aPE%array_list(next_array_in_list)
382          ar%NrDims    = NrDims
383          ar%A_dim     = dims
384          ar%data      = array_adr
385       end do
386
387       return
388    END SUBROUTINE PMC_C_Set_DataArray_2d
389
390    SUBROUTINE PMC_C_Set_DataArray_3d (array)
391
392       IMPLICIT none
393
394       REAL(wp),INTENT(IN),DIMENSION(:,:,:), POINTER ::  array
395
396       INTEGER                              ::  NrDims
397       INTEGER,DIMENSION (4)                ::  dims
398       TYPE(c_ptr)                          ::  array_adr
399       INTEGER                              ::  i
400       TYPE(PeDef),POINTER                  ::  aPE
401       TYPE(ArrayDef),POINTER               ::  ar
402
403       dims = 1
404
405       NrDims    = 3
406       dims(1)   = size(array,1)
407       dims(2)   = size(array,2)
408       dims(3)   = size(array,3)
409
410       array_adr = c_loc(array)
411
412       do i=1,me%inter_npes
413          aPE => me%PEs(i)
414          ar  => aPE%array_list(next_array_in_list)
415          ar%NrDims    = NrDims
416          ar%A_dim     = dims
417          ar%data      = array_adr
418       end do
419
420       return
421    END SUBROUTINE PMC_C_Set_DataArray_3d
422
423   SUBROUTINE PMC_C_setInd_and_AllocMem
424
425      IMPLICIT none
426
427!--   naming convention:  appending       _sc  -> server to client transfer
428!--                                       _cs  -> client to server transfer
429!--                                       Recv -> server to client transfer
430!--                                       Send -> client to server transfer
431
432      INTEGER                                 :: i, istat, ierr, j
433      INTEGER,PARAMETER                       :: NoINdex=-1
434      INTEGER                                 :: rcount
435      INTEGER                                 :: arlen, myIndex, tag
436      INTEGER(idp)                            :: bufsize                   ! Size of MPI data Window
437      TYPE(PeDef),POINTER                     :: aPE
438      TYPE(ArrayDef),POINTER                  :: ar
439      INTEGER,DIMENSION(1024)                 :: req
440      character(len=DA_Namelen)               :: myName
441      Type(c_ptr)                             :: base_ptr
442      REAL(kind=wp),DIMENSION(:),POINTER,save :: base_array_sc             !Base array
443      REAL(kind=wp),DIMENSION(:),POINTER,save :: base_array_cs             !Base array
444      INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize
445
446      myIndex = 0
447      bufsize = 8
448
449!--   Server to client direction
450
451!--   First stride, Compute size and set index
452
453      do i=1,me%inter_npes
454         aPE => me%PEs(i)
455         tag = 200
456
457         do j=1,aPE%Nr_arrays
458            ar  => aPE%array_list(j)
459
460            ! Receive Index from client
461            tag = tag+1
462            CALL MPI_Recv (myIndex, 1, MPI_INTEGER, i-1, tag, me%inter_comm, MPI_STATUS_IGNORE, ierr)
463
464            if(ar%NrDims == 3) then
465               bufsize = max(bufsize,ar%A_dim(1)*ar%A_dim(2)*ar%A_dim(3))    ! determine max, because client buffer is allocated only once
466            else
467               bufsize = max(bufsize,ar%A_dim(1)*ar%A_dim(2))
468            end if
469            ar%RecvIndex = myIndex
470
471           end do
472      end do
473
474
475!--   Create RMA (One Sided Communication) data buffer
476!--   The buffer for MPI_Get can be PE local, i.e. it can but must not be part of the MPI RMA window
477
478      CALL PMC_Alloc_mem (base_array_sc, bufsize, base_ptr)
479      me%TotalBufferSize = bufsize*wp                          ! Total buffer size in Byte
480
481!--   Second stride, Set Buffer pointer
482
483      do i=1,me%inter_npes
484         aPE => me%PEs(i)
485
486         do j=1,aPE%Nr_arrays
487            ar  => aPE%array_list(j)
488            ar%RecvBuf = base_ptr
489         end do
490      end do
491
492!--   Client to server direction
493
494      myIndex = 1
495      rCount  = 0
496      bufsize = 8
497
498      do i=1,me%inter_npes
499         aPE => me%PEs(i)
500         tag = 300
501         do j=1,aPE%Nr_arrays
502            ar  => aPE%array_list(j)
503            if(ar%NrDims == 2) then
504               arlen     = aPE%NrEle                        ! 2D
505            else if(ar%NrDims == 3) then
506               arlen     = aPE%NrEle*ar%A_dim(1)            ! 3D
507            end if
508
509            tag    = tag+1
510            rCount = rCount+1
511            if(aPE%NrEle > 0)  then
512               CALL MPI_Isend (myIndex, 1, MPI_INTEGER, i-1, tag, me%inter_comm, req(rCount),ierr)
513               ar%SendIndex = myIndex
514            else
515               CALL MPI_Isend (NoIndex, 1, MPI_INTEGER, i-1, tag, me%inter_comm, req(rCount),ierr)
516               ar%SendIndex = NoIndex
517            end if
518
519            if(rCount == 1024) then                                  ! Maximum of 1024 outstanding requests
520               CALL MPI_Waitall (rCount, req, MPI_STATUSES_IGNORE, ierr)
521               rCount = 0;
522            end if
523
524            if(aPE%NrEle > 0)  then
525               ar%SendSize  = arlen
526               myIndex     = myIndex+arlen
527               bufsize     = bufsize+arlen
528            end if
529          end do
530         if(rCount > 0) then                                          ! Wait for all send completed
531            CALL MPI_Waitall (rCount, req, MPI_STATUSES_IGNORE, ierr)
532         end if
533      end do
534
535!--   Create RMA (One Sided Communication) window for data buffer client to server transfer
536!--   The buffer of MPI_Get (counter part of transfer) can be PE-local, i.e. it can but must not be part of the MPI RMA window
537!--   Only one RMA window is required to prepare the data for server -> client transfer on the server side and
538!--                                                       for client -> server transfer on the client side
539
540      CALL PMC_Alloc_mem (base_array_cs, bufsize)
541      me%TotalBufferSize = bufsize*wp                          !Total buffer size in Byte
542
543      WinSize = me%TotalBufferSize
544      CALL MPI_Win_create (base_array_cs, WinSize, wp, MPI_INFO_NULL, me%intra_comm, me%win_server_client, ierr);
545      CALL MPI_Win_fence (0, me%win_server_client, ierr);                    !  Open Window to set data
546      CALL MPI_Barrier(me%intra_comm, ierr)
547
548!--   Second stride, Set Buffer pointer
549
550      do i=1,me%inter_npes
551         aPE => me%PEs(i)
552
553         do j=1,aPE%Nr_arrays
554            ar  => aPE%array_list(j)
555            if(aPE%NrEle > 0)  then
556              ar%SendBuf = c_loc(base_array_cs(ar%SendIndex))
557              if(ar%SendIndex+ar%SendSize > bufsize) then
558                 write(0,'(a,i4,4i7,1x,a)') 'Client Buffer too small ',i,      &
559                     ar%SendIndex,ar%SendSize,ar%SendIndex+ar%SendSize,bufsize,trim(ar%name)
560                 CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr)
561              end if
562            end if
563         end do
564      end do
565
566      return
567   END SUBROUTINE PMC_C_setInd_and_AllocMem
568
569   SUBROUTINE PMC_C_GetBuffer (WaitTime)
570
571      IMPLICIT none
572
573      REAL(wp), INTENT(OUT), optional   ::  WaitTime
574
575      !-- local variables
576      INTEGER                           ::  ip, ij, ierr, j
577      INTEGER                           ::  nr  ! Number of Elements to getb from server
578      INTEGER                           ::  myIndex
579      REAL(wp)                          ::  t1,t2
580      TYPE(PeDef),POINTER               ::  aPE
581      TYPE(ArrayDef),POINTER            ::  ar
582      INTEGER,DIMENSION(1)              ::  buf_shape
583      REAL(wp),POINTER,DIMENSION(:)     ::  buf
584      REAL(wp),POINTER,DIMENSION(:,:)   ::  data_2d
585      REAL(wp),POINTER,DIMENSION(:,:,:) ::  data_3d
586      character(len=DA_Namelen)         ::  myName
587      INTEGER(kind=MPI_ADDRESS_KIND)    ::  target_disp
588
589!
590!--   Synchronization of the model is done in pmci_client_synchronize and pmci_server_synchronize
591!--   Therefor the RMA window can be filled without sychronization at this point and a barrier
592!--   is not necessary
593!--   Please note that WaitTime has to be set in PMC_S_FillBuffer AND PMC_C_GetBuffer
594      if(present(WaitTime))  then
595         t1 = PMC_Time()
596         CALL MPI_Barrier(me%intra_comm, ierr)
597         t2 = PMC_Time()
598         WaitTime = t2-t1
599      end if
600
601      CALL MPI_Barrier(me%intra_comm, ierr)                         ! Wait for buffer is filled
602
603      do ip=1,me%inter_npes
604         aPE => me%PEs(ip)
605
606         do j=1,aPE%Nr_arrays
607            ar  => aPE%array_list(j)
608            if(ar%NrDims == 2) then
609               nr = aPE%NrEle
610            else if(ar%NrDims == 3) then
611               nr = aPE%NrEle*ar%A_dim(1)
612            end if
613
614            buf_shape(1) = nr
615            CALL c_f_pointer(ar%RecvBuf, buf, buf_shape)
616!
617!--         MPI passive target RMA
618            if(nr > 0)   then
619               target_disp = (ar%RecvIndex-1)
620               CALL MPI_Win_lock (MPI_LOCK_SHARED , ip-1, 0, me%win_server_client, ierr)
621               CALL MPI_Get (buf, nr, MPI_REAL, ip-1, target_disp, nr, MPI_REAL, me%win_server_client, ierr)
622               CALL MPI_Win_unlock (ip-1, me%win_server_client, ierr)
623            end if
624
625            myIndex = 1
626            if(ar%NrDims == 2) then
627
628               CALL c_f_pointer(ar%data, data_2d, ar%A_dim(1:2))
629               do ij=1,aPE%NrEle
630                  data_2d(aPE%locInd(ij)%j,aPE%locInd(ij)%i) = buf(myIndex)
631                  myIndex = myIndex+1
632               end do
633            else if(ar%NrDims == 3) then
634               CALL c_f_pointer(ar%data, data_3d, ar%A_dim(1:3))
635               do ij=1,aPE%NrEle
636                  data_3d(:,aPE%locInd(ij)%j,aPE%locInd(ij)%i) = buf(myIndex:myIndex+ar%A_dim(1)-1)
637                  myIndex = myIndex+ar%A_dim(1)
638               end do
639            end if
640
641         end do
642      end do
643      return
644   END SUBROUTINE PMC_C_GetBuffer
645
646   SUBROUTINE PMC_C_PutBuffer (WaitTime)
647
648      IMPLICIT none
649
650      REAL(wp), INTENT(OUT), optional   :: WaitTime
651
652      !-- local variables
653      INTEGER                           ::  ip, ij, ierr, j
654      INTEGER                           ::  nr  ! Number of Elements to getb from server
655      INTEGER                           ::  myIndex
656      REAL(wp)                          ::  t1,t2
657      TYPE(PeDef),POINTER               ::  aPE
658      TYPE(ArrayDef),POINTER            ::  ar
659      INTEGER,DIMENSION(1)              ::  buf_shape
660      REAL(wp),POINTER,DIMENSION(:)     ::  buf
661      REAL(wp),POINTER,DIMENSION(:,:)   ::  data_2d
662      REAL(wp),POINTER,DIMENSION(:,:,:) ::  data_3d
663      character(len=DA_Namelen)         ::  myName
664      INTEGER(kind=MPI_ADDRESS_KIND)    ::  target_disp
665
666      t1 = PMC_Time()
667      CALL MPI_Barrier(me%intra_comm, ierr)              ! Wait for empty buffer
668      t2 = PMC_Time()
669      if(present(WaitTime)) WaitTime = t2-t1
670
671      do ip=1,me%inter_npes
672         aPE => me%PEs(ip)
673
674         do j=1,aPE%Nr_arrays
675            ar  => aPE%array_list(j)
676            myIndex=1
677            if(ar%NrDims == 2) then
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               end do
685            else if(ar%NrDims == 3) then
686               buf_shape(1) = aPE%NrEle*ar%A_dim(1)
687               CALL c_f_pointer(ar%SendBuf, buf, buf_shape)
688               CALL c_f_pointer(ar%data, data_3d, ar%A_dim(1:3))
689               do ij=1,aPE%NrEle
690                  buf(myIndex:myIndex+ar%A_dim(1)-1) = data_3d(:,aPE%locInd(ij)%j,aPE%locInd(ij)%i)
691                  myIndex = myIndex+ar%A_dim(1)
692               end do
693            end if
694          end do
695      end do
696
697
698!      CALL MPI_Win_fence (0, me%win_server_client, ierr)      ! Fence might do it, test later
699      CALL MPI_Barrier(me%intra_comm, ierr)                   ! buffer is filled
700
701      return
702    END SUBROUTINE PMC_C_PutBuffer
703
704#endif
705END MODULE pmc_client
Note: See TracBrowser for help on using the repository browser.