source: palm/trunk/SOURCE/pmc_server.f90 @ 1762

Last change on this file since 1762 was 1762, checked in by hellstea, 8 years ago

Introduction of nested domain system

  • Property svn:keywords set to Id
File size: 23.9 KB
Line 
1MODULE pmc_server
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-2015 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23! Former revisions:
24! -----------------
25! $Id: pmc_server.f90 1762 2016-02-25 12:31:13Z hellstea $
26!
27! Intoduction of the pure FORTRAN Palm Model Coupler     (PMC)  12.11.2015  K. Ketelsen
28!
29! Description:
30! ------------
31!
32! Server part of Palm Model Coupler
33!------------------------------------------------------------------------------!
34
35   use, intrinsic :: iso_c_binding
36
37   USE  mpi
38   USE  kinds,                     ONLY: wp, iwp
39   USE  PMC_general,               ONLY: ClientDef, PMC_MAX_MODELL,PMC_sort, DA_NameDef, DA_Desclen, DA_Namelen,       &
40                                         PMC_G_SetName, PMC_G_GetName, PeDef, ArrayDef
41   USE  PMC_handle_communicator,   ONLY: m_model_comm,m_model_rank,m_model_npes, m_to_client_comm,                     &
42                                         PMC_Server_for_Client, m_world_rank
43   USE   PMC_MPI_wrapper,          ONLY: PMC_Send_to_Client, PMC_Recv_from_Client, PMC_Bcast, PMC_Inter_Bcast,         &
44                                         PMC_Alloc_mem, PMC_Time
45
46   IMPLICIT none
47   PRIVATE
48   SAVE
49
50   TYPE ClientIndexDef
51      INTEGER                                        :: NrPoints
52      INTEGER,DIMENSION(:,:),allocatable             :: index_list_2d
53   END TYPE ClientIndexDef
54
55   TYPE(ClientDef),DIMENSION(PMC_MAX_MODELL)          :: Clients
56   TYPE(ClientIndexDef),DIMENSION(PMC_MAX_MODELL)     :: indClients
57
58   PUBLIC PMC_Server_for_Client
59
60   INTEGER, PARAMETER :: dp = wp
61
62   ! INTERFACE section
63
64   INTERFACE PMC_ServerInit
65      MODULE procedure  PMC_ServerInit
66   END INTERFACE PMC_ServerInit
67
68    INTERFACE PMC_S_Set_2D_index_list
69        MODULE procedure PMC_S_Set_2D_index_list
70    END INTERFACE PMC_S_Set_2D_index_list
71
72    INTERFACE PMC_S_GetNextArray
73        MODULE procedure PMC_S_GetNextArray
74    END INTERFACE PMC_S_GetNextArray
75
76    INTERFACE PMC_S_Set_DataArray
77        MODULE procedure PMC_S_Set_DataArray_2d
78        MODULE procedure PMC_S_Set_DataArray_3d
79    END INTERFACE PMC_S_Set_DataArray
80
81    INTERFACE PMC_S_setInd_and_AllocMem
82        MODULE procedure PMC_S_setInd_and_AllocMem
83    END INTERFACE PMC_S_setInd_and_AllocMem
84
85    INTERFACE PMC_S_FillBuffer
86        MODULE procedure PMC_S_FillBuffer
87    END INTERFACE PMC_S_FillBuffer
88
89    INTERFACE PMC_S_GetData_from_Buffer
90        MODULE procedure PMC_S_GetData_from_Buffer
91    END INTERFACE PMC_S_GetData_from_Buffer
92
93    ! PUBLIC section
94
95    PUBLIC PMC_ServerInit, PMC_S_Set_2D_index_list, PMC_S_GetNextArray, PMC_S_Set_DataArray
96    PUBLIC PMC_S_setInd_and_AllocMem, PMC_S_FillBuffer, PMC_S_GetData_from_Buffer
97
98CONTAINS
99
100   SUBROUTINE PMC_ServerInit
101      IMPLICIT none
102      INTEGER                 :: i
103      INTEGER                 :: j
104      INTEGER                 :: ClientId
105      INTEGER                 :: istat
106
107      do i=1,size(PMC_Server_for_Client)-1
108         if(m_model_comm == 0) write(0,*) 'PMC_Server: Initialize client Id',PMC_Server_for_Client(i)
109
110         ClientId = PMC_Server_for_Client(i)
111
112         Clients(ClientId)%model_comm = m_model_comm
113         Clients(ClientId)%inter_comm = m_to_client_comm(ClientId)
114
115         ! Get rank and size
116         CALL MPI_Comm_rank (Clients(ClientId)%model_comm, Clients(ClientId)%model_rank, istat);
117         CALL MPI_Comm_size (Clients(ClientId)%model_comm, Clients(ClientId)%model_npes, istat);
118         CALL MPI_Comm_remote_size (Clients(ClientId)%inter_comm, Clients(ClientId)%inter_npes, istat);
119
120         ! Intra communicater is used for MPI_Get
121         CALL MPI_Intercomm_merge (Clients(ClientId)%inter_comm, .false., Clients(ClientId)%intra_comm, istat);
122         CALL MPI_Comm_rank (Clients(ClientId)%intra_comm, Clients(ClientId)%intra_rank, istat);
123
124         write(9,*) 'ClientId ',i,ClientId,m_world_rank, Clients(ClientId)%inter_npes
125
126         ALLOCATE (Clients(ClientId)%PEs(Clients(ClientId)%inter_npes))
127
128         do j=1,Clients(ClientId)%inter_npes                                ! Loop over all client PEs
129           NULLIFY(Clients(ClientId)%PEs(j)%Arrays)
130         end do
131
132         CALL Get_DA_names_from_client (ClientId)
133      end do
134
135      return
136   END SUBROUTINE PMC_ServerInit
137
138    SUBROUTINE PMC_S_Set_2D_index_list (ClientId, index_list)
139        IMPLICIT none
140        INTEGER,INTENT(IN)                         :: ClientId
141        INTEGER,DIMENSION(:,:),INTENT(INOUT)       :: index_list      !Index list will be modified in sort, therefore INOUT
142
143        !-- Local variables
144        INTEGER                 :: ip,is,ie,ian,ic,n
145        INTEGER                 :: istat
146
147        if(m_model_rank == 0)   then
148            CALL PMC_sort (index_list, 6)                       ! Sort to ascending Server PE
149            is = 1
150
151            do ip=0,m_model_npes-1
152
153                !       Split into Server PEs
154                ie = is-1                                     !there may be no entry for this PE
155                if(is <= size(index_list,2) .and. ie >= 0)  then
156                    do while ( index_list(6,ie+1) == ip)
157                        ie = ie+1
158                        if( ie == size(index_list,2)) EXIT
159                    end do
160
161                    ian = ie-is+1
162                else
163                    is  = -1
164                    ie  = -2
165                    ian = 0
166                end if
167
168                !       Send data to other server PEs
169
170                if(ip == 0)   then
171                    indClients(ClientId)%NrPoints = ian
172                    if(ian > 0)   then
173                        ALLOCATE (indClients(ClientId)%index_list_2d(6,ian))
174                        indClients(ClientId)%index_list_2d(:,1:ian) = index_list(:,is:ie)
175                    end if
176                else
177                    CALL MPI_Send (ian, 1, MPI_INTEGER, ip, 1000, m_model_comm, istat)
178                    if(ian > 0) then
179                        CALL MPI_Send (index_list(1,is), 6*ian, MPI_INTEGER, ip, 1001,                  &
180                            m_model_comm, istat)
181                    end if
182                end if
183                is = ie+1
184            end do
185        else
186            CALL MPI_Recv (indClients(ClientId)%NrPoints, 1, MPI_INTEGER, 0, 1000, m_model_comm,     &
187                MPI_STATUS_IGNORE, istat)
188            ian = indClients(ClientId)%NrPoints
189             if(ian > 0) then
190                ALLOCATE(indClients(ClientId)%index_list_2d(6,ian))
191                CALL MPI_RECV (indClients(ClientId)%index_list_2d, 6*ian, MPI_INTEGER, 0, 1001,        &
192                    m_model_comm, MPI_STATUS_IGNORE, istat)
193            end if
194        end if
195
196        CALL Set_PE_index_list (ClientId,Clients(ClientId),indClients(ClientId)%index_list_2d,indClients(ClientId)%NrPoints)
197
198        return
199    END SUBROUTINE PMC_S_Set_2D_index_list
200
201    logical function PMC_S_GetNextArray (ClientId, myName,Client_PeIndex)
202        INTEGER,INTENT(IN)                         :: ClientId
203        CHARACTER(len=*),INTENT(OUT)               :: myName
204
205        !-- local variables
206        INTEGER                      :: MyCoupleIndex
207        logical                      :: MyLast
208        CHARACTER(len=DA_Namelen)    :: loName
209        INTEGER,INTENT(IN),optional  :: Client_PeIndex
210
211        loName = ' '
212
213        CALL PMC_G_GetName (clients(ClientId), MyCoupleIndex, loName, MyLast, Client_PeIndex)
214
215        myName    = loName
216
217        PMC_S_GetNextArray = .NOT. MyLast                   ! Return true if valid array
218
219        return
220    END function PMC_S_GetNextArray
221
222    SUBROUTINE PMC_S_Set_DataArray_2d (ClientId, array)
223        IMPLICIT none
224        INTEGER,INTENT(IN)                         :: ClientId
225        REAL(kind=dp),INTENT(IN),DIMENSION(:,:)    :: array
226        !-- local variables
227        INTEGER                           :: NrDims
228        INTEGER,DIMENSION (4)             :: dims
229        INTEGER                           :: dim_order
230        TYPE(c_ptr)                       :: array_adr
231
232        dims = 1
233
234        NrDims    = 2
235        dims(1)   = size(array,1)
236        dims(2)   = size(array,2)
237        dim_order = 2
238
239        array_adr = c_loc(array)
240
241        CALL PMC_S_SetArray (ClientId, NrDims, dims, dim_order, array_adr)
242
243        return
244    END SUBROUTINE PMC_S_Set_DataArray_2d
245
246    SUBROUTINE PMC_S_Set_DataArray_3d (ClientId, array, nz_cl, nz)
247        IMPLICIT none
248        INTEGER,INTENT(IN)                         :: ClientId
249        REAL(kind=dp),INTENT(IN),DIMENSION(:,:,:)  :: array
250        INTEGER,INTENT(IN)                         :: nz_cl
251        INTEGER,INTENT(IN)                         :: nz
252        !-- local variables
253        INTEGER                           :: NrDims
254        INTEGER,DIMENSION (4)             :: dims
255        INTEGER                           :: dim_order
256        TYPE(c_ptr)                       :: array_adr
257
258        dims = 1
259
260        dims      = 0
261        NrDims    = 3
262        dims(1)   = size(array,1)
263        dims(2)   = size(array,2)
264        dims(3)   = size(array,3)
265        dim_order = 33
266        dims(4)   = nz_cl+dims(1)-nz                        ! works for first dimension 1:nz and 0:nz+1
267
268        array_adr = c_loc(array)
269
270        CALL PMC_S_SetArray (ClientId, NrDims, dims, dim_order, array_adr)
271
272        return
273   END SUBROUTINE PMC_S_Set_DataArray_3d
274
275   SUBROUTINE PMC_S_setInd_and_AllocMem (ClientId)
276      IMPLICIT none
277      INTEGER,INTENT(IN)                      :: ClientId
278
279      INTEGER                                 :: i, istat, ierr
280      INTEGER                                 :: arlen, myIndex, tag
281      INTEGER                                 :: rCount                    ! count MPI requests
282      INTEGER(kind=8)                         :: bufsize                   ! Size of MPI data Window
283      TYPE(PeDef),POINTER                     :: aPE
284      TYPE(ArrayDef),POINTER                  :: ar
285      CHARACTER(len=DA_Namelen)               :: myName
286      INTEGER,DIMENSION(1024)                 :: req
287      Type(c_ptr)                             :: base_ptr
288      REAL(kind=wp),DIMENSION(:),POINTER      :: base_array
289      INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize
290
291      myIndex = 1
292      rCount  = 0
293      bufsize = 8
294
295      ! First stride, Compute size and set index
296
297      do i=1,Clients(ClientId)%inter_npes
298         aPE => Clients(ClientId)%PEs(i)
299         tag = 200
300         do while (PMC_S_GetNextArray ( ClientId, myName,i))
301            ar  => aPE%Arrays
302            if(ar%dim_order == 2) then
303               arlen     = aPE%NrEle;                             ! 2D
304            else if(ar%dim_order == 33) then
305               arlen     = aPE%NrEle * ar%A_dim(4);               ! PALM 3D
306            else
307               arlen     = -1
308            end if
309            ar%BufIndex = myIndex
310
311            tag    = tag+1
312            rCount = rCount+1
313            CALL MPI_Isend (myIndex, 1, MPI_INTEGER, i-1, tag, Clients(ClientId)%inter_comm, req(rCount),ierr)
314
315            if(rCount == 1024) then                                  ! Maximum of 1024 outstanding requests
316               CALL MPI_Waitall (rCount, req, MPI_STATUSES_IGNORE, ierr)
317               rCount = 0;
318            end if
319
320            myIndex = myIndex+arlen
321            bufsize = bufsize+arlen
322            ar%BufSize = arlen
323
324         end do
325         if(rCount > 0) then                                          ! Wait for all send completed
326            CALL MPI_Waitall (rCount, req, MPI_STATUSES_IGNORE, ierr)
327         end if
328      end do
329
330      ! Create RMA (One Sided Communication) window for data buffer
331
332      CALL PMC_Alloc_mem (base_array, bufsize, base_ptr)
333      Clients(ClientId)%TotalBufferSize = bufsize*wp       !Total buffer size in Byte
334
335      WinSize = bufsize*wp
336!      write(9,*) 'PMC_S_SetInd_and_Mem ',m_model_rank,Clients(ClientId)%inter_npes,WinSize,bufsize
337      CALL MPI_Win_create (base_array, WinSize, wp, MPI_INFO_NULL, Clients(ClientId)%intra_comm, Clients(ClientId)%BufWin, ierr);
338      CALL MPI_Win_fence (0, Clients(ClientId)%BufWin, ierr);                    !  Open Window to set data
339      CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)
340
341      ! Second stride, Set Buffer pointer
342
343      do i=1,Clients(ClientId)%inter_npes
344         aPE => Clients(ClientId)%PEs(i)
345         do while (PMC_S_GetNextArray ( ClientId, myName,i))
346            ar  => aPE%Arrays
347            ar%SendBuf = c_loc(base_array(ar%BufIndex))                         !kk Adressrechnung ueberlegen
348            if(ar%BufIndex+ar%BufSize > bufsize) then
349               write(0,'(a,i4,4i7,1x,a)') 'Buffer too small ',i,ar%BufIndex,ar%BufSize,ar%BufIndex+ar%BufSize,bufsize,trim(myName)
350               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr)
351            end if
352         end do
353      end do
354
355      return
356   END SUBROUTINE PMC_S_setInd_and_AllocMem
357
358   SUBROUTINE PMC_S_FillBuffer (ClientId, WaitTime)
359      IMPLICIT none
360      INTEGER,INTENT(IN)                      :: ClientId
361      REAL(kind=dp),INTENT(OUT),optional      :: WaitTime
362
363      !-- local variables
364      INTEGER                                 :: ip,ij,istat,ierr
365      INTEGER                                 :: myIndex
366      REAL(kind=dp)                           :: t1,t2
367      TYPE(PeDef),POINTER                     :: aPE
368      TYPE(ArrayDef),POINTER                  :: ar
369      CHARACTER(len=DA_Namelen)               :: myName
370      INTEGER,DIMENSION(1)                    :: buf_shape
371      REAL(kind=wp),POINTER,DIMENSION(:)      :: buf
372      REAL(kind=wp),POINTER,DIMENSION(:,:)    :: data_2d
373      REAL(kind=wp),POINTER,DIMENSION(:,:,:)  :: data_3d
374
375      t1 = PMC_Time()
376      CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)              ! Wait for buffer empty
377      t2 = PMC_Time()
378      if(present(WaitTime)) WaitTime = t2-t1
379
380      do ip=1,Clients(ClientId)%inter_npes
381         aPE => Clients(ClientId)%PEs(ip)
382         do while (PMC_S_GetNextArray ( ClientId, myName,ip))
383            ar  => aPE%Arrays
384            myIndex=1
385            if(ar%dim_order == 2) then
386               buf_shape(1) = aPE%NrEle
387               CALL c_f_pointer(ar%SendBuf, buf, buf_shape)
388               CALL c_f_pointer(ar%data, data_2d, ar%A_dim(1:2))
389               do ij=1,aPE%NrEle
390                  buf(myIndex) = data_2d(aPE%locInd(ij)%j,aPE%locInd(ij)%i)
391                  myIndex = myIndex+1
392               end do
393            else if(ar%dim_order == 33) then
394               buf_shape(1) = aPE%NrEle*ar%A_dim(4)
395               CALL c_f_pointer(ar%SendBuf, buf, buf_shape)
396               CALL c_f_pointer(ar%data, data_3d, ar%A_dim(1:3))
397               do ij=1,aPE%NrEle
398                  buf(myIndex:myIndex+ar%A_dim(4)-1) = data_3d(1:ar%A_dim(4),aPE%locInd(ij)%j,aPE%locInd(ij)%i)
399                  myIndex = myIndex+ar%A_dim(4)
400               end do
401            else
402               write(0,*) "Illegal Order of Dimension ",ar%dim_order
403               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr);
404
405            end if
406          end do
407      end do
408
409      CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)              ! buffer is full
410
411      return
412   END SUBROUTINE PMC_S_FillBuffer
413
414   SUBROUTINE PMC_S_GetData_from_Buffer (ClientId, WaitTime)
415      IMPLICIT none
416      INTEGER,INTENT(IN)                      :: ClientId
417      REAL(kind=dp),INTENT(OUT),optional      :: WaitTime
418
419      !-- local variables
420      INTEGER                                 :: ip,ij,istat,ierr
421      INTEGER                                 :: myIndex
422      REAL(kind=dp)                           :: t1,t2
423      TYPE(PeDef),POINTER                     :: aPE
424      TYPE(ArrayDef),POINTER                  :: ar
425      CHARACTER(len=DA_Namelen)               :: myName
426      INTEGER,DIMENSION(1)                    :: buf_shape
427      REAL(kind=wp),POINTER,DIMENSION(:)      :: buf
428      REAL(kind=wp),POINTER,DIMENSION(:,:)    :: data_2d
429      REAL(kind=wp),POINTER,DIMENSION(:,:,:)  :: data_3d
430
431      t1 = PMC_Time()
432      CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)              ! Wait for MPI_Put from client
433      t2 = PMC_Time()
434      if(present(WaitTime)) WaitTime = t2-t1
435
436      do ip=1,Clients(ClientId)%inter_npes
437         aPE => Clients(ClientId)%PEs(ip)
438         do while (PMC_S_GetNextArray ( ClientId, myName,ip))
439            ar  => aPE%Arrays
440            myIndex=1
441            if(ar%dim_order == 2) then
442               buf_shape(1) = aPE%NrEle
443               CALL c_f_pointer(ar%SendBuf, buf, buf_shape)
444               CALL c_f_pointer(ar%data, data_2d, ar%A_dim(1:2))
445               do ij=1,aPE%NrEle
446                  data_2d(aPE%locInd(ij)%j,aPE%locInd(ij)%i) = buf(myIndex)
447                  myIndex = myIndex+1
448               end do
449            else if(ar%dim_order == 33) then
450               buf_shape(1) = aPE%NrEle*ar%A_dim(4)
451               CALL c_f_pointer(ar%SendBuf, buf, buf_shape)
452               CALL c_f_pointer(ar%data, data_3d, ar%A_dim(1:3))
453               do ij=1,aPE%NrEle
454                  data_3d(1:ar%A_dim(4),aPE%locInd(ij)%j,aPE%locInd(ij)%i) = buf(myIndex:myIndex+ar%A_dim(4)-1)
455                  myIndex = myIndex+ar%A_dim(4)
456               end do
457            else
458               write(0,*) "Illegal Order of Dimension ",ar%dim_order
459               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr);
460
461            end if
462          end do
463      end do
464
465      CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)              ! data copy finished, buffer is free for use agein
466
467        return
468   END SUBROUTINE PMC_S_GetData_from_Buffer
469
470! Private SUBROUTINEs
471
472   SUBROUTINE Get_DA_names_from_client (ClientId)
473        IMPLICIT none
474        INTEGER,INTENT(IN)                    :: ClientId
475        !-- local variables
476        type(DA_NameDef)                      :: myName
477
478        !   Get Data Array Description and Name from Client
479
480        do
481            CALL PMC_Bcast ( myName%couple_index, 0, comm=m_to_client_comm(ClientId))
482            if(myName%couple_index == -1) EXIT
483            CALL PMC_Bcast ( myName%ServerDesc,   0, comm=m_to_client_comm(ClientId))
484            CALL PMC_Bcast ( myName%NameOnServer, 0, comm=m_to_client_comm(ClientId))
485            CALL PMC_Bcast ( myName%ClientDesc,   0, comm=m_to_client_comm(ClientId))
486            CALL PMC_Bcast ( myName%NameOnClient, 0, comm=m_to_client_comm(ClientId))
487
488            CALL PMC_G_SetName (clients(ClientID), myName%couple_index, myName%NameOnServer )
489        end do
490
491        return
492   END SUBROUTINE Get_DA_names_from_client
493
494   SUBROUTINE PMC_S_SetArray (ClientId, NrDims, dims, dim_order, array_adr)
495      IMPLICIT none
496
497      INTEGER,INTENT(IN)                      :: ClientId
498      INTEGER,INTENT(IN)                      :: NrDims
499      INTEGER,INTENT(IN),DIMENSION(:)         :: dims
500      INTEGER,INTENT(IN)                      :: dim_order
501      TYPE(c_ptr),INTENT(IN)                  :: array_adr
502
503      INTEGER                                 :: i
504      TYPE(PeDef),POINTER                     :: aPE
505      TYPE(ArrayDef),POINTER                  :: ar
506      CHARACTER(len=DA_Namelen)               :: myName
507
508      !  Set Array for Client interPE 0
509
510       do i=1,Clients(ClientId)%inter_npes
511          aPE => Clients(ClientId)%PEs(i)
512          ar  => aPE%Arrays
513          ar%NrDims    = NrDims
514          ar%A_dim     = dims
515          ar%dim_order = dim_order
516          ar%data      = array_adr
517       end do
518
519      return
520   END SUBROUTINE PMC_S_SetArray
521
522
523    SUBROUTINE Set_PE_index_list (ClientId, myClient,index_list,NrP)
524       IMPLICIT none
525
526       INTEGER,INTENT(IN)                      :: ClientId
527       TYPE(ClientDef),INTENT(INOUT)           :: myClient
528       INTEGER,INTENT(IN),DIMENSION(:,:)       :: index_list
529       INTEGER,INTENT(IN)                      :: NrP
530
531!--    local variables
532       INTEGER                                 :: i,j,ind,ierr,i2
533       TYPE(PeDef),POINTER                     :: aPE
534       INTEGER                                 :: RemPE
535       INTEGER,DIMENSION(myClient%inter_npes)  :: RemInd
536       INTEGER,DIMENSION(:),POINTER            :: RemIndw
537       INTEGER,DIMENSION(:),POINTER            :: RLdef
538       INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize
539       INTEGER                                 :: indWin,indWin2
540
541       ! First, count entries for every remote client PE
542
543       do i=1,myClient%inter_npes
544          aPE => myClient%PEs(i)
545          aPE%NrEle = 0
546       end do
547
548       do j=1,NrP                                ! loop over number of cells coarse grid
549          RemPE = index_list(5,j)+1              ! Pe number remote PE
550          aPE => myClient%PEs(RemPE)
551          aPE% NrEle = aPE% NrEle+1              ! Increment Number of elements for this client Pe
552       end do
553
554       do i=1,myClient%inter_npes
555          aPE => myClient%PEs(i)
556          ALLOCATE(aPE%locInd(aPE%NrEle))
557       end do
558
559       RemInd = 0
560
561       ! Second, Create lists
562
563       do j=1,NrP                                ! loop over number of cells coarse grid
564          RemPE = index_list(5,j)+1              ! Pe number remote PE
565          aPE => myClient%PEs(RemPE)
566          RemInd(RemPE)     = RemInd(RemPE)+1
567          ind               = RemInd(RemPE)
568          aPE%locInd(ind)%i = index_list(1,j)
569          aPE%locInd(ind)%j = index_list(2,j)
570       end do
571
572       !  Prepare Number of Elements for Client PEs
573       CALL PMC_Alloc_mem (RLdef, myClient%inter_npes*2)
574       WinSize = myClient%inter_npes*c_sizeof(i)*2   ! Number of Client PEs * size of INTEGER (i just arbitrary INTEGER)
575
576       CALL MPI_Win_create (RLdef, WinSize, iwp, MPI_INFO_NULL, myClient%intra_comm, indWin, ierr);
577       CALL MPI_Win_fence (0, indWin, ierr);         !  Open Window to set data
578
579       RLdef(1) = 0                                  ! Index on Remote PE 0
580       RLdef(2) = RemInd(1)                          ! Number of Elements on Rem PE 0
581
582       do i=2,myClient%inter_npes                    ! Reserve Buffer for index array
583          i2          = (i-1)*2+1
584          RLdef(i2)   = RLdef(i2-2) + RLdef(i2-1)*2  ! Index on Remote PE
585          RLdef(i2+1) = RemInd(i)                    ! Number of Elements on Remote PE
586       end do
587
588       CALL MPI_Win_fence (0, indWin, ierr);         ! Close Window to allow client to access data
589       CALL MPI_Win_fence (0, indWin, ierr);         ! Client has retrieved data
590
591       i2 = 2*myClient%inter_npes-1
592       WinSize = (RLdef(i2)+RLdef(i2+1))*2
593       WinSize = max(WinSize,1)                      ! Make sure, MPI_Alloc_mem works
594
595       CALL PMC_Alloc_mem (RemIndw, int(WinSize))
596
597       CALL MPI_Barrier (m_model_comm, ierr)
598       CALL MPI_Win_create (RemIndw, WinSize*c_sizeof(i), iwp, MPI_INFO_NULL, myClient%intra_comm, indWin2, ierr);
599
600       CALL MPI_Win_fence (0, indWin2, ierr);         !  Open Window to set data
601       do j=1,NrP                                ! this loop creates the 2D index list
602          RemPE = index_list(5,j)+1              ! Pe number remote PE
603          aPE => myClient%PEs(RemPE)
604          i2    = RemPE*2-1
605          ind   = RLdef(i2)+1
606          RemIndw(ind)   = index_list(3,j)
607          RemIndw(ind+1) = index_list(4,j)
608          RLdef(i2) = RLdef(i2)+2
609       end do
610       CALL MPI_Win_fence (0, indWin2, ierr);      !all data set
611
612       CALL MPI_Barrier(myClient%intra_comm, ierr) ! Dont know why, but this barrier is necessary before we can free the windows
613
614       CALL MPI_Win_free(indWin, ierr)
615       CALL MPI_Win_free(indWin2, ierr)
616
617!      Sollte funktionieren, Problem mit MPI implementation
618!      https://www.lrz.de/services/software/parallel/mpi/onesided
619!       CALL MPI_Free_mem (RemIndw, ierr)
620
621       return
622    END SUBROUTINE Set_PE_index_list
623
624END MODULE pmc_server
Note: See TracBrowser for help on using the repository browser.