Back to home page

EIC code displayed by LXR

 
 

    


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

0001 ! Generated automatically.  DO NOT EDIT!
0002 
0003   include 'fftw3l.f03'
0004 
0005 
0006   type, bind(C) :: fftwl_mpi_ddim
0007      integer(C_INTPTR_T) n, ib, ob
0008   end type fftwl_mpi_ddim
0009 
0010   interface
0011     subroutine fftwl_mpi_init() bind(C, name='fftwl_mpi_init')
0012       import
0013     end subroutine fftwl_mpi_init
0014     
0015     subroutine fftwl_mpi_cleanup() bind(C, name='fftwl_mpi_cleanup')
0016       import
0017     end subroutine fftwl_mpi_cleanup
0018     
0019     integer(C_INTPTR_T) function fftwl_mpi_local_size_many_transposed(rnk,n,howmany,block0,block1,comm,local_n0,local_0_start, &
0020                                                                       local_n1,local_1_start) &
0021                                  bind(C, name='fftwl_mpi_local_size_many_transposed_f03')
0022       import
0023       integer(C_INT), value :: rnk
0024       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0025       integer(C_INTPTR_T), value :: howmany
0026       integer(C_INTPTR_T), value :: block0
0027       integer(C_INTPTR_T), value :: block1
0028       integer(C_INT32_T), value :: comm
0029       integer(C_INTPTR_T), intent(out) :: local_n0
0030       integer(C_INTPTR_T), intent(out) :: local_0_start
0031       integer(C_INTPTR_T), intent(out) :: local_n1
0032       integer(C_INTPTR_T), intent(out) :: local_1_start
0033     end function fftwl_mpi_local_size_many_transposed
0034     
0035     integer(C_INTPTR_T) function fftwl_mpi_local_size_many(rnk,n,howmany,block0,comm,local_n0,local_0_start) &
0036                                  bind(C, name='fftwl_mpi_local_size_many_f03')
0037       import
0038       integer(C_INT), value :: rnk
0039       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0040       integer(C_INTPTR_T), value :: howmany
0041       integer(C_INTPTR_T), value :: block0
0042       integer(C_INT32_T), value :: comm
0043       integer(C_INTPTR_T), intent(out) :: local_n0
0044       integer(C_INTPTR_T), intent(out) :: local_0_start
0045     end function fftwl_mpi_local_size_many
0046     
0047     integer(C_INTPTR_T) function fftwl_mpi_local_size_transposed(rnk,n,comm,local_n0,local_0_start,local_n1,local_1_start) &
0048                                  bind(C, name='fftwl_mpi_local_size_transposed_f03')
0049       import
0050       integer(C_INT), value :: rnk
0051       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0052       integer(C_INT32_T), value :: comm
0053       integer(C_INTPTR_T), intent(out) :: local_n0
0054       integer(C_INTPTR_T), intent(out) :: local_0_start
0055       integer(C_INTPTR_T), intent(out) :: local_n1
0056       integer(C_INTPTR_T), intent(out) :: local_1_start
0057     end function fftwl_mpi_local_size_transposed
0058     
0059     integer(C_INTPTR_T) function fftwl_mpi_local_size(rnk,n,comm,local_n0,local_0_start) bind(C, name='fftwl_mpi_local_size_f03')
0060       import
0061       integer(C_INT), value :: rnk
0062       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0063       integer(C_INT32_T), value :: comm
0064       integer(C_INTPTR_T), intent(out) :: local_n0
0065       integer(C_INTPTR_T), intent(out) :: local_0_start
0066     end function fftwl_mpi_local_size
0067     
0068     integer(C_INTPTR_T) function fftwl_mpi_local_size_many_1d(n0,howmany,comm,sign,flags,local_ni,local_i_start,local_no, &
0069                                                               local_o_start) bind(C, name='fftwl_mpi_local_size_many_1d_f03')
0070       import
0071       integer(C_INTPTR_T), value :: n0
0072       integer(C_INTPTR_T), value :: howmany
0073       integer(C_INT32_T), value :: comm
0074       integer(C_INT), value :: sign
0075       integer(C_INT), value :: flags
0076       integer(C_INTPTR_T), intent(out) :: local_ni
0077       integer(C_INTPTR_T), intent(out) :: local_i_start
0078       integer(C_INTPTR_T), intent(out) :: local_no
0079       integer(C_INTPTR_T), intent(out) :: local_o_start
0080     end function fftwl_mpi_local_size_many_1d
0081     
0082     integer(C_INTPTR_T) function fftwl_mpi_local_size_1d(n0,comm,sign,flags,local_ni,local_i_start,local_no,local_o_start) &
0083                                  bind(C, name='fftwl_mpi_local_size_1d_f03')
0084       import
0085       integer(C_INTPTR_T), value :: n0
0086       integer(C_INT32_T), value :: comm
0087       integer(C_INT), value :: sign
0088       integer(C_INT), value :: flags
0089       integer(C_INTPTR_T), intent(out) :: local_ni
0090       integer(C_INTPTR_T), intent(out) :: local_i_start
0091       integer(C_INTPTR_T), intent(out) :: local_no
0092       integer(C_INTPTR_T), intent(out) :: local_o_start
0093     end function fftwl_mpi_local_size_1d
0094     
0095     integer(C_INTPTR_T) function fftwl_mpi_local_size_2d(n0,n1,comm,local_n0,local_0_start) &
0096                                  bind(C, name='fftwl_mpi_local_size_2d_f03')
0097       import
0098       integer(C_INTPTR_T), value :: n0
0099       integer(C_INTPTR_T), value :: n1
0100       integer(C_INT32_T), value :: comm
0101       integer(C_INTPTR_T), intent(out) :: local_n0
0102       integer(C_INTPTR_T), intent(out) :: local_0_start
0103     end function fftwl_mpi_local_size_2d
0104     
0105     integer(C_INTPTR_T) function fftwl_mpi_local_size_2d_transposed(n0,n1,comm,local_n0,local_0_start,local_n1,local_1_start) &
0106                                  bind(C, name='fftwl_mpi_local_size_2d_transposed_f03')
0107       import
0108       integer(C_INTPTR_T), value :: n0
0109       integer(C_INTPTR_T), value :: n1
0110       integer(C_INT32_T), value :: comm
0111       integer(C_INTPTR_T), intent(out) :: local_n0
0112       integer(C_INTPTR_T), intent(out) :: local_0_start
0113       integer(C_INTPTR_T), intent(out) :: local_n1
0114       integer(C_INTPTR_T), intent(out) :: local_1_start
0115     end function fftwl_mpi_local_size_2d_transposed
0116     
0117     integer(C_INTPTR_T) function fftwl_mpi_local_size_3d(n0,n1,n2,comm,local_n0,local_0_start) &
0118                                  bind(C, name='fftwl_mpi_local_size_3d_f03')
0119       import
0120       integer(C_INTPTR_T), value :: n0
0121       integer(C_INTPTR_T), value :: n1
0122       integer(C_INTPTR_T), value :: n2
0123       integer(C_INT32_T), value :: comm
0124       integer(C_INTPTR_T), intent(out) :: local_n0
0125       integer(C_INTPTR_T), intent(out) :: local_0_start
0126     end function fftwl_mpi_local_size_3d
0127     
0128     integer(C_INTPTR_T) function fftwl_mpi_local_size_3d_transposed(n0,n1,n2,comm,local_n0,local_0_start,local_n1,local_1_start) &
0129                                  bind(C, name='fftwl_mpi_local_size_3d_transposed_f03')
0130       import
0131       integer(C_INTPTR_T), value :: n0
0132       integer(C_INTPTR_T), value :: n1
0133       integer(C_INTPTR_T), value :: n2
0134       integer(C_INT32_T), value :: comm
0135       integer(C_INTPTR_T), intent(out) :: local_n0
0136       integer(C_INTPTR_T), intent(out) :: local_0_start
0137       integer(C_INTPTR_T), intent(out) :: local_n1
0138       integer(C_INTPTR_T), intent(out) :: local_1_start
0139     end function fftwl_mpi_local_size_3d_transposed
0140     
0141     type(C_PTR) function fftwl_mpi_plan_many_transpose(n0,n1,howmany,block0,block1,in,out,comm,flags) &
0142                          bind(C, name='fftwl_mpi_plan_many_transpose_f03')
0143       import
0144       integer(C_INTPTR_T), value :: n0
0145       integer(C_INTPTR_T), value :: n1
0146       integer(C_INTPTR_T), value :: howmany
0147       integer(C_INTPTR_T), value :: block0
0148       integer(C_INTPTR_T), value :: block1
0149       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0150       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0151       integer(C_INT32_T), value :: comm
0152       integer(C_INT), value :: flags
0153     end function fftwl_mpi_plan_many_transpose
0154     
0155     type(C_PTR) function fftwl_mpi_plan_transpose(n0,n1,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_transpose_f03')
0156       import
0157       integer(C_INTPTR_T), value :: n0
0158       integer(C_INTPTR_T), value :: n1
0159       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0160       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0161       integer(C_INT32_T), value :: comm
0162       integer(C_INT), value :: flags
0163     end function fftwl_mpi_plan_transpose
0164     
0165     type(C_PTR) function fftwl_mpi_plan_many_dft(rnk,n,howmany,block,tblock,in,out,comm,sign,flags) &
0166                          bind(C, name='fftwl_mpi_plan_many_dft_f03')
0167       import
0168       integer(C_INT), value :: rnk
0169       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0170       integer(C_INTPTR_T), value :: howmany
0171       integer(C_INTPTR_T), value :: block
0172       integer(C_INTPTR_T), value :: tblock
0173       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0174       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0175       integer(C_INT32_T), value :: comm
0176       integer(C_INT), value :: sign
0177       integer(C_INT), value :: flags
0178     end function fftwl_mpi_plan_many_dft
0179     
0180     type(C_PTR) function fftwl_mpi_plan_dft(rnk,n,in,out,comm,sign,flags) bind(C, name='fftwl_mpi_plan_dft_f03')
0181       import
0182       integer(C_INT), value :: rnk
0183       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0184       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0185       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0186       integer(C_INT32_T), value :: comm
0187       integer(C_INT), value :: sign
0188       integer(C_INT), value :: flags
0189     end function fftwl_mpi_plan_dft
0190     
0191     type(C_PTR) function fftwl_mpi_plan_dft_1d(n0,in,out,comm,sign,flags) bind(C, name='fftwl_mpi_plan_dft_1d_f03')
0192       import
0193       integer(C_INTPTR_T), value :: n0
0194       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0195       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0196       integer(C_INT32_T), value :: comm
0197       integer(C_INT), value :: sign
0198       integer(C_INT), value :: flags
0199     end function fftwl_mpi_plan_dft_1d
0200     
0201     type(C_PTR) function fftwl_mpi_plan_dft_2d(n0,n1,in,out,comm,sign,flags) bind(C, name='fftwl_mpi_plan_dft_2d_f03')
0202       import
0203       integer(C_INTPTR_T), value :: n0
0204       integer(C_INTPTR_T), value :: n1
0205       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0206       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0207       integer(C_INT32_T), value :: comm
0208       integer(C_INT), value :: sign
0209       integer(C_INT), value :: flags
0210     end function fftwl_mpi_plan_dft_2d
0211     
0212     type(C_PTR) function fftwl_mpi_plan_dft_3d(n0,n1,n2,in,out,comm,sign,flags) bind(C, name='fftwl_mpi_plan_dft_3d_f03')
0213       import
0214       integer(C_INTPTR_T), value :: n0
0215       integer(C_INTPTR_T), value :: n1
0216       integer(C_INTPTR_T), value :: n2
0217       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0218       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0219       integer(C_INT32_T), value :: comm
0220       integer(C_INT), value :: sign
0221       integer(C_INT), value :: flags
0222     end function fftwl_mpi_plan_dft_3d
0223     
0224     type(C_PTR) function fftwl_mpi_plan_many_r2r(rnk,n,howmany,iblock,oblock,in,out,comm,kind,flags) &
0225                          bind(C, name='fftwl_mpi_plan_many_r2r_f03')
0226       import
0227       integer(C_INT), value :: rnk
0228       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0229       integer(C_INTPTR_T), value :: howmany
0230       integer(C_INTPTR_T), value :: iblock
0231       integer(C_INTPTR_T), value :: oblock
0232       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0233       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0234       integer(C_INT32_T), value :: comm
0235       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0236       integer(C_INT), value :: flags
0237     end function fftwl_mpi_plan_many_r2r
0238     
0239     type(C_PTR) function fftwl_mpi_plan_r2r(rnk,n,in,out,comm,kind,flags) bind(C, name='fftwl_mpi_plan_r2r_f03')
0240       import
0241       integer(C_INT), value :: rnk
0242       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0243       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0244       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0245       integer(C_INT32_T), value :: comm
0246       integer(C_FFTW_R2R_KIND), dimension(*), intent(in) :: kind
0247       integer(C_INT), value :: flags
0248     end function fftwl_mpi_plan_r2r
0249     
0250     type(C_PTR) function fftwl_mpi_plan_r2r_2d(n0,n1,in,out,comm,kind0,kind1,flags) bind(C, name='fftwl_mpi_plan_r2r_2d_f03')
0251       import
0252       integer(C_INTPTR_T), value :: n0
0253       integer(C_INTPTR_T), value :: n1
0254       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0255       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0256       integer(C_INT32_T), value :: comm
0257       integer(C_FFTW_R2R_KIND), value :: kind0
0258       integer(C_FFTW_R2R_KIND), value :: kind1
0259       integer(C_INT), value :: flags
0260     end function fftwl_mpi_plan_r2r_2d
0261     
0262     type(C_PTR) function fftwl_mpi_plan_r2r_3d(n0,n1,n2,in,out,comm,kind0,kind1,kind2,flags) &
0263                          bind(C, name='fftwl_mpi_plan_r2r_3d_f03')
0264       import
0265       integer(C_INTPTR_T), value :: n0
0266       integer(C_INTPTR_T), value :: n1
0267       integer(C_INTPTR_T), value :: n2
0268       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0269       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0270       integer(C_INT32_T), value :: comm
0271       integer(C_FFTW_R2R_KIND), value :: kind0
0272       integer(C_FFTW_R2R_KIND), value :: kind1
0273       integer(C_FFTW_R2R_KIND), value :: kind2
0274       integer(C_INT), value :: flags
0275     end function fftwl_mpi_plan_r2r_3d
0276     
0277     type(C_PTR) function fftwl_mpi_plan_many_dft_r2c(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0278                          bind(C, name='fftwl_mpi_plan_many_dft_r2c_f03')
0279       import
0280       integer(C_INT), value :: rnk
0281       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0282       integer(C_INTPTR_T), value :: howmany
0283       integer(C_INTPTR_T), value :: iblock
0284       integer(C_INTPTR_T), value :: oblock
0285       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0286       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0287       integer(C_INT32_T), value :: comm
0288       integer(C_INT), value :: flags
0289     end function fftwl_mpi_plan_many_dft_r2c
0290     
0291     type(C_PTR) function fftwl_mpi_plan_dft_r2c(rnk,n,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_r2c_f03')
0292       import
0293       integer(C_INT), value :: rnk
0294       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0295       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0296       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0297       integer(C_INT32_T), value :: comm
0298       integer(C_INT), value :: flags
0299     end function fftwl_mpi_plan_dft_r2c
0300     
0301     type(C_PTR) function fftwl_mpi_plan_dft_r2c_2d(n0,n1,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_r2c_2d_f03')
0302       import
0303       integer(C_INTPTR_T), value :: n0
0304       integer(C_INTPTR_T), value :: n1
0305       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0306       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0307       integer(C_INT32_T), value :: comm
0308       integer(C_INT), value :: flags
0309     end function fftwl_mpi_plan_dft_r2c_2d
0310     
0311     type(C_PTR) function fftwl_mpi_plan_dft_r2c_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_r2c_3d_f03')
0312       import
0313       integer(C_INTPTR_T), value :: n0
0314       integer(C_INTPTR_T), value :: n1
0315       integer(C_INTPTR_T), value :: n2
0316       real(C_LONG_DOUBLE), dimension(*), intent(out) :: in
0317       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0318       integer(C_INT32_T), value :: comm
0319       integer(C_INT), value :: flags
0320     end function fftwl_mpi_plan_dft_r2c_3d
0321     
0322     type(C_PTR) function fftwl_mpi_plan_many_dft_c2r(rnk,n,howmany,iblock,oblock,in,out,comm,flags) &
0323                          bind(C, name='fftwl_mpi_plan_many_dft_c2r_f03')
0324       import
0325       integer(C_INT), value :: rnk
0326       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0327       integer(C_INTPTR_T), value :: howmany
0328       integer(C_INTPTR_T), value :: iblock
0329       integer(C_INTPTR_T), value :: oblock
0330       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0331       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0332       integer(C_INT32_T), value :: comm
0333       integer(C_INT), value :: flags
0334     end function fftwl_mpi_plan_many_dft_c2r
0335     
0336     type(C_PTR) function fftwl_mpi_plan_dft_c2r(rnk,n,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_c2r_f03')
0337       import
0338       integer(C_INT), value :: rnk
0339       integer(C_INTPTR_T), dimension(*), intent(in) :: n
0340       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0341       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0342       integer(C_INT32_T), value :: comm
0343       integer(C_INT), value :: flags
0344     end function fftwl_mpi_plan_dft_c2r
0345     
0346     type(C_PTR) function fftwl_mpi_plan_dft_c2r_2d(n0,n1,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_c2r_2d_f03')
0347       import
0348       integer(C_INTPTR_T), value :: n0
0349       integer(C_INTPTR_T), value :: n1
0350       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0351       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0352       integer(C_INT32_T), value :: comm
0353       integer(C_INT), value :: flags
0354     end function fftwl_mpi_plan_dft_c2r_2d
0355     
0356     type(C_PTR) function fftwl_mpi_plan_dft_c2r_3d(n0,n1,n2,in,out,comm,flags) bind(C, name='fftwl_mpi_plan_dft_c2r_3d_f03')
0357       import
0358       integer(C_INTPTR_T), value :: n0
0359       integer(C_INTPTR_T), value :: n1
0360       integer(C_INTPTR_T), value :: n2
0361       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: in
0362       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0363       integer(C_INT32_T), value :: comm
0364       integer(C_INT), value :: flags
0365     end function fftwl_mpi_plan_dft_c2r_3d
0366     
0367     subroutine fftwl_mpi_gather_wisdom(comm_) bind(C, name='fftwl_mpi_gather_wisdom_f03')
0368       import
0369       integer(C_INT32_T), value :: comm_
0370     end subroutine fftwl_mpi_gather_wisdom
0371     
0372     subroutine fftwl_mpi_broadcast_wisdom(comm_) bind(C, name='fftwl_mpi_broadcast_wisdom_f03')
0373       import
0374       integer(C_INT32_T), value :: comm_
0375     end subroutine fftwl_mpi_broadcast_wisdom
0376     
0377     subroutine fftwl_mpi_execute_dft(p,in,out) bind(C, name='fftwl_mpi_execute_dft')
0378       import
0379       type(C_PTR), value :: p
0380       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0381       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0382     end subroutine fftwl_mpi_execute_dft
0383     
0384     subroutine fftwl_mpi_execute_dft_r2c(p,in,out) bind(C, name='fftwl_mpi_execute_dft_r2c')
0385       import
0386       type(C_PTR), value :: p
0387       real(C_LONG_DOUBLE), dimension(*), intent(inout) :: in
0388       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(out) :: out
0389     end subroutine fftwl_mpi_execute_dft_r2c
0390     
0391     subroutine fftwl_mpi_execute_dft_c2r(p,in,out) bind(C, name='fftwl_mpi_execute_dft_c2r')
0392       import
0393       type(C_PTR), value :: p
0394       complex(C_LONG_DOUBLE_COMPLEX), dimension(*), intent(inout) :: in
0395       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0396     end subroutine fftwl_mpi_execute_dft_c2r
0397     
0398     subroutine fftwl_mpi_execute_r2r(p,in,out) bind(C, name='fftwl_mpi_execute_r2r')
0399       import
0400       type(C_PTR), value :: p
0401       real(C_LONG_DOUBLE), dimension(*), intent(inout) :: in
0402       real(C_LONG_DOUBLE), dimension(*), intent(out) :: out
0403     end subroutine fftwl_mpi_execute_r2r
0404     
0405   end interface