Back to home page

EIC code displayed by LXR

 
 

    


Warning, /include/fftw3-mpi.f03 is written in an unsupported language. File is not indexed.

0001 ! Generated automatically.  DO NOT EDIT!
0002 
0003   include 'fftw3.f03'
0004 
0005   integer(C_INTPTR_T), parameter :: FFTW_MPI_DEFAULT_BLOCK = 0
0006   integer(C_INT), parameter :: FFTW_MPI_SCRAMBLED_IN = 134217728
0007   integer(C_INT), parameter :: FFTW_MPI_SCRAMBLED_OUT = 268435456
0008   integer(C_INT), parameter :: FFTW_MPI_TRANSPOSED_IN = 536870912
0009   integer(C_INT), parameter :: FFTW_MPI_TRANSPOSED_OUT = 1073741824
0010 
0011   type, bind(C) :: fftw_mpi_ddim
0012      integer(C_INTPTR_T) n, ib, ob
0013   end type fftw_mpi_ddim
0014 
0015   interface
0016     subroutine fftw_mpi_init() bind(C, name='fftw_mpi_init')
0017       import
0018     end subroutine fftw_mpi_init
0019     
0020     subroutine fftw_mpi_cleanup() bind(C, name='fftw_mpi_cleanup')
0021       import
0022     end subroutine fftw_mpi_cleanup
0023     
0024     integer(C_INTPTR_T) function fftw_mpi_local_size_many_transposed(rnk,n,howmany,block0,block1,comm,local_n0,local_0_start, &
0025                                                                      local_n1,local_1_start) &
0026                                  bind(C, name='fftw_mpi_local_size_many_transposed_f03')
0027       import
0028       integer(C_INT), value :: rnk
0029       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0030       integer(C_INTPTR_T), value :: howmany
0031       integer(C_INTPTR_T), value :: block0
0032       integer(C_INTPTR_T), value :: block1
0033       integer(C_INT32_T), value :: comm
0034       integer(C_INTPTR_T), intent(out) :: local_n0
0035       integer(C_INTPTR_T), intent(out) :: local_0_start
0036       integer(C_INTPTR_T), intent(out) :: local_n1
0037       integer(C_INTPTR_T), intent(out) :: local_1_start
0038     end function fftw_mpi_local_size_many_transposed
0039     
0040     integer(C_INTPTR_T) function fftw_mpi_local_size_many(rnk,n,howmany,block0,comm,local_n0,local_0_start) &
0041                                  bind(C, name='fftw_mpi_local_size_many_f03')
0042       import
0043       integer(C_INT), value :: rnk
0044       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0045       integer(C_INTPTR_T), value :: howmany
0046       integer(C_INTPTR_T), value :: block0
0047       integer(C_INT32_T), value :: comm
0048       integer(C_INTPTR_T), intent(out) :: local_n0
0049       integer(C_INTPTR_T), intent(out) :: local_0_start
0050     end function fftw_mpi_local_size_many
0051     
0052     integer(C_INTPTR_T) function fftw_mpi_local_size_transposed(rnk,n,comm,local_n0,local_0_start,local_n1,local_1_start) &
0053                                  bind(C, name='fftw_mpi_local_size_transposed_f03')
0054       import
0055       integer(C_INT), value :: rnk
0056       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0057       integer(C_INT32_T), value :: comm
0058       integer(C_INTPTR_T), intent(out) :: local_n0
0059       integer(C_INTPTR_T), intent(out) :: local_0_start
0060       integer(C_INTPTR_T), intent(out) :: local_n1
0061       integer(C_INTPTR_T), intent(out) :: local_1_start
0062     end function fftw_mpi_local_size_transposed
0063     
0064     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')
0065       import
0066       integer(C_INT), value :: rnk
0067       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0068       integer(C_INT32_T), value :: comm
0069       integer(C_INTPTR_T), intent(out) :: local_n0
0070       integer(C_INTPTR_T), intent(out) :: local_0_start
0071     end function fftw_mpi_local_size
0072     
0073     integer(C_INTPTR_T) function fftw_mpi_local_size_many_1d(n0,howmany,comm,sign,flags,local_ni,local_i_start,local_no, &
0074                                                              local_o_start) bind(C, name='fftw_mpi_local_size_many_1d_f03')
0075       import
0076       integer(C_INTPTR_T), value :: n0
0077       integer(C_INTPTR_T), value :: howmany
0078       integer(C_INT32_T), value :: comm
0079       integer(C_INT), value :: sign
0080       integer(C_INT), value :: flags
0081       integer(C_INTPTR_T), intent(out) :: local_ni
0082       integer(C_INTPTR_T), intent(out) :: local_i_start
0083       integer(C_INTPTR_T), intent(out) :: local_no
0084       integer(C_INTPTR_T), intent(out) :: local_o_start
0085     end function fftw_mpi_local_size_many_1d
0086     
0087     integer(C_INTPTR_T) function fftw_mpi_local_size_1d(n0,comm,sign,flags,local_ni,local_i_start,local_no,local_o_start) &
0088                                  bind(C, name='fftw_mpi_local_size_1d_f03')
0089       import
0090       integer(C_INTPTR_T), value :: n0
0091       integer(C_INT32_T), value :: comm
0092       integer(C_INT), value :: sign
0093       integer(C_INT), value :: flags
0094       integer(C_INTPTR_T), intent(out) :: local_ni
0095       integer(C_INTPTR_T), intent(out) :: local_i_start
0096       integer(C_INTPTR_T), intent(out) :: local_no
0097       integer(C_INTPTR_T), intent(out) :: local_o_start
0098     end function fftw_mpi_local_size_1d
0099     
0100     integer(C_INTPTR_T) function fftw_mpi_local_size_2d(n0,n1,comm,local_n0,local_0_start) &
0101                                  bind(C, name='fftw_mpi_local_size_2d_f03')
0102       import
0103       integer(C_INTPTR_T), value :: n0
0104       integer(C_INTPTR_T), value :: n1
0105       integer(C_INT32_T), value :: comm
0106       integer(C_INTPTR_T), intent(out) :: local_n0
0107       integer(C_INTPTR_T), intent(out) :: local_0_start
0108     end function fftw_mpi_local_size_2d
0109     
0110     integer(C_INTPTR_T) function fftw_mpi_local_size_2d_transposed(n0,n1,comm,local_n0,local_0_start,local_n1,local_1_start) &
0111                                  bind(C, name='fftw_mpi_local_size_2d_transposed_f03')
0112       import
0113       integer(C_INTPTR_T), value :: n0
0114       integer(C_INTPTR_T), value :: n1
0115       integer(C_INT32_T), value :: comm
0116       integer(C_INTPTR_T), intent(out) :: local_n0
0117       integer(C_INTPTR_T), intent(out) :: local_0_start
0118       integer(C_INTPTR_T), intent(out) :: local_n1
0119       integer(C_INTPTR_T), intent(out) :: local_1_start
0120     end function fftw_mpi_local_size_2d_transposed
0121     
0122     integer(C_INTPTR_T) function fftw_mpi_local_size_3d(n0,n1,n2,comm,local_n0,local_0_start) &
0123                                  bind(C, name='fftw_mpi_local_size_3d_f03')
0124       import
0125       integer(C_INTPTR_T), value :: n0
0126       integer(C_INTPTR_T), value :: n1
0127       integer(C_INTPTR_T), value :: n2
0128       integer(C_INT32_T), value :: comm
0129       integer(C_INTPTR_T), intent(out) :: local_n0
0130       integer(C_INTPTR_T), intent(out) :: local_0_start
0131     end function fftw_mpi_local_size_3d
0132     
0133     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) &
0134                                  bind(C, name='fftw_mpi_local_size_3d_transposed_f03')
0135       import
0136       integer(C_INTPTR_T), value :: n0
0137       integer(C_INTPTR_T), value :: n1
0138       integer(C_INTPTR_T), value :: n2
0139       integer(C_INT32_T), value :: comm
0140       integer(C_INTPTR_T), intent(out) :: local_n0
0141       integer(C_INTPTR_T), intent(out) :: local_0_start
0142       integer(C_INTPTR_T), intent(out) :: local_n1
0143       integer(C_INTPTR_T), intent(out) :: local_1_start
0144     end function fftw_mpi_local_size_3d_transposed
0145     
0146     type(C_PTR) function fftw_mpi_plan_many_transpose(n0,n1,howmany,block0,block1,in,out,comm,flags) &
0147                          bind(C, name='fftw_mpi_plan_many_transpose_f03')
0148       import
0149       integer(C_INTPTR_T), value :: n0
0150       integer(C_INTPTR_T), value :: n1
0151       integer(C_INTPTR_T), value :: howmany
0152       integer(C_INTPTR_T), value :: block0
0153       integer(C_INTPTR_T), value :: block1
0154       real(C_DOUBLE), dimension(*), intent(out) :: in
0155       real(C_DOUBLE), dimension(*), intent(out) :: out
0156       integer(C_INT32_T), value :: comm
0157       integer(C_INT), value :: flags
0158     end function fftw_mpi_plan_many_transpose
0159     
0160     type(C_PTR) function fftw_mpi_plan_transpose(n0,n1,in,out,comm,flags) bind(C, name='fftw_mpi_plan_transpose_f03')
0161       import
0162       integer(C_INTPTR_T), value :: n0
0163       integer(C_INTPTR_T), value :: n1
0164       real(C_DOUBLE), dimension(*), intent(out) :: in
0165       real(C_DOUBLE), dimension(*), intent(out) :: out
0166       integer(C_INT32_T), value :: comm
0167       integer(C_INT), value :: flags
0168     end function fftw_mpi_plan_transpose
0169     
0170     type(C_PTR) function fftw_mpi_plan_many_dft(rnk,n,howmany,block,tblock,in,out,comm,sign,flags) &
0171                          bind(C, name='fftw_mpi_plan_many_dft_f03')
0172       import
0173       integer(C_INT), value :: rnk
0174       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0175       integer(C_INTPTR_T), value :: howmany
0176       integer(C_INTPTR_T), value :: block
0177       integer(C_INTPTR_T), value :: tblock
0178       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0179       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0180       integer(C_INT32_T), value :: comm
0181       integer(C_INT), value :: sign
0182       integer(C_INT), value :: flags
0183     end function fftw_mpi_plan_many_dft
0184     
0185     type(C_PTR) function fftw_mpi_plan_dft(rnk,n,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_f03')
0186       import
0187       integer(C_INT), value :: rnk
0188       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0189       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0190       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0191       integer(C_INT32_T), value :: comm
0192       integer(C_INT), value :: sign
0193       integer(C_INT), value :: flags
0194     end function fftw_mpi_plan_dft
0195     
0196     type(C_PTR) function fftw_mpi_plan_dft_1d(n0,in,out,comm,sign,flags) bind(C, name='fftw_mpi_plan_dft_1d_f03')
0197       import
0198       integer(C_INTPTR_T), value :: n0
0199       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0200       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0201       integer(C_INT32_T), value :: comm
0202       integer(C_INT), value :: sign
0203       integer(C_INT), value :: flags
0204     end function fftw_mpi_plan_dft_1d
0205     
0206     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')
0207       import
0208       integer(C_INTPTR_T), value :: n0
0209       integer(C_INTPTR_T), value :: n1
0210       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0211       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0212       integer(C_INT32_T), value :: comm
0213       integer(C_INT), value :: sign
0214       integer(C_INT), value :: flags
0215     end function fftw_mpi_plan_dft_2d
0216     
0217     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')
0218       import
0219       integer(C_INTPTR_T), value :: n0
0220       integer(C_INTPTR_T), value :: n1
0221       integer(C_INTPTR_T), value :: n2
0222       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0223       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0224       integer(C_INT32_T), value :: comm
0225       integer(C_INT), value :: sign
0226       integer(C_INT), value :: flags
0227     end function fftw_mpi_plan_dft_3d
0228     
0229     type(C_PTR) function fftw_mpi_plan_many_r2r(rnk,n,howmany,iblock,oblock,in,out,comm,kind,flags) &
0230                          bind(C, name='fftw_mpi_plan_many_r2r_f03')
0231       import
0232       integer(C_INT), value :: rnk
0233       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0234       integer(C_INTPTR_T), value :: howmany
0235       integer(C_INTPTR_T), value :: iblock
0236       integer(C_INTPTR_T), value :: oblock
0237       real(C_DOUBLE), dimension(*), intent(out) :: in
0238       real(C_DOUBLE), dimension(*), intent(out) :: out
0239       integer(C_INT32_T), value :: comm
0240       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0241       integer(C_INT), value :: flags
0242     end function fftw_mpi_plan_many_r2r
0243     
0244     type(C_PTR) function fftw_mpi_plan_r2r(rnk,n,in,out,comm,kind,flags) bind(C, name='fftw_mpi_plan_r2r_f03')
0245       import
0246       integer(C_INT), value :: rnk
0247       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0248       real(C_DOUBLE), dimension(*), intent(out) :: in
0249       real(C_DOUBLE), dimension(*), intent(out) :: out
0250       integer(C_INT32_T), value :: comm
0251       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0252       integer(C_INT), value :: flags
0253     end function fftw_mpi_plan_r2r
0254     
0255     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')
0256       import
0257       integer(C_INTPTR_T), value :: n0
0258       integer(C_INTPTR_T), value :: n1
0259       real(C_DOUBLE), dimension(*), intent(out) :: in
0260       real(C_DOUBLE), dimension(*), intent(out) :: out
0261       integer(C_INT32_T), value :: comm
0262       integer(C_FFTW_R2R_KIND), value :: kind0
0263       integer(C_FFTW_R2R_KIND), value :: kind1
0264       integer(C_INT), value :: flags
0265     end function fftw_mpi_plan_r2r_2d
0266     
0267     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')
0268       import
0269       integer(C_INTPTR_T), value :: n0
0270       integer(C_INTPTR_T), value :: n1
0271       integer(C_INTPTR_T), value :: n2
0272       real(C_DOUBLE), dimension(*), intent(out) :: in
0273       real(C_DOUBLE), dimension(*), intent(out) :: out
0274       integer(C_INT32_T), value :: comm
0275       integer(C_FFTW_R2R_KIND), value :: kind0
0276       integer(C_FFTW_R2R_KIND), value :: kind1
0277       integer(C_FFTW_R2R_KIND), value :: kind2
0278       integer(C_INT), value :: flags
0279     end function fftw_mpi_plan_r2r_3d
0280     
0281     type(C_PTR) function fftw_mpi_plan_many_dft_r2c(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0282                          bind(C, name='fftw_mpi_plan_many_dft_r2c_f03')
0283       import
0284       integer(C_INT), value :: rnk
0285       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0286       integer(C_INTPTR_T), value :: howmany
0287       integer(C_INTPTR_T), value :: iblock
0288       integer(C_INTPTR_T), value :: oblock
0289       real(C_DOUBLE), dimension(*), intent(out) :: in
0290       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0291       integer(C_INT32_T), value :: comm
0292       integer(C_INT), value :: flags
0293     end function fftw_mpi_plan_many_dft_r2c
0294     
0295     type(C_PTR) function fftw_mpi_plan_dft_r2c(rnk,n,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_r2c_f03')
0296       import
0297       integer(C_INT), value :: rnk
0298       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0299       real(C_DOUBLE), dimension(*), intent(out) :: in
0300       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0301       integer(C_INT32_T), value :: comm
0302       integer(C_INT), value :: flags
0303     end function fftw_mpi_plan_dft_r2c
0304     
0305     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')
0306       import
0307       integer(C_INTPTR_T), value :: n0
0308       integer(C_INTPTR_T), value :: n1
0309       real(C_DOUBLE), dimension(*), intent(out) :: in
0310       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0311       integer(C_INT32_T), value :: comm
0312       integer(C_INT), value :: flags
0313     end function fftw_mpi_plan_dft_r2c_2d
0314     
0315     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')
0316       import
0317       integer(C_INTPTR_T), value :: n0
0318       integer(C_INTPTR_T), value :: n1
0319       integer(C_INTPTR_T), value :: n2
0320       real(C_DOUBLE), dimension(*), intent(out) :: in
0321       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0322       integer(C_INT32_T), value :: comm
0323       integer(C_INT), value :: flags
0324     end function fftw_mpi_plan_dft_r2c_3d
0325     
0326     type(C_PTR) function fftw_mpi_plan_many_dft_c2r(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0327                          bind(C, name='fftw_mpi_plan_many_dft_c2r_f03')
0328       import
0329       integer(C_INT), value :: rnk
0330       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0331       integer(C_INTPTR_T), value :: howmany
0332       integer(C_INTPTR_T), value :: iblock
0333       integer(C_INTPTR_T), value :: oblock
0334       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0335       real(C_DOUBLE), dimension(*), intent(out) :: out
0336       integer(C_INT32_T), value :: comm
0337       integer(C_INT), value :: flags
0338     end function fftw_mpi_plan_many_dft_c2r
0339     
0340     type(C_PTR) function fftw_mpi_plan_dft_c2r(rnk,n,in,out,comm,flags) bind(C, name='fftw_mpi_plan_dft_c2r_f03')
0341       import
0342       integer(C_INT), value :: rnk
0343       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0344       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0345       real(C_DOUBLE), dimension(*), intent(out) :: out
0346       integer(C_INT32_T), value :: comm
0347       integer(C_INT), value :: flags
0348     end function fftw_mpi_plan_dft_c2r
0349     
0350     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')
0351       import
0352       integer(C_INTPTR_T), value :: n0
0353       integer(C_INTPTR_T), value :: n1
0354       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0355       real(C_DOUBLE), dimension(*), intent(out) :: out
0356       integer(C_INT32_T), value :: comm
0357       integer(C_INT), value :: flags
0358     end function fftw_mpi_plan_dft_c2r_2d
0359     
0360     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')
0361       import
0362       integer(C_INTPTR_T), value :: n0
0363       integer(C_INTPTR_T), value :: n1
0364       integer(C_INTPTR_T), value :: n2
0365       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0366       real(C_DOUBLE), dimension(*), intent(out) :: out
0367       integer(C_INT32_T), value :: comm
0368       integer(C_INT), value :: flags
0369     end function fftw_mpi_plan_dft_c2r_3d
0370     
0371     subroutine fftw_mpi_gather_wisdom(comm_) bind(C, name='fftw_mpi_gather_wisdom_f03')
0372       import
0373       integer(C_INT32_T), value :: comm_
0374     end subroutine fftw_mpi_gather_wisdom
0375     
0376     subroutine fftw_mpi_broadcast_wisdom(comm_) bind(C, name='fftw_mpi_broadcast_wisdom_f03')
0377       import
0378       integer(C_INT32_T), value :: comm_
0379     end subroutine fftw_mpi_broadcast_wisdom
0380     
0381     subroutine fftw_mpi_execute_dft(p,in,out) bind(C, name='fftw_mpi_execute_dft')
0382       import
0383       type(C_PTR), value :: p
0384       complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0385       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0386     end subroutine fftw_mpi_execute_dft
0387     
0388     subroutine fftw_mpi_execute_dft_r2c(p,in,out) bind(C, name='fftw_mpi_execute_dft_r2c')
0389       import
0390       type(C_PTR), value :: p
0391       real(C_DOUBLE), dimension(*), intent(inout) :: in
0392       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0393     end subroutine fftw_mpi_execute_dft_r2c
0394     
0395     subroutine fftw_mpi_execute_dft_c2r(p,in,out) bind(C, name='fftw_mpi_execute_dft_c2r')
0396       import
0397       type(C_PTR), value :: p
0398       complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0399       real(C_DOUBLE), dimension(*), intent(out) :: out
0400     end subroutine fftw_mpi_execute_dft_c2r
0401     
0402     subroutine fftw_mpi_execute_r2r(p,in,out) bind(C, name='fftw_mpi_execute_r2r')
0403       import
0404       type(C_PTR), value :: p
0405       real(C_DOUBLE), dimension(*), intent(inout) :: in
0406       real(C_DOUBLE), dimension(*), intent(out) :: out
0407     end subroutine fftw_mpi_execute_r2r
0408     
0409   end interface
0410 
0411   type, bind(C) :: fftwf_mpi_ddim
0412      integer(C_INTPTR_T) n, ib, ob
0413   end type fftwf_mpi_ddim
0414 
0415   interface
0416     subroutine fftwf_mpi_init() bind(C, name='fftwf_mpi_init')
0417       import
0418     end subroutine fftwf_mpi_init
0419     
0420     subroutine fftwf_mpi_cleanup() bind(C, name='fftwf_mpi_cleanup')
0421       import
0422     end subroutine fftwf_mpi_cleanup
0423     
0424     integer(C_INTPTR_T) function fftwf_mpi_local_size_many_transposed(rnk,n,howmany,block0,block1,comm,local_n0,local_0_start, &
0425                                                                       local_n1,local_1_start) &
0426                                  bind(C, name='fftwf_mpi_local_size_many_transposed_f03')
0427       import
0428       integer(C_INT), value :: rnk
0429       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0430       integer(C_INTPTR_T), value :: howmany
0431       integer(C_INTPTR_T), value :: block0
0432       integer(C_INTPTR_T), value :: block1
0433       integer(C_INT32_T), value :: comm
0434       integer(C_INTPTR_T), intent(out) :: local_n0
0435       integer(C_INTPTR_T), intent(out) :: local_0_start
0436       integer(C_INTPTR_T), intent(out) :: local_n1
0437       integer(C_INTPTR_T), intent(out) :: local_1_start
0438     end function fftwf_mpi_local_size_many_transposed
0439     
0440     integer(C_INTPTR_T) function fftwf_mpi_local_size_many(rnk,n,howmany,block0,comm,local_n0,local_0_start) &
0441                                  bind(C, name='fftwf_mpi_local_size_many_f03')
0442       import
0443       integer(C_INT), value :: rnk
0444       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0445       integer(C_INTPTR_T), value :: howmany
0446       integer(C_INTPTR_T), value :: block0
0447       integer(C_INT32_T), value :: comm
0448       integer(C_INTPTR_T), intent(out) :: local_n0
0449       integer(C_INTPTR_T), intent(out) :: local_0_start
0450     end function fftwf_mpi_local_size_many
0451     
0452     integer(C_INTPTR_T) function fftwf_mpi_local_size_transposed(rnk,n,comm,local_n0,local_0_start,local_n1,local_1_start) &
0453                                  bind(C, name='fftwf_mpi_local_size_transposed_f03')
0454       import
0455       integer(C_INT), value :: rnk
0456       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0457       integer(C_INT32_T), value :: comm
0458       integer(C_INTPTR_T), intent(out) :: local_n0
0459       integer(C_INTPTR_T), intent(out) :: local_0_start
0460       integer(C_INTPTR_T), intent(out) :: local_n1
0461       integer(C_INTPTR_T), intent(out) :: local_1_start
0462     end function fftwf_mpi_local_size_transposed
0463     
0464     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')
0465       import
0466       integer(C_INT), value :: rnk
0467       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0468       integer(C_INT32_T), value :: comm
0469       integer(C_INTPTR_T), intent(out) :: local_n0
0470       integer(C_INTPTR_T), intent(out) :: local_0_start
0471     end function fftwf_mpi_local_size
0472     
0473     integer(C_INTPTR_T) function fftwf_mpi_local_size_many_1d(n0,howmany,comm,sign,flags,local_ni,local_i_start,local_no, &
0474                                                               local_o_start) bind(C, name='fftwf_mpi_local_size_many_1d_f03')
0475       import
0476       integer(C_INTPTR_T), value :: n0
0477       integer(C_INTPTR_T), value :: howmany
0478       integer(C_INT32_T), value :: comm
0479       integer(C_INT), value :: sign
0480       integer(C_INT), value :: flags
0481       integer(C_INTPTR_T), intent(out) :: local_ni
0482       integer(C_INTPTR_T), intent(out) :: local_i_start
0483       integer(C_INTPTR_T), intent(out) :: local_no
0484       integer(C_INTPTR_T), intent(out) :: local_o_start
0485     end function fftwf_mpi_local_size_many_1d
0486     
0487     integer(C_INTPTR_T) function fftwf_mpi_local_size_1d(n0,comm,sign,flags,local_ni,local_i_start,local_no,local_o_start) &
0488                                  bind(C, name='fftwf_mpi_local_size_1d_f03')
0489       import
0490       integer(C_INTPTR_T), value :: n0
0491       integer(C_INT32_T), value :: comm
0492       integer(C_INT), value :: sign
0493       integer(C_INT), value :: flags
0494       integer(C_INTPTR_T), intent(out) :: local_ni
0495       integer(C_INTPTR_T), intent(out) :: local_i_start
0496       integer(C_INTPTR_T), intent(out) :: local_no
0497       integer(C_INTPTR_T), intent(out) :: local_o_start
0498     end function fftwf_mpi_local_size_1d
0499     
0500     integer(C_INTPTR_T) function fftwf_mpi_local_size_2d(n0,n1,comm,local_n0,local_0_start) &
0501                                  bind(C, name='fftwf_mpi_local_size_2d_f03')
0502       import
0503       integer(C_INTPTR_T), value :: n0
0504       integer(C_INTPTR_T), value :: n1
0505       integer(C_INT32_T), value :: comm
0506       integer(C_INTPTR_T), intent(out) :: local_n0
0507       integer(C_INTPTR_T), intent(out) :: local_0_start
0508     end function fftwf_mpi_local_size_2d
0509     
0510     integer(C_INTPTR_T) function fftwf_mpi_local_size_2d_transposed(n0,n1,comm,local_n0,local_0_start,local_n1,local_1_start) &
0511                                  bind(C, name='fftwf_mpi_local_size_2d_transposed_f03')
0512       import
0513       integer(C_INTPTR_T), value :: n0
0514       integer(C_INTPTR_T), value :: n1
0515       integer(C_INT32_T), value :: comm
0516       integer(C_INTPTR_T), intent(out) :: local_n0
0517       integer(C_INTPTR_T), intent(out) :: local_0_start
0518       integer(C_INTPTR_T), intent(out) :: local_n1
0519       integer(C_INTPTR_T), intent(out) :: local_1_start
0520     end function fftwf_mpi_local_size_2d_transposed
0521     
0522     integer(C_INTPTR_T) function fftwf_mpi_local_size_3d(n0,n1,n2,comm,local_n0,local_0_start) &
0523                                  bind(C, name='fftwf_mpi_local_size_3d_f03')
0524       import
0525       integer(C_INTPTR_T), value :: n0
0526       integer(C_INTPTR_T), value :: n1
0527       integer(C_INTPTR_T), value :: n2
0528       integer(C_INT32_T), value :: comm
0529       integer(C_INTPTR_T), intent(out) :: local_n0
0530       integer(C_INTPTR_T), intent(out) :: local_0_start
0531     end function fftwf_mpi_local_size_3d
0532     
0533     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) &
0534                                  bind(C, name='fftwf_mpi_local_size_3d_transposed_f03')
0535       import
0536       integer(C_INTPTR_T), value :: n0
0537       integer(C_INTPTR_T), value :: n1
0538       integer(C_INTPTR_T), value :: n2
0539       integer(C_INT32_T), value :: comm
0540       integer(C_INTPTR_T), intent(out) :: local_n0
0541       integer(C_INTPTR_T), intent(out) :: local_0_start
0542       integer(C_INTPTR_T), intent(out) :: local_n1
0543       integer(C_INTPTR_T), intent(out) :: local_1_start
0544     end function fftwf_mpi_local_size_3d_transposed
0545     
0546     type(C_PTR) function fftwf_mpi_plan_many_transpose(n0,n1,howmany,block0,block1,in,out,comm,flags) &
0547                          bind(C, name='fftwf_mpi_plan_many_transpose_f03')
0548       import
0549       integer(C_INTPTR_T), value :: n0
0550       integer(C_INTPTR_T), value :: n1
0551       integer(C_INTPTR_T), value :: howmany
0552       integer(C_INTPTR_T), value :: block0
0553       integer(C_INTPTR_T), value :: block1
0554       real(C_FLOAT), dimension(*), intent(out) :: in
0555       real(C_FLOAT), dimension(*), intent(out) :: out
0556       integer(C_INT32_T), value :: comm
0557       integer(C_INT), value :: flags
0558     end function fftwf_mpi_plan_many_transpose
0559     
0560     type(C_PTR) function fftwf_mpi_plan_transpose(n0,n1,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_transpose_f03')
0561       import
0562       integer(C_INTPTR_T), value :: n0
0563       integer(C_INTPTR_T), value :: n1
0564       real(C_FLOAT), dimension(*), intent(out) :: in
0565       real(C_FLOAT), dimension(*), intent(out) :: out
0566       integer(C_INT32_T), value :: comm
0567       integer(C_INT), value :: flags
0568     end function fftwf_mpi_plan_transpose
0569     
0570     type(C_PTR) function fftwf_mpi_plan_many_dft(rnk,n,howmany,block,tblock,in,out,comm,sign,flags) &
0571                          bind(C, name='fftwf_mpi_plan_many_dft_f03')
0572       import
0573       integer(C_INT), value :: rnk
0574       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0575       integer(C_INTPTR_T), value :: howmany
0576       integer(C_INTPTR_T), value :: block
0577       integer(C_INTPTR_T), value :: tblock
0578       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0579       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0580       integer(C_INT32_T), value :: comm
0581       integer(C_INT), value :: sign
0582       integer(C_INT), value :: flags
0583     end function fftwf_mpi_plan_many_dft
0584     
0585     type(C_PTR) function fftwf_mpi_plan_dft(rnk,n,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_f03')
0586       import
0587       integer(C_INT), value :: rnk
0588       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0589       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0590       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0591       integer(C_INT32_T), value :: comm
0592       integer(C_INT), value :: sign
0593       integer(C_INT), value :: flags
0594     end function fftwf_mpi_plan_dft
0595     
0596     type(C_PTR) function fftwf_mpi_plan_dft_1d(n0,in,out,comm,sign,flags) bind(C, name='fftwf_mpi_plan_dft_1d_f03')
0597       import
0598       integer(C_INTPTR_T), value :: n0
0599       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0600       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0601       integer(C_INT32_T), value :: comm
0602       integer(C_INT), value :: sign
0603       integer(C_INT), value :: flags
0604     end function fftwf_mpi_plan_dft_1d
0605     
0606     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')
0607       import
0608       integer(C_INTPTR_T), value :: n0
0609       integer(C_INTPTR_T), value :: n1
0610       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0611       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0612       integer(C_INT32_T), value :: comm
0613       integer(C_INT), value :: sign
0614       integer(C_INT), value :: flags
0615     end function fftwf_mpi_plan_dft_2d
0616     
0617     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')
0618       import
0619       integer(C_INTPTR_T), value :: n0
0620       integer(C_INTPTR_T), value :: n1
0621       integer(C_INTPTR_T), value :: n2
0622       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0623       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0624       integer(C_INT32_T), value :: comm
0625       integer(C_INT), value :: sign
0626       integer(C_INT), value :: flags
0627     end function fftwf_mpi_plan_dft_3d
0628     
0629     type(C_PTR) function fftwf_mpi_plan_many_r2r(rnk,n,howmany,iblock,oblock,in,out,comm,kind,flags) &
0630                          bind(C, name='fftwf_mpi_plan_many_r2r_f03')
0631       import
0632       integer(C_INT), value :: rnk
0633       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0634       integer(C_INTPTR_T), value :: howmany
0635       integer(C_INTPTR_T), value :: iblock
0636       integer(C_INTPTR_T), value :: oblock
0637       real(C_FLOAT), dimension(*), intent(out) :: in
0638       real(C_FLOAT), dimension(*), intent(out) :: out
0639       integer(C_INT32_T), value :: comm
0640       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0641       integer(C_INT), value :: flags
0642     end function fftwf_mpi_plan_many_r2r
0643     
0644     type(C_PTR) function fftwf_mpi_plan_r2r(rnk,n,in,out,comm,kind,flags) bind(C, name='fftwf_mpi_plan_r2r_f03')
0645       import
0646       integer(C_INT), value :: rnk
0647       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0648       real(C_FLOAT), dimension(*), intent(out) :: in
0649       real(C_FLOAT), dimension(*), intent(out) :: out
0650       integer(C_INT32_T), value :: comm
0651       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0652       integer(C_INT), value :: flags
0653     end function fftwf_mpi_plan_r2r
0654     
0655     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')
0656       import
0657       integer(C_INTPTR_T), value :: n0
0658       integer(C_INTPTR_T), value :: n1
0659       real(C_FLOAT), dimension(*), intent(out) :: in
0660       real(C_FLOAT), dimension(*), intent(out) :: out
0661       integer(C_INT32_T), value :: comm
0662       integer(C_FFTW_R2R_KIND), value :: kind0
0663       integer(C_FFTW_R2R_KIND), value :: kind1
0664       integer(C_INT), value :: flags
0665     end function fftwf_mpi_plan_r2r_2d
0666     
0667     type(C_PTR) function fftwf_mpi_plan_r2r_3d(n0,n1,n2,in,out,comm,kind0,kind1,kind2,flags) &
0668                          bind(C, name='fftwf_mpi_plan_r2r_3d_f03')
0669       import
0670       integer(C_INTPTR_T), value :: n0
0671       integer(C_INTPTR_T), value :: n1
0672       integer(C_INTPTR_T), value :: n2
0673       real(C_FLOAT), dimension(*), intent(out) :: in
0674       real(C_FLOAT), dimension(*), intent(out) :: out
0675       integer(C_INT32_T), value :: comm
0676       integer(C_FFTW_R2R_KIND), value :: kind0
0677       integer(C_FFTW_R2R_KIND), value :: kind1
0678       integer(C_FFTW_R2R_KIND), value :: kind2
0679       integer(C_INT), value :: flags
0680     end function fftwf_mpi_plan_r2r_3d
0681     
0682     type(C_PTR) function fftwf_mpi_plan_many_dft_r2c(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0683                          bind(C, name='fftwf_mpi_plan_many_dft_r2c_f03')
0684       import
0685       integer(C_INT), value :: rnk
0686       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0687       integer(C_INTPTR_T), value :: howmany
0688       integer(C_INTPTR_T), value :: iblock
0689       integer(C_INTPTR_T), value :: oblock
0690       real(C_FLOAT), dimension(*), intent(out) :: in
0691       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0692       integer(C_INT32_T), value :: comm
0693       integer(C_INT), value :: flags
0694     end function fftwf_mpi_plan_many_dft_r2c
0695     
0696     type(C_PTR) function fftwf_mpi_plan_dft_r2c(rnk,n,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_r2c_f03')
0697       import
0698       integer(C_INT), value :: rnk
0699       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0700       real(C_FLOAT), dimension(*), intent(out) :: in
0701       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0702       integer(C_INT32_T), value :: comm
0703       integer(C_INT), value :: flags
0704     end function fftwf_mpi_plan_dft_r2c
0705     
0706     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')
0707       import
0708       integer(C_INTPTR_T), value :: n0
0709       integer(C_INTPTR_T), value :: n1
0710       real(C_FLOAT), dimension(*), intent(out) :: in
0711       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0712       integer(C_INT32_T), value :: comm
0713       integer(C_INT), value :: flags
0714     end function fftwf_mpi_plan_dft_r2c_2d
0715     
0716     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')
0717       import
0718       integer(C_INTPTR_T), value :: n0
0719       integer(C_INTPTR_T), value :: n1
0720       integer(C_INTPTR_T), value :: n2
0721       real(C_FLOAT), dimension(*), intent(out) :: in
0722       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0723       integer(C_INT32_T), value :: comm
0724       integer(C_INT), value :: flags
0725     end function fftwf_mpi_plan_dft_r2c_3d
0726     
0727     type(C_PTR) function fftwf_mpi_plan_many_dft_c2r(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0728                          bind(C, name='fftwf_mpi_plan_many_dft_c2r_f03')
0729       import
0730       integer(C_INT), value :: rnk
0731       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0732       integer(C_INTPTR_T), value :: howmany
0733       integer(C_INTPTR_T), value :: iblock
0734       integer(C_INTPTR_T), value :: oblock
0735       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0736       real(C_FLOAT), dimension(*), intent(out) :: out
0737       integer(C_INT32_T), value :: comm
0738       integer(C_INT), value :: flags
0739     end function fftwf_mpi_plan_many_dft_c2r
0740     
0741     type(C_PTR) function fftwf_mpi_plan_dft_c2r(rnk,n,in,out,comm,flags) bind(C, name='fftwf_mpi_plan_dft_c2r_f03')
0742       import
0743       integer(C_INT), value :: rnk
0744       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0745       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0746       real(C_FLOAT), dimension(*), intent(out) :: out
0747       integer(C_INT32_T), value :: comm
0748       integer(C_INT), value :: flags
0749     end function fftwf_mpi_plan_dft_c2r
0750     
0751     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')
0752       import
0753       integer(C_INTPTR_T), value :: n0
0754       integer(C_INTPTR_T), value :: n1
0755       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0756       real(C_FLOAT), dimension(*), intent(out) :: out
0757       integer(C_INT32_T), value :: comm
0758       integer(C_INT), value :: flags
0759     end function fftwf_mpi_plan_dft_c2r_2d
0760     
0761     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')
0762       import
0763       integer(C_INTPTR_T), value :: n0
0764       integer(C_INTPTR_T), value :: n1
0765       integer(C_INTPTR_T), value :: n2
0766       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0767       real(C_FLOAT), dimension(*), intent(out) :: out
0768       integer(C_INT32_T), value :: comm
0769       integer(C_INT), value :: flags
0770     end function fftwf_mpi_plan_dft_c2r_3d
0771     
0772     subroutine fftwf_mpi_gather_wisdom(comm_) bind(C, name='fftwf_mpi_gather_wisdom_f03')
0773       import
0774       integer(C_INT32_T), value :: comm_
0775     end subroutine fftwf_mpi_gather_wisdom
0776     
0777     subroutine fftwf_mpi_broadcast_wisdom(comm_) bind(C, name='fftwf_mpi_broadcast_wisdom_f03')
0778       import
0779       integer(C_INT32_T), value :: comm_
0780     end subroutine fftwf_mpi_broadcast_wisdom
0781     
0782     subroutine fftwf_mpi_execute_dft(p,in,out) bind(C, name='fftwf_mpi_execute_dft')
0783       import
0784       type(C_PTR), value :: p
0785       complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
0786       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0787     end subroutine fftwf_mpi_execute_dft
0788     
0789     subroutine fftwf_mpi_execute_dft_r2c(p,in,out) bind(C, name='fftwf_mpi_execute_dft_r2c')
0790       import
0791       type(C_PTR), value :: p
0792       real(C_FLOAT), dimension(*), intent(inout) :: in
0793       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0794     end subroutine fftwf_mpi_execute_dft_r2c
0795     
0796     subroutine fftwf_mpi_execute_dft_c2r(p,in,out) bind(C, name='fftwf_mpi_execute_dft_c2r')
0797       import
0798       type(C_PTR), value :: p
0799       complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
0800       real(C_FLOAT), dimension(*), intent(out) :: out
0801     end subroutine fftwf_mpi_execute_dft_c2r
0802     
0803     subroutine fftwf_mpi_execute_r2r(p,in,out) bind(C, name='fftwf_mpi_execute_r2r')
0804       import
0805       type(C_PTR), value :: p
0806       real(C_FLOAT), dimension(*), intent(inout) :: in
0807       real(C_FLOAT), dimension(*), intent(out) :: out
0808     end subroutine fftwf_mpi_execute_r2r
0809     
0810   end interface