1! Generated automatically.  DO NOT EDIT!
2
3  include 'fftw3.f03'
4
5  integer(C_INTPTR_T), parameter :: FFTW_MPI_DEFAULT_BLOCK = 0
6  integer(C_INT), parameter :: FFTW_MPI_SCRAMBLED_IN = 134217728
7  integer(C_INT), parameter :: FFTW_MPI_SCRAMBLED_OUT = 268435456
8  integer(C_INT), parameter :: FFTW_MPI_TRANSPOSED_IN = 536870912
9  integer(C_INT), parameter :: FFTW_MPI_TRANSPOSED_OUT = 1073741824
10
11  type, bind(C) :: fftw_mpi_ddim
12     integer(C_INTPTR_T) n, ib, ob
13  end type fftw_mpi_ddim
14
15  interface
16    subroutine fftw_mpi_init() bind(C, name='fftw_mpi_init')
17      import
18    end subroutine fftw_mpi_init
19
20    subroutine fftw_mpi_cleanup() bind(C, name='fftw_mpi_cleanup')
21      import
22    end subroutine fftw_mpi_cleanup
23
24    integer(C_INTPTR_T) function fftw_mpi_local_size_many_transposed(rnk,n,howmany,block0,block1,comm,local_n0,local_0_start, &
25                                                                     local_n1,local_1_start) &
26                                 bind(C, name='fftw_mpi_local_size_many_transposed_f03')
27      import
28      integer(C_INT), value :: rnk
29      integer(C_INTPTR_T), dimension(*), intent(in) :: n
30      integer(C_INTPTR_T), value :: howmany
31      integer(C_INTPTR_T), value :: block0
32      integer(C_INTPTR_T), value :: block1
33      integer(C_MPI_FINT), value :: comm
34      integer(C_INTPTR_T), intent(out) :: local_n0
35      integer(C_INTPTR_T), intent(out) :: local_0_start
36      integer(C_INTPTR_T), intent(out) :: local_n1
37      integer(C_INTPTR_T), intent(out) :: local_1_start
38    end function fftw_mpi_local_size_many_transposed
39
40    integer(C_INTPTR_T) function fftw_mpi_local_size_many(rnk,n,howmany,block0,comm,local_n0,local_0_start) &
41                                 bind(C, name='fftw_mpi_local_size_many_f03')
42      import
43      integer(C_INT), value :: rnk
44      integer(C_INTPTR_T), dimension(*), intent(in) :: n
45      integer(C_INTPTR_T), value :: howmany
46      integer(C_INTPTR_T), value :: block0
47      integer(C_MPI_FINT), value :: comm
48      integer(C_INTPTR_T), intent(out) :: local_n0
49      integer(C_INTPTR_T), intent(out) :: local_0_start
50    end function fftw_mpi_local_size_many
51
52    integer(C_INTPTR_T) function fftw_mpi_local_size_transposed(rnk,n,comm,local_n0,local_0_start,local_n1,local_1_start) &
53                                 bind(C, name='fftw_mpi_local_size_transposed_f03')
54      import
55      integer(C_INT), value :: rnk
56      integer(C_INTPTR_T), dimension(*), intent(in) :: n
57      integer(C_MPI_FINT), value :: comm
58      integer(C_INTPTR_T), intent(out) :: local_n0
59      integer(C_INTPTR_T), intent(out) :: local_0_start
60      integer(C_INTPTR_T), intent(out) :: local_n1
61      integer(C_INTPTR_T), intent(out) :: local_1_start
62    end function fftw_mpi_local_size_transposed
63
64    integer(C_INTPTR_T) function fftw_mpi_local_size(rnk,n,comm,local_n0,local_0_start) bind(C, name='fftw_mpi_local_size_f03')
65      import
66      integer(C_INT), value :: rnk
67      integer(C_INTPTR_T), dimension(*), intent(in) :: n
68      integer(C_MPI_FINT), value :: comm
69      integer(C_INTPTR_T), intent(out) :: local_n0
70      integer(C_INTPTR_T), intent(out) :: local_0_start
71    end function fftw_mpi_local_size
72
73    integer(C_INTPTR_T) function fftw_mpi_local_size_many_1d(n0,howmany,comm,sign,flags,local_ni,local_i_start,local_no, &
74                                                             local_o_start) bind(C, name='fftw_mpi_local_size_many_1d_f03')
75      import
76      integer(C_INTPTR_T), value :: n0
77      integer(C_INTPTR_T), value :: howmany
78      integer(C_MPI_FINT), value :: comm
79      integer(C_INT), value :: sign
80      integer(C_INT), value :: flags
81      integer(C_INTPTR_T), intent(out) :: local_ni
82      integer(C_INTPTR_T), intent(out) :: local_i_start
83      integer(C_INTPTR_T), intent(out) :: local_no
84      integer(C_INTPTR_T), intent(out) :: local_o_start
85    end function fftw_mpi_local_size_many_1d
86
87    integer(C_INTPTR_T) function fftw_mpi_local_size_1d(n0,comm,sign,flags,local_ni,local_i_start,local_no,local_o_start) &
88                                 bind(C, name='fftw_mpi_local_size_1d_f03')
89      import
90      integer(C_INTPTR_T), value :: n0
91      integer(C_MPI_FINT), value :: comm
92      integer(C_INT), value :: sign
93      integer(C_INT), value :: flags
94      integer(C_INTPTR_T), intent(out) :: local_ni
95      integer(C_INTPTR_T), intent(out) :: local_i_start
96      integer(C_INTPTR_T), intent(out) :: local_no
97      integer(C_INTPTR_T), intent(out) :: local_o_start
98    end function fftw_mpi_local_size_1d
99
100    integer(C_INTPTR_T) function fftw_mpi_local_size_2d(n0,n1,comm,local_n0,local_0_start) &
101                                 bind(C, name='fftw_mpi_local_size_2d_f03')
102      import
103      integer(C_INTPTR_T), value :: n0
104      integer(C_INTPTR_T), value :: n1
105      integer(C_MPI_FINT), value :: comm
106      integer(C_INTPTR_T), intent(out) :: local_n0
107      integer(C_INTPTR_T), intent(out) :: local_0_start
108    end function fftw_mpi_local_size_2d
109
110    integer(C_INTPTR_T) function fftw_mpi_local_size_2d_transposed(n0,n1,comm,local_n0,local_0_start,local_n1,local_1_start) &
111                                 bind(C, name='fftw_mpi_local_size_2d_transposed_f03')
112      import
113      integer(C_INTPTR_T), value :: n0
114      integer(C_INTPTR_T), value :: n1
115      integer(C_MPI_FINT), value :: comm
116      integer(C_INTPTR_T), intent(out) :: local_n0
117      integer(C_INTPTR_T), intent(out) :: local_0_start
118      integer(C_INTPTR_T), intent(out) :: local_n1
119      integer(C_INTPTR_T), intent(out) :: local_1_start
120    end function fftw_mpi_local_size_2d_transposed
121
122    integer(C_INTPTR_T) function fftw_mpi_local_size_3d(n0,n1,n2,comm,local_n0,local_0_start) &
123                                 bind(C, name='fftw_mpi_local_size_3d_f03')
124      import
125      integer(C_INTPTR_T), value :: n0
126      integer(C_INTPTR_T), value :: n1
127      integer(C_INTPTR_T), value :: n2
128      integer(C_MPI_FINT), value :: comm
129      integer(C_INTPTR_T), intent(out) :: local_n0
130      integer(C_INTPTR_T), intent(out) :: local_0_start
131    end function fftw_mpi_local_size_3d
132
133    integer(C_INTPTR_T) function fftw_mpi_local_size_3d_transposed(n0,n1,n2,comm,local_n0,local_0_start,local_n1,local_1_start) &
134                                 bind(C, name='fftw_mpi_local_size_3d_transposed_f03')
135      import
136      integer(C_INTPTR_T), value :: n0
137      integer(C_INTPTR_T), value :: n1
138      integer(C_INTPTR_T), value :: n2
139      integer(C_MPI_FINT), value :: comm
140      integer(C_INTPTR_T), intent(out) :: local_n0
141      integer(C_INTPTR_T), intent(out) :: local_0_start
142      integer(C_INTPTR_T), intent(out) :: local_n1
143      integer(C_INTPTR_T), intent(out) :: local_1_start
144    end function fftw_mpi_local_size_3d_transposed
145
146    type(C_PTR) function fftw_mpi_plan_many_transpose(n0,n1,howmany,block0,block1,in,out,comm,flags) &
147                         bind(C, name='fftw_mpi_plan_many_transpose_f03')
148      import
149      integer(C_INTPTR_T), value :: n0
150      integer(C_INTPTR_T), value :: n1
151      integer(C_INTPTR_T), value :: howmany
152      integer(C_INTPTR_T), value :: block0
153      integer(C_INTPTR_T), value :: block1
154      real(C_DOUBLE), dimension(*), intent(out) :: in
155      real(C_DOUBLE), dimension(*), intent(out) :: out
156      integer(C_MPI_FINT), value :: comm
157      integer(C_INT), value :: flags
158    end function fftw_mpi_plan_many_transpose
159
160    type(C_PTR) function fftw_mpi_plan_transpose(n0,n1,in,out,comm,flags) bind(C, name='fftw_mpi_plan_transpose_f03')
161      import
162      integer(C_INTPTR_T), value :: n0
163      integer(C_INTPTR_T), value :: n1
164      real(C_DOUBLE), dimension(*), intent(out) :: in
165      real(C_DOUBLE), dimension(*), intent(out) :: out
166      integer(C_MPI_FINT), value :: comm
167      integer(C_INT), value :: flags
168    end function fftw_mpi_plan_transpose
169
170    type(C_PTR) function fftw_mpi_plan_many_dft(rnk,n,howmany,block,tblock,in,out,comm,sign,flags) &
171                         bind(C, name='fftw_mpi_plan_many_dft_f03')
172      import
173      integer(C_INT), value :: rnk
174      integer(C_INTPTR_T), dimension(*), intent(in) :: n
175      integer(C_INTPTR_T), value :: howmany
176      integer(C_INTPTR_T), value :: block
177      integer(C_INTPTR_T), value :: tblock
178      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
179      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
180      integer(C_MPI_FINT), value :: comm
181      integer(C_INT), value :: sign
182      integer(C_INT), value :: flags
183    end function fftw_mpi_plan_many_dft
184
185    type(C_PTR) function fftw_mpi_plan_dft(rnk,n,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_f03')
186      import
187      integer(C_INT), value :: rnk
188      integer(C_INTPTR_T), dimension(*), intent(in) :: n
189      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
190      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
191      integer(C_MPI_FINT), value :: comm
192      integer(C_INT), value :: sign
193      integer(C_INT), value :: flags
194    end function fftw_mpi_plan_dft
195
196    type(C_PTR) function fftw_mpi_plan_dft_1d(n0,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_1d_f03')
197      import
198      integer(C_INTPTR_T), value :: n0
199      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
200      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
201      integer(C_MPI_FINT), value :: comm
202      integer(C_INT), value :: sign
203      integer(C_INT), value :: flags
204    end function fftw_mpi_plan_dft_1d
205
206    type(C_PTR) function fftw_mpi_plan_dft_2d(n0,n1,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_2d_f03')
207      import
208      integer(C_INTPTR_T), value :: n0
209      integer(C_INTPTR_T), value :: n1
210      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
211      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
212      integer(C_MPI_FINT), value :: comm
213      integer(C_INT), value :: sign
214      integer(C_INT), value :: flags
215    end function fftw_mpi_plan_dft_2d
216
217    type(C_PTR) function fftw_mpi_plan_dft_3d(n0,n1,n2,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_3d_f03')
218      import
219      integer(C_INTPTR_T), value :: n0
220      integer(C_INTPTR_T), value :: n1
221      integer(C_INTPTR_T), value :: n2
222      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
223      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
224      integer(C_MPI_FINT), value :: comm
225      integer(C_INT), value :: sign
226      integer(C_INT), value :: flags
227    end function fftw_mpi_plan_dft_3d
228
229    type(C_PTR) function fftw_mpi_plan_many_r2r(rnk,n,howmany,iblock,oblock,in,out,comm,kind,flags) &
230                         bind(C, name='fftw_mpi_plan_many_r2r_f03')
231      import
232      integer(C_INT), value :: rnk
233      integer(C_INTPTR_T), dimension(*), intent(in) :: n
234      integer(C_INTPTR_T), value :: howmany
235      integer(C_INTPTR_T), value :: iblock
236      integer(C_INTPTR_T), value :: oblock
237      real(C_DOUBLE), dimension(*), intent(out) :: in
238      real(C_DOUBLE), dimension(*), intent(out) :: out
239      integer(C_MPI_FINT), value :: comm
240      integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
241      integer(C_INT), value :: flags
242    end function fftw_mpi_plan_many_r2r
243
244    type(C_PTR) function fftw_mpi_plan_r2r(rnk,n,in,out,comm,kind,flags) bind(C, name='fftw_mpi_plan_r2r_f03')
245      import
246      integer(C_INT), value :: rnk
247      integer(C_INTPTR_T), dimension(*), intent(in) :: n
248      real(C_DOUBLE), dimension(*), intent(out) :: in
249      real(C_DOUBLE), dimension(*), intent(out) :: out
250      integer(C_MPI_FINT), value :: comm
251      integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
252      integer(C_INT), value :: flags
253    end function fftw_mpi_plan_r2r
254
255    type(C_PTR) function fftw_mpi_plan_r2r_2d(n0,n1,in,out,comm,kind0,kind1,flags) bind(C, name='fftw_mpi_plan_r2r_2d_f03')
256      import
257      integer(C_INTPTR_T), value :: n0
258      integer(C_INTPTR_T), value :: n1
259      real(C_DOUBLE), dimension(*), intent(out) :: in
260      real(C_DOUBLE), dimension(*), intent(out) :: out
261      integer(C_MPI_FINT), value :: comm
262      integer(C_FFTW_R2R_KIND), value :: kind0
263      integer(C_FFTW_R2R_KIND), value :: kind1
264      integer(C_INT), value :: flags
265    end function fftw_mpi_plan_r2r_2d
266
267    type(C_PTR) function fftw_mpi_plan_r2r_3d(n0,n1,n2,in,out,comm,kind0,kind1,kind2,flags) bind(C, name='fftw_mpi_plan_r2r_3d_f03')
268      import
269      integer(C_INTPTR_T), value :: n0
270      integer(C_INTPTR_T), value :: n1
271      integer(C_INTPTR_T), value :: n2
272      real(C_DOUBLE), dimension(*), intent(out) :: in
273      real(C_DOUBLE), dimension(*), intent(out) :: out
274      integer(C_MPI_FINT), value :: comm
275      integer(C_FFTW_R2R_KIND), value :: kind0
276      integer(C_FFTW_R2R_KIND), value :: kind1
277      integer(C_FFTW_R2R_KIND), value :: kind2
278      integer(C_INT), value :: flags
279    end function fftw_mpi_plan_r2r_3d
280
281    type(C_PTR) function fftw_mpi_plan_many_dft_r2c(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
282                         bind(C, name='fftw_mpi_plan_many_dft_r2c_f03')
283      import
284      integer(C_INT), value :: rnk
285      integer(C_INTPTR_T), dimension(*), intent(in) :: n
286      integer(C_INTPTR_T), value :: howmany
287      integer(C_INTPTR_T), value :: iblock
288      integer(C_INTPTR_T), value :: oblock
289      real(C_DOUBLE), dimension(*), intent(out) :: in
290      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
291      integer(C_MPI_FINT), value :: comm
292      integer(C_INT), value :: flags
293    end function fftw_mpi_plan_many_dft_r2c
294
295    type(C_PTR) function fftw_mpi_plan_dft_r2c(rnk,n,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_r2c_f03')
296      import
297      integer(C_INT), value :: rnk
298      integer(C_INTPTR_T), dimension(*), intent(in) :: n
299      real(C_DOUBLE), dimension(*), intent(out) :: in
300      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
301      integer(C_MPI_FINT), value :: comm
302      integer(C_INT), value :: flags
303    end function fftw_mpi_plan_dft_r2c
304
305    type(C_PTR) function fftw_mpi_plan_dft_r2c_2d(n0,n1,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_r2c_2d_f03')
306      import
307      integer(C_INTPTR_T), value :: n0
308      integer(C_INTPTR_T), value :: n1
309      real(C_DOUBLE), dimension(*), intent(out) :: in
310      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
311      integer(C_MPI_FINT), value :: comm
312      integer(C_INT), value :: flags
313    end function fftw_mpi_plan_dft_r2c_2d
314
315    type(C_PTR) function fftw_mpi_plan_dft_r2c_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_r2c_3d_f03')
316      import
317      integer(C_INTPTR_T), value :: n0
318      integer(C_INTPTR_T), value :: n1
319      integer(C_INTPTR_T), value :: n2
320      real(C_DOUBLE), dimension(*), intent(out) :: in
321      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
322      integer(C_MPI_FINT), value :: comm
323      integer(C_INT), value :: flags
324    end function fftw_mpi_plan_dft_r2c_3d
325
326    type(C_PTR) function fftw_mpi_plan_many_dft_c2r(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
327                         bind(C, name='fftw_mpi_plan_many_dft_c2r_f03')
328      import
329      integer(C_INT), value :: rnk
330      integer(C_INTPTR_T), dimension(*), intent(in) :: n
331      integer(C_INTPTR_T), value :: howmany
332      integer(C_INTPTR_T), value :: iblock
333      integer(C_INTPTR_T), value :: oblock
334      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
335      real(C_DOUBLE), dimension(*), intent(out) :: out
336      integer(C_MPI_FINT), value :: comm
337      integer(C_INT), value :: flags
338    end function fftw_mpi_plan_many_dft_c2r
339
340    type(C_PTR) function fftw_mpi_plan_dft_c2r(rnk,n,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_c2r_f03')
341      import
342      integer(C_INT), value :: rnk
343      integer(C_INTPTR_T), dimension(*), intent(in) :: n
344      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
345      real(C_DOUBLE), dimension(*), intent(out) :: out
346      integer(C_MPI_FINT), value :: comm
347      integer(C_INT), value :: flags
348    end function fftw_mpi_plan_dft_c2r
349
350    type(C_PTR) function fftw_mpi_plan_dft_c2r_2d(n0,n1,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_c2r_2d_f03')
351      import
352      integer(C_INTPTR_T), value :: n0
353      integer(C_INTPTR_T), value :: n1
354      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
355      real(C_DOUBLE), dimension(*), intent(out) :: out
356      integer(C_MPI_FINT), value :: comm
357      integer(C_INT), value :: flags
358    end function fftw_mpi_plan_dft_c2r_2d
359
360    type(C_PTR) function fftw_mpi_plan_dft_c2r_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_c2r_3d_f03')
361      import
362      integer(C_INTPTR_T), value :: n0
363      integer(C_INTPTR_T), value :: n1
364      integer(C_INTPTR_T), value :: n2
365      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
366      real(C_DOUBLE), dimension(*), intent(out) :: out
367      integer(C_MPI_FINT), value :: comm
368      integer(C_INT), value :: flags
369    end function fftw_mpi_plan_dft_c2r_3d
370
371    subroutine fftw_mpi_gather_wisdom(comm_) bind(C, name='fftw_mpi_gather_wisdom_f03')
372      import
373      integer(C_MPI_FINT), value :: comm_
374    end subroutine fftw_mpi_gather_wisdom
375
376    subroutine fftw_mpi_broadcast_wisdom(comm_) bind(C, name='fftw_mpi_broadcast_wisdom_f03')
377      import
378      integer(C_MPI_FINT), value :: comm_
379    end subroutine fftw_mpi_broadcast_wisdom
380
381    subroutine fftw_mpi_execute_dft(p,in,out) bind(C, name='fftw_mpi_execute_dft')
382      import
383      type(C_PTR), value :: p
384      complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
385      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
386    end subroutine fftw_mpi_execute_dft
387
388    subroutine fftw_mpi_execute_dft_r2c(p,in,out) bind(C, name='fftw_mpi_execute_dft_r2c')
389      import
390      type(C_PTR), value :: p
391      real(C_DOUBLE), dimension(*), intent(inout) :: in
392      complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
393    end subroutine fftw_mpi_execute_dft_r2c
394
395    subroutine fftw_mpi_execute_dft_c2r(p,in,out) bind(C, name='fftw_mpi_execute_dft_c2r')
396      import
397      type(C_PTR), value :: p
398      complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
399      real(C_DOUBLE), dimension(*), intent(out) :: out
400    end subroutine fftw_mpi_execute_dft_c2r
401
402    subroutine fftw_mpi_execute_r2r(p,in,out) bind(C, name='fftw_mpi_execute_r2r')
403      import
404      type(C_PTR), value :: p
405      real(C_DOUBLE), dimension(*), intent(inout) :: in
406      real(C_DOUBLE), dimension(*), intent(out) :: out
407    end subroutine fftw_mpi_execute_r2r
408
409  end interface
410
411  type, bind(C) :: fftwf_mpi_ddim
412     integer(C_INTPTR_T) n, ib, ob
413  end type fftwf_mpi_ddim
414
415  interface
416    subroutine fftwf_mpi_init() bind(C, name='fftwf_mpi_init')
417      import
418    end subroutine fftwf_mpi_init
419
420    subroutine fftwf_mpi_cleanup() bind(C, name='fftwf_mpi_cleanup')
421      import
422    end subroutine fftwf_mpi_cleanup
423
424    integer(C_INTPTR_T) function fftwf_mpi_local_size_many_transposed(rnk,n,howmany,block0,block1,comm,local_n0,local_0_start, &
425                                                                      local_n1,local_1_start) &
426                                 bind(C, name='fftwf_mpi_local_size_many_transposed_f03')
427      import
428      integer(C_INT), value :: rnk
429      integer(C_INTPTR_T), dimension(*), intent(in) :: n
430      integer(C_INTPTR_T), value :: howmany
431      integer(C_INTPTR_T), value :: block0
432      integer(C_INTPTR_T), value :: block1
433      integer(C_MPI_FINT), value :: comm
434      integer(C_INTPTR_T), intent(out) :: local_n0
435      integer(C_INTPTR_T), intent(out) :: local_0_start
436      integer(C_INTPTR_T), intent(out) :: local_n1
437      integer(C_INTPTR_T), intent(out) :: local_1_start
438    end function fftwf_mpi_local_size_many_transposed
439
440    integer(C_INTPTR_T) function fftwf_mpi_local_size_many(rnk,n,howmany,block0,comm,local_n0,local_0_start) &
441                                 bind(C, name='fftwf_mpi_local_size_many_f03')
442      import
443      integer(C_INT), value :: rnk
444      integer(C_INTPTR_T), dimension(*), intent(in) :: n
445      integer(C_INTPTR_T), value :: howmany
446      integer(C_INTPTR_T), value :: block0
447      integer(C_MPI_FINT), value :: comm
448      integer(C_INTPTR_T), intent(out) :: local_n0
449      integer(C_INTPTR_T), intent(out) :: local_0_start
450    end function fftwf_mpi_local_size_many
451
452    integer(C_INTPTR_T) function fftwf_mpi_local_size_transposed(rnk,n,comm,local_n0,local_0_start,local_n1,local_1_start) &
453                                 bind(C, name='fftwf_mpi_local_size_transposed_f03')
454      import
455      integer(C_INT), value :: rnk
456      integer(C_INTPTR_T), dimension(*), intent(in) :: n
457      integer(C_MPI_FINT), value :: comm
458      integer(C_INTPTR_T), intent(out) :: local_n0
459      integer(C_INTPTR_T), intent(out) :: local_0_start
460      integer(C_INTPTR_T), intent(out) :: local_n1
461      integer(C_INTPTR_T), intent(out) :: local_1_start
462    end function fftwf_mpi_local_size_transposed
463
464    integer(C_INTPTR_T) function fftwf_mpi_local_size(rnk,n,comm,local_n0,local_0_start) bind(C, name='fftwf_mpi_local_size_f03')
465      import
466      integer(C_INT), value :: rnk
467      integer(C_INTPTR_T), dimension(*), intent(in) :: n
468      integer(C_MPI_FINT), value :: comm
469      integer(C_INTPTR_T), intent(out) :: local_n0
470      integer(C_INTPTR_T), intent(out) :: local_0_start
471    end function fftwf_mpi_local_size
472
473    integer(C_INTPTR_T) function fftwf_mpi_local_size_many_1d(n0,howmany,comm,sign,flags,local_ni,local_i_start,local_no, &
474                                                              local_o_start) bind(C, name='fftwf_mpi_local_size_many_1d_f03')
475      import
476      integer(C_INTPTR_T), value :: n0
477      integer(C_INTPTR_T), value :: howmany
478      integer(C_MPI_FINT), value :: comm
479      integer(C_INT), value :: sign
480      integer(C_INT), value :: flags
481      integer(C_INTPTR_T), intent(out) :: local_ni
482      integer(C_INTPTR_T), intent(out) :: local_i_start
483      integer(C_INTPTR_T), intent(out) :: local_no
484      integer(C_INTPTR_T), intent(out) :: local_o_start
485    end function fftwf_mpi_local_size_many_1d
486
487    integer(C_INTPTR_T) function fftwf_mpi_local_size_1d(n0,comm,sign,flags,local_ni,local_i_start,local_no,local_o_start) &
488                                 bind(C, name='fftwf_mpi_local_size_1d_f03')
489      import
490      integer(C_INTPTR_T), value :: n0
491      integer(C_MPI_FINT), value :: comm
492      integer(C_INT), value :: sign
493      integer(C_INT), value :: flags
494      integer(C_INTPTR_T), intent(out) :: local_ni
495      integer(C_INTPTR_T), intent(out) :: local_i_start
496      integer(C_INTPTR_T), intent(out) :: local_no
497      integer(C_INTPTR_T), intent(out) :: local_o_start
498    end function fftwf_mpi_local_size_1d
499
500    integer(C_INTPTR_T) function fftwf_mpi_local_size_2d(n0,n1,comm,local_n0,local_0_start) &
501                                 bind(C, name='fftwf_mpi_local_size_2d_f03')
502      import
503      integer(C_INTPTR_T), value :: n0
504      integer(C_INTPTR_T), value :: n1
505      integer(C_MPI_FINT), value :: comm
506      integer(C_INTPTR_T), intent(out) :: local_n0
507      integer(C_INTPTR_T), intent(out) :: local_0_start
508    end function fftwf_mpi_local_size_2d
509
510    integer(C_INTPTR_T) function fftwf_mpi_local_size_2d_transposed(n0,n1,comm,local_n0,local_0_start,local_n1,local_1_start) &
511                                 bind(C, name='fftwf_mpi_local_size_2d_transposed_f03')
512      import
513      integer(C_INTPTR_T), value :: n0
514      integer(C_INTPTR_T), value :: n1
515      integer(C_MPI_FINT), value :: comm
516      integer(C_INTPTR_T), intent(out) :: local_n0
517      integer(C_INTPTR_T), intent(out) :: local_0_start
518      integer(C_INTPTR_T), intent(out) :: local_n1
519      integer(C_INTPTR_T), intent(out) :: local_1_start
520    end function fftwf_mpi_local_size_2d_transposed
521
522    integer(C_INTPTR_T) function fftwf_mpi_local_size_3d(n0,n1,n2,comm,local_n0,local_0_start) &
523                                 bind(C, name='fftwf_mpi_local_size_3d_f03')
524      import
525      integer(C_INTPTR_T), value :: n0
526      integer(C_INTPTR_T), value :: n1
527      integer(C_INTPTR_T), value :: n2
528      integer(C_MPI_FINT), value :: comm
529      integer(C_INTPTR_T), intent(out) :: local_n0
530      integer(C_INTPTR_T), intent(out) :: local_0_start
531    end function fftwf_mpi_local_size_3d
532
533    integer(C_INTPTR_T) function fftwf_mpi_local_size_3d_transposed(n0,n1,n2,comm,local_n0,local_0_start,local_n1,local_1_start) &
534                                 bind(C, name='fftwf_mpi_local_size_3d_transposed_f03')
535      import
536      integer(C_INTPTR_T), value :: n0
537      integer(C_INTPTR_T), value :: n1
538      integer(C_INTPTR_T), value :: n2
539      integer(C_MPI_FINT), value :: comm
540      integer(C_INTPTR_T), intent(out) :: local_n0
541      integer(C_INTPTR_T), intent(out) :: local_0_start
542      integer(C_INTPTR_T), intent(out) :: local_n1
543      integer(C_INTPTR_T), intent(out) :: local_1_start
544    end function fftwf_mpi_local_size_3d_transposed
545
546    type(C_PTR) function fftwf_mpi_plan_many_transpose(n0,n1,howmany,block0,block1,in,out,comm,flags) &
547                         bind(C, name='fftwf_mpi_plan_many_transpose_f03')
548      import
549      integer(C_INTPTR_T), value :: n0
550      integer(C_INTPTR_T), value :: n1
551      integer(C_INTPTR_T), value :: howmany
552      integer(C_INTPTR_T), value :: block0
553      integer(C_INTPTR_T), value :: block1
554      real(C_FLOAT), dimension(*), intent(out) :: in
555      real(C_FLOAT), dimension(*), intent(out) :: out
556      integer(C_MPI_FINT), value :: comm
557      integer(C_INT), value :: flags
558    end function fftwf_mpi_plan_many_transpose
559
560    type(C_PTR) function fftwf_mpi_plan_transpose(n0,n1,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_transpose_f03')
561      import
562      integer(C_INTPTR_T), value :: n0
563      integer(C_INTPTR_T), value :: n1
564      real(C_FLOAT), dimension(*), intent(out) :: in
565      real(C_FLOAT), dimension(*), intent(out) :: out
566      integer(C_MPI_FINT), value :: comm
567      integer(C_INT), value :: flags
568    end function fftwf_mpi_plan_transpose
569
570    type(C_PTR) function fftwf_mpi_plan_many_dft(rnk,n,howmany,block,tblock,in,out,comm,sign,flags) &
571                         bind(C, name='fftwf_mpi_plan_many_dft_f03')
572      import
573      integer(C_INT), value :: rnk
574      integer(C_INTPTR_T), dimension(*), intent(in) :: n
575      integer(C_INTPTR_T), value :: howmany
576      integer(C_INTPTR_T), value :: block
577      integer(C_INTPTR_T), value :: tblock
578      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
579      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
580      integer(C_MPI_FINT), value :: comm
581      integer(C_INT), value :: sign
582      integer(C_INT), value :: flags
583    end function fftwf_mpi_plan_many_dft
584
585    type(C_PTR) function fftwf_mpi_plan_dft(rnk,n,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_f03')
586      import
587      integer(C_INT), value :: rnk
588      integer(C_INTPTR_T), dimension(*), intent(in) :: n
589      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
590      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
591      integer(C_MPI_FINT), value :: comm
592      integer(C_INT), value :: sign
593      integer(C_INT), value :: flags
594    end function fftwf_mpi_plan_dft
595
596    type(C_PTR) function fftwf_mpi_plan_dft_1d(n0,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_1d_f03')
597      import
598      integer(C_INTPTR_T), value :: n0
599      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
600      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
601      integer(C_MPI_FINT), value :: comm
602      integer(C_INT), value :: sign
603      integer(C_INT), value :: flags
604    end function fftwf_mpi_plan_dft_1d
605
606    type(C_PTR) function fftwf_mpi_plan_dft_2d(n0,n1,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_2d_f03')
607      import
608      integer(C_INTPTR_T), value :: n0
609      integer(C_INTPTR_T), value :: n1
610      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
611      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
612      integer(C_MPI_FINT), value :: comm
613      integer(C_INT), value :: sign
614      integer(C_INT), value :: flags
615    end function fftwf_mpi_plan_dft_2d
616
617    type(C_PTR) function fftwf_mpi_plan_dft_3d(n0,n1,n2,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_3d_f03')
618      import
619      integer(C_INTPTR_T), value :: n0
620      integer(C_INTPTR_T), value :: n1
621      integer(C_INTPTR_T), value :: n2
622      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
623      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
624      integer(C_MPI_FINT), value :: comm
625      integer(C_INT), value :: sign
626      integer(C_INT), value :: flags
627    end function fftwf_mpi_plan_dft_3d
628
629    type(C_PTR) function fftwf_mpi_plan_many_r2r(rnk,n,howmany,iblock,oblock,in,out,comm,kind,flags) &
630                         bind(C, name='fftwf_mpi_plan_many_r2r_f03')
631      import
632      integer(C_INT), value :: rnk
633      integer(C_INTPTR_T), dimension(*), intent(in) :: n
634      integer(C_INTPTR_T), value :: howmany
635      integer(C_INTPTR_T), value :: iblock
636      integer(C_INTPTR_T), value :: oblock
637      real(C_FLOAT), dimension(*), intent(out) :: in
638      real(C_FLOAT), dimension(*), intent(out) :: out
639      integer(C_MPI_FINT), value :: comm
640      integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
641      integer(C_INT), value :: flags
642    end function fftwf_mpi_plan_many_r2r
643
644    type(C_PTR) function fftwf_mpi_plan_r2r(rnk,n,in,out,comm,kind,flags) bind(C, name='fftwf_mpi_plan_r2r_f03')
645      import
646      integer(C_INT), value :: rnk
647      integer(C_INTPTR_T), dimension(*), intent(in) :: n
648      real(C_FLOAT), dimension(*), intent(out) :: in
649      real(C_FLOAT), dimension(*), intent(out) :: out
650      integer(C_MPI_FINT), value :: comm
651      integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
652      integer(C_INT), value :: flags
653    end function fftwf_mpi_plan_r2r
654
655    type(C_PTR) function fftwf_mpi_plan_r2r_2d(n0,n1,in,out,comm,kind0,kind1,flags) bind(C, name='fftwf_mpi_plan_r2r_2d_f03')
656      import
657      integer(C_INTPTR_T), value :: n0
658      integer(C_INTPTR_T), value :: n1
659      real(C_FLOAT), dimension(*), intent(out) :: in
660      real(C_FLOAT), dimension(*), intent(out) :: out
661      integer(C_MPI_FINT), value :: comm
662      integer(C_FFTW_R2R_KIND), value :: kind0
663      integer(C_FFTW_R2R_KIND), value :: kind1
664      integer(C_INT), value :: flags
665    end function fftwf_mpi_plan_r2r_2d
666
667    type(C_PTR) function fftwf_mpi_plan_r2r_3d(n0,n1,n2,in,out,comm,kind0,kind1,kind2,flags) &
668                         bind(C, name='fftwf_mpi_plan_r2r_3d_f03')
669      import
670      integer(C_INTPTR_T), value :: n0
671      integer(C_INTPTR_T), value :: n1
672      integer(C_INTPTR_T), value :: n2
673      real(C_FLOAT), dimension(*), intent(out) :: in
674      real(C_FLOAT), dimension(*), intent(out) :: out
675      integer(C_MPI_FINT), value :: comm
676      integer(C_FFTW_R2R_KIND), value :: kind0
677      integer(C_FFTW_R2R_KIND), value :: kind1
678      integer(C_FFTW_R2R_KIND), value :: kind2
679      integer(C_INT), value :: flags
680    end function fftwf_mpi_plan_r2r_3d
681
682    type(C_PTR) function fftwf_mpi_plan_many_dft_r2c(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
683                         bind(C, name='fftwf_mpi_plan_many_dft_r2c_f03')
684      import
685      integer(C_INT), value :: rnk
686      integer(C_INTPTR_T), dimension(*), intent(in) :: n
687      integer(C_INTPTR_T), value :: howmany
688      integer(C_INTPTR_T), value :: iblock
689      integer(C_INTPTR_T), value :: oblock
690      real(C_FLOAT), dimension(*), intent(out) :: in
691      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
692      integer(C_MPI_FINT), value :: comm
693      integer(C_INT), value :: flags
694    end function fftwf_mpi_plan_many_dft_r2c
695
696    type(C_PTR) function fftwf_mpi_plan_dft_r2c(rnk,n,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_r2c_f03')
697      import
698      integer(C_INT), value :: rnk
699      integer(C_INTPTR_T), dimension(*), intent(in) :: n
700      real(C_FLOAT), dimension(*), intent(out) :: in
701      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
702      integer(C_MPI_FINT), value :: comm
703      integer(C_INT), value :: flags
704    end function fftwf_mpi_plan_dft_r2c
705
706    type(C_PTR) function fftwf_mpi_plan_dft_r2c_2d(n0,n1,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_r2c_2d_f03')
707      import
708      integer(C_INTPTR_T), value :: n0
709      integer(C_INTPTR_T), value :: n1
710      real(C_FLOAT), dimension(*), intent(out) :: in
711      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
712      integer(C_MPI_FINT), value :: comm
713      integer(C_INT), value :: flags
714    end function fftwf_mpi_plan_dft_r2c_2d
715
716    type(C_PTR) function fftwf_mpi_plan_dft_r2c_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_r2c_3d_f03')
717      import
718      integer(C_INTPTR_T), value :: n0
719      integer(C_INTPTR_T), value :: n1
720      integer(C_INTPTR_T), value :: n2
721      real(C_FLOAT), dimension(*), intent(out) :: in
722      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
723      integer(C_MPI_FINT), value :: comm
724      integer(C_INT), value :: flags
725    end function fftwf_mpi_plan_dft_r2c_3d
726
727    type(C_PTR) function fftwf_mpi_plan_many_dft_c2r(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
728                         bind(C, name='fftwf_mpi_plan_many_dft_c2r_f03')
729      import
730      integer(C_INT), value :: rnk
731      integer(C_INTPTR_T), dimension(*), intent(in) :: n
732      integer(C_INTPTR_T), value :: howmany
733      integer(C_INTPTR_T), value :: iblock
734      integer(C_INTPTR_T), value :: oblock
735      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
736      real(C_FLOAT), dimension(*), intent(out) :: out
737      integer(C_MPI_FINT), value :: comm
738      integer(C_INT), value :: flags
739    end function fftwf_mpi_plan_many_dft_c2r
740
741    type(C_PTR) function fftwf_mpi_plan_dft_c2r(rnk,n,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_c2r_f03')
742      import
743      integer(C_INT), value :: rnk
744      integer(C_INTPTR_T), dimension(*), intent(in) :: n
745      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
746      real(C_FLOAT), dimension(*), intent(out) :: out
747      integer(C_MPI_FINT), value :: comm
748      integer(C_INT), value :: flags
749    end function fftwf_mpi_plan_dft_c2r
750
751    type(C_PTR) function fftwf_mpi_plan_dft_c2r_2d(n0,n1,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_c2r_2d_f03')
752      import
753      integer(C_INTPTR_T), value :: n0
754      integer(C_INTPTR_T), value :: n1
755      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
756      real(C_FLOAT), dimension(*), intent(out) :: out
757      integer(C_MPI_FINT), value :: comm
758      integer(C_INT), value :: flags
759    end function fftwf_mpi_plan_dft_c2r_2d
760
761    type(C_PTR) function fftwf_mpi_plan_dft_c2r_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_c2r_3d_f03')
762      import
763      integer(C_INTPTR_T), value :: n0
764      integer(C_INTPTR_T), value :: n1
765      integer(C_INTPTR_T), value :: n2
766      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
767      real(C_FLOAT), dimension(*), intent(out) :: out
768      integer(C_MPI_FINT), value :: comm
769      integer(C_INT), value :: flags
770    end function fftwf_mpi_plan_dft_c2r_3d
771
772    subroutine fftwf_mpi_gather_wisdom(comm_) bind(C, name='fftwf_mpi_gather_wisdom_f03')
773      import
774      integer(C_MPI_FINT), value :: comm_
775    end subroutine fftwf_mpi_gather_wisdom
776
777    subroutine fftwf_mpi_broadcast_wisdom(comm_) bind(C, name='fftwf_mpi_broadcast_wisdom_f03')
778      import
779      integer(C_MPI_FINT), value :: comm_
780    end subroutine fftwf_mpi_broadcast_wisdom
781
782    subroutine fftwf_mpi_execute_dft(p,in,out) bind(C, name='fftwf_mpi_execute_dft')
783      import
784      type(C_PTR), value :: p
785      complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
786      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
787    end subroutine fftwf_mpi_execute_dft
788
789    subroutine fftwf_mpi_execute_dft_r2c(p,in,out) bind(C, name='fftwf_mpi_execute_dft_r2c')
790      import
791      type(C_PTR), value :: p
792      real(C_FLOAT), dimension(*), intent(inout) :: in
793      complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
794    end subroutine fftwf_mpi_execute_dft_r2c
795
796    subroutine fftwf_mpi_execute_dft_c2r(p,in,out) bind(C, name='fftwf_mpi_execute_dft_c2r')
797      import
798      type(C_PTR), value :: p
799      complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
800      real(C_FLOAT), dimension(*), intent(out) :: out
801    end subroutine fftwf_mpi_execute_dft_c2r
802
803    subroutine fftwf_mpi_execute_r2r(p,in,out) bind(C, name='fftwf_mpi_execute_r2r')
804      import
805      type(C_PTR), value :: p
806      real(C_FLOAT), dimension(*), intent(inout) :: in
807      real(C_FLOAT), dimension(*), intent(out) :: out
808    end subroutine fftwf_mpi_execute_r2r
809
810  end interface
811