Back to home page

EIC code displayed by LXR

 
 

    


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

0001 ! Generated automatically.  DO NOT EDIT!
0002 
0003   integer, parameter :: C_FFTW_R2R_KIND = C_INT32_T
0004 
0005   integer(C_INT), parameter :: FFTW_R2HC = 0
0006   integer(C_INT), parameter :: FFTW_HC2R = 1
0007   integer(C_INT), parameter :: FFTW_DHT = 2
0008   integer(C_INT), parameter :: FFTW_REDFT00 = 3
0009   integer(C_INT), parameter :: FFTW_REDFT01 = 4
0010   integer(C_INT), parameter :: FFTW_REDFT10 = 5
0011   integer(C_INT), parameter :: FFTW_REDFT11 = 6
0012   integer(C_INT), parameter :: FFTW_RODFT00 = 7
0013   integer(C_INT), parameter :: FFTW_RODFT01 = 8
0014   integer(C_INT), parameter :: FFTW_RODFT10 = 9
0015   integer(C_INT), parameter :: FFTW_RODFT11 = 10
0016   integer(C_INT), parameter :: FFTW_FORWARD = -1
0017   integer(C_INT), parameter :: FFTW_BACKWARD = +1
0018   integer(C_INT), parameter :: FFTW_MEASURE = 0
0019   integer(C_INT), parameter :: FFTW_DESTROY_INPUT = 1
0020   integer(C_INT), parameter :: FFTW_UNALIGNED = 2
0021   integer(C_INT), parameter :: FFTW_CONSERVE_MEMORY = 4
0022   integer(C_INT), parameter :: FFTW_EXHAUSTIVE = 8
0023   integer(C_INT), parameter :: FFTW_PRESERVE_INPUT = 16
0024   integer(C_INT), parameter :: FFTW_PATIENT = 32
0025   integer(C_INT), parameter :: FFTW_ESTIMATE = 64
0026   integer(C_INT), parameter :: FFTW_WISDOM_ONLY = 2097152
0027   integer(C_INT), parameter :: FFTW_ESTIMATE_PATIENT = 128
0028   integer(C_INT), parameter :: FFTW_BELIEVE_PCOST = 256
0029   integer(C_INT), parameter :: FFTW_NO_DFT_R2HC = 512
0030   integer(C_INT), parameter :: FFTW_NO_NONTHREADED = 1024
0031   integer(C_INT), parameter :: FFTW_NO_BUFFERING = 2048
0032   integer(C_INT), parameter :: FFTW_NO_INDIRECT_OP = 4096
0033   integer(C_INT), parameter :: FFTW_ALLOW_LARGE_GENERIC = 8192
0034   integer(C_INT), parameter :: FFTW_NO_RANK_SPLITS = 16384
0035   integer(C_INT), parameter :: FFTW_NO_VRANK_SPLITS = 32768
0036   integer(C_INT), parameter :: FFTW_NO_VRECURSE = 65536
0037   integer(C_INT), parameter :: FFTW_NO_SIMD = 131072
0038   integer(C_INT), parameter :: FFTW_NO_SLOW = 262144
0039   integer(C_INT), parameter :: FFTW_NO_FIXED_RADIX_LARGE_N = 524288
0040   integer(C_INT), parameter :: FFTW_ALLOW_PRUNING = 1048576
0041 
0042   type, bind(C) :: fftw_iodim
0043      integer(C_INT) n, is, os
0044   end type fftw_iodim
0045   type, bind(C) :: fftw_iodim64
0046      integer(C_INTPTR_T) n, is, os
0047   end type fftw_iodim64
0048 
0049   interface
0050     type(C_PTR) function fftw_plan_dft(rank,n,in,out,sign,flags) bind(C, name='fftw_plan_dft')
0051       import
0052       integer(C_INT), value :: rank
0053       integer(C_INT), dimension(*), intent(in) :: n
0054       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0055       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0056       integer(C_INT), value :: sign
0057       integer(C_INT), value :: flags
0058     end function fftw_plan_dft
0059     
0060     type(C_PTR) function fftw_plan_dft_1d(n,in,out,sign,flags) bind(C, name='fftw_plan_dft_1d')
0061       import
0062       integer(C_INT), value :: n
0063       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0064       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0065       integer(C_INT), value :: sign
0066       integer(C_INT), value :: flags
0067     end function fftw_plan_dft_1d
0068     
0069     type(C_PTR) function fftw_plan_dft_2d(n0,n1,in,out,sign,flags) bind(C, name='fftw_plan_dft_2d')
0070       import
0071       integer(C_INT), value :: n0
0072       integer(C_INT), value :: n1
0073       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0074       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0075       integer(C_INT), value :: sign
0076       integer(C_INT), value :: flags
0077     end function fftw_plan_dft_2d
0078     
0079     type(C_PTR) function fftw_plan_dft_3d(n0,n1,n2,in,out,sign,flags) bind(C, name='fftw_plan_dft_3d')
0080       import
0081       integer(C_INT), value :: n0
0082       integer(C_INT), value :: n1
0083       integer(C_INT), value :: n2
0084       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0085       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0086       integer(C_INT), value :: sign
0087       integer(C_INT), value :: flags
0088     end function fftw_plan_dft_3d
0089     
0090     type(C_PTR) function fftw_plan_many_dft(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,sign,flags) &
0091                          bind(C, name='fftw_plan_many_dft')
0092       import
0093       integer(C_INT), value :: rank
0094       integer(C_INT), dimension(*), intent(in) :: n
0095       integer(C_INT), value :: howmany
0096       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0097       integer(C_INT), dimension(*), intent(in) :: inembed
0098       integer(C_INT), value :: istride
0099       integer(C_INT), value :: idist
0100       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0101       integer(C_INT), dimension(*), intent(in) :: onembed
0102       integer(C_INT), value :: ostride
0103       integer(C_INT), value :: odist
0104       integer(C_INT), value :: sign
0105       integer(C_INT), value :: flags
0106     end function fftw_plan_many_dft
0107     
0108     type(C_PTR) function fftw_plan_guru_dft(rank,dims,howmany_rank,howmany_dims,in,out,sign,flags) &
0109                          bind(C, name='fftw_plan_guru_dft')
0110       import
0111       integer(C_INT), value :: rank
0112       type(fftw_iodim), dimension(*), intent(in) :: dims
0113       integer(C_INT), value :: howmany_rank
0114       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0115       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0116       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0117       integer(C_INT), value :: sign
0118       integer(C_INT), value :: flags
0119     end function fftw_plan_guru_dft
0120     
0121     type(C_PTR) function fftw_plan_guru_split_dft(rank,dims,howmany_rank,howmany_dims,ri,ii,ro,io,flags) &
0122                          bind(C, name='fftw_plan_guru_split_dft')
0123       import
0124       integer(C_INT), value :: rank
0125       type(fftw_iodim), dimension(*), intent(in) :: dims
0126       integer(C_INT), value :: howmany_rank
0127       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0128       real(C_DOUBLE), dimension(*), intent(out) :: ri
0129       real(C_DOUBLE), dimension(*), intent(out) :: ii
0130       real(C_DOUBLE), dimension(*), intent(out) :: ro
0131       real(C_DOUBLE), dimension(*), intent(out) :: io
0132       integer(C_INT), value :: flags
0133     end function fftw_plan_guru_split_dft
0134     
0135     type(C_PTR) function fftw_plan_guru64_dft(rank,dims,howmany_rank,howmany_dims,in,out,sign,flags) &
0136                          bind(C, name='fftw_plan_guru64_dft')
0137       import
0138       integer(C_INT), value :: rank
0139       type(fftw_iodim64), dimension(*), intent(in) :: dims
0140       integer(C_INT), value :: howmany_rank
0141       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0142       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0143       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0144       integer(C_INT), value :: sign
0145       integer(C_INT), value :: flags
0146     end function fftw_plan_guru64_dft
0147     
0148     type(C_PTR) function fftw_plan_guru64_split_dft(rank,dims,howmany_rank,howmany_dims,ri,ii,ro,io,flags) &
0149                          bind(C, name='fftw_plan_guru64_split_dft')
0150       import
0151       integer(C_INT), value :: rank
0152       type(fftw_iodim64), dimension(*), intent(in) :: dims
0153       integer(C_INT), value :: howmany_rank
0154       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0155       real(C_DOUBLE), dimension(*), intent(out) :: ri
0156       real(C_DOUBLE), dimension(*), intent(out) :: ii
0157       real(C_DOUBLE), dimension(*), intent(out) :: ro
0158       real(C_DOUBLE), dimension(*), intent(out) :: io
0159       integer(C_INT), value :: flags
0160     end function fftw_plan_guru64_split_dft
0161     
0162     subroutine fftw_execute_dft(p,in,out) bind(C, name='fftw_execute_dft')
0163       import
0164       type(C_PTR), value :: p
0165       complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0166       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0167     end subroutine fftw_execute_dft
0168     
0169     subroutine fftw_execute_split_dft(p,ri,ii,ro,io) bind(C, name='fftw_execute_split_dft')
0170       import
0171       type(C_PTR), value :: p
0172       real(C_DOUBLE), dimension(*), intent(inout) :: ri
0173       real(C_DOUBLE), dimension(*), intent(inout) :: ii
0174       real(C_DOUBLE), dimension(*), intent(out) :: ro
0175       real(C_DOUBLE), dimension(*), intent(out) :: io
0176     end subroutine fftw_execute_split_dft
0177     
0178     type(C_PTR) function fftw_plan_many_dft_r2c(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,flags) &
0179                          bind(C, name='fftw_plan_many_dft_r2c')
0180       import
0181       integer(C_INT), value :: rank
0182       integer(C_INT), dimension(*), intent(in) :: n
0183       integer(C_INT), value :: howmany
0184       real(C_DOUBLE), dimension(*), intent(out) :: in
0185       integer(C_INT), dimension(*), intent(in) :: inembed
0186       integer(C_INT), value :: istride
0187       integer(C_INT), value :: idist
0188       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0189       integer(C_INT), dimension(*), intent(in) :: onembed
0190       integer(C_INT), value :: ostride
0191       integer(C_INT), value :: odist
0192       integer(C_INT), value :: flags
0193     end function fftw_plan_many_dft_r2c
0194     
0195     type(C_PTR) function fftw_plan_dft_r2c(rank,n,in,out,flags) bind(C, name='fftw_plan_dft_r2c')
0196       import
0197       integer(C_INT), value :: rank
0198       integer(C_INT), dimension(*), intent(in) :: n
0199       real(C_DOUBLE), dimension(*), intent(out) :: in
0200       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0201       integer(C_INT), value :: flags
0202     end function fftw_plan_dft_r2c
0203     
0204     type(C_PTR) function fftw_plan_dft_r2c_1d(n,in,out,flags) bind(C, name='fftw_plan_dft_r2c_1d')
0205       import
0206       integer(C_INT), value :: n
0207       real(C_DOUBLE), dimension(*), intent(out) :: in
0208       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0209       integer(C_INT), value :: flags
0210     end function fftw_plan_dft_r2c_1d
0211     
0212     type(C_PTR) function fftw_plan_dft_r2c_2d(n0,n1,in,out,flags) bind(C, name='fftw_plan_dft_r2c_2d')
0213       import
0214       integer(C_INT), value :: n0
0215       integer(C_INT), value :: n1
0216       real(C_DOUBLE), dimension(*), intent(out) :: in
0217       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0218       integer(C_INT), value :: flags
0219     end function fftw_plan_dft_r2c_2d
0220     
0221     type(C_PTR) function fftw_plan_dft_r2c_3d(n0,n1,n2,in,out,flags) bind(C, name='fftw_plan_dft_r2c_3d')
0222       import
0223       integer(C_INT), value :: n0
0224       integer(C_INT), value :: n1
0225       integer(C_INT), value :: n2
0226       real(C_DOUBLE), dimension(*), intent(out) :: in
0227       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0228       integer(C_INT), value :: flags
0229     end function fftw_plan_dft_r2c_3d
0230     
0231     type(C_PTR) function fftw_plan_many_dft_c2r(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,flags) &
0232                          bind(C, name='fftw_plan_many_dft_c2r')
0233       import
0234       integer(C_INT), value :: rank
0235       integer(C_INT), dimension(*), intent(in) :: n
0236       integer(C_INT), value :: howmany
0237       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0238       integer(C_INT), dimension(*), intent(in) :: inembed
0239       integer(C_INT), value :: istride
0240       integer(C_INT), value :: idist
0241       real(C_DOUBLE), dimension(*), intent(out) :: out
0242       integer(C_INT), dimension(*), intent(in) :: onembed
0243       integer(C_INT), value :: ostride
0244       integer(C_INT), value :: odist
0245       integer(C_INT), value :: flags
0246     end function fftw_plan_many_dft_c2r
0247     
0248     type(C_PTR) function fftw_plan_dft_c2r(rank,n,in,out,flags) bind(C, name='fftw_plan_dft_c2r')
0249       import
0250       integer(C_INT), value :: rank
0251       integer(C_INT), dimension(*), intent(in) :: n
0252       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0253       real(C_DOUBLE), dimension(*), intent(out) :: out
0254       integer(C_INT), value :: flags
0255     end function fftw_plan_dft_c2r
0256     
0257     type(C_PTR) function fftw_plan_dft_c2r_1d(n,in,out,flags) bind(C, name='fftw_plan_dft_c2r_1d')
0258       import
0259       integer(C_INT), value :: n
0260       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0261       real(C_DOUBLE), dimension(*), intent(out) :: out
0262       integer(C_INT), value :: flags
0263     end function fftw_plan_dft_c2r_1d
0264     
0265     type(C_PTR) function fftw_plan_dft_c2r_2d(n0,n1,in,out,flags) bind(C, name='fftw_plan_dft_c2r_2d')
0266       import
0267       integer(C_INT), value :: n0
0268       integer(C_INT), value :: n1
0269       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0270       real(C_DOUBLE), dimension(*), intent(out) :: out
0271       integer(C_INT), value :: flags
0272     end function fftw_plan_dft_c2r_2d
0273     
0274     type(C_PTR) function fftw_plan_dft_c2r_3d(n0,n1,n2,in,out,flags) bind(C, name='fftw_plan_dft_c2r_3d')
0275       import
0276       integer(C_INT), value :: n0
0277       integer(C_INT), value :: n1
0278       integer(C_INT), value :: n2
0279       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0280       real(C_DOUBLE), dimension(*), intent(out) :: out
0281       integer(C_INT), value :: flags
0282     end function fftw_plan_dft_c2r_3d
0283     
0284     type(C_PTR) function fftw_plan_guru_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0285                          bind(C, name='fftw_plan_guru_dft_r2c')
0286       import
0287       integer(C_INT), value :: rank
0288       type(fftw_iodim), dimension(*), intent(in) :: dims
0289       integer(C_INT), value :: howmany_rank
0290       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0291       real(C_DOUBLE), dimension(*), intent(out) :: in
0292       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0293       integer(C_INT), value :: flags
0294     end function fftw_plan_guru_dft_r2c
0295     
0296     type(C_PTR) function fftw_plan_guru_dft_c2r(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0297                          bind(C, name='fftw_plan_guru_dft_c2r')
0298       import
0299       integer(C_INT), value :: rank
0300       type(fftw_iodim), dimension(*), intent(in) :: dims
0301       integer(C_INT), value :: howmany_rank
0302       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0303       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0304       real(C_DOUBLE), dimension(*), intent(out) :: out
0305       integer(C_INT), value :: flags
0306     end function fftw_plan_guru_dft_c2r
0307     
0308     type(C_PTR) function fftw_plan_guru_split_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,ro,io,flags) &
0309                          bind(C, name='fftw_plan_guru_split_dft_r2c')
0310       import
0311       integer(C_INT), value :: rank
0312       type(fftw_iodim), dimension(*), intent(in) :: dims
0313       integer(C_INT), value :: howmany_rank
0314       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0315       real(C_DOUBLE), dimension(*), intent(out) :: in
0316       real(C_DOUBLE), dimension(*), intent(out) :: ro
0317       real(C_DOUBLE), dimension(*), intent(out) :: io
0318       integer(C_INT), value :: flags
0319     end function fftw_plan_guru_split_dft_r2c
0320     
0321     type(C_PTR) function fftw_plan_guru_split_dft_c2r(rank,dims,howmany_rank,howmany_dims,ri,ii,out,flags) &
0322                          bind(C, name='fftw_plan_guru_split_dft_c2r')
0323       import
0324       integer(C_INT), value :: rank
0325       type(fftw_iodim), dimension(*), intent(in) :: dims
0326       integer(C_INT), value :: howmany_rank
0327       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0328       real(C_DOUBLE), dimension(*), intent(out) :: ri
0329       real(C_DOUBLE), dimension(*), intent(out) :: ii
0330       real(C_DOUBLE), dimension(*), intent(out) :: out
0331       integer(C_INT), value :: flags
0332     end function fftw_plan_guru_split_dft_c2r
0333     
0334     type(C_PTR) function fftw_plan_guru64_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0335                          bind(C, name='fftw_plan_guru64_dft_r2c')
0336       import
0337       integer(C_INT), value :: rank
0338       type(fftw_iodim64), dimension(*), intent(in) :: dims
0339       integer(C_INT), value :: howmany_rank
0340       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0341       real(C_DOUBLE), dimension(*), intent(out) :: in
0342       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0343       integer(C_INT), value :: flags
0344     end function fftw_plan_guru64_dft_r2c
0345     
0346     type(C_PTR) function fftw_plan_guru64_dft_c2r(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0347                          bind(C, name='fftw_plan_guru64_dft_c2r')
0348       import
0349       integer(C_INT), value :: rank
0350       type(fftw_iodim64), dimension(*), intent(in) :: dims
0351       integer(C_INT), value :: howmany_rank
0352       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0353       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0354       real(C_DOUBLE), dimension(*), intent(out) :: out
0355       integer(C_INT), value :: flags
0356     end function fftw_plan_guru64_dft_c2r
0357     
0358     type(C_PTR) function fftw_plan_guru64_split_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,ro,io,flags) &
0359                          bind(C, name='fftw_plan_guru64_split_dft_r2c')
0360       import
0361       integer(C_INT), value :: rank
0362       type(fftw_iodim64), dimension(*), intent(in) :: dims
0363       integer(C_INT), value :: howmany_rank
0364       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0365       real(C_DOUBLE), dimension(*), intent(out) :: in
0366       real(C_DOUBLE), dimension(*), intent(out) :: ro
0367       real(C_DOUBLE), dimension(*), intent(out) :: io
0368       integer(C_INT), value :: flags
0369     end function fftw_plan_guru64_split_dft_r2c
0370     
0371     type(C_PTR) function fftw_plan_guru64_split_dft_c2r(rank,dims,howmany_rank,howmany_dims,ri,ii,out,flags) &
0372                          bind(C, name='fftw_plan_guru64_split_dft_c2r')
0373       import
0374       integer(C_INT), value :: rank
0375       type(fftw_iodim64), dimension(*), intent(in) :: dims
0376       integer(C_INT), value :: howmany_rank
0377       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0378       real(C_DOUBLE), dimension(*), intent(out) :: ri
0379       real(C_DOUBLE), dimension(*), intent(out) :: ii
0380       real(C_DOUBLE), dimension(*), intent(out) :: out
0381       integer(C_INT), value :: flags
0382     end function fftw_plan_guru64_split_dft_c2r
0383     
0384     subroutine fftw_execute_dft_r2c(p,in,out) bind(C, name='fftw_execute_dft_r2c')
0385       import
0386       type(C_PTR), value :: p
0387       real(C_DOUBLE), dimension(*), intent(inout) :: in
0388       complex(C_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0389     end subroutine fftw_execute_dft_r2c
0390     
0391     subroutine fftw_execute_dft_c2r(p,in,out) bind(C, name='fftw_execute_dft_c2r')
0392       import
0393       type(C_PTR), value :: p
0394       complex(C_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0395       real(C_DOUBLE), dimension(*), intent(out) :: out
0396     end subroutine fftw_execute_dft_c2r
0397     
0398     subroutine fftw_execute_split_dft_r2c(p,in,ro,io) bind(C, name='fftw_execute_split_dft_r2c')
0399       import
0400       type(C_PTR), value :: p
0401       real(C_DOUBLE), dimension(*), intent(inout) :: in
0402       real(C_DOUBLE), dimension(*), intent(out) :: ro
0403       real(C_DOUBLE), dimension(*), intent(out) :: io
0404     end subroutine fftw_execute_split_dft_r2c
0405     
0406     subroutine fftw_execute_split_dft_c2r(p,ri,ii,out) bind(C, name='fftw_execute_split_dft_c2r')
0407       import
0408       type(C_PTR), value :: p
0409       real(C_DOUBLE), dimension(*), intent(inout) :: ri
0410       real(C_DOUBLE), dimension(*), intent(inout) :: ii
0411       real(C_DOUBLE), dimension(*), intent(out) :: out
0412     end subroutine fftw_execute_split_dft_c2r
0413     
0414     type(C_PTR) function fftw_plan_many_r2r(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,kind,flags) &
0415                          bind(C, name='fftw_plan_many_r2r')
0416       import
0417       integer(C_INT), value :: rank
0418       integer(C_INT), dimension(*), intent(in) :: n
0419       integer(C_INT), value :: howmany
0420       real(C_DOUBLE), dimension(*), intent(out) :: in
0421       integer(C_INT), dimension(*), intent(in) :: inembed
0422       integer(C_INT), value :: istride
0423       integer(C_INT), value :: idist
0424       real(C_DOUBLE), dimension(*), intent(out) :: out
0425       integer(C_INT), dimension(*), intent(in) :: onembed
0426       integer(C_INT), value :: ostride
0427       integer(C_INT), value :: odist
0428       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0429       integer(C_INT), value :: flags
0430     end function fftw_plan_many_r2r
0431     
0432     type(C_PTR) function fftw_plan_r2r(rank,n,in,out,kind,flags) bind(C, name='fftw_plan_r2r')
0433       import
0434       integer(C_INT), value :: rank
0435       integer(C_INT), dimension(*), intent(in) :: n
0436       real(C_DOUBLE), dimension(*), intent(out) :: in
0437       real(C_DOUBLE), dimension(*), intent(out) :: out
0438       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0439       integer(C_INT), value :: flags
0440     end function fftw_plan_r2r
0441     
0442     type(C_PTR) function fftw_plan_r2r_1d(n,in,out,kind,flags) bind(C, name='fftw_plan_r2r_1d')
0443       import
0444       integer(C_INT), value :: n
0445       real(C_DOUBLE), dimension(*), intent(out) :: in
0446       real(C_DOUBLE), dimension(*), intent(out) :: out
0447       integer(C_FFTW_R2R_KIND), value :: kind
0448       integer(C_INT), value :: flags
0449     end function fftw_plan_r2r_1d
0450     
0451     type(C_PTR) function fftw_plan_r2r_2d(n0,n1,in,out,kind0,kind1,flags) bind(C, name='fftw_plan_r2r_2d')
0452       import
0453       integer(C_INT), value :: n0
0454       integer(C_INT), value :: n1
0455       real(C_DOUBLE), dimension(*), intent(out) :: in
0456       real(C_DOUBLE), dimension(*), intent(out) :: out
0457       integer(C_FFTW_R2R_KIND), value :: kind0
0458       integer(C_FFTW_R2R_KIND), value :: kind1
0459       integer(C_INT), value :: flags
0460     end function fftw_plan_r2r_2d
0461     
0462     type(C_PTR) function fftw_plan_r2r_3d(n0,n1,n2,in,out,kind0,kind1,kind2,flags) bind(C, name='fftw_plan_r2r_3d')
0463       import
0464       integer(C_INT), value :: n0
0465       integer(C_INT), value :: n1
0466       integer(C_INT), value :: n2
0467       real(C_DOUBLE), dimension(*), intent(out) :: in
0468       real(C_DOUBLE), dimension(*), intent(out) :: out
0469       integer(C_FFTW_R2R_KIND), value :: kind0
0470       integer(C_FFTW_R2R_KIND), value :: kind1
0471       integer(C_FFTW_R2R_KIND), value :: kind2
0472       integer(C_INT), value :: flags
0473     end function fftw_plan_r2r_3d
0474     
0475     type(C_PTR) function fftw_plan_guru_r2r(rank,dims,howmany_rank,howmany_dims,in,out,kind,flags) &
0476                          bind(C, name='fftw_plan_guru_r2r')
0477       import
0478       integer(C_INT), value :: rank
0479       type(fftw_iodim), dimension(*), intent(in) :: dims
0480       integer(C_INT), value :: howmany_rank
0481       type(fftw_iodim), dimension(*), intent(in) :: howmany_dims
0482       real(C_DOUBLE), dimension(*), intent(out) :: in
0483       real(C_DOUBLE), dimension(*), intent(out) :: out
0484       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0485       integer(C_INT), value :: flags
0486     end function fftw_plan_guru_r2r
0487     
0488     type(C_PTR) function fftw_plan_guru64_r2r(rank,dims,howmany_rank,howmany_dims,in,out,kind,flags) &
0489                          bind(C, name='fftw_plan_guru64_r2r')
0490       import
0491       integer(C_INT), value :: rank
0492       type(fftw_iodim64), dimension(*), intent(in) :: dims
0493       integer(C_INT), value :: howmany_rank
0494       type(fftw_iodim64), dimension(*), intent(in) :: howmany_dims
0495       real(C_DOUBLE), dimension(*), intent(out) :: in
0496       real(C_DOUBLE), dimension(*), intent(out) :: out
0497       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0498       integer(C_INT), value :: flags
0499     end function fftw_plan_guru64_r2r
0500     
0501     subroutine fftw_execute_r2r(p,in,out) bind(C, name='fftw_execute_r2r')
0502       import
0503       type(C_PTR), value :: p
0504       real(C_DOUBLE), dimension(*), intent(inout) :: in
0505       real(C_DOUBLE), dimension(*), intent(out) :: out
0506     end subroutine fftw_execute_r2r
0507     
0508     subroutine fftw_destroy_plan(p) bind(C, name='fftw_destroy_plan')
0509       import
0510       type(C_PTR), value :: p
0511     end subroutine fftw_destroy_plan
0512     
0513     subroutine fftw_forget_wisdom() bind(C, name='fftw_forget_wisdom')
0514       import
0515     end subroutine fftw_forget_wisdom
0516     
0517     subroutine fftw_cleanup() bind(C, name='fftw_cleanup')
0518       import
0519     end subroutine fftw_cleanup
0520     
0521     subroutine fftw_set_timelimit(t) bind(C, name='fftw_set_timelimit')
0522       import
0523       real(C_DOUBLE), value :: t
0524     end subroutine fftw_set_timelimit
0525     
0526     subroutine fftw_plan_with_nthreads(nthreads) bind(C, name='fftw_plan_with_nthreads')
0527       import
0528       integer(C_INT), value :: nthreads
0529     end subroutine fftw_plan_with_nthreads
0530     
0531     integer(C_INT) function fftw_planner_nthreads() bind(C, name='fftw_planner_nthreads')
0532       import
0533     end function fftw_planner_nthreads
0534     
0535     integer(C_INT) function fftw_init_threads() bind(C, name='fftw_init_threads')
0536       import
0537     end function fftw_init_threads
0538     
0539     subroutine fftw_cleanup_threads() bind(C, name='fftw_cleanup_threads')
0540       import
0541     end subroutine fftw_cleanup_threads
0542     
0543 ! Unable to generate Fortran interface for fftw_threads_set_callback
0544     subroutine fftw_make_planner_thread_safe() bind(C, name='fftw_make_planner_thread_safe')
0545       import
0546     end subroutine fftw_make_planner_thread_safe
0547     
0548     integer(C_INT) function fftw_export_wisdom_to_filename(filename) bind(C, name='fftw_export_wisdom_to_filename')
0549       import
0550       character(C_CHAR), dimension(*), intent(in) :: filename
0551     end function fftw_export_wisdom_to_filename
0552     
0553     subroutine fftw_export_wisdom_to_file(output_file) bind(C, name='fftw_export_wisdom_to_file')
0554       import
0555       type(C_PTR), value :: output_file
0556     end subroutine fftw_export_wisdom_to_file
0557     
0558     type(C_PTR) function fftw_export_wisdom_to_string() bind(C, name='fftw_export_wisdom_to_string')
0559       import
0560     end function fftw_export_wisdom_to_string
0561     
0562     subroutine fftw_export_wisdom(write_char,data) bind(C, name='fftw_export_wisdom')
0563       import
0564       type(C_FUNPTR), value :: write_char
0565       type(C_PTR), value :: data
0566     end subroutine fftw_export_wisdom
0567     
0568     integer(C_INT) function fftw_import_system_wisdom() bind(C, name='fftw_import_system_wisdom')
0569       import
0570     end function fftw_import_system_wisdom
0571     
0572     integer(C_INT) function fftw_import_wisdom_from_filename(filename) bind(C, name='fftw_import_wisdom_from_filename')
0573       import
0574       character(C_CHAR), dimension(*), intent(in) :: filename
0575     end function fftw_import_wisdom_from_filename
0576     
0577     integer(C_INT) function fftw_import_wisdom_from_file(input_file) bind(C, name='fftw_import_wisdom_from_file')
0578       import
0579       type(C_PTR), value :: input_file
0580     end function fftw_import_wisdom_from_file
0581     
0582     integer(C_INT) function fftw_import_wisdom_from_string(input_string) bind(C, name='fftw_import_wisdom_from_string')
0583       import
0584       character(C_CHAR), dimension(*), intent(in) :: input_string
0585     end function fftw_import_wisdom_from_string
0586     
0587     integer(C_INT) function fftw_import_wisdom(read_char,data) bind(C, name='fftw_import_wisdom')
0588       import
0589       type(C_FUNPTR), value :: read_char
0590       type(C_PTR), value :: data
0591     end function fftw_import_wisdom
0592     
0593     subroutine fftw_fprint_plan(p,output_file) bind(C, name='fftw_fprint_plan')
0594       import
0595       type(C_PTR), value :: p
0596       type(C_PTR), value :: output_file
0597     end subroutine fftw_fprint_plan
0598     
0599     subroutine fftw_print_plan(p) bind(C, name='fftw_print_plan')
0600       import
0601       type(C_PTR), value :: p
0602     end subroutine fftw_print_plan
0603     
0604     type(C_PTR) function fftw_sprint_plan(p) bind(C, name='fftw_sprint_plan')
0605       import
0606       type(C_PTR), value :: p
0607     end function fftw_sprint_plan
0608     
0609     type(C_PTR) function fftw_malloc(n) bind(C, name='fftw_malloc')
0610       import
0611       integer(C_SIZE_T), value :: n
0612     end function fftw_malloc
0613     
0614     type(C_PTR) function fftw_alloc_real(n) bind(C, name='fftw_alloc_real')
0615       import
0616       integer(C_SIZE_T), value :: n
0617     end function fftw_alloc_real
0618     
0619     type(C_PTR) function fftw_alloc_complex(n) bind(C, name='fftw_alloc_complex')
0620       import
0621       integer(C_SIZE_T), value :: n
0622     end function fftw_alloc_complex
0623     
0624     subroutine fftw_free(p) bind(C, name='fftw_free')
0625       import
0626       type(C_PTR), value :: p
0627     end subroutine fftw_free
0628     
0629     subroutine fftw_flops(p,add,mul,fmas) bind(C, name='fftw_flops')
0630       import
0631       type(C_PTR), value :: p
0632       real(C_DOUBLE), intent(out) :: add
0633       real(C_DOUBLE), intent(out) :: mul
0634       real(C_DOUBLE), intent(out) :: fmas
0635     end subroutine fftw_flops
0636     
0637     real(C_DOUBLE) function fftw_estimate_cost(p) bind(C, name='fftw_estimate_cost')
0638       import
0639       type(C_PTR), value :: p
0640     end function fftw_estimate_cost
0641     
0642     real(C_DOUBLE) function fftw_cost(p) bind(C, name='fftw_cost')
0643       import
0644       type(C_PTR), value :: p
0645     end function fftw_cost
0646     
0647     integer(C_INT) function fftw_alignment_of(p) bind(C, name='fftw_alignment_of')
0648       import
0649       real(C_DOUBLE), dimension(*), intent(out) :: p
0650     end function fftw_alignment_of
0651     
0652   end interface
0653 
0654   type, bind(C) :: fftwf_iodim
0655      integer(C_INT) n, is, os
0656   end type fftwf_iodim
0657   type, bind(C) :: fftwf_iodim64
0658      integer(C_INTPTR_T) n, is, os
0659   end type fftwf_iodim64
0660 
0661   interface
0662     type(C_PTR) function fftwf_plan_dft(rank,n,in,out,sign,flags) bind(C, name='fftwf_plan_dft')
0663       import
0664       integer(C_INT), value :: rank
0665       integer(C_INT), dimension(*), intent(in) :: n
0666       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0667       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0668       integer(C_INT), value :: sign
0669       integer(C_INT), value :: flags
0670     end function fftwf_plan_dft
0671     
0672     type(C_PTR) function fftwf_plan_dft_1d(n,in,out,sign,flags) bind(C, name='fftwf_plan_dft_1d')
0673       import
0674       integer(C_INT), value :: n
0675       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0676       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0677       integer(C_INT), value :: sign
0678       integer(C_INT), value :: flags
0679     end function fftwf_plan_dft_1d
0680     
0681     type(C_PTR) function fftwf_plan_dft_2d(n0,n1,in,out,sign,flags) bind(C, name='fftwf_plan_dft_2d')
0682       import
0683       integer(C_INT), value :: n0
0684       integer(C_INT), value :: n1
0685       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0686       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0687       integer(C_INT), value :: sign
0688       integer(C_INT), value :: flags
0689     end function fftwf_plan_dft_2d
0690     
0691     type(C_PTR) function fftwf_plan_dft_3d(n0,n1,n2,in,out,sign,flags) bind(C, name='fftwf_plan_dft_3d')
0692       import
0693       integer(C_INT), value :: n0
0694       integer(C_INT), value :: n1
0695       integer(C_INT), value :: n2
0696       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0697       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0698       integer(C_INT), value :: sign
0699       integer(C_INT), value :: flags
0700     end function fftwf_plan_dft_3d
0701     
0702     type(C_PTR) function fftwf_plan_many_dft(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,sign,flags) &
0703                          bind(C, name='fftwf_plan_many_dft')
0704       import
0705       integer(C_INT), value :: rank
0706       integer(C_INT), dimension(*), intent(in) :: n
0707       integer(C_INT), value :: howmany
0708       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0709       integer(C_INT), dimension(*), intent(in) :: inembed
0710       integer(C_INT), value :: istride
0711       integer(C_INT), value :: idist
0712       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0713       integer(C_INT), dimension(*), intent(in) :: onembed
0714       integer(C_INT), value :: ostride
0715       integer(C_INT), value :: odist
0716       integer(C_INT), value :: sign
0717       integer(C_INT), value :: flags
0718     end function fftwf_plan_many_dft
0719     
0720     type(C_PTR) function fftwf_plan_guru_dft(rank,dims,howmany_rank,howmany_dims,in,out,sign,flags) &
0721                          bind(C, name='fftwf_plan_guru_dft')
0722       import
0723       integer(C_INT), value :: rank
0724       type(fftwf_iodim), dimension(*), intent(in) :: dims
0725       integer(C_INT), value :: howmany_rank
0726       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0727       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0728       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0729       integer(C_INT), value :: sign
0730       integer(C_INT), value :: flags
0731     end function fftwf_plan_guru_dft
0732     
0733     type(C_PTR) function fftwf_plan_guru_split_dft(rank,dims,howmany_rank,howmany_dims,ri,ii,ro,io,flags) &
0734                          bind(C, name='fftwf_plan_guru_split_dft')
0735       import
0736       integer(C_INT), value :: rank
0737       type(fftwf_iodim), dimension(*), intent(in) :: dims
0738       integer(C_INT), value :: howmany_rank
0739       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0740       real(C_FLOAT), dimension(*), intent(out) :: ri
0741       real(C_FLOAT), dimension(*), intent(out) :: ii
0742       real(C_FLOAT), dimension(*), intent(out) :: ro
0743       real(C_FLOAT), dimension(*), intent(out) :: io
0744       integer(C_INT), value :: flags
0745     end function fftwf_plan_guru_split_dft
0746     
0747     type(C_PTR) function fftwf_plan_guru64_dft(rank,dims,howmany_rank,howmany_dims,in,out,sign,flags) &
0748                          bind(C, name='fftwf_plan_guru64_dft')
0749       import
0750       integer(C_INT), value :: rank
0751       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0752       integer(C_INT), value :: howmany_rank
0753       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0754       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0755       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0756       integer(C_INT), value :: sign
0757       integer(C_INT), value :: flags
0758     end function fftwf_plan_guru64_dft
0759     
0760     type(C_PTR) function fftwf_plan_guru64_split_dft(rank,dims,howmany_rank,howmany_dims,ri,ii,ro,io,flags) &
0761                          bind(C, name='fftwf_plan_guru64_split_dft')
0762       import
0763       integer(C_INT), value :: rank
0764       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0765       integer(C_INT), value :: howmany_rank
0766       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0767       real(C_FLOAT), dimension(*), intent(out) :: ri
0768       real(C_FLOAT), dimension(*), intent(out) :: ii
0769       real(C_FLOAT), dimension(*), intent(out) :: ro
0770       real(C_FLOAT), dimension(*), intent(out) :: io
0771       integer(C_INT), value :: flags
0772     end function fftwf_plan_guru64_split_dft
0773     
0774     subroutine fftwf_execute_dft(p,in,out) bind(C, name='fftwf_execute_dft')
0775       import
0776       type(C_PTR), value :: p
0777       complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
0778       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0779     end subroutine fftwf_execute_dft
0780     
0781     subroutine fftwf_execute_split_dft(p,ri,ii,ro,io) bind(C, name='fftwf_execute_split_dft')
0782       import
0783       type(C_PTR), value :: p
0784       real(C_FLOAT), dimension(*), intent(inout) :: ri
0785       real(C_FLOAT), dimension(*), intent(inout) :: ii
0786       real(C_FLOAT), dimension(*), intent(out) :: ro
0787       real(C_FLOAT), dimension(*), intent(out) :: io
0788     end subroutine fftwf_execute_split_dft
0789     
0790     type(C_PTR) function fftwf_plan_many_dft_r2c(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,flags) &
0791                          bind(C, name='fftwf_plan_many_dft_r2c')
0792       import
0793       integer(C_INT), value :: rank
0794       integer(C_INT), dimension(*), intent(in) :: n
0795       integer(C_INT), value :: howmany
0796       real(C_FLOAT), dimension(*), intent(out) :: in
0797       integer(C_INT), dimension(*), intent(in) :: inembed
0798       integer(C_INT), value :: istride
0799       integer(C_INT), value :: idist
0800       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0801       integer(C_INT), dimension(*), intent(in) :: onembed
0802       integer(C_INT), value :: ostride
0803       integer(C_INT), value :: odist
0804       integer(C_INT), value :: flags
0805     end function fftwf_plan_many_dft_r2c
0806     
0807     type(C_PTR) function fftwf_plan_dft_r2c(rank,n,in,out,flags) bind(C, name='fftwf_plan_dft_r2c')
0808       import
0809       integer(C_INT), value :: rank
0810       integer(C_INT), dimension(*), intent(in) :: n
0811       real(C_FLOAT), dimension(*), intent(out) :: in
0812       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0813       integer(C_INT), value :: flags
0814     end function fftwf_plan_dft_r2c
0815     
0816     type(C_PTR) function fftwf_plan_dft_r2c_1d(n,in,out,flags) bind(C, name='fftwf_plan_dft_r2c_1d')
0817       import
0818       integer(C_INT), value :: n
0819       real(C_FLOAT), dimension(*), intent(out) :: in
0820       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0821       integer(C_INT), value :: flags
0822     end function fftwf_plan_dft_r2c_1d
0823     
0824     type(C_PTR) function fftwf_plan_dft_r2c_2d(n0,n1,in,out,flags) bind(C, name='fftwf_plan_dft_r2c_2d')
0825       import
0826       integer(C_INT), value :: n0
0827       integer(C_INT), value :: n1
0828       real(C_FLOAT), dimension(*), intent(out) :: in
0829       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0830       integer(C_INT), value :: flags
0831     end function fftwf_plan_dft_r2c_2d
0832     
0833     type(C_PTR) function fftwf_plan_dft_r2c_3d(n0,n1,n2,in,out,flags) bind(C, name='fftwf_plan_dft_r2c_3d')
0834       import
0835       integer(C_INT), value :: n0
0836       integer(C_INT), value :: n1
0837       integer(C_INT), value :: n2
0838       real(C_FLOAT), dimension(*), intent(out) :: in
0839       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0840       integer(C_INT), value :: flags
0841     end function fftwf_plan_dft_r2c_3d
0842     
0843     type(C_PTR) function fftwf_plan_many_dft_c2r(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,flags) &
0844                          bind(C, name='fftwf_plan_many_dft_c2r')
0845       import
0846       integer(C_INT), value :: rank
0847       integer(C_INT), dimension(*), intent(in) :: n
0848       integer(C_INT), value :: howmany
0849       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0850       integer(C_INT), dimension(*), intent(in) :: inembed
0851       integer(C_INT), value :: istride
0852       integer(C_INT), value :: idist
0853       real(C_FLOAT), dimension(*), intent(out) :: out
0854       integer(C_INT), dimension(*), intent(in) :: onembed
0855       integer(C_INT), value :: ostride
0856       integer(C_INT), value :: odist
0857       integer(C_INT), value :: flags
0858     end function fftwf_plan_many_dft_c2r
0859     
0860     type(C_PTR) function fftwf_plan_dft_c2r(rank,n,in,out,flags) bind(C, name='fftwf_plan_dft_c2r')
0861       import
0862       integer(C_INT), value :: rank
0863       integer(C_INT), dimension(*), intent(in) :: n
0864       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0865       real(C_FLOAT), dimension(*), intent(out) :: out
0866       integer(C_INT), value :: flags
0867     end function fftwf_plan_dft_c2r
0868     
0869     type(C_PTR) function fftwf_plan_dft_c2r_1d(n,in,out,flags) bind(C, name='fftwf_plan_dft_c2r_1d')
0870       import
0871       integer(C_INT), value :: n
0872       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0873       real(C_FLOAT), dimension(*), intent(out) :: out
0874       integer(C_INT), value :: flags
0875     end function fftwf_plan_dft_c2r_1d
0876     
0877     type(C_PTR) function fftwf_plan_dft_c2r_2d(n0,n1,in,out,flags) bind(C, name='fftwf_plan_dft_c2r_2d')
0878       import
0879       integer(C_INT), value :: n0
0880       integer(C_INT), value :: n1
0881       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0882       real(C_FLOAT), dimension(*), intent(out) :: out
0883       integer(C_INT), value :: flags
0884     end function fftwf_plan_dft_c2r_2d
0885     
0886     type(C_PTR) function fftwf_plan_dft_c2r_3d(n0,n1,n2,in,out,flags) bind(C, name='fftwf_plan_dft_c2r_3d')
0887       import
0888       integer(C_INT), value :: n0
0889       integer(C_INT), value :: n1
0890       integer(C_INT), value :: n2
0891       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0892       real(C_FLOAT), dimension(*), intent(out) :: out
0893       integer(C_INT), value :: flags
0894     end function fftwf_plan_dft_c2r_3d
0895     
0896     type(C_PTR) function fftwf_plan_guru_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0897                          bind(C, name='fftwf_plan_guru_dft_r2c')
0898       import
0899       integer(C_INT), value :: rank
0900       type(fftwf_iodim), dimension(*), intent(in) :: dims
0901       integer(C_INT), value :: howmany_rank
0902       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0903       real(C_FLOAT), dimension(*), intent(out) :: in
0904       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0905       integer(C_INT), value :: flags
0906     end function fftwf_plan_guru_dft_r2c
0907     
0908     type(C_PTR) function fftwf_plan_guru_dft_c2r(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0909                          bind(C, name='fftwf_plan_guru_dft_c2r')
0910       import
0911       integer(C_INT), value :: rank
0912       type(fftwf_iodim), dimension(*), intent(in) :: dims
0913       integer(C_INT), value :: howmany_rank
0914       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0915       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0916       real(C_FLOAT), dimension(*), intent(out) :: out
0917       integer(C_INT), value :: flags
0918     end function fftwf_plan_guru_dft_c2r
0919     
0920     type(C_PTR) function fftwf_plan_guru_split_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,ro,io,flags) &
0921                          bind(C, name='fftwf_plan_guru_split_dft_r2c')
0922       import
0923       integer(C_INT), value :: rank
0924       type(fftwf_iodim), dimension(*), intent(in) :: dims
0925       integer(C_INT), value :: howmany_rank
0926       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0927       real(C_FLOAT), dimension(*), intent(out) :: in
0928       real(C_FLOAT), dimension(*), intent(out) :: ro
0929       real(C_FLOAT), dimension(*), intent(out) :: io
0930       integer(C_INT), value :: flags
0931     end function fftwf_plan_guru_split_dft_r2c
0932     
0933     type(C_PTR) function fftwf_plan_guru_split_dft_c2r(rank,dims,howmany_rank,howmany_dims,ri,ii,out,flags) &
0934                          bind(C, name='fftwf_plan_guru_split_dft_c2r')
0935       import
0936       integer(C_INT), value :: rank
0937       type(fftwf_iodim), dimension(*), intent(in) :: dims
0938       integer(C_INT), value :: howmany_rank
0939       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
0940       real(C_FLOAT), dimension(*), intent(out) :: ri
0941       real(C_FLOAT), dimension(*), intent(out) :: ii
0942       real(C_FLOAT), dimension(*), intent(out) :: out
0943       integer(C_INT), value :: flags
0944     end function fftwf_plan_guru_split_dft_c2r
0945     
0946     type(C_PTR) function fftwf_plan_guru64_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0947                          bind(C, name='fftwf_plan_guru64_dft_r2c')
0948       import
0949       integer(C_INT), value :: rank
0950       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0951       integer(C_INT), value :: howmany_rank
0952       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0953       real(C_FLOAT), dimension(*), intent(out) :: in
0954       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
0955       integer(C_INT), value :: flags
0956     end function fftwf_plan_guru64_dft_r2c
0957     
0958     type(C_PTR) function fftwf_plan_guru64_dft_c2r(rank,dims,howmany_rank,howmany_dims,in,out,flags) &
0959                          bind(C, name='fftwf_plan_guru64_dft_c2r')
0960       import
0961       integer(C_INT), value :: rank
0962       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0963       integer(C_INT), value :: howmany_rank
0964       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0965       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: in
0966       real(C_FLOAT), dimension(*), intent(out) :: out
0967       integer(C_INT), value :: flags
0968     end function fftwf_plan_guru64_dft_c2r
0969     
0970     type(C_PTR) function fftwf_plan_guru64_split_dft_r2c(rank,dims,howmany_rank,howmany_dims,in,ro,io,flags) &
0971                          bind(C, name='fftwf_plan_guru64_split_dft_r2c')
0972       import
0973       integer(C_INT), value :: rank
0974       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0975       integer(C_INT), value :: howmany_rank
0976       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0977       real(C_FLOAT), dimension(*), intent(out) :: in
0978       real(C_FLOAT), dimension(*), intent(out) :: ro
0979       real(C_FLOAT), dimension(*), intent(out) :: io
0980       integer(C_INT), value :: flags
0981     end function fftwf_plan_guru64_split_dft_r2c
0982     
0983     type(C_PTR) function fftwf_plan_guru64_split_dft_c2r(rank,dims,howmany_rank,howmany_dims,ri,ii,out,flags) &
0984                          bind(C, name='fftwf_plan_guru64_split_dft_c2r')
0985       import
0986       integer(C_INT), value :: rank
0987       type(fftwf_iodim64), dimension(*), intent(in) :: dims
0988       integer(C_INT), value :: howmany_rank
0989       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
0990       real(C_FLOAT), dimension(*), intent(out) :: ri
0991       real(C_FLOAT), dimension(*), intent(out) :: ii
0992       real(C_FLOAT), dimension(*), intent(out) :: out
0993       integer(C_INT), value :: flags
0994     end function fftwf_plan_guru64_split_dft_c2r
0995     
0996     subroutine fftwf_execute_dft_r2c(p,in,out) bind(C, name='fftwf_execute_dft_r2c')
0997       import
0998       type(C_PTR), value :: p
0999       real(C_FLOAT), dimension(*), intent(inout) :: in
1000       complex(C_FLOAT_COMPLEX), dimension(*), intent(out) :: out
1001     end subroutine fftwf_execute_dft_r2c
1002     
1003     subroutine fftwf_execute_dft_c2r(p,in,out) bind(C, name='fftwf_execute_dft_c2r')
1004       import
1005       type(C_PTR), value :: p
1006       complex(C_FLOAT_COMPLEX), dimension(*), intent(inout) :: in
1007       real(C_FLOAT), dimension(*), intent(out) :: out
1008     end subroutine fftwf_execute_dft_c2r
1009     
1010     subroutine fftwf_execute_split_dft_r2c(p,in,ro,io) bind(C, name='fftwf_execute_split_dft_r2c')
1011       import
1012       type(C_PTR), value :: p
1013       real(C_FLOAT), dimension(*), intent(inout) :: in
1014       real(C_FLOAT), dimension(*), intent(out) :: ro
1015       real(C_FLOAT), dimension(*), intent(out) :: io
1016     end subroutine fftwf_execute_split_dft_r2c
1017     
1018     subroutine fftwf_execute_split_dft_c2r(p,ri,ii,out) bind(C, name='fftwf_execute_split_dft_c2r')
1019       import
1020       type(C_PTR), value :: p
1021       real(C_FLOAT), dimension(*), intent(inout) :: ri
1022       real(C_FLOAT), dimension(*), intent(inout) :: ii
1023       real(C_FLOAT), dimension(*), intent(out) :: out
1024     end subroutine fftwf_execute_split_dft_c2r
1025     
1026     type(C_PTR) function fftwf_plan_many_r2r(rank,n,howmany,in,inembed,istride,idist,out,onembed,ostride,odist,kind,flags) &
1027                          bind(C, name='fftwf_plan_many_r2r')
1028       import
1029       integer(C_INT), value :: rank
1030       integer(C_INT), dimension(*), intent(in) :: n
1031       integer(C_INT), value :: howmany
1032       real(C_FLOAT), dimension(*), intent(out) :: in
1033       integer(C_INT), dimension(*), intent(in) :: inembed
1034       integer(C_INT), value :: istride
1035       integer(C_INT), value :: idist
1036       real(C_FLOAT), dimension(*), intent(out) :: out
1037       integer(C_INT), dimension(*), intent(in) :: onembed
1038       integer(C_INT), value :: ostride
1039       integer(C_INT), value :: odist
1040       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
1041       integer(C_INT), value :: flags
1042     end function fftwf_plan_many_r2r
1043     
1044     type(C_PTR) function fftwf_plan_r2r(rank,n,in,out,kind,flags) bind(C, name='fftwf_plan_r2r')
1045       import
1046       integer(C_INT), value :: rank
1047       integer(C_INT), dimension(*), intent(in) :: n
1048       real(C_FLOAT), dimension(*), intent(out) :: in
1049       real(C_FLOAT), dimension(*), intent(out) :: out
1050       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
1051       integer(C_INT), value :: flags
1052     end function fftwf_plan_r2r
1053     
1054     type(C_PTR) function fftwf_plan_r2r_1d(n,in,out,kind,flags) bind(C, name='fftwf_plan_r2r_1d')
1055       import
1056       integer(C_INT), value :: n
1057       real(C_FLOAT), dimension(*), intent(out) :: in
1058       real(C_FLOAT), dimension(*), intent(out) :: out
1059       integer(C_FFTW_R2R_KIND), value :: kind
1060       integer(C_INT), value :: flags
1061     end function fftwf_plan_r2r_1d
1062     
1063     type(C_PTR) function fftwf_plan_r2r_2d(n0,n1,in,out,kind0,kind1,flags) bind(C, name='fftwf_plan_r2r_2d')
1064       import
1065       integer(C_INT), value :: n0
1066       integer(C_INT), value :: n1
1067       real(C_FLOAT), dimension(*), intent(out) :: in
1068       real(C_FLOAT), dimension(*), intent(out) :: out
1069       integer(C_FFTW_R2R_KIND), value :: kind0
1070       integer(C_FFTW_R2R_KIND), value :: kind1
1071       integer(C_INT), value :: flags
1072     end function fftwf_plan_r2r_2d
1073     
1074     type(C_PTR) function fftwf_plan_r2r_3d(n0,n1,n2,in,out,kind0,kind1,kind2,flags) bind(C, name='fftwf_plan_r2r_3d')
1075       import
1076       integer(C_INT), value :: n0
1077       integer(C_INT), value :: n1
1078       integer(C_INT), value :: n2
1079       real(C_FLOAT), dimension(*), intent(out) :: in
1080       real(C_FLOAT), dimension(*), intent(out) :: out
1081       integer(C_FFTW_R2R_KIND), value :: kind0
1082       integer(C_FFTW_R2R_KIND), value :: kind1
1083       integer(C_FFTW_R2R_KIND), value :: kind2
1084       integer(C_INT), value :: flags
1085     end function fftwf_plan_r2r_3d
1086     
1087     type(C_PTR) function fftwf_plan_guru_r2r(rank,dims,howmany_rank,howmany_dims,in,out,kind,flags) &
1088                          bind(C, name='fftwf_plan_guru_r2r')
1089       import
1090       integer(C_INT), value :: rank
1091       type(fftwf_iodim), dimension(*), intent(in) :: dims
1092       integer(C_INT), value :: howmany_rank
1093       type(fftwf_iodim), dimension(*), intent(in) :: howmany_dims
1094       real(C_FLOAT), dimension(*), intent(out) :: in
1095       real(C_FLOAT), dimension(*), intent(out) :: out
1096       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
1097       integer(C_INT), value :: flags
1098     end function fftwf_plan_guru_r2r
1099     
1100     type(C_PTR) function fftwf_plan_guru64_r2r(rank,dims,howmany_rank,howmany_dims,in,out,kind,flags) &
1101                          bind(C, name='fftwf_plan_guru64_r2r')
1102       import
1103       integer(C_INT), value :: rank
1104       type(fftwf_iodim64), dimension(*), intent(in) :: dims
1105       integer(C_INT), value :: howmany_rank
1106       type(fftwf_iodim64), dimension(*), intent(in) :: howmany_dims
1107       real(C_FLOAT), dimension(*), intent(out) :: in
1108       real(C_FLOAT), dimension(*), intent(out) :: out
1109       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
1110       integer(C_INT), value :: flags
1111     end function fftwf_plan_guru64_r2r
1112     
1113     subroutine fftwf_execute_r2r(p,in,out) bind(C, name='fftwf_execute_r2r')
1114       import
1115       type(C_PTR), value :: p
1116       real(C_FLOAT), dimension(*), intent(inout) :: in
1117       real(C_FLOAT), dimension(*), intent(out) :: out
1118     end subroutine fftwf_execute_r2r
1119     
1120     subroutine fftwf_destroy_plan(p) bind(C, name='fftwf_destroy_plan')
1121       import
1122       type(C_PTR), value :: p
1123     end subroutine fftwf_destroy_plan
1124     
1125     subroutine fftwf_forget_wisdom() bind(C, name='fftwf_forget_wisdom')
1126       import
1127     end subroutine fftwf_forget_wisdom
1128     
1129     subroutine fftwf_cleanup() bind(C, name='fftwf_cleanup')
1130       import
1131     end subroutine fftwf_cleanup
1132     
1133     subroutine fftwf_set_timelimit(t) bind(C, name='fftwf_set_timelimit')
1134       import
1135       real(C_DOUBLE), value :: t
1136     end subroutine fftwf_set_timelimit
1137     
1138     subroutine fftwf_plan_with_nthreads(nthreads) bind(C, name='fftwf_plan_with_nthreads')
1139       import
1140       integer(C_INT), value :: nthreads
1141     end subroutine fftwf_plan_with_nthreads
1142     
1143     integer(C_INT) function fftwf_planner_nthreads() bind(C, name='fftwf_planner_nthreads')
1144       import
1145     end function fftwf_planner_nthreads
1146     
1147     integer(C_INT) function fftwf_init_threads() bind(C, name='fftwf_init_threads')
1148       import
1149     end function fftwf_init_threads
1150     
1151     subroutine fftwf_cleanup_threads() bind(C, name='fftwf_cleanup_threads')
1152       import
1153     end subroutine fftwf_cleanup_threads
1154     
1155 ! Unable to generate Fortran interface for fftwf_threads_set_callback
1156     subroutine fftwf_make_planner_thread_safe() bind(C, name='fftwf_make_planner_thread_safe')
1157       import
1158     end subroutine fftwf_make_planner_thread_safe
1159     
1160     integer(C_INT) function fftwf_export_wisdom_to_filename(filename) bind(C, name='fftwf_export_wisdom_to_filename')
1161       import
1162       character(C_CHAR), dimension(*), intent(in) :: filename
1163     end function fftwf_export_wisdom_to_filename
1164     
1165     subroutine fftwf_export_wisdom_to_file(output_file) bind(C, name='fftwf_export_wisdom_to_file')
1166       import
1167       type(C_PTR), value :: output_file
1168     end subroutine fftwf_export_wisdom_to_file
1169     
1170     type(C_PTR) function fftwf_export_wisdom_to_string() bind(C, name='fftwf_export_wisdom_to_string')
1171       import
1172     end function fftwf_export_wisdom_to_string
1173     
1174     subroutine fftwf_export_wisdom(write_char,data) bind(C, name='fftwf_export_wisdom')
1175       import
1176       type(C_FUNPTR), value :: write_char
1177       type(C_PTR), value :: data
1178     end subroutine fftwf_export_wisdom
1179     
1180     integer(C_INT) function fftwf_import_system_wisdom() bind(C, name='fftwf_import_system_wisdom')
1181       import
1182     end function fftwf_import_system_wisdom
1183     
1184     integer(C_INT) function fftwf_import_wisdom_from_filename(filename) bind(C, name='fftwf_import_wisdom_from_filename')
1185       import
1186       character(C_CHAR), dimension(*), intent(in) :: filename
1187     end function fftwf_import_wisdom_from_filename
1188     
1189     integer(C_INT) function fftwf_import_wisdom_from_file(input_file) bind(C, name='fftwf_import_wisdom_from_file')
1190       import
1191       type(C_PTR), value :: input_file
1192     end function fftwf_import_wisdom_from_file
1193     
1194     integer(C_INT) function fftwf_import_wisdom_from_string(input_string) bind(C, name='fftwf_import_wisdom_from_string')
1195       import
1196       character(C_CHAR), dimension(*), intent(in) :: input_string
1197     end function fftwf_import_wisdom_from_string
1198     
1199     integer(C_INT) function fftwf_import_wisdom(read_char,data) bind(C, name='fftwf_import_wisdom')
1200       import
1201       type(C_FUNPTR), value :: read_char
1202       type(C_PTR), value :: data
1203     end function fftwf_import_wisdom
1204     
1205     subroutine fftwf_fprint_plan(p,output_file) bind(C, name='fftwf_fprint_plan')
1206       import
1207       type(C_PTR), value :: p
1208       type(C_PTR), value :: output_file
1209     end subroutine fftwf_fprint_plan
1210     
1211     subroutine fftwf_print_plan(p) bind(C, name='fftwf_print_plan')
1212       import
1213       type(C_PTR), value :: p
1214     end subroutine fftwf_print_plan
1215     
1216     type(C_PTR) function fftwf_sprint_plan(p) bind(C, name='fftwf_sprint_plan')
1217       import
1218       type(C_PTR), value :: p
1219     end function fftwf_sprint_plan
1220     
1221     type(C_PTR) function fftwf_malloc(n) bind(C, name='fftwf_malloc')
1222       import
1223       integer(C_SIZE_T), value :: n
1224     end function fftwf_malloc
1225     
1226     type(C_PTR) function fftwf_alloc_real(n) bind(C, name='fftwf_alloc_real')
1227       import
1228       integer(C_SIZE_T), value :: n
1229     end function fftwf_alloc_real
1230     
1231     type(C_PTR) function fftwf_alloc_complex(n) bind(C, name='fftwf_alloc_complex')
1232       import
1233       integer(C_SIZE_T), value :: n
1234     end function fftwf_alloc_complex
1235     
1236     subroutine fftwf_free(p) bind(C, name='fftwf_free')
1237       import
1238       type(C_PTR), value :: p
1239     end subroutine fftwf_free
1240     
1241     subroutine fftwf_flops(p,add,mul,fmas) bind(C, name='fftwf_flops')
1242       import
1243       type(C_PTR), value :: p
1244       real(C_DOUBLE), intent(out) :: add
1245       real(C_DOUBLE), intent(out) :: mul
1246       real(C_DOUBLE), intent(out) :: fmas
1247     end subroutine fftwf_flops
1248     
1249     real(C_DOUBLE) function fftwf_estimate_cost(p) bind(C, name='fftwf_estimate_cost')
1250       import
1251       type(C_PTR), value :: p
1252     end function fftwf_estimate_cost
1253     
1254     real(C_DOUBLE) function fftwf_cost(p) bind(C, name='fftwf_cost')
1255       import
1256       type(C_PTR), value :: p
1257     end function fftwf_cost
1258     
1259     integer(C_INT) function fftwf_alignment_of(p) bind(C, name='fftwf_alignment_of')
1260       import
1261       real(C_FLOAT), dimension(*), intent(out) :: p
1262     end function fftwf_alignment_of
1263     
1264   end interface