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

Last change on this file since 1779 was 1779, checked in by raasch, 8 years ago

pmc array management changed from linked list to sequential loop; further small changes and cosmetics for the pmc

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