source: palm/trunk/SOURCE/pmc_mpi_wrapper.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: 18.3 KB
Line 
1MODULE pmc_mpi_wrapper
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_mpi_wrapper.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! MPI Wrapper of Palm Model Coupler
33!------------------------------------------------------------------------------!
34
35   use, intrinsic :: iso_c_binding
36
37   USE  mpi
38   USE  kinds,         ONLY: wp
39   USE  PMC_handle_communicator, ONLY: m_to_server_comm, m_to_client_comm, m_model_comm, m_model_rank
40   IMPLICIT none
41   PRIVATE
42   SAVE
43
44   INTEGER, PARAMETER :: dp = wp
45
46
47   ! INTERFACE section
48
49   INTERFACE PMC_Send_to_Server
50      MODULE PROCEDURE PMC_Send_to_Server_INTEGER
51      MODULE PROCEDURE PMC_Send_to_Server_INTEGER_2
52      MODULE PROCEDURE PMC_Send_to_Server_real_r1
53      MODULE PROCEDURE PMC_Send_to_Server_real_r2
54      MODULE PROCEDURE PMC_Send_to_Server_real_r3
55   END INTERFACE PMC_Send_to_Server
56
57   INTERFACE PMC_Recv_from_Server
58      MODULE PROCEDURE PMC_Recv_from_Server_INTEGER
59      MODULE PROCEDURE PMC_Recv_from_Server_real_r1
60      MODULE PROCEDURE PMC_Recv_from_Server_real_r2
61      MODULE PROCEDURE PMC_Recv_from_Server_real_r3
62   END INTERFACE PMC_Recv_from_Server
63
64   INTERFACE PMC_Send_to_Client
65      MODULE PROCEDURE PMC_Send_to_Client_INTEGER
66      MODULE PROCEDURE PMC_Send_to_Client_real_r1
67      MODULE PROCEDURE PMC_Send_to_Client_real_r2
68      MODULE PROCEDURE PMC_Send_to_Client_real_r3
69   END INTERFACE PMC_Send_to_Client
70
71   INTERFACE PMC_Recv_from_Client
72      MODULE PROCEDURE PMC_Recv_from_Client_INTEGER
73      MODULE PROCEDURE PMC_Recv_from_Client_INTEGER_2
74      MODULE PROCEDURE PMC_Recv_from_Client_real_r1
75      MODULE PROCEDURE PMC_Recv_from_Client_real_r2
76      MODULE PROCEDURE PMC_Recv_from_Client_real_r3
77   END INTERFACE PMC_Recv_from_Client
78
79   INTERFACE PMC_Bcast
80      MODULE PROCEDURE PMC_Bcast_INTEGER
81      MODULE PROCEDURE PMC_Bcast_character
82   END INTERFACE PMC_Bcast
83
84   INTERFACE PMC_Inter_Bcast
85      MODULE PROCEDURE PMC_Inter_Bcast_INTEGER_1
86   END INTERFACE PMC_Inter_Bcast
87
88   INTERFACE PMC_Alloc_mem
89      MODULE PROCEDURE PMC_Alloc_mem_INTEGER_1
90      MODULE PROCEDURE PMC_Alloc_mem_Real_1
91   END INTERFACE PMC_Alloc_mem
92
93   INTERFACE PMC_TIME
94      MODULE PROCEDURE PMC_TIME
95   END INTERFACE PMC_TIME
96
97   PUBLIC PMC_Send_to_Server, PMC_Recv_from_Server
98   PUBLIC PMC_Send_to_Client, PMC_Recv_from_Client
99   PUBLIC PMC_Bcast, PMC_Inter_Bcast, PMC_Alloc_mem
100   PUBLIC PMC_TIME
101
102CONTAINS
103
104   SUBROUTINE  PMC_Send_to_Server_INTEGER (buf, n, Server_rank, tag, ierr)
105      IMPLICIT     none
106      INTEGER, DIMENSION(:), INTENT(IN)         :: buf
107      INTEGER, INTENT(IN)                       :: n
108      INTEGER, INTENT(IN)                       :: Server_rank
109      INTEGER, INTENT(IN)                       :: tag
110      INTEGER, INTENT(OUT)                      :: ierr
111   
112      ierr = 0
113      CALL MPI_Send (buf, n, MPI_INTEGER, Server_rank, tag, m_to_server_comm, ierr)
114   
115      return
116   END SUBROUTINE  PMC_Send_to_Server_INTEGER
117
118   SUBROUTINE  PMC_Recv_from_Server_INTEGER (buf, n, Server_rank, tag, ierr)
119      IMPLICIT     none
120      INTEGER, DIMENSION(:), INTENT(OUT)        :: buf
121      INTEGER, INTENT(IN)                       :: n
122      INTEGER, INTENT(IN)                       :: Server_rank
123      INTEGER, INTENT(IN)                       :: tag
124      INTEGER, INTENT(OUT)                      :: ierr
125
126      ierr = 0
127      CALL MPI_Recv (buf, n, MPI_INTEGER, Server_rank, tag, m_to_server_comm, &
128         MPI_STATUS_IGNORE, ierr)
129
130      return
131   END SUBROUTINE  PMC_Recv_from_Server_INTEGER
132
133   SUBROUTINE  PMC_Send_to_Server_INTEGER_2 (buf, n, Server_rank, tag, ierr)
134      IMPLICIT     none
135      INTEGER, DIMENSION(:,:), INTENT(IN)       :: buf
136      INTEGER, INTENT(IN)                       :: n
137      INTEGER, INTENT(IN)                       :: Server_rank
138      INTEGER, INTENT(IN)                       :: tag
139      INTEGER, INTENT(OUT)                      :: ierr
140
141      ierr = 0
142      CALL MPI_Send (buf, n, MPI_INTEGER, Server_rank, tag, m_to_server_comm, ierr)
143
144      return
145   END SUBROUTINE  PMC_Send_to_Server_INTEGER_2
146
147   SUBROUTINE  PMC_Send_to_Server_real_r1 (buf, n, Server_rank, tag, ierr)
148      IMPLICIT     none
149      REAL(kind=dp), DIMENSION(:), INTENT(IN)   :: buf
150      INTEGER, INTENT(IN)                       :: n
151      INTEGER, INTENT(IN)                       :: Server_rank
152      INTEGER, INTENT(IN)                       :: tag
153      INTEGER, INTENT(OUT)                      :: ierr
154
155      ierr = 0
156      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, ierr)
157
158      return
159   END SUBROUTINE  PMC_Send_to_Server_real_r1
160
161   SUBROUTINE  PMC_Recv_from_Server_real_r1 (buf, n, Server_rank, tag, ierr)
162      IMPLICIT     none
163      REAL(kind=dp), DIMENSION(:), INTENT(OUT)  :: buf
164      INTEGER, INTENT(IN)                       :: n
165      INTEGER, INTENT(IN)                       :: Server_rank
166      INTEGER, INTENT(IN)                       :: tag
167      INTEGER, INTENT(OUT)                      :: ierr
168
169      ierr = 0
170      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, &
171         MPI_STATUS_IGNORE, ierr)
172
173      return
174   END SUBROUTINE  PMC_Recv_from_Server_real_r1
175
176   SUBROUTINE  PMC_Send_to_Server_real_r2 (buf, n, Server_rank, tag, ierr)
177      IMPLICIT     none
178      REAL(kind=dp), DIMENSION(:,:), INTENT(IN) :: buf
179      INTEGER, INTENT(IN)                       :: n
180      INTEGER, INTENT(IN)                       :: Server_rank
181      INTEGER, INTENT(IN)                       :: tag
182      INTEGER, INTENT(OUT)                      :: ierr
183
184      ierr = 0
185      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, ierr)
186
187      return
188   END SUBROUTINE  PMC_Send_to_Server_real_r2
189
190   SUBROUTINE  PMC_Recv_from_Server_real_r2 (buf, n, Server_rank, tag, ierr)
191      IMPLICIT     none
192      REAL(kind=dp), DIMENSION(:,:),INTENT(OUT) :: buf
193      INTEGER, INTENT(IN)                       :: n
194      INTEGER, INTENT(IN)                       :: Server_rank
195      INTEGER, INTENT(IN)                       :: tag
196      INTEGER, INTENT(OUT)                      :: ierr
197
198      ierr = 0
199      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, &
200         MPI_STATUS_IGNORE, ierr)
201
202      return
203   END SUBROUTINE  PMC_Recv_from_Server_real_r2
204
205   SUBROUTINE  PMC_Send_to_Server_real_r3 (buf, n, Server_rank, tag, ierr)
206      IMPLICIT     none
207      REAL(kind=dp), DIMENSION(:,:,:), INTENT(IN) :: buf
208      INTEGER, INTENT(IN)                         :: n
209      INTEGER, INTENT(IN)                         :: Server_rank
210      INTEGER, INTENT(IN)                         :: tag
211      INTEGER, INTENT(OUT)                        :: ierr
212
213      ierr = 0
214      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, ierr)
215
216      return
217   END SUBROUTINE  PMC_Send_to_Server_real_r3
218
219   SUBROUTINE  PMC_Recv_from_Server_real_r3 (buf, n, Server_rank, tag, ierr)
220      IMPLICIT     none
221      REAL(kind=dp), DIMENSION(:,:,:),INTENT(OUT) :: buf
222      INTEGER, INTENT(IN)                         :: n
223      INTEGER, INTENT(IN)                         :: Server_rank
224      INTEGER, INTENT(IN)                         :: tag
225      INTEGER, INTENT(OUT)                        :: ierr
226
227      ierr = 0
228      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Server_rank, tag, m_to_server_comm, &
229         MPI_STATUS_IGNORE, ierr)
230
231      return
232   END SUBROUTINE  PMC_Recv_from_Server_real_r3
233
234
235   SUBROUTINE  PMC_Send_to_Client_INTEGER (Client_id, buf, n, Client_rank, tag, ierr)
236      IMPLICIT     none
237      INTEGER, INTENT(IN)                       :: Client_id
238      INTEGER, DIMENSION(:), INTENT(IN)         :: buf
239      INTEGER, INTENT(IN)                       :: n
240      INTEGER, INTENT(IN)                       :: Client_rank
241      INTEGER, INTENT(IN)                       :: tag
242      INTEGER, INTENT(OUT)                      :: ierr
243
244      ierr = 0
245      CALL MPI_Send (buf, n, MPI_INTEGER, Client_rank, tag, m_to_client_comm(Client_id), ierr)
246
247      return
248   END SUBROUTINE  PMC_Send_to_Client_INTEGER
249
250   SUBROUTINE  PMC_Recv_from_Client_INTEGER (Client_id, buf, n, Client_rank, tag, ierr)
251      IMPLICIT     none
252      INTEGER, INTENT(IN)                       :: Client_id
253      INTEGER, DIMENSION(:), INTENT(INOUT)      :: buf
254      INTEGER, INTENT(IN)                       :: n
255      INTEGER, INTENT(IN)                       :: Client_rank
256      INTEGER, INTENT(IN)                       :: tag
257      INTEGER, INTENT(OUT)                      :: ierr
258
259      ierr = 0
260      CALL MPI_Recv (buf, n, MPI_INTEGER, Client_rank, tag, m_to_client_comm(Client_id), &
261         MPI_STATUS_IGNORE, ierr)
262
263      return
264   END SUBROUTINE  PMC_Recv_from_Client_INTEGER
265
266   SUBROUTINE  PMC_Recv_from_Client_INTEGER_2 (Client_id, buf, n, Client_rank, tag, ierr)
267      IMPLICIT     none
268      INTEGER, INTENT(IN)                       :: Client_id
269      INTEGER, DIMENSION(:,:), INTENT(OUT)      :: buf
270      INTEGER, INTENT(IN)                       :: n
271      INTEGER, INTENT(IN)                       :: Client_rank
272      INTEGER, INTENT(IN)                       :: tag
273      INTEGER, INTENT(OUT)                      :: ierr
274
275      ierr = 0
276      CALL MPI_Recv (buf, n, MPI_INTEGER, Client_rank, tag, m_to_client_comm(Client_id), &
277         MPI_STATUS_IGNORE, ierr)
278
279      return
280   END SUBROUTINE  PMC_Recv_from_Client_INTEGER_2
281
282   SUBROUTINE  PMC_Send_to_Client_real_r1 (Client_id, buf, n, Client_rank, tag, ierr)
283      IMPLICIT     none
284      INTEGER, INTENT(IN)                       :: Client_id
285      REAL(kind=dp), DIMENSION(:), INTENT(IN)   :: buf
286      INTEGER, INTENT(IN)                       :: n
287      INTEGER, INTENT(IN)                       :: Client_rank
288      INTEGER, INTENT(IN)                       :: tag
289      INTEGER, INTENT(OUT)                      :: ierr
290
291      ierr = 0
292      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
293         ierr)
294
295      return
296   END SUBROUTINE  PMC_Send_to_Client_real_r1
297
298   SUBROUTINE  PMC_Recv_from_Client_real_r1 (Client_id, buf, n, Client_rank, tag, ierr)
299      IMPLICIT     none
300      INTEGER, INTENT(IN)                       :: Client_id
301      REAL(kind=dp), DIMENSION(:), INTENT(INOUT):: buf
302      INTEGER, INTENT(IN)                       :: n
303      INTEGER, INTENT(IN)                       :: Client_rank
304      INTEGER, INTENT(IN)                       :: tag
305      INTEGER, INTENT(OUT)                      :: ierr
306
307      ierr = 0
308      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
309         MPI_STATUS_IGNORE, ierr)
310
311      return
312   END SUBROUTINE  PMC_Recv_from_Client_real_r1
313
314   SUBROUTINE  PMC_Send_to_Client_real_r2 (Client_id, buf, n, Client_rank, tag, ierr)
315      IMPLICIT     none
316      INTEGER, INTENT(IN)                       :: Client_id
317      REAL(kind=dp), DIMENSION(:,:), INTENT(IN) :: buf
318      INTEGER, INTENT(IN)                       :: n
319      INTEGER, INTENT(IN)                       :: Client_rank
320      INTEGER, INTENT(IN)                       :: tag
321      INTEGER, INTENT(OUT)                      :: ierr
322
323      ierr = 0
324      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
325         ierr)
326
327      return
328   END SUBROUTINE  PMC_Send_to_Client_real_r2
329
330   SUBROUTINE  PMC_Recv_from_Client_real_r2 (Client_id, buf, n, Client_rank, tag, ierr)
331      IMPLICIT     none
332      INTEGER, INTENT(IN)                       :: Client_id
333      REAL(kind=dp), DIMENSION(:,:), INTENT(OUT):: buf
334      INTEGER, INTENT(IN)                       :: n
335      INTEGER, INTENT(IN)                       :: Client_rank
336      INTEGER, INTENT(IN)                       :: tag
337      INTEGER, INTENT(OUT)                      :: ierr
338
339      ierr = 0
340      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
341         MPI_STATUS_IGNORE, ierr)
342
343      return
344   END SUBROUTINE  PMC_Recv_from_Client_real_r2
345
346   SUBROUTINE  PMC_Send_to_Client_real_r3 (Client_id, buf, n, Client_rank, tag, ierr)
347      IMPLICIT     none
348      INTEGER, INTENT(IN)                         :: Client_id
349      REAL(kind=dp), DIMENSION(:,:,:), INTENT(IN) :: buf
350      INTEGER, INTENT(IN)                         :: n
351      INTEGER, INTENT(IN)                         :: Client_rank
352      INTEGER, INTENT(IN)                         :: tag
353      INTEGER, INTENT(OUT)                        :: ierr
354
355      ierr = 0
356      CALL MPI_Send (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
357         ierr)
358
359      return
360   END SUBROUTINE  PMC_Send_to_Client_real_r3
361
362   SUBROUTINE  PMC_Recv_from_Client_real_r3 (Client_id, buf, n, Client_rank, tag, ierr)
363      IMPLICIT     none
364      INTEGER, INTENT(IN)                         :: Client_id
365      REAL(kind=dp), DIMENSION(:,:,:), INTENT(OUT):: buf
366      INTEGER, INTENT(IN)                         :: n
367      INTEGER, INTENT(IN)                         :: Client_rank
368      INTEGER, INTENT(IN)                         :: tag
369      INTEGER, INTENT(OUT)                        :: ierr
370
371      ierr = 0
372      CALL MPI_Recv (buf, n, MPI_DOUBLE_PRECISION, Client_rank, tag, m_to_client_comm(Client_id), &
373         MPI_STATUS_IGNORE, ierr)
374
375      return
376   END SUBROUTINE  PMC_Recv_from_Client_real_r3
377
378   SUBROUTINE  PMC_Bcast_INTEGER (buf, root_pe, comm, ierr)
379      IMPLICIT     none
380      INTEGER, INTENT(INOUT)                      :: buf
381      INTEGER, INTENT(IN)                         :: root_pe
382      INTEGER, INTENT(IN),optional                :: comm
383      INTEGER, INTENT(OUT),optional               :: ierr
384      !-- local variables
385      INTEGER                                     :: myComm
386      INTEGER                                     :: myErr
387
388      if(present (comm))  then
389         myComm = comm
390      else
391         myComm = m_model_comm
392      end if
393
394      CALL MPI_Bcast (buf, 1, MPI_INTEGER, root_pe, myComm, myErr)
395
396      if(present (ierr))  then
397         ierr = myErr
398      end if
399
400      return
401   END SUBROUTINE  PMC_Bcast_INTEGER
402
403   SUBROUTINE  PMC_Bcast_character (buf, root_pe, comm, ierr)
404      IMPLICIT     none
405      character(len=*), INTENT(INOUT)             :: buf
406      INTEGER, INTENT(IN)                         :: root_pe
407      INTEGER, INTENT(IN),optional                :: comm
408      INTEGER, INTENT(OUT),optional               :: ierr
409      !-- local variables
410      INTEGER                                     :: myComm
411      INTEGER                                     :: myErr
412
413      if(present (comm))  then
414         myComm = comm
415      else
416         myComm = m_model_comm
417      end if
418
419      CALL MPI_Bcast (buf, len(buf), MPI_Character, root_pe, myComm, myErr)
420
421      if(present (ierr))  then
422         ierr = myErr
423      end if
424
425      return
426   END SUBROUTINE  PMC_Bcast_character
427
428   SUBROUTINE  PMC_Inter_Bcast_INTEGER_1 (buf, Client_id, ierr)
429      IMPLICIT     none
430      INTEGER, INTENT(INOUT),DIMENSION(:)         :: buf
431      INTEGER, INTENT(IN),optional                :: Client_id
432      INTEGER, INTENT(OUT),optional               :: ierr
433      !-- local variables
434      INTEGER                                     :: myComm
435      INTEGER                                     :: myErr
436      INTEGER                                     :: root_pe
437
438      !   PE 0 Server Broadcast to all Client PE's
439
440      if(present (Client_id))  then
441         myComm  = m_to_client_comm(Client_id)
442         if(m_model_rank == 0)  then
443            root_pe = MPI_ROOT
444         else
445            root_pe = MPI_PROC_NULL
446         end if
447      else
448         myComm  = m_to_server_comm
449         root_pe = 0
450      end if
451
452      CALL MPI_Bcast (buf, size(buf), MPI_INTEGER, root_pe, myComm, myErr)
453
454      if(present (ierr))  then
455         ierr = myErr
456      end if
457
458      return
459   END SUBROUTINE  PMC_Inter_Bcast_INTEGER_1
460
461!  Allocate  Memory with MPI_Alloc_mem using intermediate C-pointer
462
463   SUBROUTINE  PMC_Alloc_mem_INTEGER_1 (iarray, idim1)
464      IMPLICIT     none
465      INTEGER,DIMENSION(:),POINTER,INTENT(INOUT) :: iarray
466      INTEGER,INTENT(IN)                         :: idim1
467
468      Type(c_ptr)                             :: p_myInd
469      INTEGER,DIMENSION(1)                    :: aShape
470      INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize
471      INTEGER                                 :: ierr
472
473      WinSize = idim1*c_sizeof(ierr)                          ! Length of INTEGER
474
475      CALL MPI_Alloc_mem  (WinSize , MPI_INFO_NULL, p_myInd, ierr);
476      aShape(1) = idim1
477      CALL c_f_pointer(p_myInd,iarray,aShape)
478
479      return
480   END SUBROUTINE  PMC_Alloc_mem_INTEGER_1
481
482   SUBROUTINE  PMC_Alloc_mem_Real_1 (array, idim1, base_ptr)
483      IMPLICIT     none
484      REAL(kind=wp),DIMENSION(:),POINTER,INTENT(INOUT) :: array
485      INTEGER(kind=8),INTENT(IN)                       :: idim1
486      Type(c_ptr),INTENT(OUT),optional                 :: base_ptr
487
488
489      Type(c_ptr)                             :: p_myInd
490      INTEGER,DIMENSION(1)                    :: aShape
491      INTEGER(KIND=MPI_ADDRESS_KIND)          :: WinSize
492      INTEGER                                 :: ierr
493
494      WinSize = idim1*wp                          ! Length of INTEGER
495
496      CALL MPI_Alloc_mem  (WinSize , MPI_INFO_NULL, p_myInd, ierr);
497      aShape(1) = idim1
498      CALL c_f_pointer(p_myInd,array,aShape)
499
500      if(present(base_ptr))   then
501         base_ptr = p_myInd
502      end if
503
504      return
505   END SUBROUTINE  PMC_Alloc_mem_Real_1
506
507   FUNCTION PMC_TIME ()
508      REAL(kind=wp)          :: PMC_TIME
509
510      PMC_TIME = MPI_Wtime ()
511
512      return
513
514    END FUNCTION PMC_TIME
515
516 END MODULE pmc_mpi_wrapper
Note: See TracBrowser for help on using the repository browser.