1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6! MPI-3.0 A.3
7module pmpi_f08
8use,intrinsic :: iso_c_binding, only: c_ptr
9use :: mpi_f08_types
10use :: mpi_f08_compile_constants
11use :: mpi_f08_link_constants
12use :: mpi_f08_callbacks
13
14implicit none
15
16interface PMPI_Bsend
17    subroutine PMPIR_Bsend_f08ts(buf, count, datatype, dest, tag, comm, ierror)
18        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
19        implicit none
20        type(*), dimension(..), intent(in) :: buf
21        integer, intent(in) :: count, dest, tag
22        type(MPI_Datatype), intent(in) :: datatype
23        type(MPI_Comm), intent(in) :: comm
24        integer, optional, intent(out) :: ierror
25    end subroutine PMPIR_Bsend_f08ts
26end interface PMPI_Bsend
27
28interface PMPI_Bsend_init
29    subroutine PMPIR_Bsend_init_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
30        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
31        implicit none
32        type(*), dimension(..) :: buf
33        integer, intent(in) :: count, dest, tag
34        type(MPI_Datatype), intent(in) :: datatype
35        type(MPI_Comm), intent(in) :: comm
36        type(MPI_Request), intent(out) :: request
37        integer, optional, intent(out) :: ierror
38    end subroutine PMPIR_Bsend_init_f08ts
39end interface PMPI_Bsend_init
40
41interface PMPI_Buffer_attach
42    subroutine PMPIR_Buffer_attach_f08ts(buffer, size, ierror)
43        implicit none
44        type(*), dimension(..) :: buffer
45        integer, intent(in) :: size
46        integer, optional, intent(out) :: ierror
47    end subroutine PMPIR_Buffer_attach_f08ts
48end interface PMPI_Buffer_attach
49
50interface PMPI_Buffer_detach
51    subroutine PMPIR_Buffer_detach_f08(buffer_addr, size, ierror)
52        use, intrinsic :: iso_c_binding, only : c_ptr
53        implicit none
54        type(c_ptr) :: buffer_addr
55        integer, intent(out) :: size
56        integer, optional, intent(out) :: ierror
57    end subroutine PMPIR_Buffer_detach_f08
58end interface PMPI_Buffer_detach
59
60interface PMPI_Cancel
61    subroutine PMPIR_Cancel_f08(request, ierror)
62        use :: mpi_f08_types, only : MPI_Request
63        implicit none
64        type(MPI_Request), intent(in) :: request
65        integer, optional, intent(out) :: ierror
66    end subroutine PMPIR_Cancel_f08
67end interface PMPI_Cancel
68
69interface PMPI_Get_count
70    subroutine PMPIR_Get_count_f08(status, datatype, count, ierror)
71        use :: mpi_f08_types, only : MPI_Status, MPI_Datatype
72        implicit none
73        type(MPI_Status), intent(in) :: status
74        type(MPI_Datatype), intent(in) :: datatype
75        integer, intent(out) :: count
76        integer, optional, intent(out) :: ierror
77    end subroutine PMPIR_Get_count_f08
78end interface PMPI_Get_count
79
80interface PMPI_Ibsend
81    subroutine PMPIR_Ibsend_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
82        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
83        implicit none
84        type(*), dimension(..), intent(in), asynchronous :: buf
85        integer, intent(in) :: count, dest, tag
86        type(MPI_Datatype), intent(in) :: datatype
87        type(MPI_Comm), intent(in) :: comm
88        type(MPI_Request), intent(out) :: request
89        integer, optional, intent(out) :: ierror
90    end subroutine PMPIR_Ibsend_f08ts
91end interface PMPI_Ibsend
92
93interface PMPI_Iprobe
94    subroutine PMPIR_Iprobe_f08(source, tag, comm, flag, status, ierror)
95        use :: mpi_f08_types, only : MPI_Comm, MPI_Status
96        implicit none
97        integer, intent(in) :: source, tag
98        type(MPI_Comm), intent(in) :: comm
99        logical, intent(out) :: flag
100        type(MPI_Status) :: status
101        integer, optional, intent(out) :: ierror
102    end subroutine PMPIR_Iprobe_f08
103end interface PMPI_Iprobe
104
105interface PMPI_Irecv
106    subroutine PMPIR_Irecv_f08ts(buf, count, datatype, source, tag, comm, request, ierror)
107        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
108        implicit none
109        type(*), dimension(..), asynchronous :: buf
110        integer, intent(in) :: count, source, tag
111        type(MPI_Datatype), intent(in) :: datatype
112        type(MPI_Comm), intent(in) :: comm
113        type(MPI_Request), intent(out) :: request
114        integer, optional, intent(out) :: ierror
115    end subroutine PMPIR_Irecv_f08ts
116end interface PMPI_Irecv
117
118interface PMPI_Irsend
119    subroutine PMPIR_Irsend_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
120        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
121        implicit none
122        type(*), dimension(..), intent(in), asynchronous :: buf
123        integer, intent(in) :: count, dest, tag
124        type(MPI_Datatype), intent(in) :: datatype
125        type(MPI_Comm), intent(in) :: comm
126        type(MPI_Request), intent(out) :: request
127        integer, optional, intent(out) :: ierror
128    end subroutine PMPIR_Irsend_f08ts
129end interface PMPI_Irsend
130
131interface PMPI_Isend
132    subroutine PMPIR_Isend_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
133        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
134        implicit none
135        type(*), dimension(..), intent(in), asynchronous :: buf
136        integer, intent(in) :: count, dest, tag
137        type(MPI_Datatype), intent(in) :: datatype
138        type(MPI_Comm), intent(in) :: comm
139        type(MPI_Request), intent(out) :: request
140        integer, optional, intent(out) :: ierror
141    end subroutine PMPIR_Isend_f08ts
142end interface PMPI_Isend
143
144interface PMPI_Issend
145    subroutine PMPIR_Issend_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
146        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
147        implicit none
148        type(*), dimension(..), intent(in), asynchronous :: buf
149        integer, intent(in) :: count, dest, tag
150        type(MPI_Datatype), intent(in) :: datatype
151        type(MPI_Comm), intent(in) :: comm
152        type(MPI_Request), intent(out) :: request
153        integer, optional, intent(out) :: ierror
154    end subroutine PMPIR_Issend_f08ts
155end interface PMPI_Issend
156
157interface PMPI_Probe
158    subroutine PMPIR_Probe_f08(source, tag, comm, status, ierror)
159        use :: mpi_f08_types, only : MPI_Comm, MPI_Status
160        implicit none
161        integer, intent(in) :: source, tag
162        type(MPI_Comm), intent(in) :: comm
163        type(MPI_Status) :: status
164        integer, optional, intent(out) :: ierror
165    end subroutine PMPIR_Probe_f08
166end interface PMPI_Probe
167
168interface PMPI_Recv
169    subroutine PMPIR_Recv_f08ts(buf, count, datatype, source, tag, comm, status, ierror)
170        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Status
171        implicit none
172        type(*), dimension(..) :: buf
173        integer, intent(in) :: count, source, tag
174        type(MPI_Datatype), intent(in) :: datatype
175        type(MPI_Comm), intent(in) :: comm
176        type(MPI_Status) :: status
177        integer, optional, intent(out) :: ierror
178    end subroutine PMPIR_Recv_f08ts
179end interface PMPI_Recv
180
181interface PMPI_Recv_init
182    subroutine PMPIR_Recv_init_f08ts(buf, count, datatype, source, tag, comm, request, ierror)
183        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
184        implicit none
185        type(*), dimension(..) :: buf
186        integer, intent(in) :: count, source, tag
187        type(MPI_Datatype), intent(in) :: datatype
188        type(MPI_Comm), intent(in) :: comm
189        type(MPI_Request), intent(out) :: request
190        integer, optional, intent(out) :: ierror
191    end subroutine PMPIR_Recv_init_f08ts
192end interface PMPI_Recv_init
193
194interface PMPI_Request_free
195    subroutine PMPIR_Request_free_f08(request, ierror)
196        use :: mpi_f08_types, only : MPI_Request
197        implicit none
198        type(MPI_Request), intent(inout) :: request
199        integer, optional, intent(out) :: ierror
200    end subroutine PMPIR_Request_free_f08
201end interface PMPI_Request_free
202
203interface PMPI_Request_get_status
204    subroutine PMPIR_Request_get_status_f08(request, flag, status, ierror)
205        use :: mpi_f08_types, only : MPI_Request, MPI_Status
206        implicit none
207        type(MPI_Request), intent(in) :: request
208        logical, intent(out) :: flag
209        type(MPI_Status) :: status
210        integer, optional, intent(out) :: ierror
211    end subroutine PMPIR_Request_get_status_f08
212end interface PMPI_Request_get_status
213
214interface PMPI_Rsend
215    subroutine PMPIR_Rsend_f08ts(buf, count, datatype, dest, tag, comm, ierror)
216        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
217        implicit none
218        type(*), dimension(..), intent(in) :: buf
219        integer, intent(in) :: count, dest, tag
220        type(MPI_Datatype), intent(in) :: datatype
221        type(MPI_Comm), intent(in) :: comm
222        integer, optional, intent(out) :: ierror
223    end subroutine PMPIR_Rsend_f08ts
224end interface PMPI_Rsend
225
226interface PMPI_Rsend_init
227    subroutine PMPIR_Rsend_init_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
228        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
229        implicit none
230        type(*), dimension(..) :: buf
231        integer, intent(in) :: count, dest, tag
232        type(MPI_Datatype), intent(in) :: datatype
233        type(MPI_Comm), intent(in) :: comm
234        type(MPI_Request), intent(out) :: request
235        integer, optional, intent(out) :: ierror
236    end subroutine PMPIR_Rsend_init_f08ts
237end interface PMPI_Rsend_init
238
239interface PMPI_Send
240    subroutine PMPIR_Send_f08ts(buf, count, datatype, dest, tag, comm, ierror)
241        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
242        implicit none
243        type(*), dimension(..), intent(in) :: buf
244        integer, intent(in) :: count, dest, tag
245        type(MPI_Datatype), intent(in) :: datatype
246        type(MPI_Comm), intent(in) :: comm
247        integer, optional, intent(out) :: ierror
248    end subroutine PMPIR_Send_f08ts
249end interface PMPI_Send
250
251interface PMPI_Sendrecv
252    subroutine PMPIR_Sendrecv_f08ts(sendbuf, sendcount, sendtype, dest, sendtag, recvbuf, &
253                   recvcount, recvtype, source, recvtag, comm, status, ierror)
254        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Status
255        implicit none
256        type(*), dimension(..), intent(in) :: sendbuf
257        type(*), dimension(..) :: recvbuf
258        integer, intent(in) :: sendcount, dest, sendtag, recvcount, source, recvtag
259        type(MPI_Datatype), intent(in) :: sendtype, recvtype
260        type(MPI_Comm), intent(in) :: comm
261        type(MPI_Status) :: status
262        integer, optional, intent(out) :: ierror
263    end subroutine PMPIR_Sendrecv_f08ts
264end interface PMPI_Sendrecv
265
266interface PMPI_Sendrecv_replace
267    subroutine PMPIR_Sendrecv_replace_f08ts(buf, count, datatype, dest, sendtag, source, recvtag, &
268                   comm, status, ierror)
269        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Status
270        implicit none
271        type(*), dimension(..) :: buf
272        integer, intent(in) :: count, dest, sendtag, source, recvtag
273        type(MPI_Datatype), intent(in) :: datatype
274        type(MPI_Comm), intent(in) :: comm
275        type(MPI_Status) :: status
276        integer, optional, intent(out) :: ierror
277    end subroutine PMPIR_Sendrecv_replace_f08ts
278end interface PMPI_Sendrecv_replace
279
280interface PMPI_Send_init
281    subroutine PMPIR_Send_init_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
282        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
283        implicit none
284        type(*), dimension(..) :: buf
285        integer, intent(in) :: count, dest, tag
286        type(MPI_Datatype), intent(in) :: datatype
287        type(MPI_Comm), intent(in) :: comm
288        type(MPI_Request), intent(out) :: request
289        integer, optional, intent(out) :: ierror
290    end subroutine PMPIR_Send_init_f08ts
291end interface PMPI_Send_init
292
293interface PMPI_Ssend
294    subroutine PMPIR_Ssend_f08ts(buf, count, datatype, dest, tag, comm, ierror)
295        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
296        implicit none
297        type(*), dimension(..), intent(in) :: buf
298        integer, intent(in) :: count, dest, tag
299        type(MPI_Datatype), intent(in) :: datatype
300        type(MPI_Comm), intent(in) :: comm
301        integer, optional, intent(out) :: ierror
302    end subroutine PMPIR_Ssend_f08ts
303end interface PMPI_Ssend
304
305interface PMPI_Ssend_init
306    subroutine PMPIR_Ssend_init_f08ts(buf, count, datatype, dest, tag, comm, request, ierror)
307        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
308        implicit none
309        type(*), dimension(..) :: buf
310        integer, intent(in) :: count, dest, tag
311        type(MPI_Datatype), intent(in) :: datatype
312        type(MPI_Comm), intent(in) :: comm
313        type(MPI_Request), intent(out) :: request
314        integer, optional, intent(out) :: ierror
315    end subroutine PMPIR_Ssend_init_f08ts
316end interface PMPI_Ssend_init
317
318interface PMPI_Start
319    subroutine PMPIR_Start_f08(request, ierror)
320        use :: mpi_f08_types, only : MPI_Request
321        implicit none
322        type(MPI_Request), intent(inout) :: request
323        integer, optional, intent(out) :: ierror
324    end subroutine PMPIR_Start_f08
325end interface PMPI_Start
326
327interface PMPI_Startall
328    subroutine PMPIR_Startall_f08(count, array_of_requests, ierror)
329        use :: mpi_f08_types, only : MPI_Request
330        implicit none
331        integer, intent(in) :: count
332        type(MPI_Request), intent(inout) :: array_of_requests(count)
333        integer, optional, intent(out) :: ierror
334    end subroutine PMPIR_Startall_f08
335end interface PMPI_Startall
336
337interface PMPI_Test
338    subroutine PMPIR_Test_f08(request, flag, status, ierror)
339        use :: mpi_f08_types, only : MPI_Request, MPI_Status
340        implicit none
341        type(MPI_Request), intent(inout) :: request
342        logical, intent(out) :: flag
343        type(MPI_Status) :: status
344        integer, optional, intent(out) :: ierror
345    end subroutine PMPIR_Test_f08
346end interface PMPI_Test
347
348interface PMPI_Testall
349    subroutine PMPIR_Testall_f08(count, array_of_requests, flag, array_of_statuses, ierror)
350        use :: mpi_f08_types, only : MPI_Request, MPI_Status
351        implicit none
352        integer, intent(in) :: count
353        type(MPI_Request), intent(inout) :: array_of_requests(count)
354        logical, intent(out) :: flag
355        type(MPI_Status) :: array_of_statuses(*)
356        integer, optional, intent(out) :: ierror
357    end subroutine PMPIR_Testall_f08
358end interface PMPI_Testall
359
360interface PMPI_Testany
361    subroutine PMPIR_Testany_f08(count, array_of_requests, index, flag, status, ierror)
362        use :: mpi_f08_types, only : MPI_Request, MPI_Status
363        implicit none
364        integer, intent(in) :: count
365        type(MPI_Request), intent(inout) :: array_of_requests(count)
366        integer, intent(out) :: index
367        logical, intent(out) :: flag
368        type(MPI_Status) :: status
369        integer, optional, intent(out) :: ierror
370    end subroutine PMPIR_Testany_f08
371end interface PMPI_Testany
372
373interface PMPI_Testsome
374    subroutine PMPIR_Testsome_f08(incount, array_of_requests, outcount, &
375                   array_of_indices, array_of_statuses, ierror)
376        use :: mpi_f08_types, only : MPI_Request, MPI_Status
377        implicit none
378        integer, intent(in) :: incount
379        type(MPI_Request), intent(inout) :: array_of_requests(incount)
380        integer, intent(out) :: outcount, array_of_indices(*)
381        type(MPI_Status) :: array_of_statuses(*)
382        integer, optional, intent(out) :: ierror
383    end subroutine PMPIR_Testsome_f08
384end interface PMPI_Testsome
385
386interface PMPI_Test_cancelled
387    subroutine PMPIR_Test_cancelled_f08(status, flag, ierror)
388        use :: mpi_f08_types, only : MPI_Status
389        implicit none
390        type(MPI_Status), intent(in) :: status
391        logical, intent(out) :: flag
392        integer, optional, intent(out) :: ierror
393    end subroutine PMPIR_Test_cancelled_f08
394end interface PMPI_Test_cancelled
395
396interface PMPI_Wait
397    subroutine PMPIR_Wait_f08(request, status, ierror)
398        use :: mpi_f08_types, only : MPI_Request, MPI_Status
399        implicit none
400        type(MPI_Request), intent(inout) :: request
401        type(MPI_Status) :: status
402        integer, optional, intent(out) :: ierror
403    end subroutine PMPIR_Wait_f08
404end interface PMPI_Wait
405
406interface PMPI_Waitall
407    subroutine PMPIR_Waitall_f08(count, array_of_requests, array_of_statuses, ierror)
408        use :: mpi_f08_types, only : MPI_Request, MPI_Status
409        implicit none
410        integer, intent(in) :: count
411        type(MPI_Request), intent(inout) :: array_of_requests(count)
412        type(MPI_Status) :: array_of_statuses(*)
413        integer, optional, intent(out) :: ierror
414    end subroutine PMPIR_Waitall_f08
415end interface PMPI_Waitall
416
417interface PMPI_Waitany
418    subroutine PMPIR_Waitany_f08(count, array_of_requests, index, status, ierror)
419        use :: mpi_f08_types, only : MPI_Request, MPI_Status
420        implicit none
421        integer, intent(in) :: count
422        type(MPI_Request), intent(inout) :: array_of_requests(count)
423        integer, intent(out) :: index
424        type(MPI_Status) :: status
425        integer, optional, intent(out) :: ierror
426    end subroutine PMPIR_Waitany_f08
427end interface PMPI_Waitany
428
429interface PMPI_Waitsome
430    subroutine PMPIR_Waitsome_f08(incount, array_of_requests, outcount, &
431                   array_of_indices, array_of_statuses, ierror)
432        use :: mpi_f08_types, only : MPI_Request, MPI_Status
433        implicit none
434        integer, intent(in) :: incount
435        type(MPI_Request), intent(inout) :: array_of_requests(incount)
436        integer, intent(out) :: outcount, array_of_indices(*)
437        type(MPI_Status) :: array_of_statuses(*)
438        integer, optional, intent(out) :: ierror
439    end subroutine PMPIR_Waitsome_f08
440end interface PMPI_Waitsome
441
442interface PMPI_Get_address
443    subroutine PMPIR_Get_address_f08ts(location, address, ierror)
444        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
445        implicit none
446        type(*), dimension(..), asynchronous :: location
447        integer(MPI_ADDRESS_KIND), intent(out) :: address
448        integer, optional, intent(out) :: ierror
449    end subroutine PMPIR_Get_address_f08ts
450end interface PMPI_Get_address
451
452interface PMPI_Get_elements
453    subroutine PMPIR_Get_elements_f08(status, datatype, count, ierror)
454        use :: mpi_f08_types, only : MPI_Status, MPI_Datatype
455        implicit none
456        type(MPI_Status), intent(in) :: status
457        type(MPI_Datatype), intent(in) :: datatype
458        integer, intent(out) :: count
459        integer, optional, intent(out) :: ierror
460    end subroutine PMPIR_Get_elements_f08
461end interface PMPI_Get_elements
462
463interface PMPI_Get_elements_x
464    subroutine PMPIR_Get_elements_x_f08(status, datatype, count, ierror)
465        use :: mpi_f08_types, only : MPI_Status, MPI_Datatype
466        use :: mpi_f08_compile_constants, only : MPI_COUNT_KIND
467        implicit none
468        type(MPI_Status), intent(in) :: status
469        type(MPI_Datatype), intent(in) :: datatype
470        integer(MPI_COUNT_KIND), intent(out) :: count
471        integer, optional, intent(out) :: ierror
472    end subroutine PMPIR_Get_elements_x_f08
473end interface PMPI_Get_elements_x
474
475interface PMPI_Pack
476    subroutine PMPIR_Pack_f08ts(inbuf, incount, datatype, outbuf, outsize, position, comm, ierror)
477        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
478        implicit none
479        type(*), dimension(..), intent(in) :: inbuf
480        type(*), dimension(..) :: outbuf
481        integer, intent(in) :: incount, outsize
482        type(MPI_Datatype), intent(in) :: datatype
483        integer, intent(inout) :: position
484        type(MPI_Comm), intent(in) :: comm
485        integer, optional, intent(out) :: ierror
486    end subroutine PMPIR_Pack_f08ts
487end interface PMPI_Pack
488
489interface PMPI_Pack_external
490    subroutine PMPIR_Pack_external_f08ts(datarep, inbuf, incount, datatype, outbuf, outsize, &
491                                      position, ierror)
492        use :: mpi_f08_types, only : MPI_Datatype
493        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
494        implicit none
495        character(len=*), intent(in) :: datarep
496        type(*), dimension(..), intent(in) :: inbuf
497        type(*), dimension(..) :: outbuf
498        integer, intent(in) :: incount
499        type(MPI_Datatype), intent(in) :: datatype
500        integer(MPI_ADDRESS_KIND), intent(in) :: outsize
501        integer(MPI_ADDRESS_KIND), intent(inout) :: position
502        integer, optional, intent(out) :: ierror
503    end subroutine PMPIR_Pack_external_f08ts
504end interface PMPI_Pack_external
505
506interface PMPI_Pack_external_size
507    subroutine PMPIR_Pack_external_size_f08(datarep, incount, datatype, size, ierror)
508        use :: mpi_f08_types, only : MPI_Datatype
509        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
510        implicit none
511        type(MPI_Datatype), intent(in) :: datatype
512        integer, intent(in) :: incount
513        character(len=*), intent(in) :: datarep
514        integer(MPI_ADDRESS_KIND), intent(out) :: size
515        integer, optional, intent(out) :: ierror
516    end subroutine PMPIR_Pack_external_size_f08
517end interface PMPI_Pack_external_size
518
519interface PMPI_Pack_size
520    subroutine PMPIR_Pack_size_f08(incount, datatype, comm, size, ierror)
521        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
522        implicit none
523        integer, intent(in) :: incount
524        type(MPI_Datatype), intent(in) :: datatype
525        type(MPI_Comm), intent(in) :: comm
526        integer, intent(out) :: size
527        integer, optional, intent(out) :: ierror
528    end subroutine PMPIR_Pack_size_f08
529end interface PMPI_Pack_size
530
531interface PMPI_Type_commit
532    subroutine PMPIR_Type_commit_f08(datatype, ierror)
533        use :: mpi_f08_types, only : MPI_Datatype
534        implicit none
535        type(MPI_Datatype), intent(inout) :: datatype
536        integer, optional, intent(out) :: ierror
537    end subroutine PMPIR_Type_commit_f08
538end interface PMPI_Type_commit
539
540interface PMPI_Type_contiguous
541    subroutine PMPIR_Type_contiguous_f08(count, oldtype, newtype, ierror)
542        use :: mpi_f08_types, only : MPI_Datatype
543        implicit none
544        integer, intent(in) :: count
545        type(MPI_Datatype), intent(in) :: oldtype
546        type(MPI_Datatype), intent(out) :: newtype
547        integer, optional, intent(out) :: ierror
548    end subroutine PMPIR_Type_contiguous_f08
549end interface PMPI_Type_contiguous
550
551interface PMPI_Type_create_darray
552    subroutine PMPIR_Type_create_darray_f08(size, rank, ndims, array_of_gsizes, &
553                   array_of_distribs, array_of_dargs, array_of_psizes, order, &
554                   oldtype, newtype, ierror)
555        use :: mpi_f08_types, only : MPI_Datatype
556        implicit none
557        integer, intent(in) :: size, rank, ndims, order
558        integer, intent(in) :: array_of_gsizes(ndims), array_of_distribs(ndims)
559        integer, intent(in) :: array_of_dargs(ndims), array_of_psizes(ndims)
560        type(MPI_Datatype), intent(in) :: oldtype
561        type(MPI_Datatype), intent(out) :: newtype
562        integer, optional, intent(out) :: ierror
563    end subroutine PMPIR_Type_create_darray_f08
564end interface PMPI_Type_create_darray
565
566interface PMPI_Type_create_hindexed
567    subroutine PMPIR_Type_create_hindexed_f08(count, array_of_blocklengths, &
568                   array_of_displacements, oldtype, newtype, ierror)
569        use :: mpi_f08_types, only : MPI_Datatype
570        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
571        implicit none
572        integer, intent(in) :: count
573        integer, intent(in) :: array_of_blocklengths(count)
574        integer(MPI_ADDRESS_KIND), intent(in) :: array_of_displacements(count)
575        type(MPI_Datatype), intent(in) :: oldtype
576        type(MPI_Datatype), intent(out) :: newtype
577        integer, optional, intent(out) :: ierror
578    end subroutine PMPIR_Type_create_hindexed_f08
579end interface PMPI_Type_create_hindexed
580
581interface PMPI_Type_create_hvector
582    subroutine PMPIR_Type_create_hvector_f08(count, blocklength, stride, oldtype, newtype, ierror)
583        use :: mpi_f08_types, only : MPI_Datatype
584        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
585        implicit none
586        integer, intent(in) :: count, blocklength
587        integer(MPI_ADDRESS_KIND), intent(in) :: stride
588        type(MPI_Datatype), intent(in) :: oldtype
589        type(MPI_Datatype), intent(out) :: newtype
590        integer, optional, intent(out) :: ierror
591    end subroutine PMPIR_Type_create_hvector_f08
592end interface PMPI_Type_create_hvector
593
594interface PMPI_Type_create_indexed_block
595    subroutine PMPIR_Type_create_indexed_block_f08(count, blocklength, &
596                   array_of_displacements, oldtype, newtype, ierror)
597        use :: mpi_f08_types, only : MPI_Datatype
598        implicit none
599        integer, intent(in) :: count, blocklength
600        integer, intent(in) :: array_of_displacements(count)
601        type(MPI_Datatype), intent(in) :: oldtype
602        type(MPI_Datatype), intent(out) :: newtype
603        integer, optional, intent(out) :: ierror
604    end subroutine PMPIR_Type_create_indexed_block_f08
605end interface PMPI_Type_create_indexed_block
606
607interface PMPI_Type_create_hindexed_block
608    subroutine PMPIR_Type_create_hindexed_block_f08(count, blocklength, &
609                                array_of_displacements, oldtype, newtype, ierror)
610        use :: mpi_f08_types, only : MPI_Datatype
611        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
612        implicit none
613        integer, intent(in) :: count, blocklength
614        integer(MPI_ADDRESS_KIND), intent(in) :: array_of_displacements(count)
615        type(MPI_Datatype), intent(in) :: oldtype
616        type(MPI_Datatype), intent(out) :: newtype
617        integer, optional, intent(out) :: ierror
618    end subroutine PMPIR_Type_create_hindexed_block_f08
619end interface PMPI_Type_create_hindexed_block
620
621interface PMPI_Type_create_resized
622    subroutine PMPIR_Type_create_resized_f08(oldtype, lb, extent, newtype, ierror)
623        use :: mpi_f08_types, only : MPI_Datatype
624        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
625        implicit none
626        integer(MPI_ADDRESS_KIND), intent(in) :: lb, extent
627        type(MPI_Datatype), intent(in) :: oldtype
628        type(MPI_Datatype), intent(out) :: newtype
629        integer, optional, intent(out) :: ierror
630    end subroutine PMPIR_Type_create_resized_f08
631end interface PMPI_Type_create_resized
632
633interface PMPI_Type_create_struct
634    subroutine PMPIR_Type_create_struct_f08(count, array_of_blocklengths, &
635                                array_of_displacements, array_of_types, newtype, ierror)
636        use :: mpi_f08_types, only : MPI_Datatype
637        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
638        implicit none
639        integer, intent(in) :: count
640        integer, intent(in) :: array_of_blocklengths(count)
641        integer(MPI_ADDRESS_KIND), intent(in) :: array_of_displacements(count)
642        type(MPI_Datatype), intent(in) :: array_of_types(count)
643        type(MPI_Datatype), intent(out) :: newtype
644        integer, optional, intent(out) :: ierror
645    end subroutine PMPIR_Type_create_struct_f08
646end interface PMPI_Type_create_struct
647
648interface PMPI_Type_create_subarray
649    subroutine PMPIR_Type_create_subarray_f08(ndims, array_of_sizes, array_of_subsizes, &
650                         array_of_starts, order, oldtype, newtype, ierror)
651        use :: mpi_f08_types, only : MPI_Datatype
652        implicit none
653        integer, intent(in) :: ndims, order
654        integer, intent(in) :: array_of_sizes(ndims), array_of_subsizes(ndims)
655        integer, intent(in) :: array_of_starts(ndims)
656        type(MPI_Datatype), intent(in) :: oldtype
657        type(MPI_Datatype), intent(out) :: newtype
658        integer, optional, intent(out) :: ierror
659    end subroutine PMPIR_Type_create_subarray_f08
660end interface PMPI_Type_create_subarray
661
662interface PMPI_Type_dup
663    subroutine PMPIR_Type_dup_f08(oldtype, newtype, ierror)
664        use :: mpi_f08_types, only : MPI_Datatype
665        implicit none
666        type(MPI_Datatype), intent(in) :: oldtype
667        type(MPI_Datatype), intent(out) :: newtype
668        integer, optional, intent(out) :: ierror
669    end subroutine PMPIR_Type_dup_f08
670end interface PMPI_Type_dup
671
672interface PMPI_Type_free
673    subroutine PMPIR_Type_free_f08(datatype, ierror)
674        use :: mpi_f08_types, only : MPI_Datatype
675        implicit none
676        type(MPI_Datatype), intent(inout) :: datatype
677        integer, optional, intent(out) :: ierror
678    end subroutine PMPIR_Type_free_f08
679end interface PMPI_Type_free
680
681interface PMPI_Type_get_contents
682    subroutine PMPIR_Type_get_contents_f08(datatype, max_integers, max_addresses, max_datatypes, &
683                 array_of_integers, array_of_addresses, array_of_datatypes, ierror)
684        use :: mpi_f08_types, only : MPI_Datatype
685        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
686        implicit none
687        type(MPI_Datatype), intent(in) :: datatype
688        integer, intent(in) :: max_integers, max_addresses, max_datatypes
689        integer, intent(out) :: array_of_integers(max_integers)
690        integer(MPI_ADDRESS_KIND), intent(out) :: array_of_addresses(max_addresses)
691        type(MPI_Datatype), intent(out) :: array_of_datatypes(max_datatypes)
692        integer, optional, intent(out) :: ierror
693    end subroutine PMPIR_Type_get_contents_f08
694end interface PMPI_Type_get_contents
695
696interface PMPI_Type_get_envelope
697    subroutine PMPIR_Type_get_envelope_f08(datatype, num_integers, num_addresses, num_datatypes, &
698                                          combiner, ierror)
699        use :: mpi_f08_types, only : MPI_Datatype
700        implicit none
701        type(MPI_Datatype), intent(in) :: datatype
702        integer, intent(out) :: num_integers, num_addresses, num_datatypes, combiner
703        integer, optional, intent(out) :: ierror
704    end subroutine PMPIR_Type_get_envelope_f08
705end interface PMPI_Type_get_envelope
706
707interface PMPI_Type_get_extent
708    subroutine PMPIR_Type_get_extent_f08(datatype, lb, extent, ierror)
709        use :: mpi_f08_types, only : MPI_Datatype
710        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
711        implicit none
712        type(MPI_Datatype), intent(in) :: datatype
713        integer(MPI_ADDRESS_KIND), intent(out) :: lb, extent
714        integer, optional, intent(out) :: ierror
715    end subroutine PMPIR_Type_get_extent_f08
716end interface PMPI_Type_get_extent
717
718interface PMPI_Type_get_extent_x
719    subroutine PMPIR_Type_get_extent_x_f08(datatype, lb, extent, ierror)
720        use :: mpi_f08_types, only : MPI_Datatype
721        use :: mpi_f08_compile_constants, only : MPI_COUNT_KIND
722        implicit none
723        type(MPI_Datatype), intent(in) :: datatype
724        integer(MPI_COUNT_KIND), intent(out) :: lb, extent
725        integer, optional, intent(out) :: ierror
726    end subroutine PMPIR_Type_get_extent_x_f08
727end interface PMPI_Type_get_extent_x
728
729interface PMPI_Type_get_true_extent
730    subroutine PMPIR_Type_get_true_extent_f08(datatype, true_lb, true_extent, ierror)
731        use :: mpi_f08_types, only : MPI_Datatype
732        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
733        implicit none
734        type(MPI_Datatype), intent(in) :: datatype
735        integer(MPI_ADDRESS_KIND), intent(out) :: true_lb, true_extent
736        integer, optional, intent(out) :: ierror
737    end subroutine PMPIR_Type_get_true_extent_f08
738end interface PMPI_Type_get_true_extent
739
740interface PMPI_Type_get_true_extent_x
741    subroutine PMPIR_Type_get_true_extent_x_f08(datatype, true_lb, true_extent, ierror)
742        use :: mpi_f08_types, only : MPI_Datatype
743        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
744        use :: mpi_f08_compile_constants, only : MPI_COUNT_KIND
745        implicit none
746        type(MPI_Datatype), intent(in) :: datatype
747        integer(MPI_COUNT_KIND), intent(out) :: true_lb, true_extent
748        integer, optional, intent(out) :: ierror
749    end subroutine PMPIR_Type_get_true_extent_x_f08
750end interface PMPI_Type_get_true_extent_x
751
752interface PMPI_Type_indexed
753    subroutine PMPIR_Type_indexed_f08(count, array_of_blocklengths, &
754                                     array_of_displacements, oldtype, newtype, ierror)
755        use :: mpi_f08_types, only : MPI_Datatype
756        implicit none
757        integer, intent(in) :: count
758        integer, intent(in) :: array_of_blocklengths(count), array_of_displacements(count)
759        type(MPI_Datatype), intent(in) :: oldtype
760        type(MPI_Datatype), intent(out) :: newtype
761        integer, optional, intent(out) :: ierror
762    end subroutine PMPIR_Type_indexed_f08
763end interface PMPI_Type_indexed
764
765interface PMPI_Type_size
766    subroutine PMPIR_Type_size_f08(datatype, size, ierror)
767        use :: mpi_f08_types, only : MPI_Datatype
768        implicit none
769        type(MPI_Datatype), intent(in) :: datatype
770        integer, intent(out) :: size
771        integer, optional, intent(out) :: ierror
772    end subroutine PMPIR_Type_size_f08
773end interface PMPI_Type_size
774
775interface PMPI_Type_size_x
776    subroutine PMPIR_Type_size_x_f08(datatype, size, ierror)
777        use :: mpi_f08_types, only : MPI_Datatype
778        use :: mpi_f08_compile_constants, only : MPI_COUNT_KIND
779        implicit none
780        type(MPI_Datatype), intent(in) :: datatype
781        integer(MPI_COUNT_KIND), intent(out) :: size
782        integer, optional, intent(out) :: ierror
783    end subroutine PMPIR_Type_size_x_f08
784end interface PMPI_Type_size_x
785
786interface PMPI_Type_vector
787    subroutine PMPIR_Type_vector_f08(count, blocklength, stride, oldtype, newtype, ierror)
788        use :: mpi_f08_types, only : MPI_Datatype
789        implicit none
790        integer, intent(in) :: count, blocklength, stride
791        type(MPI_Datatype), intent(in) :: oldtype
792        type(MPI_Datatype), intent(out) :: newtype
793        integer, optional, intent(out) :: ierror
794    end subroutine PMPIR_Type_vector_f08
795end interface PMPI_Type_vector
796
797interface PMPI_Unpack
798    subroutine PMPIR_Unpack_f08ts(inbuf, insize, position, outbuf, outcount, datatype, comm, &
799                               ierror)
800        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
801        implicit none
802        type(*), dimension(..), intent(in) :: inbuf
803        type(*), dimension(..) :: outbuf
804        integer, intent(in) :: insize, outcount
805        integer, intent(inout) :: position
806        type(MPI_Datatype), intent(in) :: datatype
807        type(MPI_Comm), intent(in) :: comm
808        integer, optional, intent(out) :: ierror
809    end subroutine PMPIR_Unpack_f08ts
810end interface PMPI_Unpack
811
812interface PMPI_Unpack_external
813    subroutine PMPIR_Unpack_external_f08ts(datarep, inbuf, insize, position, outbuf, outcount, &
814                                        datatype, ierror)
815        use :: mpi_f08_types, only : MPI_Datatype
816        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
817        implicit none
818        character(len=*), intent(in) :: datarep
819        type(*), dimension(..), intent(in) :: inbuf
820        type(*), dimension(..) :: outbuf
821        integer(MPI_ADDRESS_KIND), intent(in) :: insize
822        integer(MPI_ADDRESS_KIND), intent(inout) :: position
823        integer, intent(in) :: outcount
824        type(MPI_Datatype), intent(in) :: datatype
825        integer, optional, intent(out) :: ierror
826    end subroutine PMPIR_Unpack_external_f08ts
827end interface PMPI_Unpack_external
828
829interface PMPI_Allgather
830    subroutine PMPIR_Allgather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
831                                  comm, ierror)
832        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
833        implicit none
834        type(*), dimension(..), intent(in) :: sendbuf
835        type(*), dimension(..) :: recvbuf
836        integer, intent(in) :: sendcount, recvcount
837        type(MPI_Datatype), intent(in) :: sendtype, recvtype
838        type(MPI_Comm), intent(in) :: comm
839        integer, optional, intent(out) :: ierror
840    end subroutine PMPIR_Allgather_f08ts
841end interface PMPI_Allgather
842
843interface PMPI_Iallgather
844    subroutine PMPIR_Iallgather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
845                                  comm, request, ierror)
846        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
847        implicit none
848        type(*), dimension(..), intent(in), asynchronous :: sendbuf
849        type(*), dimension(..), asynchronous :: recvbuf
850        integer, intent(in) :: sendcount, recvcount
851        type(MPI_Datatype), intent(in) :: sendtype, recvtype
852        type(MPI_Comm), intent(in) :: comm
853        type(MPI_Request), intent(out) :: request
854        integer, optional, intent(out) :: ierror
855    end subroutine PMPIR_Iallgather_f08ts
856end interface PMPI_Iallgather
857
858interface PMPI_Allgatherv
859    subroutine PMPIR_Allgatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
860                                   recvtype, comm, ierror)
861        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
862        implicit none
863        type(*), dimension(..), intent(in) :: sendbuf
864        type(*), dimension(..) :: recvbuf
865        integer, intent(in) :: sendcount
866        integer, intent(in) :: recvcounts(*), displs(*)
867        type(MPI_Datatype), intent(in) :: sendtype, recvtype
868        type(MPI_Comm), intent(in) :: comm
869        integer, optional, intent(out) :: ierror
870    end subroutine PMPIR_Allgatherv_f08ts
871end interface PMPI_Allgatherv
872
873interface PMPI_Iallgatherv
874    subroutine PMPIR_Iallgatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
875                                   recvtype, comm, request, ierror)
876        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
877        implicit none
878        type(*), dimension(..), intent(in), asynchronous :: sendbuf
879        type(*), dimension(..), asynchronous :: recvbuf
880        integer, intent(in) :: sendcount
881        integer, intent(in) :: recvcounts(*), displs(*)
882        type(MPI_Datatype), intent(in) :: sendtype, recvtype
883        type(MPI_Comm), intent(in) :: comm
884        type(MPI_Request), intent(out) :: request
885        integer, optional, intent(out) :: ierror
886    end subroutine PMPIR_Iallgatherv_f08ts
887end interface PMPI_Iallgatherv
888
889interface PMPI_Allreduce
890    subroutine PMPIR_Allreduce_f08ts(sendbuf, recvbuf, count, datatype, op, comm, ierror)
891        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
892        implicit none
893        type(*), dimension(..), intent(in) :: sendbuf
894        type(*), dimension(..) :: recvbuf
895        integer, intent(in) :: count
896        type(MPI_Datatype), intent(in) :: datatype
897        type(MPI_Op), intent(in) :: op
898        type(MPI_Comm), intent(in) :: comm
899        integer, optional, intent(out) :: ierror
900    end subroutine PMPIR_Allreduce_f08ts
901end interface PMPI_Allreduce
902
903interface PMPI_Iallreduce
904    subroutine PMPIR_Iallreduce_f08ts(sendbuf, recvbuf, count, datatype, op, comm, request, ierror)
905        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
906        implicit none
907        type(*), dimension(..), intent(in), asynchronous :: sendbuf
908        type(*), dimension(..), asynchronous :: recvbuf
909        integer, intent(in) :: count
910        type(MPI_Datatype), intent(in) :: datatype
911        type(MPI_Op), intent(in) :: op
912        type(MPI_Comm), intent(in) :: comm
913        type(MPI_Request), intent(out) :: request
914        integer, optional, intent(out) :: ierror
915    end subroutine PMPIR_Iallreduce_f08ts
916end interface PMPI_Iallreduce
917
918interface PMPI_Alltoall
919    subroutine PMPIR_Alltoall_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
920                                 comm, ierror)
921        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
922        implicit none
923        type(*), dimension(..), intent(in) :: sendbuf
924        type(*), dimension(..) :: recvbuf
925        integer, intent(in) :: sendcount, recvcount
926        type(MPI_Datatype), intent(in) :: sendtype, recvtype
927        type(MPI_Comm), intent(in) :: comm
928        integer, optional, intent(out) :: ierror
929    end subroutine PMPIR_Alltoall_f08ts
930end interface PMPI_Alltoall
931
932interface PMPI_Ialltoall
933    subroutine PMPIR_Ialltoall_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
934                                 comm, request, ierror)
935        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
936        implicit none
937        type(*), dimension(..), intent(in), asynchronous :: sendbuf
938        type(*), dimension(..), asynchronous :: recvbuf
939        integer, intent(in) :: sendcount, recvcount
940        type(MPI_Datatype), intent(in) :: sendtype, recvtype
941        type(MPI_Comm), intent(in) :: comm
942        type(MPI_Request), intent(out) :: request
943        integer, optional, intent(out) :: ierror
944    end subroutine PMPIR_Ialltoall_f08ts
945end interface PMPI_Ialltoall
946
947interface PMPI_Alltoallv
948    subroutine PMPIR_Alltoallv_f08ts(sendbuf, sendcounts, sdispls, sendtype, recvbuf, recvcounts, &
949                                  rdispls, recvtype, comm, ierror)
950        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
951        implicit none
952        type(*), dimension(..), intent(in) :: sendbuf
953        type(*), dimension(..) :: recvbuf
954        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
955        type(MPI_Datatype), intent(in) :: sendtype, recvtype
956        type(MPI_Comm), intent(in) :: comm
957        integer, optional, intent(out) :: ierror
958    end subroutine PMPIR_Alltoallv_f08ts
959end interface PMPI_Alltoallv
960
961interface PMPI_Ialltoallv
962    subroutine PMPIR_Ialltoallv_f08ts(sendbuf, sendcounts, sdispls, sendtype, recvbuf, recvcounts, &
963                                  rdispls, recvtype, comm, request, ierror)
964        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
965        implicit none
966        type(*), dimension(..), intent(in), asynchronous :: sendbuf
967        type(*), dimension(..), asynchronous :: recvbuf
968        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
969        type(MPI_Datatype), intent(in) :: sendtype, recvtype
970        type(MPI_Comm), intent(in) :: comm
971        type(MPI_Request), intent(out) :: request
972        integer, optional, intent(out) :: ierror
973    end subroutine PMPIR_Ialltoallv_f08ts
974end interface PMPI_Ialltoallv
975
976interface PMPI_Alltoallw
977    subroutine PMPIR_Alltoallw_f08ts(sendbuf, sendcounts, sdispls, sendtypes, recvbuf, recvcounts, &
978                                  rdispls, recvtypes, comm, ierror)
979        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
980        implicit none
981        type(*), dimension(..), intent(in) :: sendbuf
982        type(*), dimension(..) :: recvbuf
983        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
984        type(MPI_Datatype), intent(in) :: sendtypes(*), recvtypes(*)
985        type(MPI_Comm), intent(in) :: comm
986        integer, optional, intent(out) :: ierror
987    end subroutine PMPIR_Alltoallw_f08ts
988end interface PMPI_Alltoallw
989
990interface PMPI_Ialltoallw
991    subroutine PMPIR_Ialltoallw_f08ts(sendbuf, sendcounts, sdispls, sendtypes, recvbuf, recvcounts, &
992                                  rdispls, recvtypes, comm, request, ierror)
993        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
994        implicit none
995        type(*), dimension(..), intent(in), asynchronous :: sendbuf
996        type(*), dimension(..), asynchronous :: recvbuf
997        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
998        type(MPI_Datatype), intent(in) :: sendtypes(*), recvtypes(*)
999        type(MPI_Comm), intent(in) :: comm
1000        type(MPI_Request), intent(out) :: request
1001        integer, optional, intent(out) :: ierror
1002    end subroutine PMPIR_Ialltoallw_f08ts
1003end interface PMPI_Ialltoallw
1004
1005interface PMPI_Barrier
1006    subroutine PMPIR_Barrier_f08(comm, ierror)
1007        use :: mpi_f08_types, only : MPI_Comm
1008        implicit none
1009        type(MPI_Comm), intent(in) :: comm
1010        integer, optional, intent(out) :: ierror
1011    end subroutine PMPIR_Barrier_f08
1012end interface PMPI_Barrier
1013
1014interface PMPI_Ibarrier
1015    subroutine PMPIR_Ibarrier_f08(comm, request, ierror)
1016        use :: mpi_f08_types, only : MPI_Comm, MPI_Request
1017        implicit none
1018        type(MPI_Comm), intent(in) :: comm
1019        type(MPI_Request), intent(out) :: request
1020        integer, optional, intent(out) :: ierror
1021    end subroutine PMPIR_Ibarrier_f08
1022end interface PMPI_Ibarrier
1023
1024interface PMPI_Bcast
1025    subroutine PMPIR_Bcast_f08ts(buffer, count, datatype, root, comm, ierror)
1026        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
1027        implicit none
1028        type(*), dimension(..) :: buffer
1029        integer, intent(in) :: count, root
1030        type(MPI_Datatype), intent(in) :: datatype
1031        type(MPI_Comm), intent(in) :: comm
1032        integer, optional, intent(out) :: ierror
1033    end subroutine PMPIR_Bcast_f08ts
1034end interface PMPI_Bcast
1035
1036interface PMPI_Ibcast
1037    subroutine PMPIR_Ibcast_f08ts(buffer, count, datatype, root, comm, request, ierror)
1038        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
1039        implicit none
1040        type(*), dimension(..), asynchronous :: buffer
1041        integer, intent(in) :: count, root
1042        type(MPI_Datatype), intent(in) :: datatype
1043        type(MPI_Comm), intent(in) :: comm
1044        type(MPI_Request), intent(out) :: request
1045        integer, optional, intent(out) :: ierror
1046    end subroutine PMPIR_Ibcast_f08ts
1047end interface PMPI_Ibcast
1048
1049interface PMPI_Exscan
1050    subroutine PMPIR_Exscan_f08ts(sendbuf, recvbuf, count, datatype, op, comm, ierror)
1051        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
1052        implicit none
1053        type(*), dimension(..), intent(in) :: sendbuf
1054        type(*), dimension(..) :: recvbuf
1055        integer, intent(in) :: count
1056        type(MPI_Datatype), intent(in) :: datatype
1057        type(MPI_Op), intent(in) :: op
1058        type(MPI_Comm), intent(in) :: comm
1059        integer, optional, intent(out) :: ierror
1060    end subroutine PMPIR_Exscan_f08ts
1061end interface PMPI_Exscan
1062
1063interface PMPI_Iexscan
1064    subroutine PMPIR_Iexscan_f08ts(sendbuf, recvbuf, count, datatype, op, comm, request, ierror)
1065        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
1066        implicit none
1067        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1068        type(*), dimension(..), asynchronous :: recvbuf
1069        integer, intent(in) :: count
1070        type(MPI_Datatype), intent(in) :: datatype
1071        type(MPI_Op), intent(in) :: op
1072        type(MPI_Comm), intent(in) :: comm
1073        type(MPI_Request), intent(out) :: request
1074        integer, optional, intent(out) :: ierror
1075    end subroutine PMPIR_Iexscan_f08ts
1076end interface PMPI_Iexscan
1077
1078interface PMPI_Gather
1079    subroutine PMPIR_Gather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
1080                               root, comm, ierror)
1081        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
1082        implicit none
1083        type(*), dimension(..), intent(in) :: sendbuf
1084        type(*), dimension(..) :: recvbuf
1085        integer, intent(in) :: sendcount, recvcount, root
1086        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1087        type(MPI_Comm), intent(in) :: comm
1088        integer, optional, intent(out) :: ierror
1089    end subroutine PMPIR_Gather_f08ts
1090end interface PMPI_Gather
1091
1092interface PMPI_Igather
1093    subroutine PMPIR_Igather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
1094                               root, comm, request, ierror)
1095        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
1096        implicit none
1097        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1098        type(*), dimension(..), asynchronous :: recvbuf
1099        integer, intent(in) :: sendcount, recvcount, root
1100        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1101        type(MPI_Comm), intent(in) :: comm
1102        type(MPI_Request), intent(out) :: request
1103        integer, optional, intent(out) :: ierror
1104    end subroutine PMPIR_Igather_f08ts
1105end interface PMPI_Igather
1106
1107interface PMPI_Gatherv
1108    subroutine PMPIR_Gatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
1109                                recvtype, root, comm, ierror)
1110        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
1111        implicit none
1112        type(*), dimension(..), intent(in) :: sendbuf
1113        type(*), dimension(..) :: recvbuf
1114        integer, intent(in) :: sendcount, root
1115        integer, intent(in) :: recvcounts(*), displs(*)
1116        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1117        type(MPI_Comm), intent(in) :: comm
1118        integer, optional, intent(out) :: ierror
1119    end subroutine PMPIR_Gatherv_f08ts
1120end interface PMPI_Gatherv
1121
1122interface PMPI_Igatherv
1123    subroutine PMPIR_Igatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
1124                                recvtype, root, comm, request, ierror)
1125        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
1126        implicit none
1127        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1128        type(*), dimension(..), asynchronous :: recvbuf
1129        integer, intent(in) :: sendcount, root
1130        integer, intent(in) :: recvcounts(*), displs(*)
1131        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1132        type(MPI_Comm), intent(in) :: comm
1133        type(MPI_Request), intent(out) :: request
1134        integer, optional, intent(out) :: ierror
1135    end subroutine PMPIR_Igatherv_f08ts
1136end interface PMPI_Igatherv
1137
1138interface PMPI_Op_commutative
1139    subroutine PMPIR_Op_commutative_f08(op, commute, ierror)
1140        use :: mpi_f08_types, only : MPI_Op
1141        implicit none
1142        type(MPI_Op), intent(in) :: op
1143        logical, intent(out) :: commute
1144        integer, optional, intent(out) :: ierror
1145    end subroutine PMPIR_Op_commutative_f08
1146end interface PMPI_Op_commutative
1147
1148interface PMPI_Op_create
1149    subroutine PMPIR_Op_create_f08(user_fn, commute, op, ierror)
1150        use :: mpi_f08_types, only : MPI_Op
1151        use :: mpi_f08_callbacks, only : MPI_User_function
1152        implicit none
1153        procedure(MPI_User_function) :: user_fn
1154        logical, intent(in) :: commute
1155        type(MPI_Op), intent(out) :: op
1156        integer, optional, intent(out) :: ierror
1157    end subroutine PMPIR_Op_create_f08
1158end interface PMPI_Op_create
1159
1160interface PMPI_Op_free
1161    subroutine PMPIR_Op_free_f08(op, ierror)
1162        use :: mpi_f08_types, only : MPI_Op
1163        implicit none
1164        type(MPI_Op), intent(inout) :: op
1165        integer, optional, intent(out) :: ierror
1166    end subroutine PMPIR_Op_free_f08
1167end interface PMPI_Op_free
1168
1169interface PMPI_Reduce
1170    subroutine PMPIR_Reduce_f08ts(sendbuf, recvbuf, count, datatype, op, root, comm, ierror)
1171        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
1172        implicit none
1173        type(*), dimension(..), intent(in) :: sendbuf
1174        type(*), dimension(..) :: recvbuf
1175        integer, intent(in) :: count, root
1176        type(MPI_Datatype), intent(in) :: datatype
1177        type(MPI_Op), intent(in) :: op
1178        type(MPI_Comm), intent(in) :: comm
1179        integer, optional, intent(out) :: ierror
1180    end subroutine PMPIR_Reduce_f08ts
1181end interface PMPI_Reduce
1182
1183interface PMPI_Ireduce
1184    subroutine PMPIR_Ireduce_f08ts(sendbuf, recvbuf, count, datatype, op, root, comm, request, ierror)
1185        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
1186        implicit none
1187        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1188        type(*), dimension(..), asynchronous :: recvbuf
1189        integer, intent(in) :: count, root
1190        type(MPI_Datatype), intent(in) :: datatype
1191        type(MPI_Op), intent(in) :: op
1192        type(MPI_Comm), intent(in) :: comm
1193        type(MPI_Request), intent(out) :: request
1194        integer, optional, intent(out) :: ierror
1195    end subroutine PMPIR_Ireduce_f08ts
1196end interface PMPI_Ireduce
1197
1198interface PMPI_Reduce_local
1199    subroutine PMPIR_Reduce_local_f08ts(inbuf, inoutbuf, count, datatype, op, ierror)
1200        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op
1201        implicit none
1202        type(*), dimension(..), intent(in) :: inbuf
1203        type(*), dimension(..) :: inoutbuf
1204        integer, intent(in) :: count
1205        type(MPI_Datatype), intent(in) :: datatype
1206        type(MPI_Op), intent(in) :: op
1207        integer, optional, intent(out) :: ierror
1208    end subroutine PMPIR_Reduce_local_f08ts
1209end interface PMPI_Reduce_local
1210
1211interface PMPI_Reduce_scatter
1212    subroutine PMPIR_Reduce_scatter_f08ts(sendbuf, recvbuf, recvcounts, datatype, op, comm, &
1213                                       ierror)
1214        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
1215        implicit none
1216        type(*), dimension(..), intent(in) :: sendbuf
1217        type(*), dimension(..) :: recvbuf
1218        integer, intent(in) :: recvcounts(*)
1219        type(MPI_Datatype), intent(in) :: datatype
1220        type(MPI_Op), intent(in) :: op
1221        type(MPI_Comm), intent(in) :: comm
1222        integer, optional, intent(out) :: ierror
1223    end subroutine PMPIR_Reduce_scatter_f08ts
1224end interface PMPI_Reduce_scatter
1225
1226interface PMPI_Ireduce_scatter
1227    subroutine PMPIR_Ireduce_scatter_f08ts(sendbuf, recvbuf, recvcounts, datatype, op, comm, &
1228                                       request, ierror)
1229        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
1230        implicit none
1231        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1232        type(*), dimension(..), asynchronous :: recvbuf
1233        integer, intent(in) :: recvcounts(*)
1234        type(MPI_Datatype), intent(in) :: datatype
1235        type(MPI_Op), intent(in) :: op
1236        type(MPI_Comm), intent(in) :: comm
1237        type(MPI_Request), intent(out) :: request
1238        integer, optional, intent(out) :: ierror
1239    end subroutine PMPIR_Ireduce_scatter_f08ts
1240end interface PMPI_Ireduce_scatter
1241
1242interface PMPI_Reduce_scatter_block
1243    subroutine PMPIR_Reduce_scatter_block_f08ts(sendbuf, recvbuf, recvcount, datatype, op, comm, &
1244                                             ierror)
1245        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
1246        implicit none
1247        type(*), dimension(..), intent(in) :: sendbuf
1248        type(*), dimension(..) :: recvbuf
1249        integer, intent(in) :: recvcount
1250        type(MPI_Datatype), intent(in) :: datatype
1251        type(MPI_Op), intent(in) :: op
1252        type(MPI_Comm), intent(in) :: comm
1253        integer, optional, intent(out) :: ierror
1254    end subroutine PMPIR_Reduce_scatter_block_f08ts
1255end interface PMPI_Reduce_scatter_block
1256
1257interface PMPI_Ireduce_scatter_block
1258    subroutine PMPIR_Ireduce_scatter_block_f08ts(sendbuf, recvbuf, recvcount, datatype, op, comm, &
1259                                             request, ierror)
1260        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
1261        implicit none
1262        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1263        type(*), dimension(..), asynchronous :: recvbuf
1264        integer, intent(in) :: recvcount
1265        type(MPI_Datatype), intent(in) :: datatype
1266        type(MPI_Op), intent(in) :: op
1267        type(MPI_Comm), intent(in) :: comm
1268        type(MPI_Request), intent(out) :: request
1269        integer, optional, intent(out) :: ierror
1270    end subroutine PMPIR_Ireduce_scatter_block_f08ts
1271end interface PMPI_Ireduce_scatter_block
1272
1273interface PMPI_Scan
1274    subroutine PMPIR_Scan_f08ts(sendbuf, recvbuf, count, datatype, op, comm, ierror)
1275        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm
1276        implicit none
1277        type(*), dimension(..), intent(in) :: sendbuf
1278        type(*), dimension(..) :: recvbuf
1279        integer, intent(in) :: count
1280        type(MPI_Datatype), intent(in) :: datatype
1281        type(MPI_Op), intent(in) :: op
1282        type(MPI_Comm), intent(in) :: comm
1283        integer, optional, intent(out) :: ierror
1284    end subroutine PMPIR_Scan_f08ts
1285end interface PMPI_Scan
1286
1287interface PMPI_Iscan
1288    subroutine PMPIR_Iscan_f08ts(sendbuf, recvbuf, count, datatype, op, comm, request, ierror)
1289        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Comm, MPI_Request
1290        implicit none
1291        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1292        type(*), dimension(..), asynchronous :: recvbuf
1293        integer, intent(in) :: count
1294        type(MPI_Datatype), intent(in) :: datatype
1295        type(MPI_Op), intent(in) :: op
1296        type(MPI_Comm), intent(in) :: comm
1297        type(MPI_Request), intent(out) :: request
1298        integer, optional, intent(out) :: ierror
1299    end subroutine PMPIR_Iscan_f08ts
1300end interface PMPI_Iscan
1301
1302interface PMPI_Scatter
1303    subroutine PMPIR_Scatter_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
1304                                root, comm, ierror)
1305        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
1306        implicit none
1307        type(*), dimension(..), intent(in) :: sendbuf
1308        type(*), dimension(..) :: recvbuf
1309        integer, intent(in) :: sendcount, recvcount, root
1310        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1311        type(MPI_Comm), intent(in) :: comm
1312        integer, optional, intent(out) :: ierror
1313    end subroutine PMPIR_Scatter_f08ts
1314end interface PMPI_Scatter
1315
1316interface PMPI_Iscatter
1317    subroutine PMPIR_Iscatter_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
1318                                root, comm, request, ierror)
1319        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
1320        implicit none
1321        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1322        type(*), dimension(..), asynchronous :: recvbuf
1323        integer, intent(in) :: sendcount, recvcount, root
1324        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1325        type(MPI_Comm), intent(in) :: comm
1326        type(MPI_Request), intent(out) :: request
1327        integer, optional, intent(out) :: ierror
1328    end subroutine PMPIR_Iscatter_f08ts
1329end interface PMPI_Iscatter
1330
1331interface PMPI_Scatterv
1332    subroutine PMPIR_Scatterv_f08ts(sendbuf, sendcounts, displs, sendtype, recvbuf, recvcount, &
1333                                 recvtype, root, comm, ierror)
1334        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
1335        implicit none
1336        type(*), dimension(..), intent(in) :: sendbuf
1337        type(*), dimension(..) :: recvbuf
1338        integer, intent(in) :: recvcount, root
1339        integer, intent(in) :: sendcounts(*), displs(*)
1340        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1341        type(MPI_Comm), intent(in) :: comm
1342        integer, optional, intent(out) :: ierror
1343    end subroutine PMPIR_Scatterv_f08ts
1344end interface PMPI_Scatterv
1345
1346interface PMPI_Iscatterv
1347    subroutine PMPIR_Iscatterv_f08ts(sendbuf, sendcounts, displs, sendtype, recvbuf, recvcount, &
1348                                 recvtype, root, comm, request, ierror)
1349        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
1350        implicit none
1351        type(*), dimension(..), intent(in), asynchronous :: sendbuf
1352        type(*), dimension(..), asynchronous :: recvbuf
1353        integer, intent(in) :: recvcount, root
1354        integer, intent(in) :: sendcounts(*), displs(*)
1355        type(MPI_Datatype), intent(in) :: sendtype, recvtype
1356        type(MPI_Comm), intent(in) :: comm
1357        type(MPI_Request), intent(out) :: request
1358        integer, optional, intent(out) :: ierror
1359    end subroutine PMPIR_Iscatterv_f08ts
1360end interface PMPI_Iscatterv
1361
1362interface PMPI_Comm_compare
1363    subroutine PMPIR_Comm_compare_f08(comm1,comm2,result, ierror)
1364        use :: mpi_f08_types, only : MPI_Comm
1365        implicit none
1366        type(MPI_Comm), intent(in) :: comm1
1367        type(MPI_Comm), intent(in) :: comm2
1368        integer, intent(out) :: result
1369        integer, optional, intent(out) :: ierror
1370    end subroutine PMPIR_Comm_compare_f08
1371end interface PMPI_Comm_compare
1372
1373interface PMPI_Comm_create
1374    subroutine PMPIR_Comm_create_f08(comm, group, newcomm, ierror)
1375        use :: mpi_f08_types, only : MPI_Comm, MPI_Group
1376        implicit none
1377        type(MPI_Comm), intent(in) :: comm
1378        type(MPI_Group), intent(in) :: group
1379        type(MPI_Comm), intent(out) :: newcomm
1380        integer, optional, intent(out) :: ierror
1381    end subroutine PMPIR_Comm_create_f08
1382end interface PMPI_Comm_create
1383
1384interface PMPI_Comm_create_group
1385    subroutine PMPIR_Comm_create_group_f08(comm, group, tag, newcomm, ierror)
1386        use :: mpi_f08_types, only : MPI_Comm, MPI_Group
1387        implicit none
1388        type(MPI_Comm), intent(in) :: comm
1389        type(MPI_Group), intent(in) :: group
1390        integer, intent(in) :: tag
1391        type(MPI_Comm), intent(out) :: newcomm
1392        integer, optional, intent(out) :: ierror
1393    end subroutine PMPIR_Comm_create_group_f08
1394end interface PMPI_Comm_create_group
1395
1396interface PMPI_Comm_create_keyval
1397    subroutine PMPIR_Comm_create_keyval_f08(comm_copy_attr_fn, comm_delete_attr_fn, comm_keyval, &
1398                                           extra_state, ierror)
1399        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1400        use :: mpi_f08_callbacks, only : MPI_Comm_copy_attr_function
1401        use :: mpi_f08_callbacks, only : MPI_Comm_delete_attr_function
1402        implicit none
1403        procedure(MPI_Comm_copy_attr_function) :: comm_copy_attr_fn
1404        procedure(MPI_Comm_delete_attr_function) :: comm_delete_attr_fn
1405        integer, intent(out) :: comm_keyval
1406        integer(MPI_ADDRESS_KIND), intent(in) :: extra_state
1407        integer, optional, intent(out) :: ierror
1408    end subroutine PMPIR_Comm_create_keyval_f08
1409end interface PMPI_Comm_create_keyval
1410
1411interface PMPI_Comm_delete_attr
1412    subroutine PMPIR_Comm_delete_attr_f08(comm, comm_keyval, ierror)
1413        use :: mpi_f08_types, only : MPI_Comm
1414        implicit none
1415        type(MPI_Comm), intent(in) :: comm
1416        integer, intent(in) :: comm_keyval
1417        integer, optional, intent(out) :: ierror
1418    end subroutine PMPIR_Comm_delete_attr_f08
1419end interface PMPI_Comm_delete_attr
1420
1421interface PMPI_Comm_dup
1422    subroutine PMPIR_Comm_dup_f08(comm, newcomm, ierror)
1423        use :: mpi_f08_types, only : MPI_Comm
1424        implicit none
1425        type(MPI_Comm), intent(in) :: comm
1426        type(MPI_Comm), intent(out) :: newcomm
1427        integer, optional, intent(out) :: ierror
1428    end subroutine PMPIR_Comm_dup_f08
1429end interface PMPI_Comm_dup
1430
1431interface PMPI_Comm_dup_with_info
1432    subroutine PMPIR_Comm_dup_with_info_f08(comm, info, newcomm, ierror)
1433        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
1434        implicit none
1435        type(MPI_Comm), intent(in) :: comm
1436        type(MPI_Info), intent(in) :: info
1437        type(MPI_Comm), intent(out) :: newcomm
1438        integer, optional, intent(out) :: ierror
1439    end subroutine PMPIR_Comm_dup_with_info_f08
1440end interface PMPI_Comm_dup_with_info
1441
1442interface PMPI_Comm_idup
1443    subroutine PMPIR_Comm_idup_f08(comm, newcomm, request, ierror)
1444        use :: mpi_f08_types, only : MPI_Comm, MPI_Request
1445        implicit none
1446        type(MPI_Comm), intent(in) :: comm
1447        type(MPI_Comm), intent(out), asynchronous :: newcomm
1448        type(MPI_Request), intent(out) :: request
1449        integer, optional, intent(out) :: ierror
1450    end subroutine PMPIR_Comm_idup_f08
1451end interface PMPI_Comm_idup
1452
1453interface PMPI_Comm_free
1454    subroutine PMPIR_Comm_free_f08(comm, ierror)
1455        use :: mpi_f08_types, only : MPI_Comm
1456        implicit none
1457        type(MPI_Comm), intent(inout) :: comm
1458        integer, optional, intent(out) :: ierror
1459    end subroutine PMPIR_Comm_free_f08
1460end interface PMPI_Comm_free
1461
1462interface PMPI_Comm_free_keyval
1463    subroutine PMPIR_Comm_free_keyval_f08(comm_keyval, ierror)
1464        implicit none
1465        integer, intent(inout) :: comm_keyval
1466        integer, optional, intent(out) :: ierror
1467    end subroutine PMPIR_Comm_free_keyval_f08
1468end interface PMPI_Comm_free_keyval
1469
1470interface PMPI_Comm_get_attr
1471    subroutine PMPIR_Comm_get_attr_f08(comm, comm_keyval, attribute_val, flag, ierror)
1472        use :: mpi_f08_types, only : MPI_Comm
1473        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1474        implicit none
1475        type(MPI_Comm), intent(in) :: comm
1476        integer, intent(in) :: comm_keyval
1477        integer(MPI_ADDRESS_KIND), intent(out) :: attribute_val
1478        logical, intent(out) :: flag
1479        integer, optional, intent(out) :: ierror
1480    end subroutine PMPIR_Comm_get_attr_f08
1481end interface PMPI_Comm_get_attr
1482
1483interface PMPI_Comm_get_info
1484    subroutine PMPIR_Comm_get_info_f08(comm, info_used, ierror)
1485        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
1486        implicit none
1487        type(MPI_Comm), intent(in) :: comm
1488        type(MPI_Info), intent(out) :: info_used
1489        integer, optional, intent(out) :: ierror
1490    end subroutine PMPIR_Comm_get_info_f08
1491end interface PMPI_Comm_get_info
1492
1493interface PMPI_Comm_get_name
1494    subroutine PMPIR_Comm_get_name_f08(comm, comm_name, resultlen, ierror)
1495        use :: mpi_f08_types, only : MPI_Comm
1496        use :: mpi_f08_compile_constants, only : MPI_MAX_OBJECT_NAME
1497        implicit none
1498        type(MPI_Comm), intent(in) :: comm
1499        character(len=MPI_MAX_OBJECT_NAME), intent(out) :: comm_name
1500        integer, intent(out) :: resultlen
1501        integer, optional, intent(out) :: ierror
1502    end subroutine PMPIR_Comm_get_name_f08
1503end interface PMPI_Comm_get_name
1504
1505interface PMPI_Comm_group
1506    subroutine PMPIR_Comm_group_f08(comm, group, ierror)
1507        use :: mpi_f08_types, only : MPI_Comm, MPI_Group
1508        implicit none
1509        type(MPI_Comm), intent(in) :: comm
1510        type(MPI_Group), intent(out) :: group
1511        integer, optional, intent(out) :: ierror
1512    end subroutine PMPIR_Comm_group_f08
1513end interface PMPI_Comm_group
1514
1515interface PMPI_Comm_rank
1516    subroutine PMPIR_Comm_rank_f08(comm, rank, ierror)
1517        use :: mpi_f08_types, only : MPI_Comm
1518        implicit none
1519        type(MPI_Comm), intent(in) :: comm
1520        integer, intent(out) :: rank
1521        integer, optional, intent(out) :: ierror
1522    end subroutine PMPIR_Comm_rank_f08
1523end interface PMPI_Comm_rank
1524
1525interface PMPI_Comm_remote_group
1526    subroutine PMPIR_Comm_remote_group_f08(comm, group, ierror)
1527        use :: mpi_f08_types, only : MPI_Comm, MPI_Group
1528        implicit none
1529        type(MPI_Comm), intent(in) :: comm
1530        type(MPI_Group), intent(out) :: group
1531        integer, optional, intent(out) :: ierror
1532    end subroutine PMPIR_Comm_remote_group_f08
1533end interface PMPI_Comm_remote_group
1534
1535interface PMPI_Comm_remote_size
1536    subroutine PMPIR_Comm_remote_size_f08(comm, size, ierror)
1537        use :: mpi_f08_types, only : MPI_Comm
1538        implicit none
1539        type(MPI_Comm), intent(in) :: comm
1540        integer, intent(out) :: size
1541        integer, optional, intent(out) :: ierror
1542    end subroutine PMPIR_Comm_remote_size_f08
1543end interface PMPI_Comm_remote_size
1544
1545interface PMPI_Comm_set_attr
1546    subroutine PMPIR_Comm_set_attr_f08(comm, comm_keyval, attribute_val, ierror)
1547        use :: mpi_f08_types, only : MPI_Comm
1548        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1549        implicit none
1550        type(MPI_Comm), intent(in) :: comm
1551        integer, intent(in) :: comm_keyval
1552        integer(MPI_ADDRESS_KIND), intent(in) :: attribute_val
1553        integer, optional, intent(out) :: ierror
1554    end subroutine PMPIR_Comm_set_attr_f08
1555end interface PMPI_Comm_set_attr
1556
1557interface PMPI_Comm_set_info
1558    subroutine PMPIR_Comm_set_info_f08(comm, info, ierror)
1559        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
1560        implicit none
1561        type(MPI_Comm), intent(in) :: comm
1562        type(MPI_Info), intent(in) :: info
1563        integer, optional, intent(out) :: ierror
1564    end subroutine PMPIR_Comm_set_info_f08
1565end interface PMPI_Comm_set_info
1566
1567interface PMPI_Comm_set_name
1568    subroutine PMPIR_Comm_set_name_f08(comm, comm_name, ierror)
1569        use :: mpi_f08_types, only : MPI_Comm
1570        implicit none
1571        type(MPI_Comm), intent(in) :: comm
1572        character(len=*), intent(in) :: comm_name
1573        integer, optional, intent(out) :: ierror
1574    end subroutine PMPIR_Comm_set_name_f08
1575end interface PMPI_Comm_set_name
1576
1577interface PMPI_Comm_size
1578    subroutine PMPIR_Comm_size_f08(comm, size, ierror)
1579        use :: mpi_f08_types, only : MPI_Comm
1580        implicit none
1581        type(MPI_Comm), intent(in) :: comm
1582        integer, intent(out) :: size
1583        integer, optional, intent(out) :: ierror
1584    end subroutine PMPIR_Comm_size_f08
1585end interface PMPI_Comm_size
1586
1587interface PMPI_Comm_split
1588    subroutine PMPIR_Comm_split_f08(comm, color, key, newcomm, ierror)
1589        use :: mpi_f08_types, only : MPI_Comm
1590        implicit none
1591        type(MPI_Comm), intent(in) :: comm
1592        integer, intent(in) :: color, key
1593        type(MPI_Comm), intent(out) :: newcomm
1594        integer, optional, intent(out) :: ierror
1595    end subroutine PMPIR_Comm_split_f08
1596end interface PMPI_Comm_split
1597
1598interface PMPI_Comm_test_inter
1599    subroutine PMPIR_Comm_test_inter_f08(comm, flag, ierror)
1600        use :: mpi_f08_types, only : MPI_Comm
1601        implicit none
1602        type(MPI_Comm), intent(in) :: comm
1603        logical, intent(out) :: flag
1604        integer, optional, intent(out) :: ierror
1605    end subroutine PMPIR_Comm_test_inter_f08
1606end interface PMPI_Comm_test_inter
1607
1608interface PMPI_Group_compare
1609    subroutine PMPIR_Group_compare_f08(group1,group2,result, ierror)
1610        use :: mpi_f08_types, only : MPI_Group
1611        implicit none
1612        type(MPI_Group), intent(in) :: group1, group2
1613        integer, intent(out) :: result
1614        integer, optional, intent(out) :: ierror
1615    end subroutine PMPIR_Group_compare_f08
1616end interface PMPI_Group_compare
1617
1618interface PMPI_Group_difference
1619    subroutine PMPIR_Group_difference_f08(group1,group2,newgroup, ierror)
1620        use :: mpi_f08_types, only : MPI_Group
1621        implicit none
1622        type(MPI_Group), intent(in) :: group1, group2
1623        type(MPI_Group), intent(out) :: newgroup
1624        integer, optional, intent(out) :: ierror
1625    end subroutine PMPIR_Group_difference_f08
1626end interface PMPI_Group_difference
1627
1628interface PMPI_Group_excl
1629    subroutine PMPIR_Group_excl_f08(group, n,ranks, newgroup, ierror)
1630        use :: mpi_f08_types, only : MPI_Group
1631        implicit none
1632        type(MPI_Group), intent(in) :: group
1633        integer, intent(in) :: n, ranks(n)
1634        type(MPI_Group), intent(out) :: newgroup
1635        integer, optional, intent(out) :: ierror
1636    end subroutine PMPIR_Group_excl_f08
1637end interface PMPI_Group_excl
1638
1639interface PMPI_Group_free
1640    subroutine PMPIR_Group_free_f08(group, ierror)
1641        use :: mpi_f08_types, only : MPI_Group
1642        implicit none
1643        type(MPI_Group), intent(inout) :: group
1644        integer, optional, intent(out) :: ierror
1645    end subroutine PMPIR_Group_free_f08
1646end interface PMPI_Group_free
1647
1648interface PMPI_Group_incl
1649    subroutine PMPIR_Group_incl_f08(group, n,ranks, newgroup, ierror)
1650        use :: mpi_f08_types, only : MPI_Group
1651        implicit none
1652        integer, intent(in) :: n, ranks(n)
1653        type(MPI_Group), intent(in) :: group
1654        type(MPI_Group), intent(out) :: newgroup
1655        integer, optional, intent(out) :: ierror
1656    end subroutine PMPIR_Group_incl_f08
1657end interface PMPI_Group_incl
1658
1659interface PMPI_Group_intersection
1660    subroutine PMPIR_Group_intersection_f08(group1,group2,newgroup, ierror)
1661        use :: mpi_f08_types, only : MPI_Group
1662        implicit none
1663        type(MPI_Group), intent(in) :: group1, group2
1664        type(MPI_Group), intent(out) :: newgroup
1665        integer, optional, intent(out) :: ierror
1666    end subroutine PMPIR_Group_intersection_f08
1667end interface PMPI_Group_intersection
1668
1669interface PMPI_Group_range_excl
1670    subroutine PMPIR_Group_range_excl_f08(group, n,ranges, newgroup, ierror)
1671        use :: mpi_f08_types, only : MPI_Group
1672        implicit none
1673        type(MPI_Group), intent(in) :: group
1674        integer, intent(in) :: n, ranges(3,n)
1675        type(MPI_Group), intent(out) :: newgroup
1676        integer, optional, intent(out) :: ierror
1677    end subroutine PMPIR_Group_range_excl_f08
1678end interface PMPI_Group_range_excl
1679
1680interface PMPI_Group_range_incl
1681    subroutine PMPIR_Group_range_incl_f08(group, n,ranges, newgroup, ierror)
1682        use :: mpi_f08_types, only : MPI_Group
1683        implicit none
1684        type(MPI_Group), intent(in) :: group
1685        integer, intent(in) :: n, ranges(3,n)
1686        type(MPI_Group), intent(out) :: newgroup
1687        integer, optional, intent(out) :: ierror
1688    end subroutine PMPIR_Group_range_incl_f08
1689end interface PMPI_Group_range_incl
1690
1691interface PMPI_Group_rank
1692    subroutine PMPIR_Group_rank_f08(group, rank, ierror)
1693        use :: mpi_f08_types, only : MPI_Group
1694        implicit none
1695        type(MPI_Group), intent(in) :: group
1696        integer, intent(out) :: rank
1697        integer, optional, intent(out) :: ierror
1698    end subroutine PMPIR_Group_rank_f08
1699end interface PMPI_Group_rank
1700
1701interface PMPI_Group_size
1702    subroutine PMPIR_Group_size_f08(group, size, ierror)
1703        use :: mpi_f08_types, only : MPI_Group
1704        implicit none
1705        type(MPI_Group), intent(in) :: group
1706        integer, intent(out) :: size
1707        integer, optional, intent(out) :: ierror
1708    end subroutine PMPIR_Group_size_f08
1709end interface PMPI_Group_size
1710
1711interface PMPI_Group_translate_ranks
1712    subroutine PMPIR_Group_translate_ranks_f08(group1,n, ranks1,group2,ranks2,ierror)
1713        use :: mpi_f08_types, only : MPI_Group
1714        implicit none
1715        type(MPI_Group), intent(in) :: group1, group2
1716        integer, intent(in) :: n
1717        integer, intent(in) :: ranks1(n)
1718        integer, intent(out) :: ranks2(n)
1719        integer, optional, intent(out) :: ierror
1720    end subroutine PMPIR_Group_translate_ranks_f08
1721end interface PMPI_Group_translate_ranks
1722
1723interface PMPI_Group_union
1724    subroutine PMPIR_Group_union_f08(group1,group2,newgroup, ierror)
1725        use :: mpi_f08_types, only : MPI_Group
1726        implicit none
1727        type(MPI_Group), intent(in) :: group1, group2
1728        type(MPI_Group), intent(out) :: newgroup
1729        integer, optional, intent(out) :: ierror
1730    end subroutine PMPIR_Group_union_f08
1731end interface PMPI_Group_union
1732
1733interface PMPI_Intercomm_create
1734    subroutine PMPIR_Intercomm_create_f08(local_comm, local_leader, peer_comm, remote_leader, &
1735                                         tag, newintercomm, ierror)
1736        use :: mpi_f08_types, only : MPI_Comm
1737        implicit none
1738        type(MPI_Comm), intent(in) :: local_comm, peer_comm
1739        integer, intent(in) :: local_leader, remote_leader, tag
1740        type(MPI_Comm), intent(out) :: newintercomm
1741        integer, optional, intent(out) :: ierror
1742    end subroutine PMPIR_Intercomm_create_f08
1743end interface PMPI_Intercomm_create
1744
1745interface PMPI_Intercomm_merge
1746    subroutine PMPIR_Intercomm_merge_f08(intercomm, high, newintracomm, ierror)
1747        use :: mpi_f08_types, only : MPI_Comm
1748        implicit none
1749        type(MPI_Comm), intent(in) :: intercomm
1750        logical, intent(in) :: high
1751        type(MPI_Comm), intent(out) :: newintracomm
1752        integer, optional, intent(out) :: ierror
1753    end subroutine PMPIR_Intercomm_merge_f08
1754end interface PMPI_Intercomm_merge
1755
1756interface PMPI_Type_create_keyval
1757    subroutine PMPIR_Type_create_keyval_f08(type_copy_attr_fn, type_delete_attr_fn, type_keyval, &
1758                                           extra_state, ierror)
1759        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1760        use :: mpi_f08_callbacks, only : MPI_Type_copy_attr_function
1761        use :: mpi_f08_callbacks, only : MPI_Type_delete_attr_function
1762        implicit none
1763        procedure(MPI_Type_copy_attr_function) :: type_copy_attr_fn
1764        procedure(MPI_Type_delete_attr_function) :: type_delete_attr_fn
1765        integer, intent(out) :: type_keyval
1766        integer(MPI_ADDRESS_KIND), intent(in) :: extra_state
1767        integer, optional, intent(out) :: ierror
1768    end subroutine PMPIR_Type_create_keyval_f08
1769end interface PMPI_Type_create_keyval
1770
1771interface PMPI_Type_delete_attr
1772    subroutine PMPIR_Type_delete_attr_f08(datatype, type_keyval, ierror)
1773        use :: mpi_f08_types, only : MPI_Datatype
1774        implicit none
1775        type(MPI_Datatype), intent(in) :: datatype
1776        integer, intent(in) :: type_keyval
1777        integer, optional, intent(out) :: ierror
1778    end subroutine PMPIR_Type_delete_attr_f08
1779end interface PMPI_Type_delete_attr
1780
1781interface PMPI_Type_free_keyval
1782    subroutine PMPIR_Type_free_keyval_f08(type_keyval, ierror)
1783        implicit none
1784        integer, intent(inout) :: type_keyval
1785        integer, optional, intent(out) :: ierror
1786    end subroutine PMPIR_Type_free_keyval_f08
1787end interface PMPI_Type_free_keyval
1788
1789interface PMPI_Type_get_attr
1790    subroutine PMPIR_Type_get_attr_f08(datatype, type_keyval, attribute_val, flag, ierror)
1791        use :: mpi_f08_types, only : MPI_Datatype
1792        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1793        implicit none
1794        type(MPI_Datatype), intent(in) :: datatype
1795        integer, intent(in) :: type_keyval
1796        integer(MPI_ADDRESS_KIND), intent(out) :: attribute_val
1797        logical, intent(out) :: flag
1798        integer, optional, intent(out) :: ierror
1799    end subroutine PMPIR_Type_get_attr_f08
1800end interface PMPI_Type_get_attr
1801
1802interface PMPI_Type_get_name
1803    subroutine PMPIR_Type_get_name_f08(datatype, type_name, resultlen, ierror)
1804        use :: mpi_f08_types, only : MPI_Datatype
1805        use :: mpi_f08_compile_constants, only : MPI_MAX_OBJECT_NAME
1806        implicit none
1807        type(MPI_Datatype), intent(in) :: datatype
1808        character(len=MPI_MAX_OBJECT_NAME), intent(out) :: type_name
1809        integer, intent(out) :: resultlen
1810        integer, optional, intent(out) :: ierror
1811    end subroutine PMPIR_Type_get_name_f08
1812end interface PMPI_Type_get_name
1813
1814interface PMPI_Type_set_attr
1815    subroutine PMPIR_Type_set_attr_f08(datatype, type_keyval, attribute_val, ierror)
1816        use :: mpi_f08_types, only : MPI_Datatype
1817        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1818        implicit none
1819        type(MPI_Datatype), intent(in) :: datatype
1820        integer, intent(in) :: type_keyval
1821        integer(MPI_ADDRESS_KIND), intent(in) :: attribute_val
1822        integer, optional, intent(out) :: ierror
1823    end subroutine PMPIR_Type_set_attr_f08
1824end interface PMPI_Type_set_attr
1825
1826interface PMPI_Type_set_name
1827    subroutine PMPIR_Type_set_name_f08(datatype, type_name, ierror)
1828        use :: mpi_f08_types, only : MPI_Datatype
1829        implicit none
1830        type(MPI_Datatype), intent(in) :: datatype
1831        character(len=*), intent(in) :: type_name
1832        integer, optional, intent(out) :: ierror
1833    end subroutine PMPIR_Type_set_name_f08
1834end interface PMPI_Type_set_name
1835
1836interface PMPI_Win_create_keyval
1837    subroutine PMPIR_Win_create_keyval_f08(win_copy_attr_fn, win_delete_attr_fn, win_keyval, &
1838                                          extra_state, ierror)
1839        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1840        use :: mpi_f08_callbacks, only : MPI_Win_copy_attr_function
1841        use :: mpi_f08_callbacks, only : MPI_Win_delete_attr_function
1842        implicit none
1843        procedure(MPI_Win_copy_attr_function) :: win_copy_attr_fn
1844        procedure(MPI_Win_delete_attr_function) :: win_delete_attr_fn
1845        integer, intent(out) :: win_keyval
1846        integer(MPI_ADDRESS_KIND), intent(in) :: extra_state
1847        integer, optional, intent(out) :: ierror
1848    end subroutine PMPIR_Win_create_keyval_f08
1849end interface PMPI_Win_create_keyval
1850
1851interface PMPI_Win_delete_attr
1852    subroutine PMPIR_Win_delete_attr_f08(win, win_keyval, ierror)
1853        use :: mpi_f08_types, only : MPI_Win
1854        implicit none
1855        type(MPI_Win), intent(in) :: win
1856        integer, intent(in) :: win_keyval
1857        integer, optional, intent(out) :: ierror
1858    end subroutine PMPIR_Win_delete_attr_f08
1859end interface PMPI_Win_delete_attr
1860
1861interface PMPI_Win_free_keyval
1862    subroutine PMPIR_Win_free_keyval_f08(win_keyval, ierror)
1863        implicit none
1864        integer, intent(inout) :: win_keyval
1865        integer, optional, intent(out) :: ierror
1866    end subroutine PMPIR_Win_free_keyval_f08
1867end interface PMPI_Win_free_keyval
1868
1869interface PMPI_Win_get_attr
1870    subroutine PMPIR_Win_get_attr_f08(win, win_keyval, attribute_val, flag, ierror)
1871        use :: mpi_f08_types, only : MPI_Win
1872        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1873        implicit none
1874        type(MPI_Win), intent(in) :: win
1875        integer, intent(in) :: win_keyval
1876        integer(MPI_ADDRESS_KIND), intent(out) :: attribute_val
1877        logical, intent(out) :: flag
1878        integer, optional, intent(out) :: ierror
1879    end subroutine PMPIR_Win_get_attr_f08
1880end interface PMPI_Win_get_attr
1881
1882interface PMPI_Win_get_name
1883    subroutine PMPIR_Win_get_name_f08(win, win_name, resultlen, ierror)
1884        use :: mpi_f08_types, only : MPI_Win
1885        use :: mpi_f08_compile_constants, only : MPI_MAX_OBJECT_NAME
1886        implicit none
1887        type(MPI_Win), intent(in) :: win
1888        character(len=MPI_MAX_OBJECT_NAME), intent(out) :: win_name
1889        integer, intent(out) :: resultlen
1890        integer, optional, intent(out) :: ierror
1891    end subroutine PMPIR_Win_get_name_f08
1892end interface PMPI_Win_get_name
1893
1894interface PMPI_Win_set_attr
1895    subroutine PMPIR_Win_set_attr_f08(win, win_keyval, attribute_val, ierror)
1896        use :: mpi_f08_types, only : MPI_Win
1897        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
1898        implicit none
1899        type(MPI_Win), intent(in) :: win
1900        integer, intent(in) :: win_keyval
1901        integer(MPI_ADDRESS_KIND), intent(in) :: attribute_val
1902        integer, optional, intent(out) :: ierror
1903    end subroutine PMPIR_Win_set_attr_f08
1904end interface PMPI_Win_set_attr
1905
1906interface PMPI_Win_set_name
1907    subroutine PMPIR_Win_set_name_f08(win, win_name, ierror)
1908        use :: mpi_f08_types, only : MPI_Win
1909        implicit none
1910        type(MPI_Win), intent(in) :: win
1911        character(len=*), intent(in) :: win_name
1912        integer, optional, intent(out) :: ierror
1913    end subroutine PMPIR_Win_set_name_f08
1914end interface PMPI_Win_set_name
1915
1916interface PMPI_Cartdim_get
1917    subroutine PMPIR_Cartdim_get_f08(comm, ndims, ierror)
1918        use :: mpi_f08_types, only : MPI_Comm
1919        implicit none
1920        type(MPI_Comm), intent(in) :: comm
1921        integer, intent(out) :: ndims
1922        integer, optional, intent(out) :: ierror
1923    end subroutine PMPIR_Cartdim_get_f08
1924end interface PMPI_Cartdim_get
1925
1926interface PMPI_Cart_coords
1927    subroutine PMPIR_Cart_coords_f08(comm, rank, maxdims, coords, ierror)
1928        use :: mpi_f08_types, only : MPI_Comm
1929        implicit none
1930        type(MPI_Comm), intent(in) :: comm
1931        integer, intent(in) :: rank, maxdims
1932        integer, intent(out) :: coords(maxdims)
1933        integer, optional, intent(out) :: ierror
1934    end subroutine PMPIR_Cart_coords_f08
1935end interface PMPI_Cart_coords
1936
1937interface PMPI_Cart_create
1938    subroutine PMPIR_Cart_create_f08(comm_old, ndims, dims, periods, reorder, comm_cart, ierror)
1939        use :: mpi_f08_types, only : MPI_Comm
1940        implicit none
1941        type(MPI_Comm), intent(in) :: comm_old
1942        integer, intent(in) :: ndims, dims(ndims)
1943        logical, intent(in) :: periods(ndims), reorder
1944        type(MPI_Comm), intent(out) :: comm_cart
1945        integer, optional, intent(out) :: ierror
1946    end subroutine PMPIR_Cart_create_f08
1947end interface PMPI_Cart_create
1948
1949interface PMPI_Cart_get
1950    subroutine PMPIR_Cart_get_f08(comm, maxdims, dims, periods, coords, ierror)
1951        use :: mpi_f08_types, only : MPI_Comm
1952        implicit none
1953        type(MPI_Comm), intent(in) :: comm
1954        integer, intent(in) :: maxdims
1955        integer, intent(out) :: dims(maxdims), coords(maxdims)
1956        logical, intent(out) :: periods(maxdims)
1957        integer, optional, intent(out) :: ierror
1958    end subroutine PMPIR_Cart_get_f08
1959end interface PMPI_Cart_get
1960
1961interface PMPI_Cart_map
1962    subroutine PMPIR_Cart_map_f08(comm, ndims, dims, periods, newrank, ierror)
1963        use :: mpi_f08_types, only : MPI_Comm
1964        implicit none
1965        type(MPI_Comm), intent(in) :: comm
1966        integer, intent(in) :: ndims, dims(ndims)
1967        logical, intent(in) :: periods(ndims)
1968        integer, intent(out) :: newrank
1969        integer, optional, intent(out) :: ierror
1970    end subroutine PMPIR_Cart_map_f08
1971end interface PMPI_Cart_map
1972
1973interface PMPI_Cart_rank
1974    subroutine PMPIR_Cart_rank_f08(comm, coords, rank, ierror)
1975        use :: mpi_f08_types, only : MPI_Comm
1976        implicit none
1977        type(MPI_Comm), intent(in) :: comm
1978        integer, intent(in) :: coords(*)
1979        integer, intent(out) :: rank
1980        integer, optional, intent(out) :: ierror
1981    end subroutine PMPIR_Cart_rank_f08
1982end interface PMPI_Cart_rank
1983
1984interface PMPI_Cart_shift
1985    subroutine PMPIR_Cart_shift_f08(comm, direction, disp, rank_source, rank_dest, ierror)
1986        use :: mpi_f08_types, only : MPI_Comm
1987        implicit none
1988        type(MPI_Comm), intent(in) :: comm
1989        integer, intent(in) :: direction, disp
1990        integer, intent(out) :: rank_source, rank_dest
1991        integer, optional, intent(out) :: ierror
1992    end subroutine PMPIR_Cart_shift_f08
1993end interface PMPI_Cart_shift
1994
1995interface PMPI_Cart_sub
1996    subroutine PMPIR_Cart_sub_f08(comm, remain_dims, newcomm, ierror)
1997        use :: mpi_f08_types, only : MPI_Comm
1998        implicit none
1999        type(MPI_Comm), intent(in) :: comm
2000        logical, intent(in) :: remain_dims(*)
2001        type(MPI_Comm), intent(out) :: newcomm
2002        integer, optional, intent(out) :: ierror
2003    end subroutine PMPIR_Cart_sub_f08
2004end interface PMPI_Cart_sub
2005
2006interface PMPI_Dims_create
2007    subroutine PMPIR_Dims_create_f08(nnodes, ndims, dims, ierror)
2008        implicit none
2009        integer, intent(in) :: nnodes, ndims
2010        integer, intent(inout) :: dims(ndims)
2011        integer, optional, intent(out) :: ierror
2012    end subroutine PMPIR_Dims_create_f08
2013end interface PMPI_Dims_create
2014
2015interface PMPI_Dist_graph_create
2016    subroutine PMPIR_Dist_graph_create_f08(comm_old, n,sources, degrees, destinations, weights, &
2017                                          info, reorder, comm_dist_graph, ierror)
2018        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
2019        implicit none
2020        type(MPI_Comm), intent(in) :: comm_old
2021        integer, intent(in) :: n, sources(n), degrees(n), destinations(*), weights(*)
2022        type(MPI_Info), intent(in) :: info
2023        logical, intent(in) :: reorder
2024        type(MPI_Comm), intent(out) :: comm_dist_graph
2025        integer, optional, intent(out) :: ierror
2026    end subroutine PMPIR_Dist_graph_create_f08
2027end interface PMPI_Dist_graph_create
2028
2029interface PMPI_Dist_graph_create_adjacent
2030    subroutine PMPIR_Dist_graph_create_adjacent_f08(comm_old, indegree, sources, sourceweights, &
2031                                                   outdegree, destinations, destweights, info, reorder, &
2032                                                   comm_dist_graph, ierror)
2033        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
2034        implicit none
2035        type(MPI_Comm), intent(in) :: comm_old
2036        integer, intent(in) :: indegree
2037        integer, intent(in) :: sources(indegree)
2038        integer, intent(in) :: sourceweights(indegree)
2039        integer, intent(in) :: outdegree
2040        integer, intent(in) :: destinations(outdegree)
2041        integer, intent(in) :: destweights(outdegree)
2042        type(MPI_Info), intent(in) :: info
2043        logical, intent(in) :: reorder
2044        type(MPI_Comm), intent(out) :: comm_dist_graph
2045        integer, optional, intent(out) :: ierror
2046    end subroutine PMPIR_Dist_graph_create_adjacent_f08
2047end interface PMPI_Dist_graph_create_adjacent
2048
2049interface PMPI_Dist_graph_neighbors
2050    subroutine PMPIR_Dist_graph_neighbors_f08(comm, maxindegree, sources, sourceweights, &
2051                                             maxoutdegree, destinations, destweights, ierror)
2052        use :: mpi_f08_types, only : MPI_Comm
2053        implicit none
2054        type(MPI_Comm), intent(in) :: comm
2055        integer, intent(in) :: maxindegree, maxoutdegree
2056        integer, intent(out) :: sources(maxindegree), destinations(maxoutdegree)
2057        integer, intent(out) :: sourceweights(maxindegree), destweights(maxoutdegree)
2058        integer, optional, intent(out) :: ierror
2059    end subroutine PMPIR_Dist_graph_neighbors_f08
2060end interface PMPI_Dist_graph_neighbors
2061
2062interface PMPI_Dist_graph_neighbors_count
2063    subroutine PMPIR_Dist_graph_neighbors_count_f08(comm, indegree, outdegree, weighted, ierror)
2064        use :: mpi_f08_types, only : MPI_Comm
2065        implicit none
2066        type(MPI_Comm), intent(in) :: comm
2067        integer, intent(out) :: indegree, outdegree
2068        logical, intent(out) :: weighted
2069        integer, optional, intent(out) :: ierror
2070    end subroutine PMPIR_Dist_graph_neighbors_count_f08
2071end interface PMPI_Dist_graph_neighbors_count
2072
2073interface PMPI_Graphdims_get
2074    subroutine PMPIR_Graphdims_get_f08(comm, nnodes, nedges, ierror)
2075        use :: mpi_f08_types, only : MPI_Comm
2076        implicit none
2077        type(MPI_Comm), intent(in) :: comm
2078        integer, intent(out) :: nnodes, nedges
2079        integer, optional, intent(out) :: ierror
2080    end subroutine PMPIR_Graphdims_get_f08
2081end interface PMPI_Graphdims_get
2082
2083interface PMPI_Graph_create
2084    subroutine PMPIR_Graph_create_f08(comm_old, nnodes, index, edges, reorder, comm_graph, &
2085                                     ierror)
2086        use :: mpi_f08_types, only : MPI_Comm
2087        implicit none
2088        type(MPI_Comm), intent(in) :: comm_old
2089        integer, intent(in) :: nnodes, index(nnodes), edges(*)
2090        logical, intent(in) :: reorder
2091        type(MPI_Comm), intent(out) :: comm_graph
2092        integer, optional, intent(out) :: ierror
2093    end subroutine PMPIR_Graph_create_f08
2094end interface PMPI_Graph_create
2095
2096interface PMPI_Graph_get
2097    subroutine PMPIR_Graph_get_f08(comm, maxindex, maxedges, index, edges, ierror)
2098        use :: mpi_f08_types, only : MPI_Comm
2099        implicit none
2100        type(MPI_Comm), intent(in) :: comm
2101        integer, intent(in) :: maxindex, maxedges
2102        integer, intent(out) :: index(maxindex), edges(maxedges)
2103        integer, optional, intent(out) :: ierror
2104    end subroutine PMPIR_Graph_get_f08
2105end interface PMPI_Graph_get
2106
2107interface PMPI_Graph_map
2108    subroutine PMPIR_Graph_map_f08(comm, nnodes, index, edges, newrank, ierror)
2109        use :: mpi_f08_types, only : MPI_Comm
2110        implicit none
2111        type(MPI_Comm), intent(in) :: comm
2112        integer, intent(in) :: nnodes, index(nnodes), edges(*)
2113        integer, intent(out) :: newrank
2114        integer, optional, intent(out) :: ierror
2115    end subroutine PMPIR_Graph_map_f08
2116end interface PMPI_Graph_map
2117
2118interface PMPI_Graph_neighbors
2119    subroutine PMPIR_Graph_neighbors_f08(comm, rank, maxneighbors, neighbors, ierror)
2120        use :: mpi_f08_types, only : MPI_Comm
2121        implicit none
2122        type(MPI_Comm), intent(in) :: comm
2123        integer, intent(in) :: rank, maxneighbors
2124        integer, intent(out) :: neighbors(maxneighbors)
2125        integer, optional, intent(out) :: ierror
2126    end subroutine PMPIR_Graph_neighbors_f08
2127end interface PMPI_Graph_neighbors
2128
2129interface PMPI_Graph_neighbors_count
2130    subroutine PMPIR_Graph_neighbors_count_f08(comm, rank, nneighbors, ierror)
2131        use :: mpi_f08_types, only : MPI_Comm
2132        implicit none
2133        type(MPI_Comm), intent(in) :: comm
2134        integer, intent(in) :: rank
2135        integer, intent(out) :: nneighbors
2136        integer, optional, intent(out) :: ierror
2137    end subroutine PMPIR_Graph_neighbors_count_f08
2138end interface PMPI_Graph_neighbors_count
2139
2140interface PMPI_Topo_test
2141    subroutine PMPIR_Topo_test_f08(comm, status, ierror)
2142        use :: mpi_f08_types, only : MPI_Comm, MPI_Status
2143        implicit none
2144        type(MPI_Comm), intent(in) :: comm
2145        integer, intent(out) :: status
2146        integer, optional, intent(out) :: ierror
2147    end subroutine PMPIR_Topo_test_f08
2148end interface PMPI_Topo_test
2149
2150interface PMPI_Abort
2151    subroutine PMPIR_Abort_f08(comm, errorcode, ierror)
2152        use :: mpi_f08_types, only : MPI_Comm
2153        implicit none
2154        type(MPI_Comm), intent(in) :: comm
2155        integer, intent(in) :: errorcode
2156        integer, optional, intent(out) :: ierror
2157    end subroutine PMPIR_Abort_f08
2158end interface PMPI_Abort
2159
2160interface PMPI_Add_error_class
2161    subroutine PMPIR_Add_error_class_f08(errorclass, ierror)
2162        implicit none
2163        integer, intent(out) :: errorclass
2164        integer, optional, intent(out) :: ierror
2165    end subroutine PMPIR_Add_error_class_f08
2166end interface PMPI_Add_error_class
2167
2168interface PMPI_Add_error_code
2169    subroutine PMPIR_Add_error_code_f08(errorclass, errorcode, ierror)
2170        implicit none
2171        integer, intent(in) :: errorclass
2172        integer, intent(out) :: errorcode
2173        integer, optional, intent(out) :: ierror
2174    end subroutine PMPIR_Add_error_code_f08
2175end interface PMPI_Add_error_code
2176
2177interface PMPI_Add_error_string
2178    subroutine PMPIR_Add_error_string_f08(errorcode, string, ierror)
2179        implicit none
2180        integer, intent(in) :: errorcode
2181        character(len=*), intent(in) :: string
2182        integer, optional, intent(out) :: ierror
2183    end subroutine PMPIR_Add_error_string_f08
2184end interface PMPI_Add_error_string
2185
2186interface PMPI_Alloc_mem
2187    subroutine PMPIR_Alloc_mem_f08(size, info, baseptr, ierror)
2188        use, intrinsic :: iso_c_binding, only : c_ptr
2189        use :: mpi_f08_types, only : MPI_Info
2190        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2191        implicit none
2192        integer(MPI_ADDRESS_KIND), intent(in) :: size
2193        type(MPI_Info), intent(in) :: info
2194        type(c_ptr), intent(out) :: baseptr
2195        integer, optional, intent(out) :: ierror
2196    end subroutine PMPIR_Alloc_mem_f08
2197end interface PMPI_Alloc_mem
2198
2199interface PMPI_Comm_call_errhandler
2200    subroutine PMPIR_Comm_call_errhandler_f08(comm, errorcode, ierror)
2201        use :: mpi_f08_types, only : MPI_Comm
2202        implicit none
2203        type(MPI_Comm), intent(in) :: comm
2204        integer, intent(in) :: errorcode
2205        integer, optional, intent(out) :: ierror
2206    end subroutine PMPIR_Comm_call_errhandler_f08
2207end interface PMPI_Comm_call_errhandler
2208
2209interface PMPI_Comm_create_errhandler
2210    subroutine PMPIR_Comm_create_errhandler_f08(comm_errhandler_fn, errhandler, ierror)
2211        use :: mpi_f08_types, only : MPI_Errhandler
2212        use :: mpi_f08_callbacks, only : MPI_Comm_errhandler_function
2213        implicit none
2214        procedure(MPI_Comm_errhandler_function) :: comm_errhandler_fn
2215        type(MPI_Errhandler), intent(out) :: errhandler
2216        integer, optional, intent(out) :: ierror
2217    end subroutine PMPIR_Comm_create_errhandler_f08
2218end interface PMPI_Comm_create_errhandler
2219
2220interface PMPI_Comm_get_errhandler
2221    subroutine PMPIR_Comm_get_errhandler_f08(comm, errhandler, ierror)
2222        use :: mpi_f08_types, only : MPI_Comm, MPI_Errhandler
2223        implicit none
2224        type(MPI_Comm), intent(in) :: comm
2225        type(MPI_Errhandler), intent(out) :: errhandler
2226        integer, optional, intent(out) :: ierror
2227    end subroutine PMPIR_Comm_get_errhandler_f08
2228end interface PMPI_Comm_get_errhandler
2229
2230interface PMPI_Comm_set_errhandler
2231    subroutine PMPIR_Comm_set_errhandler_f08(comm, errhandler, ierror)
2232        use :: mpi_f08_types, only : MPI_Comm, MPI_Errhandler
2233        implicit none
2234        type(MPI_Comm), intent(in) :: comm
2235        type(MPI_Errhandler), intent(in) :: errhandler
2236        integer, optional, intent(out) :: ierror
2237    end subroutine PMPIR_Comm_set_errhandler_f08
2238end interface PMPI_Comm_set_errhandler
2239
2240interface PMPI_Errhandler_free
2241    subroutine PMPIR_Errhandler_free_f08(errhandler, ierror)
2242        use :: mpi_f08_types, only : MPI_Errhandler
2243        implicit none
2244        type(MPI_Errhandler), intent(inout) :: errhandler
2245        integer, optional, intent(out) :: ierror
2246    end subroutine PMPIR_Errhandler_free_f08
2247end interface PMPI_Errhandler_free
2248
2249interface PMPI_Error_class
2250    subroutine PMPIR_Error_class_f08(errorcode, errorclass, ierror)
2251        implicit none
2252        integer, intent(in) :: errorcode
2253        integer, intent(out) :: errorclass
2254        integer, optional, intent(out) :: ierror
2255    end subroutine PMPIR_Error_class_f08
2256end interface PMPI_Error_class
2257
2258interface PMPI_Error_string
2259    subroutine PMPIR_Error_string_f08(errorcode, string, resultlen, ierror)
2260        use :: mpi_f08_compile_constants, only : MPI_MAX_ERROR_STRING
2261        implicit none
2262        integer, intent(in) :: errorcode
2263        character(len=MPI_MAX_ERROR_STRING), intent(out) :: string
2264        integer, intent(out) :: resultlen
2265        integer, optional, intent(out) :: ierror
2266    end subroutine PMPIR_Error_string_f08
2267end interface PMPI_Error_string
2268
2269interface PMPI_File_call_errhandler
2270    subroutine PMPIR_File_call_errhandler_f08(fh, errorcode, ierror)
2271        use :: mpi_f08_types, only : MPI_File
2272        implicit none
2273        type(MPI_File), intent(in) :: fh
2274        integer, intent(in) :: errorcode
2275        integer, optional, intent(out) :: ierror
2276    end subroutine PMPIR_File_call_errhandler_f08
2277end interface PMPI_File_call_errhandler
2278
2279interface PMPI_File_create_errhandler
2280    subroutine PMPIR_File_create_errhandler_f08(file_errhandler_fn, errhandler, ierror)
2281        use :: mpi_f08_types, only : MPI_Errhandler
2282        use :: mpi_f08_callbacks, only : MPI_File_errhandler_function
2283        implicit none
2284        procedure(MPI_File_errhandler_function) :: file_errhandler_fn
2285        type(MPI_Errhandler), intent(out) :: errhandler
2286        integer, optional, intent(out) :: ierror
2287    end subroutine PMPIR_File_create_errhandler_f08
2288end interface PMPI_File_create_errhandler
2289
2290interface PMPI_File_get_errhandler
2291    subroutine PMPIR_File_get_errhandler_f08(file, errhandler, ierror)
2292        use :: mpi_f08_types, only : MPI_File, MPI_Errhandler
2293        implicit none
2294        type(MPI_File), intent(in) :: file
2295        type(MPI_Errhandler), intent(out) :: errhandler
2296        integer, optional, intent(out) :: ierror
2297    end subroutine PMPIR_File_get_errhandler_f08
2298end interface PMPI_File_get_errhandler
2299
2300interface PMPI_File_set_errhandler
2301    subroutine PMPIR_File_set_errhandler_f08(file, errhandler, ierror)
2302        use :: mpi_f08_types, only : MPI_File, MPI_Errhandler
2303        implicit none
2304        type(MPI_File), intent(in) :: file
2305        type(MPI_Errhandler), intent(in) :: errhandler
2306        integer, optional, intent(out) :: ierror
2307    end subroutine PMPIR_File_set_errhandler_f08
2308end interface PMPI_File_set_errhandler
2309
2310interface PMPI_Finalize
2311    subroutine PMPIR_Finalize_f08(ierror)
2312        implicit none
2313        integer, optional, intent(out) :: ierror
2314    end subroutine PMPIR_Finalize_f08
2315end interface PMPI_Finalize
2316
2317interface PMPI_Finalized
2318    subroutine PMPIR_Finalized_f08(flag, ierror)
2319        implicit none
2320        logical, intent(out) :: flag
2321        integer, optional, intent(out) :: ierror
2322    end subroutine PMPIR_Finalized_f08
2323end interface PMPI_Finalized
2324
2325interface PMPI_Free_mem
2326    subroutine PMPIR_Free_mem_f08(base, ierror)
2327        implicit none
2328        type(*), dimension(..), intent(in), asynchronous :: base
2329        integer, optional, intent(out) :: ierror
2330    end subroutine PMPIR_Free_mem_f08
2331end interface PMPI_Free_mem
2332
2333interface PMPI_Get_processor_name
2334    subroutine PMPIR_Get_processor_name_f08(name, resultlen, ierror)
2335        use :: mpi_f08_compile_constants, only : MPI_MAX_PROCESSOR_NAME
2336        implicit none
2337        character(len=MPI_MAX_PROCESSOR_NAME), intent(out) :: name
2338        integer, intent(out) :: resultlen
2339        integer, optional, intent(out) :: ierror
2340    end subroutine PMPIR_Get_processor_name_f08
2341end interface PMPI_Get_processor_name
2342
2343interface PMPI_Get_version
2344    subroutine PMPIR_Get_version_f08(version, subversion, ierror)
2345        implicit none
2346        integer, intent(out) :: version, subversion
2347        integer, optional, intent(out) :: ierror
2348    end subroutine PMPIR_Get_version_f08
2349end interface PMPI_Get_version
2350
2351interface PMPI_Init
2352    subroutine PMPIR_Init_f08(ierror)
2353        implicit none
2354        integer, optional, intent(out) :: ierror
2355    end subroutine PMPIR_Init_f08
2356end interface PMPI_Init
2357
2358interface PMPI_Initialized
2359    subroutine PMPIR_Initialized_f08(flag, ierror)
2360        implicit none
2361        logical, intent(out) :: flag
2362        integer, optional, intent(out) :: ierror
2363    end subroutine PMPIR_Initialized_f08
2364end interface PMPI_Initialized
2365
2366interface PMPI_Win_call_errhandler
2367    subroutine PMPIR_Win_call_errhandler_f08(win, errorcode, ierror)
2368        use :: mpi_f08_types, only : MPI_Win
2369        implicit none
2370        type(MPI_Win), intent(in) :: win
2371        integer, intent(in) :: errorcode
2372        integer, optional, intent(out) :: ierror
2373    end subroutine PMPIR_Win_call_errhandler_f08
2374end interface PMPI_Win_call_errhandler
2375
2376interface PMPI_Win_create_errhandler
2377    subroutine PMPIR_Win_create_errhandler_f08(win_errhandler_fn, errhandler, ierror)
2378        use :: mpi_f08_types, only : MPI_Errhandler
2379        use :: mpi_f08_callbacks, only : MPI_Win_errhandler_function
2380        implicit none
2381        procedure(MPI_Win_errhandler_function) :: win_errhandler_fn
2382        type(MPI_Errhandler), intent(out) :: errhandler
2383        integer, optional, intent(out) :: ierror
2384    end subroutine PMPIR_Win_create_errhandler_f08
2385end interface PMPI_Win_create_errhandler
2386
2387interface PMPI_Win_get_errhandler
2388    subroutine PMPIR_Win_get_errhandler_f08(win, errhandler, ierror)
2389        use :: mpi_f08_types, only : MPI_Win, MPI_Errhandler
2390        implicit none
2391        type(MPI_Win), intent(in) :: win
2392        type(MPI_Errhandler), intent(out) :: errhandler
2393        integer, optional, intent(out) :: ierror
2394    end subroutine PMPIR_Win_get_errhandler_f08
2395end interface PMPI_Win_get_errhandler
2396
2397interface PMPI_Win_set_errhandler
2398    subroutine PMPIR_Win_set_errhandler_f08(win, errhandler, ierror)
2399        use :: mpi_f08_types, only : MPI_Win, MPI_Errhandler
2400        implicit none
2401        type(MPI_Win), intent(in) :: win
2402        type(MPI_Errhandler), intent(in) :: errhandler
2403        integer, optional, intent(out) :: ierror
2404    end subroutine PMPIR_Win_set_errhandler_f08
2405end interface PMPI_Win_set_errhandler
2406
2407interface PMPI_Info_create
2408    subroutine PMPIR_Info_create_f08(info, ierror)
2409        use :: mpi_f08_types, only : MPI_Info
2410        implicit none
2411        type(MPI_Info), intent(out) :: info
2412        integer, optional, intent(out) :: ierror
2413    end subroutine PMPIR_Info_create_f08
2414end interface PMPI_Info_create
2415
2416interface PMPI_Info_delete
2417    subroutine PMPIR_Info_delete_f08(info, key, ierror)
2418        use :: mpi_f08_types, only : MPI_Info
2419        implicit none
2420        type(MPI_Info), intent(in) :: info
2421        character(len=*), intent(in) :: key
2422        integer, optional, intent(out) :: ierror
2423    end subroutine PMPIR_Info_delete_f08
2424end interface PMPI_Info_delete
2425
2426interface PMPI_Info_dup
2427    subroutine PMPIR_Info_dup_f08(info, newinfo, ierror)
2428        use :: mpi_f08_types, only : MPI_Info
2429        implicit none
2430        type(MPI_Info), intent(in) :: info
2431        type(MPI_Info), intent(out) :: newinfo
2432        integer, optional, intent(out) :: ierror
2433    end subroutine PMPIR_Info_dup_f08
2434end interface PMPI_Info_dup
2435
2436interface PMPI_Info_free
2437    subroutine PMPIR_Info_free_f08(info, ierror)
2438        use :: mpi_f08_types, only : MPI_Info
2439        implicit none
2440        type(MPI_Info), intent(inout) :: info
2441        integer, optional, intent(out) :: ierror
2442    end subroutine PMPIR_Info_free_f08
2443end interface PMPI_Info_free
2444
2445interface PMPI_Info_get
2446    subroutine PMPIR_Info_get_f08(info, key, valuelen, value, flag, ierror)
2447        use :: mpi_f08_types, only : MPI_Info
2448        implicit none
2449        type(MPI_Info), intent(in) :: info
2450        character(len=*), intent(in) :: key
2451        integer, intent(in) :: valuelen
2452        character(len=valuelen), intent(out) :: value
2453        logical, intent(out) :: flag
2454        integer, optional, intent(out) :: ierror
2455    end subroutine PMPIR_Info_get_f08
2456end interface PMPI_Info_get
2457
2458interface PMPI_Info_get_nkeys
2459    subroutine PMPIR_Info_get_nkeys_f08(info, nkeys, ierror)
2460        use :: mpi_f08_types, only : MPI_Info
2461        implicit none
2462        type(MPI_Info), intent(in) :: info
2463        integer, intent(out) :: nkeys
2464        integer, optional, intent(out) :: ierror
2465    end subroutine PMPIR_Info_get_nkeys_f08
2466end interface PMPI_Info_get_nkeys
2467
2468interface PMPI_Info_get_nthkey
2469    subroutine PMPIR_Info_get_nthkey_f08(info, n,key, ierror)
2470        use :: mpi_f08_types, only : MPI_Info
2471        implicit none
2472        type(MPI_Info), intent(in) :: info
2473        integer, intent(in) :: n
2474        character(len=*), intent(out) :: key
2475        integer, optional, intent(out) :: ierror
2476    end subroutine PMPIR_Info_get_nthkey_f08
2477end interface PMPI_Info_get_nthkey
2478
2479interface PMPI_Info_get_valuelen
2480    subroutine PMPIR_Info_get_valuelen_f08(info, key, valuelen, flag, ierror)
2481        use :: mpi_f08_types, only : MPI_Info
2482        implicit none
2483        type(MPI_Info), intent(in) :: info
2484        character(len=*), intent(in) :: key
2485        integer, intent(out) :: valuelen
2486        logical, intent(out) :: flag
2487        integer, optional, intent(out) :: ierror
2488    end subroutine PMPIR_Info_get_valuelen_f08
2489end interface PMPI_Info_get_valuelen
2490
2491interface PMPI_Info_set
2492    subroutine PMPIR_Info_set_f08(info, key, value, ierror)
2493        use :: mpi_f08_types, only : MPI_Info
2494        implicit none
2495        type(MPI_Info), intent(in) :: info
2496        character(len=*), intent(in) :: key, value
2497        integer, optional, intent(out) :: ierror
2498    end subroutine PMPIR_Info_set_f08
2499end interface PMPI_Info_set
2500
2501interface PMPI_Close_port
2502    subroutine PMPIR_Close_port_f08(port_name, ierror)
2503        implicit none
2504        character(len=*), intent(in) :: port_name
2505        integer, optional, intent(out) :: ierror
2506    end subroutine PMPIR_Close_port_f08
2507end interface PMPI_Close_port
2508
2509interface PMPI_Comm_accept
2510    subroutine PMPIR_Comm_accept_f08(port_name, info, root, comm, newcomm, ierror)
2511        use :: mpi_f08_types, only : MPI_Info, MPI_Comm
2512        implicit none
2513        character(len=*), intent(in) :: port_name
2514        type(MPI_Info), intent(in) :: info
2515        integer, intent(in) :: root
2516        type(MPI_Comm), intent(in) :: comm
2517        type(MPI_Comm), intent(out) :: newcomm
2518        integer, optional, intent(out) :: ierror
2519    end subroutine PMPIR_Comm_accept_f08
2520end interface PMPI_Comm_accept
2521
2522interface PMPI_Comm_connect
2523    subroutine PMPIR_Comm_connect_f08(port_name, info, root, comm, newcomm, ierror)
2524        use :: mpi_f08_types, only : MPI_Info, MPI_Comm
2525        implicit none
2526        character(len=*), intent(in) :: port_name
2527        type(MPI_Info), intent(in) :: info
2528        integer, intent(in) :: root
2529        type(MPI_Comm), intent(in) :: comm
2530        type(MPI_Comm), intent(out) :: newcomm
2531        integer, optional, intent(out) :: ierror
2532    end subroutine PMPIR_Comm_connect_f08
2533end interface PMPI_Comm_connect
2534
2535interface PMPI_Comm_disconnect
2536    subroutine PMPIR_Comm_disconnect_f08(comm, ierror)
2537        use :: mpi_f08_types, only : MPI_Comm
2538        implicit none
2539        type(MPI_Comm), intent(inout) :: comm
2540        integer, optional, intent(out) :: ierror
2541    end subroutine PMPIR_Comm_disconnect_f08
2542end interface PMPI_Comm_disconnect
2543
2544interface PMPI_Comm_get_parent
2545    subroutine PMPIR_Comm_get_parent_f08(parent, ierror)
2546        use :: mpi_f08_types, only : MPI_Comm
2547        implicit none
2548        type(MPI_Comm), intent(out) :: parent
2549        integer, optional, intent(out) :: ierror
2550    end subroutine PMPIR_Comm_get_parent_f08
2551end interface PMPI_Comm_get_parent
2552
2553interface PMPI_Comm_join
2554    subroutine PMPIR_Comm_join_f08(fd, intercomm, ierror)
2555        use :: mpi_f08_types, only : MPI_Comm
2556        implicit none
2557        integer, intent(in) :: fd
2558        type(MPI_Comm), intent(out) :: intercomm
2559        integer, optional, intent(out) :: ierror
2560    end subroutine PMPIR_Comm_join_f08
2561end interface PMPI_Comm_join
2562
2563interface PMPI_Comm_spawn
2564    subroutine PMPIR_Comm_spawn_f08(command, argv, maxprocs, info, root, comm, intercomm, &
2565                                   array_of_errcodes, ierror)
2566        use :: mpi_f08_types, only : MPI_Info, MPI_Comm
2567        implicit none
2568        character(len=*), intent(in) :: command, argv(*)
2569        integer, intent(in) :: maxprocs, root
2570        type(MPI_Info), intent(in) :: info
2571        type(MPI_Comm), intent(in) :: comm
2572        type(MPI_Comm), intent(out) :: intercomm
2573        integer :: array_of_errcodes(*)
2574        integer, optional, intent(out) :: ierror
2575    end subroutine PMPIR_Comm_spawn_f08
2576end interface PMPI_Comm_spawn
2577
2578interface PMPI_Comm_spawn_multiple
2579    subroutine PMPIR_Comm_spawn_multiple_f08(count, array_of_commands, array_of_argv, array_of_maxprocs, &
2580                                    array_of_info, root, comm, intercomm, array_of_errcodes, ierror)
2581        use :: mpi_f08_types, only : MPI_Info, MPI_Comm
2582        implicit none
2583        integer, intent(in) :: count
2584        character(len=*), intent(in) :: array_of_commands(*), array_of_argv(count,*)
2585        integer, intent(in) :: array_of_maxprocs(*)
2586        type(MPI_Info), intent(in) :: array_of_info(*)
2587        integer, intent(in) :: root
2588        type(MPI_Comm), intent(in) :: comm
2589        type(MPI_Comm), intent(out) :: intercomm
2590        integer :: array_of_errcodes(*)
2591        integer, optional, intent(out) :: ierror
2592    end subroutine PMPIR_Comm_spawn_multiple_f08
2593end interface PMPI_Comm_spawn_multiple
2594
2595interface PMPI_Lookup_name
2596    subroutine PMPIR_Lookup_name_f08(service_name, info, port_name, ierror)
2597        use :: mpi_f08_types, only : MPI_Info
2598        use :: mpi_f08_compile_constants, only : MPI_MAX_PORT_NAME
2599        implicit none
2600        character(len=*), intent(in) :: service_name
2601        type(MPI_Info), intent(in) :: info
2602        character(len=MPI_MAX_PORT_NAME), intent(out) :: port_name
2603        integer, optional, intent(out) :: ierror
2604    end subroutine PMPIR_Lookup_name_f08
2605end interface PMPI_Lookup_name
2606
2607interface PMPI_Open_port
2608    subroutine PMPIR_Open_port_f08(info, port_name, ierror)
2609        use :: mpi_f08_types, only : MPI_Info
2610        use :: mpi_f08_compile_constants, only : MPI_MAX_PORT_NAME
2611        implicit none
2612        type(MPI_Info), intent(in) :: info
2613        character(len=MPI_MAX_PORT_NAME), intent(out) :: port_name
2614        integer, optional, intent(out) :: ierror
2615    end subroutine PMPIR_Open_port_f08
2616end interface PMPI_Open_port
2617
2618interface PMPI_Publish_name
2619    subroutine PMPIR_Publish_name_f08(service_name, info, port_name, ierror)
2620        use :: mpi_f08_types, only : MPI_Info
2621        implicit none
2622        type(MPI_Info), intent(in) :: info
2623        character(len=*), intent(in) :: service_name, port_name
2624        integer, optional, intent(out) :: ierror
2625    end subroutine PMPIR_Publish_name_f08
2626end interface PMPI_Publish_name
2627
2628interface PMPI_Unpublish_name
2629    subroutine PMPIR_Unpublish_name_f08(service_name, info, port_name, ierror)
2630        use :: mpi_f08_types, only : MPI_Info
2631        implicit none
2632        character(len=*), intent(in) :: service_name, port_name
2633        type(MPI_Info), intent(in) :: info
2634        integer, optional, intent(out) :: ierror
2635    end subroutine PMPIR_Unpublish_name_f08
2636end interface PMPI_Unpublish_name
2637
2638interface PMPI_Accumulate
2639    subroutine PMPIR_Accumulate_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2640                                   target_disp, target_count, target_datatype, op, win, ierror)
2641        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Win
2642        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2643        implicit none
2644        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2645        integer, intent(in) :: origin_count, target_rank, target_count
2646        type(MPI_Datatype), intent(in) :: origin_datatype
2647        integer(MPI_ADDRESS_KIND), intent(in) :: target_disp
2648        type(MPI_Datatype), intent(in) :: target_datatype
2649        type(MPI_Op), intent(in) :: op
2650        type(MPI_Win), intent(in) :: win
2651        integer, optional, intent(out) :: ierror
2652    end subroutine PMPIR_Accumulate_f08ts
2653end interface PMPI_Accumulate
2654
2655interface PMPI_Compare_and_swap
2656    subroutine PMPIR_Compare_and_swap_f08ts(origin_addr, compare_addr, result_addr, datatype, &
2657            target_rank, target_disp, win, ierror)
2658        use :: mpi_f08_types, only : MPI_Datatype, MPI_Win
2659        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2660        implicit none
2661        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2662        type(*), dimension(..), intent(in), asynchronous :: compare_addr
2663        type(*), dimension(..), asynchronous :: result_addr
2664        type(MPI_Datatype), intent(in) :: datatype
2665        integer, intent(in) :: target_rank
2666        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2667        type(MPI_Win), intent(in) :: win
2668        integer, optional, intent(out) :: ierror
2669    end subroutine PMPIR_Compare_and_swap_f08ts
2670end interface PMPI_Compare_and_swap
2671
2672interface PMPI_Fetch_and_op
2673    subroutine PMPIR_Fetch_and_op_f08ts(origin_addr, result_addr, datatype, target_rank, &
2674            target_disp, op, win, ierror)
2675        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Win
2676        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2677        implicit none
2678        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2679        type(*), dimension(..), asynchronous :: result_addr
2680        type(MPI_Datatype), intent(in) :: datatype
2681        integer, intent(in) :: target_rank
2682        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2683        type(MPI_Op), intent(in) :: op
2684        type(MPI_Win), intent(in) :: win
2685        integer, optional, intent(out) :: ierror
2686    end subroutine PMPIR_Fetch_and_op_f08ts
2687end interface PMPI_Fetch_and_op
2688
2689interface PMPI_Get
2690    subroutine PMPIR_Get_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2691                                    target_disp, target_count, target_datatype, win, ierror)
2692        use :: mpi_f08_types, only : MPI_Datatype, MPI_Win
2693        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2694        implicit none
2695        type(*), dimension(..), asynchronous :: origin_addr
2696        integer, intent(in) :: origin_count, target_rank, target_count
2697        type(MPI_Datatype), intent(in) :: origin_datatype
2698        integer(MPI_ADDRESS_KIND), intent(in) :: target_disp
2699        type(MPI_Datatype), intent(in) :: target_datatype
2700        type(MPI_Win), intent(in) :: win
2701        integer, optional, intent(out) :: ierror
2702    end subroutine PMPIR_Get_f08ts
2703end interface PMPI_Get
2704
2705interface PMPI_Get_accumulate
2706    subroutine PMPIR_Get_accumulate_f08ts(origin_addr, origin_count, origin_datatype, result_addr, &
2707            result_count, result_datatype, target_rank, target_disp, &
2708            target_count, target_datatype, op, win, ierror)
2709        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Win
2710        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2711        implicit none
2712        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2713        type(*), dimension(..), asynchronous :: result_addr
2714        integer, intent(in) :: origin_count, result_count, target_rank, target_count
2715        type(MPI_Datatype), intent(in) :: origin_datatype, target_datatype, result_datatype
2716        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2717        type(MPI_Op), intent(in) :: op
2718        type(MPI_Win), intent(in) :: win
2719        integer, optional, intent(out) :: ierror
2720    end subroutine PMPIR_Get_accumulate_f08ts
2721end interface PMPI_Get_accumulate
2722
2723interface PMPI_Put
2724    subroutine PMPIR_Put_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2725                             target_disp, target_count, target_datatype, win, ierror)
2726        use :: mpi_f08_types, only : MPI_Datatype, MPI_Win
2727        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2728        implicit none
2729        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2730        integer, intent(in) :: origin_count, target_rank, target_count
2731        type(MPI_Datatype), intent(in) :: origin_datatype
2732        integer(MPI_ADDRESS_KIND), intent(in) :: target_disp
2733        type(MPI_Datatype), intent(in) :: target_datatype
2734        type(MPI_Win), intent(in) :: win
2735        integer, optional, intent(out) :: ierror
2736    end subroutine PMPIR_Put_f08ts
2737end interface PMPI_Put
2738
2739interface PMPI_Raccumulate
2740    subroutine PMPIR_Raccumulate_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2741            target_disp, target_count, target_datatype, op, win, request, ierror)
2742        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Win, MPI_Request
2743        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2744        implicit none
2745        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2746        integer, intent(in) :: origin_count, target_rank, target_count
2747        type(MPI_Datatype), intent(in) :: origin_datatype, target_datatype
2748        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2749        type(MPI_Op), intent(in) :: op
2750        type(MPI_Win), intent(in) :: win
2751        type(MPI_Request), intent(out) :: request
2752        integer, optional, intent(out) :: ierror
2753    end subroutine PMPIR_Raccumulate_f08ts
2754end interface PMPI_Raccumulate
2755
2756interface PMPI_Rget
2757    subroutine PMPIR_Rget_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2758            target_disp, target_count, target_datatype, win, request, ierror)
2759        use :: mpi_f08_types, only : MPI_Datatype, MPI_Win, MPI_Request
2760        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2761        implicit none
2762        type(*), dimension(..), asynchronous :: origin_addr
2763        integer, intent(in) :: origin_count, target_rank, target_count
2764        type(MPI_Datatype), intent(in) :: origin_datatype, target_datatype
2765        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2766        type(MPI_Win), intent(in) :: win
2767        type(MPI_Request), intent(out) :: request
2768        integer, optional, intent(out) :: ierror
2769    end subroutine PMPIR_Rget_f08ts
2770end interface PMPI_Rget
2771
2772interface PMPI_Rget_accumulate
2773    subroutine PMPIR_Rget_accumulate_f08ts(origin_addr, origin_count, origin_datatype, &
2774            result_addr, result_count, result_datatype, target_rank, &
2775            target_disp, target_count, target_datatype, op, win, request, ierror)
2776        use :: mpi_f08_types, only : MPI_Datatype, MPI_Op, MPI_Win, MPI_Request
2777        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2778        implicit none
2779        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2780        type(*), dimension(..), asynchronous :: result_addr
2781        integer, intent(in) :: origin_count, result_count, target_rank, target_count
2782        type(MPI_Datatype), intent(in) :: origin_datatype, target_datatype, result_datatype
2783        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2784        type(MPI_Op), intent(in) :: op
2785        type(MPI_Win), intent(in) :: win
2786        type(MPI_Request), intent(out) :: request
2787        integer, optional, intent(out) :: ierror
2788    end subroutine PMPIR_Rget_accumulate_f08ts
2789end interface PMPI_Rget_accumulate
2790
2791interface PMPI_Rput
2792    subroutine PMPIR_Rput_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
2793            target_disp, target_count, target_datatype, win, request, ierror)
2794        use :: mpi_f08_types, only : MPI_Datatype, MPI_Win, MPI_Request
2795        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2796        implicit none
2797        type(*), dimension(..), intent(in), asynchronous :: origin_addr
2798        integer, intent(in) :: origin_count, target_rank, target_count
2799        type(MPI_Datatype), intent(in) :: origin_datatype, target_datatype
2800        integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
2801        type(MPI_Win), intent(in) :: win
2802        type(MPI_Request), intent(out) :: request
2803        integer, optional, intent(out) :: ierror
2804    end subroutine PMPIR_Rput_f08ts
2805end interface PMPI_Rput
2806
2807interface PMPI_Win_allocate
2808    subroutine PMPIR_Win_allocate_f08(size, disp_unit, info, comm, baseptr, win, ierror)
2809        use, intrinsic :: iso_c_binding, only : c_ptr
2810        use :: mpi_f08_types, only : MPI_Info, MPI_Comm, MPI_Win
2811        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2812        implicit none
2813        integer(kind=MPI_ADDRESS_KIND), intent(in) :: size
2814        integer, intent(in) :: disp_unit
2815        type(MPI_Info), intent(in) :: info
2816        type(MPI_Comm), intent(in) :: comm
2817        type(c_ptr), intent(out) :: baseptr
2818        type(MPI_Win), intent(out) :: win
2819        integer, optional, intent(out) :: ierror
2820    end subroutine PMPIR_Win_allocate_f08
2821end interface PMPI_Win_allocate
2822
2823interface PMPI_Win_allocate_shared
2824    subroutine PMPIR_Win_allocate_shared_f08(size, disp_unit, info, comm, baseptr, win, ierror)
2825        use, intrinsic :: iso_c_binding, only : c_ptr
2826        use :: mpi_f08_types, only : MPI_Info, MPI_Comm, MPI_Win
2827        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2828        implicit none
2829        integer(kind=MPI_ADDRESS_KIND), intent(in) :: size
2830        integer, intent(in) :: disp_unit
2831        type(MPI_Info), intent(in) :: info
2832        type(MPI_Comm), intent(in) :: comm
2833        type(c_ptr), intent(out) :: baseptr
2834        type(MPI_Win), intent(out) :: win
2835        integer, optional, intent(out) :: ierror
2836    end subroutine PMPIR_Win_allocate_shared_f08
2837end interface PMPI_Win_allocate_shared
2838
2839interface PMPI_Win_attach
2840    subroutine PMPIR_Win_attach_f08ts(win, base, size, ierror)
2841        use :: mpi_f08_types, only : MPI_Win
2842        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2843        implicit none
2844        type(MPI_Win), intent(in) :: win
2845        type(*), dimension(..), asynchronous :: base
2846        integer(kind=MPI_ADDRESS_KIND), intent(in) :: size
2847        integer, optional, intent(out) :: ierror
2848    end subroutine PMPIR_Win_attach_f08ts
2849end interface PMPI_Win_attach
2850
2851
2852interface PMPI_Win_complete
2853    subroutine PMPIR_Win_complete_f08(win, ierror)
2854        use :: mpi_f08_types, only : MPI_Win
2855        implicit none
2856        type(MPI_Win), intent(in) :: win
2857        integer, optional, intent(out) :: ierror
2858    end subroutine PMPIR_Win_complete_f08
2859end interface PMPI_Win_complete
2860
2861interface PMPI_Win_create
2862    subroutine PMPIR_Win_create_f08ts(base, size, disp_unit, info, comm, win, ierror)
2863        use :: mpi_f08_types, only : MPI_Info, MPI_Comm, MPI_Win
2864        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
2865        implicit none
2866        type(*), dimension(..), asynchronous :: base
2867        integer(MPI_ADDRESS_KIND), intent(in) :: size
2868        integer, intent(in) :: disp_unit
2869        type(MPI_Info), intent(in) :: info
2870        type(MPI_Comm), intent(in) :: comm
2871        type(MPI_Win), intent(out) :: win
2872        integer, optional, intent(out) :: ierror
2873    end subroutine PMPIR_Win_create_f08ts
2874end interface PMPI_Win_create
2875
2876interface PMPI_Win_create_dynamic
2877    subroutine PMPIR_Win_create_dynamic_f08(info, comm, win, ierror)
2878        use :: mpi_f08_types, only : MPI_Info, MPI_Comm, MPI_Win
2879        implicit none
2880        type(MPI_Info), intent(in) :: info
2881        type(MPI_Comm), intent(in) :: comm
2882        type(MPI_Win), intent(out) :: win
2883        integer, optional, intent(out) :: ierror
2884    end subroutine PMPIR_Win_create_dynamic_f08
2885end interface PMPI_Win_create_dynamic
2886
2887interface PMPI_Win_detach
2888    subroutine PMPIR_Win_detach_f08ts(win, base, ierror)
2889        use :: mpi_f08_types, only : MPI_Win
2890        implicit none
2891        type(MPI_Win), intent(in) :: win
2892        type(*), dimension(..), asynchronous :: base
2893        integer, optional, intent(out) :: ierror
2894    end subroutine PMPIR_Win_detach_f08ts
2895end interface PMPI_Win_detach
2896
2897interface PMPI_Win_fence
2898    subroutine PMPIR_Win_fence_f08(assert, win, ierror)
2899        use :: mpi_f08_types, only : MPI_Win
2900        implicit none
2901        integer, intent(in) :: assert
2902        type(MPI_Win), intent(in) :: win
2903        integer, optional, intent(out) :: ierror
2904    end subroutine PMPIR_Win_fence_f08
2905end interface PMPI_Win_fence
2906
2907interface PMPI_Win_flush
2908    subroutine PMPIR_Win_flush_f08(rank, win, ierror)
2909        use :: mpi_f08_types, only : MPI_Win
2910        implicit none
2911        integer, intent(in) :: rank
2912        type(MPI_Win), intent(in) :: win
2913        integer, optional, intent(out) :: ierror
2914    end subroutine PMPIR_Win_flush_f08
2915end interface PMPI_Win_flush
2916
2917interface PMPI_Win_flush_all
2918    subroutine PMPIR_Win_flush_all_f08(win, ierror)
2919        use :: mpi_f08_types, only : MPI_Win
2920        implicit none
2921        type(MPI_Win), intent(in) :: win
2922        integer, optional, intent(out) :: ierror
2923    end subroutine PMPIR_Win_flush_all_f08
2924end interface PMPI_Win_flush_all
2925
2926interface PMPI_Win_flush_local
2927    subroutine PMPIR_Win_flush_local_f08(rank, win, ierror)
2928        use :: mpi_f08_types, only : MPI_Win
2929        implicit none
2930        integer, intent(in) :: rank
2931        type(MPI_Win), intent(in) :: win
2932        integer, optional, intent(out) :: ierror
2933    end subroutine PMPIR_Win_flush_local_f08
2934end interface PMPI_Win_flush_local
2935
2936interface PMPI_Win_flush_local_all
2937    subroutine PMPIR_Win_flush_local_all_f08(win, ierror)
2938        use :: mpi_f08_types, only : MPI_Win
2939        implicit none
2940        type(MPI_Win), intent(in) :: win
2941        integer, optional, intent(out) :: ierror
2942    end subroutine PMPIR_Win_flush_local_all_f08
2943end interface PMPI_Win_flush_local_all
2944
2945interface PMPI_Win_free
2946    subroutine PMPIR_Win_free_f08(win, ierror)
2947        use :: mpi_f08_types, only : MPI_Win
2948        implicit none
2949        type(MPI_Win), intent(inout) :: win
2950        integer, optional, intent(out) :: ierror
2951    end subroutine PMPIR_Win_free_f08
2952end interface PMPI_Win_free
2953
2954interface PMPI_Win_get_group
2955    subroutine PMPIR_Win_get_group_f08(win, group, ierror)
2956        use :: mpi_f08_types, only : MPI_Win, MPI_Group
2957        implicit none
2958        type(MPI_Win), intent(in) :: win
2959        type(MPI_Group), intent(out) :: group
2960        integer, optional, intent(out) :: ierror
2961    end subroutine PMPIR_Win_get_group_f08
2962end interface PMPI_Win_get_group
2963
2964interface PMPI_Win_get_info
2965    subroutine PMPIR_Win_get_info_f08(win, info_used, ierror)
2966        use :: mpi_f08_types, only : MPI_Win, MPI_Info
2967        implicit none
2968        type(MPI_Win), intent(in) :: win
2969        type(MPI_Info), intent(out) :: info_used
2970        integer, optional, intent(out) :: ierror
2971    end subroutine PMPIR_Win_get_info_f08
2972end interface PMPI_Win_get_info
2973
2974interface PMPI_Win_lock
2975    subroutine PMPIR_Win_lock_f08(lock_type, rank, assert, win, ierror)
2976        use :: mpi_f08_types, only : MPI_Win
2977        implicit none
2978        integer, intent(in) :: lock_type, rank, assert
2979        type(MPI_Win), intent(in) :: win
2980        integer, optional, intent(out) :: ierror
2981    end subroutine PMPIR_Win_lock_f08
2982end interface PMPI_Win_lock
2983
2984interface PMPI_Win_lock_all
2985    subroutine PMPIR_Win_lock_all_f08(assert, win, ierror)
2986        use :: mpi_f08_types, only : MPI_Win
2987        implicit none
2988        integer, intent(in) :: assert
2989        type(MPI_Win), intent(in) :: win
2990        integer, optional, intent(out) :: ierror
2991    end subroutine PMPIR_Win_lock_all_f08
2992end interface PMPI_Win_lock_all
2993
2994interface PMPI_Win_post
2995    subroutine PMPIR_Win_post_f08(group, assert, win, ierror)
2996        use :: mpi_f08_types, only : MPI_Group, MPI_Win
2997        implicit none
2998        type(MPI_Group), intent(in) :: group
2999        integer, intent(in) :: assert
3000        type(MPI_Win), intent(in) :: win
3001        integer, optional, intent(out) :: ierror
3002    end subroutine PMPIR_Win_post_f08
3003end interface PMPI_Win_post
3004
3005interface PMPI_Win_set_info
3006    subroutine PMPIR_Win_set_info_f08(win, info, ierror)
3007        use :: mpi_f08_types, only : MPI_Win, MPI_info
3008        implicit none
3009        type(MPI_Win), intent(in) :: win
3010        type(MPI_Info), intent(in) :: info
3011        integer, optional, intent(out) :: ierror
3012    end subroutine PMPIR_Win_set_info_f08
3013end interface PMPI_Win_set_info
3014
3015interface PMPI_Win_shared_query
3016    subroutine PMPIR_Win_shared_query_f08(win, rank, size, disp_unit, baseptr, ierror)
3017        use, intrinsic :: iso_c_binding, only : c_ptr
3018        use :: mpi_f08_types, only : MPI_Win
3019        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
3020        implicit none
3021        type(MPI_Win), intent(in) :: win
3022        integer, intent(in) :: rank
3023        integer(kind=MPI_ADDRESS_KIND), intent(out) :: size
3024        integer, intent(out) :: disp_unit
3025        type(c_ptr), intent(out) :: baseptr
3026        integer, optional, intent(out) :: ierror
3027    end subroutine PMPIR_Win_shared_query_f08
3028end interface PMPI_Win_shared_query
3029
3030interface PMPI_Win_start
3031    subroutine PMPIR_Win_start_f08(group, assert, win, ierror)
3032        use :: mpi_f08_types, only : MPI_Group, MPI_Win
3033        implicit none
3034        type(MPI_Group), intent(in) :: group
3035        integer, intent(in) :: assert
3036        type(MPI_Win), intent(in) :: win
3037        integer, optional, intent(out) :: ierror
3038    end subroutine PMPIR_Win_start_f08
3039end interface PMPI_Win_start
3040
3041interface PMPI_Win_sync
3042    subroutine PMPIR_Win_sync_f08(win, ierror)
3043        use :: mpi_f08_types, only : MPI_Win
3044        implicit none
3045        type(MPI_Win), intent(in) :: win
3046        integer, optional, intent(out) :: ierror
3047    end subroutine PMPIR_Win_sync_f08
3048end interface PMPI_Win_sync
3049
3050interface PMPI_Win_test
3051    subroutine PMPIR_Win_test_f08(win, flag, ierror)
3052        use :: mpi_f08_types, only : MPI_Win
3053        implicit none
3054        logical, intent(out) :: flag
3055        type(MPI_Win), intent(in) :: win
3056        integer, optional, intent(out) :: ierror
3057    end subroutine PMPIR_Win_test_f08
3058end interface PMPI_Win_test
3059
3060interface PMPI_Win_unlock
3061    subroutine PMPIR_Win_unlock_f08(rank, win, ierror)
3062        use :: mpi_f08_types, only : MPI_Win
3063        implicit none
3064        integer, intent(in) :: rank
3065        type(MPI_Win), intent(in) :: win
3066        integer, optional, intent(out) :: ierror
3067    end subroutine PMPIR_Win_unlock_f08
3068end interface PMPI_Win_unlock
3069
3070interface PMPI_Win_unlock_all
3071    subroutine PMPIR_Win_unlock_all_f08(win, ierror)
3072        use :: mpi_f08_types, only : MPI_Win
3073        implicit none
3074        type(MPI_Win), intent(in) :: win
3075        integer, optional, intent(out) :: ierror
3076    end subroutine PMPIR_Win_unlock_all_f08
3077end interface PMPI_Win_unlock_all
3078
3079interface PMPI_Win_wait
3080    subroutine PMPIR_Win_wait_f08(win, ierror)
3081        use :: mpi_f08_types, only : MPI_Win
3082        implicit none
3083        type(MPI_Win), intent(in) :: win
3084        integer, optional, intent(out) :: ierror
3085    end subroutine PMPIR_Win_wait_f08
3086end interface PMPI_Win_wait
3087
3088interface PMPI_Grequest_complete
3089    subroutine PMPIR_Grequest_complete_f08(request, ierror)
3090        use :: mpi_f08_types, only : MPI_Request
3091        implicit none
3092        type(MPI_Request), intent(in) :: request
3093        integer, optional, intent(out) :: ierror
3094    end subroutine PMPIR_Grequest_complete_f08
3095end interface PMPI_Grequest_complete
3096
3097interface PMPI_Grequest_start
3098    subroutine PMPIR_Grequest_start_f08(query_fn, free_fn, cancel_fn, extra_state, request, &
3099                                       ierror)
3100        use :: mpi_f08_types, only : MPI_Request
3101        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
3102        use :: mpi_f08_callbacks, only : MPI_Grequest_query_function
3103        use :: mpi_f08_callbacks, only : MPI_Grequest_free_function
3104        use :: mpi_f08_callbacks, only : MPI_Grequest_cancel_function
3105        implicit none
3106        procedure(MPI_Grequest_query_function) :: query_fn
3107        procedure(MPI_Grequest_free_function) :: free_fn
3108        procedure(MPI_Grequest_cancel_function) :: cancel_fn
3109        integer(MPI_ADDRESS_KIND), intent(in) :: extra_state
3110        type(MPI_Request), intent(out) :: request
3111        integer, optional, intent(out) :: ierror
3112    end subroutine PMPIR_Grequest_start_f08
3113end interface PMPI_Grequest_start
3114
3115interface PMPI_Init_thread
3116    subroutine PMPIR_Init_thread_f08(required, provided, ierror)
3117        implicit none
3118        integer, intent(in) :: required
3119        integer, intent(out) :: provided
3120        integer, optional, intent(out) :: ierror
3121    end subroutine PMPIR_Init_thread_f08
3122end interface PMPI_Init_thread
3123
3124interface PMPI_Is_thread_main
3125    subroutine PMPIR_Is_thread_main_f08(flag, ierror)
3126        implicit none
3127        logical, intent(out) :: flag
3128        integer, optional, intent(out) :: ierror
3129    end subroutine PMPIR_Is_thread_main_f08
3130end interface PMPI_Is_thread_main
3131
3132interface PMPI_Query_thread
3133    subroutine PMPIR_Query_thread_f08(provided, ierror)
3134        implicit none
3135        integer, intent(out) :: provided
3136        integer, optional, intent(out) :: ierror
3137    end subroutine PMPIR_Query_thread_f08
3138end interface PMPI_Query_thread
3139
3140interface PMPI_Status_set_cancelled
3141    subroutine PMPIR_Status_set_cancelled_f08(status, flag, ierror)
3142        use :: mpi_f08_types, only : MPI_Status
3143        implicit none
3144        type(MPI_Status), intent(inout) :: status
3145        logical, intent(out) :: flag
3146        integer, optional, intent(out) :: ierror
3147    end subroutine PMPIR_Status_set_cancelled_f08
3148end interface PMPI_Status_set_cancelled
3149
3150interface PMPI_Status_set_elements
3151    subroutine PMPIR_Status_set_elements_f08(status, datatype, count, ierror)
3152        use :: mpi_f08_types, only : MPI_Status, MPI_Datatype
3153        implicit none
3154        type(MPI_Status), intent(inout) :: status
3155        type(MPI_Datatype), intent(in) :: datatype
3156        integer, intent(in) :: count
3157        integer, optional, intent(out) :: ierror
3158    end subroutine PMPIR_Status_set_elements_f08
3159end interface PMPI_Status_set_elements
3160
3161interface PMPI_Status_set_elements_x
3162    subroutine PMPIR_Status_set_elements_x_f08(status, datatype, count, ierror)
3163        use :: mpi_f08_types, only : MPI_Status, MPI_Datatype
3164        use :: mpi_f08_compile_constants, only : MPI_COUNT_KIND
3165        implicit none
3166        type(MPI_Status), intent(inout) :: status
3167        type(MPI_Datatype), intent(in) :: datatype
3168        integer(MPI_COUNT_KIND), intent(in) :: count
3169        integer, optional, intent(out) :: ierror
3170    end subroutine PMPIR_Status_set_elements_x_f08
3171end interface PMPI_Status_set_elements_x
3172
3173interface PMPI_File_close
3174    subroutine PMPIR_File_close_f08(fh, ierror)
3175        use :: mpi_f08_types, only : MPI_File
3176        implicit none
3177        type(MPI_File), intent(inout) :: fh
3178        integer, optional, intent(out) :: ierror
3179    end subroutine PMPIR_File_close_f08
3180end interface PMPI_File_close
3181
3182interface PMPI_File_delete
3183    subroutine PMPIR_File_delete_f08(filename, info, ierror)
3184        use :: mpi_f08_types, only : MPI_Info
3185        implicit none
3186        character(len=*), intent(in) :: filename
3187        type(MPI_Info), intent(in) :: info
3188        integer, optional, intent(out) :: ierror
3189    end subroutine PMPIR_File_delete_f08
3190end interface PMPI_File_delete
3191
3192interface PMPI_File_get_amode
3193    subroutine PMPIR_File_get_amode_f08(fh, amode, ierror)
3194        use :: mpi_f08_types, only : MPI_File
3195        implicit none
3196        type(MPI_File), intent(in) :: fh
3197        integer, intent(out) :: amode
3198        integer, optional, intent(out) :: ierror
3199    end subroutine PMPIR_File_get_amode_f08
3200end interface PMPI_File_get_amode
3201
3202interface PMPI_File_get_atomicity
3203    subroutine PMPIR_File_get_atomicity_f08(fh, flag, ierror)
3204        use :: mpi_f08_types, only : MPI_File
3205        implicit none
3206        type(MPI_File), intent(in) :: fh
3207        logical, intent(out) :: flag
3208        integer, optional, intent(out) :: ierror
3209    end subroutine PMPIR_File_get_atomicity_f08
3210end interface PMPI_File_get_atomicity
3211
3212interface PMPI_File_get_byte_offset
3213    subroutine PMPIR_File_get_byte_offset_f08(fh, offset, disp, ierror)
3214        use :: mpi_f08_types, only : MPI_File
3215        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3216        implicit none
3217        type(MPI_File), intent(in) :: fh
3218        integer(MPI_OFFSET_KIND), intent(in) :: offset
3219        integer(MPI_OFFSET_KIND), intent(out) :: disp
3220        integer, optional, intent(out) :: ierror
3221    end subroutine PMPIR_File_get_byte_offset_f08
3222end interface PMPI_File_get_byte_offset
3223
3224interface PMPI_File_get_group
3225    subroutine PMPIR_File_get_group_f08(fh, group, ierror)
3226        use :: mpi_f08_types, only : MPI_File, MPI_Group
3227        implicit none
3228        type(MPI_File), intent(in) :: fh
3229        type(MPI_Group), intent(out) :: group
3230        integer, optional, intent(out) :: ierror
3231    end subroutine PMPIR_File_get_group_f08
3232end interface PMPI_File_get_group
3233
3234interface PMPI_File_get_info
3235    subroutine PMPIR_File_get_info_f08(fh, info_used, ierror)
3236        use :: mpi_f08_types, only : MPI_File, MPI_Info
3237        implicit none
3238        type(MPI_File), intent(in) :: fh
3239        type(MPI_Info), intent(out) :: info_used
3240        integer, optional, intent(out) :: ierror
3241    end subroutine PMPIR_File_get_info_f08
3242end interface PMPI_File_get_info
3243
3244interface PMPI_File_get_position
3245    subroutine PMPIR_File_get_position_f08(fh, offset, ierror)
3246        use :: mpi_f08_types, only : MPI_File
3247        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3248        implicit none
3249        type(MPI_File), intent(in) :: fh
3250        integer(MPI_OFFSET_KIND), intent(out) :: offset
3251        integer, optional, intent(out) :: ierror
3252    end subroutine PMPIR_File_get_position_f08
3253end interface PMPI_File_get_position
3254
3255interface PMPI_File_get_position_shared
3256    subroutine PMPIR_File_get_position_shared_f08(fh, offset, ierror)
3257        use :: mpi_f08_types, only : MPI_File
3258        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3259        implicit none
3260        type(MPI_File), intent(in) :: fh
3261        integer(MPI_OFFSET_KIND), intent(out) :: offset
3262        integer, optional, intent(out) :: ierror
3263    end subroutine PMPIR_File_get_position_shared_f08
3264end interface PMPI_File_get_position_shared
3265
3266interface PMPI_File_get_size
3267    subroutine PMPIR_File_get_size_f08(fh, size, ierror)
3268        use :: mpi_f08_types, only : MPI_File
3269        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3270        implicit none
3271        type(MPI_File), intent(in) :: fh
3272        integer(MPI_OFFSET_KIND), intent(out) :: size
3273        integer, optional, intent(out) :: ierror
3274    end subroutine PMPIR_File_get_size_f08
3275end interface PMPI_File_get_size
3276
3277interface PMPI_File_get_type_extent
3278    subroutine PMPIR_File_get_type_extent_f08(fh, datatype, extent, ierror)
3279        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3280        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
3281        implicit none
3282        type(MPI_File), intent(in) :: fh
3283        type(MPI_Datatype), intent(in) :: datatype
3284        integer(MPI_ADDRESS_KIND), intent(out) :: extent
3285        integer, optional, intent(out) :: ierror
3286    end subroutine PMPIR_File_get_type_extent_f08
3287end interface PMPI_File_get_type_extent
3288
3289interface PMPI_File_get_view
3290    subroutine PMPIR_File_get_view_f08(fh, disp, etype, filetype, datarep, ierror)
3291        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3292        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3293        implicit none
3294        type(MPI_File), intent(in) :: fh
3295        integer(MPI_OFFSET_KIND), intent(out) :: disp
3296        type(MPI_Datatype), intent(out) :: etype
3297        type(MPI_Datatype), intent(out) :: filetype
3298        character(len=*), intent(out) :: datarep
3299        integer, optional, intent(out) :: ierror
3300    end subroutine PMPIR_File_get_view_f08
3301end interface PMPI_File_get_view
3302
3303interface PMPI_File_iread
3304    subroutine PMPIR_File_iread_f08ts(fh, buf, count, datatype, request, ierror)
3305        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3306        implicit none
3307        type(MPI_File), intent(in) :: fh
3308        type(*), dimension(..), asynchronous :: buf
3309        integer, intent(in) :: count
3310        type(MPI_Datatype), intent(in) :: datatype
3311        type(MPI_Request), intent(out) :: request
3312        integer, optional, intent(out) :: ierror
3313    end subroutine PMPIR_File_iread_f08ts
3314end interface PMPI_File_iread
3315
3316interface PMPI_File_iread_at
3317    subroutine PMPIR_File_iread_at_f08ts(fh, offset, buf, count, datatype, request, ierror)
3318        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3319        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3320        implicit none
3321        type(MPI_File), intent(in) :: fh
3322        integer(MPI_OFFSET_KIND), intent(in) :: offset
3323        type(*), dimension(..), asynchronous :: buf
3324        integer, intent(in) :: count
3325        type(MPI_Datatype), intent(in) :: datatype
3326        type(MPI_Request), intent(out) :: request
3327        integer, optional, intent(out) :: ierror
3328    end subroutine PMPIR_File_iread_at_f08ts
3329end interface PMPI_File_iread_at
3330
3331interface PMPI_File_iread_shared
3332    subroutine PMPIR_File_iread_shared_f08ts(fh, buf, count, datatype, request, ierror)
3333        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3334        implicit none
3335        type(MPI_File), intent(in) :: fh
3336        type(*), dimension(..), asynchronous :: buf
3337        integer, intent(in) :: count
3338        type(MPI_Datatype), intent(in) :: datatype
3339        type(MPI_Request), intent(out) :: request
3340        integer, optional, intent(out) :: ierror
3341    end subroutine PMPIR_File_iread_shared_f08ts
3342end interface PMPI_File_iread_shared
3343
3344interface PMPI_File_iwrite
3345    subroutine PMPIR_File_iwrite_f08ts(fh, buf, count, datatype, request, ierror)
3346        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3347        implicit none
3348        type(MPI_File), intent(in) :: fh
3349        type(*), dimension(..), intent(in), asynchronous :: buf
3350        integer, intent(in) :: count
3351        type(MPI_Datatype), intent(in) :: datatype
3352        type(MPI_Request), intent(out) :: request
3353        integer, optional, intent(out) :: ierror
3354    end subroutine PMPIR_File_iwrite_f08ts
3355end interface PMPI_File_iwrite
3356
3357interface PMPI_File_iwrite_at
3358    subroutine PMPIR_File_iwrite_at_f08ts(fh, offset, buf, count, datatype, request, ierror)
3359        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3360        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3361        implicit none
3362        type(MPI_File), intent(in) :: fh
3363        integer(MPI_OFFSET_KIND), intent(in) :: offset
3364        type(*), dimension(..), intent(in), asynchronous :: buf
3365        integer, intent(in) :: count
3366        type(MPI_Datatype), intent(in) :: datatype
3367        type(MPI_Request), intent(out) :: request
3368        integer, optional, intent(out) :: ierror
3369    end subroutine PMPIR_File_iwrite_at_f08ts
3370end interface PMPI_File_iwrite_at
3371
3372interface PMPI_File_iwrite_shared
3373    subroutine PMPIR_File_iwrite_shared_f08ts(fh, buf, count, datatype, request, ierror)
3374        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
3375        implicit none
3376        type(*), dimension(..), intent(in), asynchronous :: buf
3377        type(MPI_File), intent(in) :: fh
3378        integer, intent(in) :: count
3379        type(MPI_Datatype), intent(in) :: datatype
3380        type(MPI_Request), intent(out) :: request
3381        integer, optional, intent(out) :: ierror
3382    end subroutine PMPIR_File_iwrite_shared_f08ts
3383end interface PMPI_File_iwrite_shared
3384
3385interface PMPI_File_open
3386    subroutine PMPIR_File_open_f08(comm, filename, amode, info, fh, ierror)
3387        use :: mpi_f08_types, only : MPI_Comm, MPI_Info, MPI_File
3388        implicit none
3389        type(MPI_Comm), intent(in) :: comm
3390        character(len=*), intent(in) :: filename
3391        integer, intent(in) :: amode
3392        type(MPI_Info), intent(in) :: info
3393        type(MPI_File), intent(out) :: fh
3394        integer, optional, intent(out) :: ierror
3395    end subroutine PMPIR_File_open_f08
3396end interface PMPI_File_open
3397
3398interface PMPI_File_preallocate
3399    subroutine PMPIR_File_preallocate_f08(fh, size, ierror)
3400        use :: mpi_f08_types, only : MPI_File
3401        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3402        implicit none
3403        type(MPI_File), intent(in) :: fh
3404        integer(MPI_OFFSET_KIND), intent(in) :: size
3405        integer, optional, intent(out) :: ierror
3406    end subroutine PMPIR_File_preallocate_f08
3407end interface PMPI_File_preallocate
3408
3409interface PMPI_File_read
3410    subroutine PMPIR_File_read_f08ts(fh, buf, count, datatype, status, ierror)
3411        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3412        implicit none
3413        type(MPI_File), intent(in) :: fh
3414        type(*), dimension(..) :: buf
3415        integer, intent(in) :: count
3416        type(MPI_Datatype), intent(in) :: datatype
3417        type(MPI_Status) :: status
3418        integer, optional, intent(out) :: ierror
3419    end subroutine PMPIR_File_read_f08ts
3420end interface PMPI_File_read
3421
3422interface PMPI_File_read_all
3423    subroutine PMPIR_File_read_all_f08ts(fh, buf, count, datatype, status, ierror)
3424        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3425        implicit none
3426        type(MPI_File), intent(in) :: fh
3427        type(*), dimension(..) :: buf
3428        integer, intent(in) :: count
3429        type(MPI_Datatype), intent(in) :: datatype
3430        type(MPI_Status) :: status
3431        integer, optional, intent(out) :: ierror
3432    end subroutine PMPIR_File_read_all_f08ts
3433end interface PMPI_File_read_all
3434
3435interface PMPI_File_read_all_begin
3436    subroutine PMPIR_File_read_all_begin_f08ts(fh, buf, count, datatype, ierror)
3437        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3438        implicit none
3439        type(MPI_File), intent(in) :: fh
3440        type(*), dimension(..) :: buf
3441        integer, intent(in) :: count
3442        type(MPI_Datatype), intent(in) :: datatype
3443        integer, optional, intent(out) :: ierror
3444    end subroutine PMPIR_File_read_all_begin_f08ts
3445end interface PMPI_File_read_all_begin
3446
3447interface PMPI_File_read_all_end
3448    subroutine PMPIR_File_read_all_end_f08ts(fh, buf, status, ierror)
3449        use :: mpi_f08_types, only : MPI_File, MPI_Status
3450        implicit none
3451        type(MPI_File), intent(in) :: fh
3452        type(*), dimension(..) :: buf
3453        type(MPI_Status) :: status
3454        integer, optional, intent(out) :: ierror
3455    end subroutine PMPIR_File_read_all_end_f08ts
3456end interface PMPI_File_read_all_end
3457
3458interface PMPI_File_read_at
3459    subroutine PMPIR_File_read_at_f08ts(fh, offset, buf, count, datatype, status, ierror)
3460        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3461        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3462        implicit none
3463        type(MPI_File), intent(in) :: fh
3464        integer(MPI_OFFSET_KIND), intent(in) :: offset
3465        type(*), dimension(..) :: buf
3466        integer, intent(in) :: count
3467        type(MPI_Datatype), intent(in) :: datatype
3468        type(MPI_Status) :: status
3469        integer, optional, intent(out) :: ierror
3470    end subroutine PMPIR_File_read_at_f08ts
3471end interface PMPI_File_read_at
3472
3473interface PMPI_File_read_at_all
3474    subroutine PMPIR_File_read_at_all_f08ts(fh, offset, buf, count, datatype, status, ierror)
3475        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3476        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3477        implicit none
3478        type(MPI_File), intent(in) :: fh
3479        integer(MPI_OFFSET_KIND), intent(in) :: offset
3480        type(*), dimension(..) :: buf
3481        integer, intent(in) :: count
3482        type(MPI_Datatype), intent(in) :: datatype
3483        type(MPI_Status) :: status
3484        integer, optional, intent(out) :: ierror
3485    end subroutine PMPIR_File_read_at_all_f08ts
3486end interface PMPI_File_read_at_all
3487
3488interface PMPI_File_read_at_all_begin
3489    subroutine PMPIR_File_read_at_all_begin_f08ts(fh, offset, buf, count, datatype, ierror)
3490        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3491        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3492        implicit none
3493        type(MPI_File), intent(in) :: fh
3494        integer(MPI_OFFSET_KIND), intent(in) :: offset
3495        type(*), dimension(..) :: buf
3496        integer, intent(in) :: count
3497        type(MPI_Datatype), intent(in) :: datatype
3498        integer, optional, intent(out) :: ierror
3499    end subroutine PMPIR_File_read_at_all_begin_f08ts
3500end interface PMPI_File_read_at_all_begin
3501
3502interface PMPI_File_read_at_all_end
3503    subroutine PMPIR_File_read_at_all_end_f08ts(fh, buf, status, ierror)
3504        use :: mpi_f08_types, only : MPI_File, MPI_Status
3505        implicit none
3506        type(MPI_File), intent(in) :: fh
3507        type(*), dimension(..) :: buf
3508        type(MPI_Status) :: status
3509        integer, optional, intent(out) :: ierror
3510    end subroutine PMPIR_File_read_at_all_end_f08ts
3511end interface PMPI_File_read_at_all_end
3512
3513interface PMPI_File_read_ordered
3514    subroutine PMPIR_File_read_ordered_f08ts(fh, buf, count, datatype, status, ierror)
3515        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3516        implicit none
3517        type(MPI_File), intent(in) :: fh
3518        type(*), dimension(..) :: buf
3519        integer, intent(in) :: count
3520        type(MPI_Datatype), intent(in) :: datatype
3521        type(MPI_Status) :: status
3522        integer, optional, intent(out) :: ierror
3523    end subroutine PMPIR_File_read_ordered_f08ts
3524end interface PMPI_File_read_ordered
3525
3526interface PMPI_File_read_ordered_begin
3527    subroutine PMPIR_File_read_ordered_begin_f08ts(fh, buf, count, datatype, ierror)
3528        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3529        implicit none
3530        type(MPI_File), intent(in) :: fh
3531        type(*), dimension(..) :: buf
3532        integer, intent(in) :: count
3533        type(MPI_Datatype), intent(in) :: datatype
3534        integer, optional, intent(out) :: ierror
3535    end subroutine PMPIR_File_read_ordered_begin_f08ts
3536end interface PMPI_File_read_ordered_begin
3537
3538interface PMPI_File_read_ordered_end
3539    subroutine PMPIR_File_read_ordered_end_f08ts(fh, buf, status, ierror)
3540        use :: mpi_f08_types, only : MPI_File, MPI_Status
3541        implicit none
3542        type(MPI_File), intent(in) :: fh
3543        type(*), dimension(..) :: buf
3544        type(MPI_Status) :: status
3545        integer, optional, intent(out) :: ierror
3546    end subroutine PMPIR_File_read_ordered_end_f08ts
3547end interface PMPI_File_read_ordered_end
3548
3549interface PMPI_File_read_shared
3550    subroutine PMPIR_File_read_shared_f08ts(fh, buf, count, datatype, status, ierror)
3551        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3552        implicit none
3553        type(MPI_File), intent(in) :: fh
3554        type(*), dimension(..) :: buf
3555        integer, intent(in) :: count
3556        type(MPI_Datatype), intent(in) :: datatype
3557        type(MPI_Status) :: status
3558        integer, optional, intent(out) :: ierror
3559    end subroutine PMPIR_File_read_shared_f08ts
3560end interface PMPI_File_read_shared
3561
3562interface PMPI_File_seek
3563    subroutine PMPIR_File_seek_f08(fh, offset, whence, ierror)
3564        use :: mpi_f08_types, only : MPI_File
3565        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3566        implicit none
3567        type(MPI_File), intent(in) :: fh
3568        integer(MPI_OFFSET_KIND), intent(in) :: offset
3569        integer, intent(in) :: whence
3570        integer, optional, intent(out) :: ierror
3571    end subroutine PMPIR_File_seek_f08
3572end interface PMPI_File_seek
3573
3574interface PMPI_File_seek_shared
3575    subroutine PMPIR_File_seek_shared_f08(fh, offset, whence, ierror)
3576        use :: mpi_f08_types, only : MPI_File
3577        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3578        implicit none
3579        type(MPI_File), intent(in) :: fh
3580        integer(MPI_OFFSET_KIND), intent(in) :: offset
3581        integer, intent(in) :: whence
3582        integer, optional, intent(out) :: ierror
3583    end subroutine PMPIR_File_seek_shared_f08
3584end interface PMPI_File_seek_shared
3585
3586interface PMPI_File_set_atomicity
3587    subroutine PMPIR_File_set_atomicity_f08(fh, flag, ierror)
3588        use :: mpi_f08_types, only : MPI_File
3589        implicit none
3590        type(MPI_File), intent(in) :: fh
3591        logical, intent(in) :: flag
3592        integer, optional, intent(out) :: ierror
3593    end subroutine PMPIR_File_set_atomicity_f08
3594end interface PMPI_File_set_atomicity
3595
3596interface PMPI_File_set_info
3597    subroutine PMPIR_File_set_info_f08(fh, info, ierror)
3598        use :: mpi_f08_types, only : MPI_File, MPI_Info
3599        implicit none
3600        type(MPI_File), intent(in) :: fh
3601        type(MPI_Info), intent(in) :: info
3602        integer, optional, intent(out) :: ierror
3603    end subroutine PMPIR_File_set_info_f08
3604end interface PMPI_File_set_info
3605
3606interface PMPI_File_set_size
3607    subroutine PMPIR_File_set_size_f08(fh, size, ierror)
3608        use :: mpi_f08_types, only : MPI_File
3609        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3610        implicit none
3611        type(MPI_File), intent(in) :: fh
3612        integer(MPI_OFFSET_KIND), intent(in) :: size
3613        integer, optional, intent(out) :: ierror
3614    end subroutine PMPIR_File_set_size_f08
3615end interface PMPI_File_set_size
3616
3617interface PMPI_File_set_view
3618    subroutine PMPIR_File_set_view_f08(fh, disp, etype, filetype, datarep, info, ierror)
3619        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Info
3620        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3621        implicit none
3622        type(MPI_File), intent(in) :: fh
3623        integer(MPI_OFFSET_KIND), intent(in) :: disp
3624        type(MPI_Datatype), intent(in) :: etype
3625        type(MPI_Datatype), intent(in) :: filetype
3626        character(len=*), intent(in) :: datarep
3627        type(MPI_Info), intent(in) :: info
3628        integer, optional, intent(out) :: ierror
3629    end subroutine PMPIR_File_set_view_f08
3630end interface PMPI_File_set_view
3631
3632interface PMPI_File_sync
3633    subroutine PMPIR_File_sync_f08(fh, ierror)
3634        use :: mpi_f08_types, only : MPI_File
3635        implicit none
3636        type(MPI_File), intent(in) :: fh
3637        integer, optional, intent(out) :: ierror
3638    end subroutine PMPIR_File_sync_f08
3639end interface PMPI_File_sync
3640
3641interface PMPI_File_write
3642    subroutine PMPIR_File_write_f08ts(fh, buf, count, datatype, status, ierror)
3643        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3644        implicit none
3645        type(MPI_File), intent(in) :: fh
3646        type(*), dimension(..), intent(in) :: buf
3647        integer, intent(in) :: count
3648        type(MPI_Datatype), intent(in) :: datatype
3649        type(MPI_Status) :: status
3650        integer, optional, intent(out) :: ierror
3651    end subroutine PMPIR_File_write_f08ts
3652end interface PMPI_File_write
3653
3654interface PMPI_File_write_all
3655    subroutine PMPIR_File_write_all_f08ts(fh, buf, count, datatype, status, ierror)
3656        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3657        implicit none
3658        type(MPI_File), intent(in) :: fh
3659        type(*), dimension(..), intent(in) :: buf
3660        integer, intent(in) :: count
3661        type(MPI_Datatype), intent(in) :: datatype
3662        type(MPI_Status) :: status
3663        integer, optional, intent(out) :: ierror
3664    end subroutine PMPIR_File_write_all_f08ts
3665end interface PMPI_File_write_all
3666
3667interface PMPI_File_write_all_begin
3668    subroutine PMPIR_File_write_all_begin_f08ts(fh, buf, count, datatype, ierror)
3669        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3670        implicit none
3671        type(MPI_File), intent(in) :: fh
3672        type(*), dimension(..), intent(in) :: buf
3673        integer, intent(in) :: count
3674        type(MPI_Datatype), intent(in) :: datatype
3675        integer, optional, intent(out) :: ierror
3676    end subroutine PMPIR_File_write_all_begin_f08ts
3677end interface PMPI_File_write_all_begin
3678
3679interface PMPI_File_write_all_end
3680    subroutine PMPIR_File_write_all_end_f08ts(fh, buf, status, ierror)
3681        use :: mpi_f08_types, only : MPI_File, MPI_Status
3682        implicit none
3683        type(MPI_File), intent(in) :: fh
3684        type(*), dimension(..), intent(in) :: buf
3685        type(MPI_Status) :: status
3686        integer, optional, intent(out) :: ierror
3687    end subroutine PMPIR_File_write_all_end_f08ts
3688end interface PMPI_File_write_all_end
3689
3690interface PMPI_File_write_at
3691    subroutine PMPIR_File_write_at_f08ts(fh, offset, buf, count, datatype, status, ierror)
3692        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3693        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3694        implicit none
3695        type(MPI_File), intent(in) :: fh
3696        integer(MPI_OFFSET_KIND), intent(in) :: offset
3697        type(*), dimension(..), intent(in) :: buf
3698        integer, intent(in) :: count
3699        type(MPI_Datatype), intent(in) :: datatype
3700        type(MPI_Status) :: status
3701        integer, optional, intent(out) :: ierror
3702    end subroutine PMPIR_File_write_at_f08ts
3703end interface PMPI_File_write_at
3704
3705interface PMPI_File_write_at_all
3706    subroutine PMPIR_File_write_at_all_f08ts(fh, offset, buf, count, datatype, status, ierror)
3707        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3708        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3709        implicit none
3710        type(MPI_File), intent(in) :: fh
3711        integer(MPI_OFFSET_KIND), intent(in) :: offset
3712        type(*), dimension(..) :: buf
3713        integer, intent(in) :: count
3714        type(MPI_Datatype), intent(in) :: datatype
3715        type(MPI_Status) :: status
3716        integer, optional, intent(out) :: ierror
3717    end subroutine PMPIR_File_write_at_all_f08ts
3718end interface PMPI_File_write_at_all
3719
3720interface PMPI_File_write_at_all_begin
3721    subroutine PMPIR_File_write_at_all_begin_f08ts(fh, offset, buf, count, datatype, ierror)
3722        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3723        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
3724        implicit none
3725        type(MPI_File), intent(in) :: fh
3726        integer(MPI_OFFSET_KIND), intent(in) :: offset
3727        type(*), dimension(..), intent(in) :: buf
3728        integer, intent(in) :: count
3729        type(MPI_Datatype), intent(in) :: datatype
3730        integer, optional, intent(out) :: ierror
3731    end subroutine PMPIR_File_write_at_all_begin_f08ts
3732end interface PMPI_File_write_at_all_begin
3733
3734interface PMPI_File_write_at_all_end
3735    subroutine PMPIR_File_write_at_all_end_f08ts(fh, buf, status, ierror)
3736        use :: mpi_f08_types, only : MPI_File, MPI_Status
3737        implicit none
3738        type(MPI_File), intent(in) :: fh
3739        type(*), dimension(..), intent(in) :: buf
3740        type(MPI_Status) :: status
3741        integer, optional, intent(out) :: ierror
3742    end subroutine PMPIR_File_write_at_all_end_f08ts
3743end interface PMPI_File_write_at_all_end
3744
3745interface PMPI_File_write_ordered
3746    subroutine PMPIR_File_write_ordered_f08ts(fh, buf, count, datatype, status, ierror)
3747        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3748        implicit none
3749        type(MPI_File), intent(in) :: fh
3750        type(*), dimension(..), intent(in) :: buf
3751        integer, intent(in) :: count
3752        type(MPI_Datatype), intent(in) :: datatype
3753        type(MPI_Status) :: status
3754        integer, optional, intent(out) :: ierror
3755    end subroutine PMPIR_File_write_ordered_f08ts
3756end interface PMPI_File_write_ordered
3757
3758interface PMPI_File_write_ordered_begin
3759    subroutine PMPIR_File_write_ordered_begin_f08ts(fh, buf, count, datatype, ierror)
3760        use :: mpi_f08_types, only : MPI_File, MPI_Datatype
3761        implicit none
3762        type(MPI_File), intent(in) :: fh
3763        type(*), dimension(..), intent(in) :: buf
3764        integer, intent(in) :: count
3765        type(MPI_Datatype), intent(in) :: datatype
3766        integer, optional, intent(out) :: ierror
3767    end subroutine PMPIR_File_write_ordered_begin_f08ts
3768end interface PMPI_File_write_ordered_begin
3769
3770interface PMPI_File_write_ordered_end
3771    subroutine PMPIR_File_write_ordered_end_f08ts(fh, buf, status, ierror)
3772        use :: mpi_f08_types, only : MPI_File, MPI_Status
3773        implicit none
3774        type(MPI_File), intent(in) :: fh
3775        type(*), dimension(..), intent(in) :: buf
3776        type(MPI_Status) :: status
3777        integer, optional, intent(out) :: ierror
3778    end subroutine PMPIR_File_write_ordered_end_f08ts
3779end interface PMPI_File_write_ordered_end
3780
3781interface PMPI_File_write_shared
3782    subroutine PMPIR_File_write_shared_f08ts(fh, buf, count, datatype, status, ierror)
3783        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Status
3784        implicit none
3785        type(MPI_File), intent(in) :: fh
3786        type(*), dimension(..), intent(in) :: buf
3787        integer, intent(in) :: count
3788        type(MPI_Datatype), intent(in) :: datatype
3789        type(MPI_Status) :: status
3790        integer, optional, intent(out) :: ierror
3791    end subroutine PMPIR_File_write_shared_f08ts
3792end interface PMPI_File_write_shared
3793
3794interface PMPI_Register_datarep
3795    subroutine PMPIR_Register_datarep_f08(datarep, read_conversion_fn, write_conversion_fn, &
3796                                                 dtype_file_extent_fn, extra_state, ierror)
3797        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
3798        use :: mpi_f08_callbacks, only : MPI_Datarep_conversion_function
3799        use :: mpi_f08_callbacks, only : MPI_Datarep_extent_function
3800        implicit none
3801        character(len=*), intent(in) :: datarep
3802        procedure(MPI_Datarep_conversion_function) :: read_conversion_fn
3803        procedure(MPI_Datarep_conversion_function) :: write_conversion_fn
3804        procedure(MPI_Datarep_extent_function) :: dtype_file_extent_fn
3805        integer(MPI_ADDRESS_KIND), intent(in) :: extra_state
3806        integer, optional, intent(out) :: ierror
3807    end subroutine PMPIR_Register_datarep_f08
3808end interface PMPI_Register_datarep
3809
3810
3811interface PMPI_Type_create_f90_complex
3812    subroutine PMPIR_Type_create_f90_complex_f08(p, r, newtype, ierror)
3813        use :: mpi_f08_types, only : MPI_Datatype
3814        implicit none
3815        integer, intent(in) :: p, r
3816        type(MPI_Datatype), intent(out) :: newtype
3817        integer, optional, intent(out) :: ierror
3818    end subroutine PMPIR_Type_create_f90_complex_f08
3819end interface PMPI_Type_create_f90_complex
3820
3821interface PMPI_Type_create_f90_integer
3822    subroutine PMPIR_Type_create_f90_integer_f08(r, newtype, ierror)
3823        use :: mpi_f08_types, only : MPI_Datatype
3824        implicit none
3825        integer, intent(in) :: r
3826        type(MPI_Datatype), intent(out) :: newtype
3827        integer, optional, intent(out) :: ierror
3828    end subroutine PMPIR_Type_create_f90_integer_f08
3829end interface PMPI_Type_create_f90_integer
3830
3831interface PMPI_Type_create_f90_real
3832    subroutine PMPIR_Type_create_f90_real_f08(p, r, newtype, ierror)
3833        use :: mpi_f08_types, only : MPI_Datatype
3834        implicit none
3835        integer, intent(in) :: p, r
3836        type(MPI_Datatype), intent(out) :: newtype
3837        integer, optional, intent(out) :: ierror
3838    end subroutine PMPIR_Type_create_f90_real_f08
3839end interface PMPI_Type_create_f90_real
3840
3841interface PMPI_Type_match_size
3842    subroutine PMPIR_Type_match_size_f08(typeclass, size, datatype, ierror)
3843        use :: mpi_f08_types, only : MPI_Datatype
3844        implicit none
3845        integer, intent(in) :: typeclass, size
3846        type(MPI_Datatype), intent(out) :: datatype
3847        integer, optional, intent(out) :: ierror
3848    end subroutine PMPIR_Type_match_size_f08
3849end interface PMPI_Type_match_size
3850
3851interface PMPI_Pcontrol
3852    subroutine PMPIR_Pcontrol_f08(level)
3853        implicit none
3854        integer, intent(in) :: level
3855    end subroutine PMPIR_Pcontrol_f08
3856end interface PMPI_Pcontrol
3857
3858interface PMPI_Comm_split_type
3859    subroutine PMPIR_Comm_split_type_f08(comm, split_type, key, info, newcomm, ierror)
3860        use :: mpi_f08_types, only : MPI_Comm, MPI_Info
3861        implicit none
3862        type(MPI_Comm), intent(in) :: comm
3863        integer, intent(in) :: split_type
3864        integer, intent(in) :: key
3865        type(MPI_Info), intent(in) :: info
3866        type(MPI_Comm), intent(out) :: newcomm
3867        integer, optional, intent(out) :: ierror
3868    end subroutine PMPIR_Comm_split_type_f08
3869end interface PMPI_Comm_split_type
3870
3871interface PMPI_F_sync_reg
3872    subroutine PMPIR_F_sync_reg_f08ts(buf)
3873        implicit none
3874        type(*), dimension(..) :: buf
3875    end subroutine PMPIR_F_sync_reg_f08ts
3876end interface PMPI_F_sync_reg
3877
3878interface PMPI_Get_library_version
3879    subroutine PMPIR_Get_library_version_f08(version, resultlen, ierror)
3880        use :: mpi_f08_compile_constants, only : MPI_MAX_LIBRARY_VERSION_STRING
3881        implicit none
3882        character(len=MPI_MAX_LIBRARY_VERSION_STRING), intent(out) :: version
3883        integer, intent(out) :: resultlen
3884        integer, optional, intent(out) :: ierror
3885    end subroutine PMPIR_Get_library_version_f08
3886end interface PMPI_Get_library_version
3887
3888interface PMPI_Mprobe
3889    subroutine PMPIR_Mprobe_f08(source, tag, comm, message, status, ierror)
3890        use :: mpi_f08_types, only : MPI_Comm, MPI_Message, MPI_Status
3891        implicit none
3892        integer, intent(in) :: source, tag
3893        type(MPI_Comm), intent(in) :: comm
3894        type(MPI_Message), intent(out) :: message
3895        type(MPI_Status) :: status
3896        integer, optional, intent(out) :: ierror
3897    end subroutine PMPIR_Mprobe_f08
3898end interface PMPI_Mprobe
3899
3900interface PMPI_Improbe
3901    subroutine PMPIR_Improbe_f08(source, tag, comm, flag, message, status, ierror)
3902        use :: mpi_f08_types, only : MPI_Comm, MPI_Message, MPI_Status
3903        implicit none
3904        integer, intent(in) :: source, tag
3905        type(MPI_Comm), intent(in) :: comm
3906        logical, intent(out) :: flag
3907        type(MPI_Message), intent(out) :: message
3908        type(MPI_Status) :: status
3909        integer, optional, intent(out) :: ierror
3910    end subroutine PMPIR_Improbe_f08
3911end interface PMPI_Improbe
3912
3913interface PMPI_Imrecv
3914    subroutine PMPIR_Imrecv_f08ts(buf, count, datatype, message, request, ierror)
3915        use :: mpi_f08_types, only : MPI_Datatype, MPI_Message, MPI_Request
3916        implicit none
3917        type(*), dimension(..), asynchronous :: buf
3918        integer, intent(in) :: count
3919        type(MPI_Datatype), intent(in) :: datatype
3920        type(MPI_Message), intent(inout) :: message
3921        type(MPI_Request), intent(out) :: request
3922        integer, optional, intent(out) :: ierror
3923    end subroutine PMPIR_Imrecv_f08ts
3924end interface PMPI_Imrecv
3925
3926interface PMPI_Mrecv
3927    subroutine PMPIR_Mrecv_f08ts(buf, count, datatype, message, status, ierror)
3928        use :: mpi_f08_types, only : MPI_Datatype, MPI_Message, MPI_Status
3929        implicit none
3930        type(*), dimension(..) :: buf
3931        integer, intent(in) :: count
3932        type(MPI_Datatype), intent(in) :: datatype
3933        type(MPI_Message), intent(inout) :: message
3934        type(MPI_Status) :: status
3935        integer, optional, intent(out) :: ierror
3936    end subroutine PMPIR_Mrecv_f08ts
3937end interface PMPI_Mrecv
3938
3939interface PMPI_Neighbor_allgather
3940    subroutine PMPIR_Neighbor_allgather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
3941                 comm, ierror)
3942        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
3943        implicit none
3944        type(*), dimension(..), intent(in) :: sendbuf
3945        type(*), dimension(..) :: recvbuf
3946        integer, intent(in) :: sendcount, recvcount
3947        type(MPI_Datatype), intent(in) :: sendtype, recvtype
3948        type(MPI_Comm), intent(in) :: comm
3949        integer, optional, intent(out) :: ierror
3950    end subroutine PMPIR_Neighbor_allgather_f08ts
3951end interface PMPI_Neighbor_allgather
3952
3953interface PMPI_Ineighbor_allgather
3954    subroutine PMPIR_Ineighbor_allgather_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
3955                 comm, request, ierror)
3956        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
3957        implicit none
3958        type(*), dimension(..), intent(in), asynchronous :: sendbuf
3959        type(*), dimension(..), asynchronous :: recvbuf
3960        integer, intent(in) :: sendcount, recvcount
3961        type(MPI_Datatype), intent(in) :: sendtype, recvtype
3962        type(MPI_Comm), intent(in) :: comm
3963        type(MPI_Request), intent(out) :: request
3964        integer, optional, intent(out) :: ierror
3965    end subroutine PMPIR_Ineighbor_allgather_f08ts
3966end interface PMPI_Ineighbor_allgather
3967
3968interface PMPI_Neighbor_allgatherv
3969    subroutine PMPIR_Neighbor_allgatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
3970                 recvtype, comm, ierror)
3971        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
3972        implicit none
3973        type(*), dimension(..), intent(in) :: sendbuf
3974        type(*), dimension(..) :: recvbuf
3975        integer, intent(in) :: sendcount
3976        integer, intent(in) :: recvcounts(*), displs(*)
3977        type(MPI_Datatype), intent(in) :: sendtype, recvtype
3978        type(MPI_Comm), intent(in) :: comm
3979        integer, optional, intent(out) :: ierror
3980    end subroutine PMPIR_Neighbor_allgatherv_f08ts
3981end interface PMPI_Neighbor_allgatherv
3982
3983interface PMPI_Ineighbor_allgatherv
3984    subroutine PMPIR_Ineighbor_allgatherv_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcounts, displs, &
3985                 recvtype, comm, request, ierror)
3986        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
3987        implicit none
3988        type(*), dimension(..), intent(in), asynchronous :: sendbuf
3989        type(*), dimension(..), asynchronous :: recvbuf
3990        integer, intent(in) :: sendcount
3991        integer, intent(in) :: recvcounts(*), displs(*)
3992        type(MPI_Datatype), intent(in) :: sendtype, recvtype
3993        type(MPI_Comm), intent(in) :: comm
3994        type(MPI_Request), intent(out) :: request
3995        integer, optional, intent(out) :: ierror
3996    end subroutine PMPIR_Ineighbor_allgatherv_f08ts
3997end interface PMPI_Ineighbor_allgatherv
3998
3999interface PMPI_Neighbor_alltoall
4000    subroutine PMPIR_Neighbor_alltoall_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
4001                 comm, ierror)
4002        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
4003        implicit none
4004        type(*), dimension(..), intent(in) :: sendbuf
4005        type(*), dimension(..) :: recvbuf
4006        integer, intent(in) :: sendcount, recvcount
4007        type(MPI_Datatype), intent(in) :: sendtype, recvtype
4008        type(MPI_Comm), intent(in) :: comm
4009        integer, optional, intent(out) :: ierror
4010    end subroutine PMPIR_Neighbor_alltoall_f08ts
4011end interface PMPI_Neighbor_alltoall
4012
4013interface PMPI_Ineighbor_alltoall
4014    subroutine PMPIR_Ineighbor_alltoall_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
4015                 comm, request, ierror)
4016        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
4017        implicit none
4018        type(*), dimension(..), intent(in), asynchronous :: sendbuf
4019        type(*), dimension(..), asynchronous :: recvbuf
4020        integer, intent(in) :: sendcount, recvcount
4021        type(MPI_Datatype), intent(in) :: sendtype, recvtype
4022        type(MPI_Comm), intent(in) :: comm
4023        type(MPI_Request), intent(out) :: request
4024        integer, optional, intent(out) :: ierror
4025    end subroutine PMPIR_Ineighbor_alltoall_f08ts
4026end interface PMPI_Ineighbor_alltoall
4027
4028interface PMPI_Neighbor_alltoallv
4029    subroutine PMPIR_Neighbor_alltoallv_f08ts(sendbuf, sendcounts, sdispls, sendtype, recvbuf, recvcounts, &
4030                 rdispls, recvtype, comm, ierror)
4031        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
4032        implicit none
4033        type(*), dimension(..), intent(in) :: sendbuf
4034        type(*), dimension(..) :: recvbuf
4035        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
4036        type(MPI_Datatype), intent(in) :: sendtype, recvtype
4037        type(MPI_Comm), intent(in) :: comm
4038        integer, optional, intent(out) :: ierror
4039    end subroutine PMPIR_Neighbor_alltoallv_f08ts
4040end interface PMPI_Neighbor_alltoallv
4041
4042interface PMPI_Ineighbor_alltoallv
4043    subroutine PMPIR_Ineighbor_alltoallv_f08ts(sendbuf, sendcounts, sdispls, sendtype, recvbuf, recvcounts, &
4044                 rdispls, recvtype, comm, request, ierror)
4045        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
4046        implicit none
4047        type(*), dimension(..), intent(in), asynchronous :: sendbuf
4048        type(*), dimension(..), asynchronous :: recvbuf
4049        integer, intent(in) :: sendcounts(*), sdispls(*), recvcounts(*), rdispls(*)
4050        type(MPI_Datatype), intent(in) :: sendtype, recvtype
4051        type(MPI_Comm), intent(in) :: comm
4052        type(MPI_Request), intent(in) :: request
4053        integer, optional, intent(out) :: ierror
4054    end subroutine PMPIR_Ineighbor_alltoallv_f08ts
4055end interface PMPI_Ineighbor_alltoallv
4056
4057interface PMPI_Neighbor_alltoallw
4058    subroutine PMPIR_Neighbor_alltoallw_f08ts(sendbuf, sendcounts, sdispls, sendtypes, recvbuf, recvcounts, &
4059                 rdispls, recvtypes, comm, ierror)
4060        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm
4061        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
4062        implicit none
4063        type(*), dimension(..), intent(in) :: sendbuf
4064        type(*), dimension(..) :: recvbuf
4065        integer, intent(in) :: sendcounts(*), recvcounts(*)
4066        integer(MPI_ADDRESS_KIND), intent(in) :: sdispls(*), rdispls(*)
4067        type(MPI_Datatype), intent(in) :: sendtypes(*), recvtypes(*)
4068        type(MPI_Comm), intent(in) :: comm
4069        integer, optional, intent(out) :: ierror
4070    end subroutine PMPIR_Neighbor_alltoallw_f08ts
4071end interface PMPI_Neighbor_alltoallw
4072
4073interface PMPI_Ineighbor_alltoallw
4074    subroutine PMPIR_Ineighbor_alltoallw_f08ts(sendbuf, sendcounts, sdispls, sendtypes, recvbuf, recvcounts, &
4075                 rdispls, recvtypes, comm, request, ierror)
4076        use :: mpi_f08_types, only : MPI_Datatype, MPI_Comm, MPI_Request
4077        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
4078        implicit none
4079        type(*), dimension(..), intent(in), asynchronous :: sendbuf
4080        type(*), dimension(..), asynchronous :: recvbuf
4081        integer, intent(in) :: sendcounts(*), recvcounts(*)
4082        integer(MPI_ADDRESS_KIND), intent(in) :: sdispls(*), rdispls(*)
4083        type(MPI_Datatype), intent(in) :: sendtypes(*), recvtypes(*)
4084        type(MPI_Comm), intent(in) :: comm
4085        type(MPI_Request), intent(in) :: request
4086        integer, optional, intent(out) :: ierror
4087    end subroutine PMPIR_Ineighbor_alltoallw_f08ts
4088end interface PMPI_Ineighbor_alltoallw
4089
4090interface PMPI_Wtick
4091    function PMPIR_Wtick_f08() result(res)
4092        implicit none
4093        double precision :: res
4094    end function PMPIR_Wtick_f08
4095end interface PMPI_Wtick
4096
4097interface PMPI_Wtime
4098    function PMPIR_Wtime_f08() result(res)
4099        implicit none
4100        double precision :: res
4101    end function PMPIR_Wtime_f08
4102end interface PMPI_Wtime
4103
4104interface PMPI_Aint_add
4105    function PMPIR_Aint_add_f08(base, disp) result(res)
4106        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
4107        implicit none
4108        integer(MPI_ADDRESS_KIND), intent(in) :: base, disp
4109        integer(MPI_ADDRESS_KIND) :: res
4110    end function PMPIR_Aint_add_f08
4111end interface PMPI_Aint_add
4112
4113interface PMPI_Aint_diff
4114    function PMPIR_Aint_diff_f08(addr1, addr2) result(res)
4115        use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
4116        implicit none
4117        integer(MPI_ADDRESS_KIND), intent(in) :: addr1, addr2
4118        integer(MPI_ADDRESS_KIND) :: res
4119    end function PMPIR_Aint_diff_f08
4120end interface PMPI_Aint_diff
4121
4122interface PMPI_File_iread_all
4123    subroutine PMPIR_File_iread_all_f08ts(fh, buf, count, datatype, request, ierror)
4124        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
4125        implicit none
4126        type(MPI_File), intent(in) :: fh
4127        type(*), dimension(..) :: buf
4128        integer, intent(in) :: count
4129        type(MPI_Datatype), intent(in) :: datatype
4130        type(MPI_Request), intent(out) :: request
4131        integer, optional, intent(out) :: ierror
4132    end subroutine PMPIR_File_iread_all_f08ts
4133end interface PMPI_File_iread_all
4134
4135interface PMPI_File_iwrite_all
4136    subroutine PMPIR_File_iwrite_all_f08ts(fh, buf, count, datatype, request, ierror)
4137        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
4138        implicit none
4139        type(MPI_File), intent(in) :: fh
4140        type(*), dimension(..), intent(in) :: buf
4141        integer, intent(in) :: count
4142        type(MPI_Datatype), intent(in) :: datatype
4143        type(MPI_Request), intent(out) :: request
4144        integer, optional, intent(out) :: ierror
4145    end subroutine PMPIR_File_iwrite_all_f08ts
4146end interface PMPI_File_iwrite_all
4147
4148interface PMPI_File_iread_at_all
4149    subroutine PMPIR_File_iread_at_all_f08ts(fh, offset, buf, count, datatype, request, ierror)
4150        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
4151        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
4152        implicit none
4153        type(MPI_File), intent(in) :: fh
4154        integer(MPI_OFFSET_KIND), intent(in) :: offset
4155        type(*), dimension(..) :: buf
4156        integer, intent(in) :: count
4157        type(MPI_Datatype), intent(in) :: datatype
4158        type(MPI_Request), intent(out) :: request
4159        integer, optional, intent(out) :: ierror
4160    end subroutine PMPIR_File_iread_at_all_f08ts
4161end interface PMPI_File_iread_at_all
4162
4163interface PMPI_File_iwrite_at_all
4164    subroutine PMPIR_File_iwrite_at_all_f08ts(fh, offset, buf, count, datatype, request, ierror)
4165        use :: mpi_f08_types, only : MPI_File, MPI_Datatype, MPI_Request
4166        use :: mpi_f08_compile_constants, only : MPI_OFFSET_KIND
4167        implicit none
4168        type(MPI_File), intent(in) :: fh
4169        integer(MPI_OFFSET_KIND), intent(in) :: offset
4170        type(*), dimension(..) :: buf
4171        integer, intent(in) :: count
4172        type(MPI_Datatype), intent(in) :: datatype
4173        type(MPI_Request), intent(out) :: request
4174        integer, optional, intent(out) :: ierror
4175    end subroutine PMPIR_File_iwrite_at_all_f08ts
4176end interface PMPI_File_iwrite_at_all
4177
4178end module pmpi_f08
4179