The way FFTW is called in the example program from John Burkardt is fundamentally incompatible with the FFTW 3.3.5 include file. The latter uses bind(c)
and kind parameters from the iso_c_binding
module. It’s likely that example program targets an earlier version of FFTW.
Here’s an example I wrote instead of calculing the derivative of a periodic function:
fftw_demo.f90
:
module fftw3
use, intrinsic :: iso_c_binding
implicit none
include 'fftw3.f03'
end module
program fftw_demo
use fftw3
implicit none
integer, parameter :: dp = kind(1.0d0)
real(dp), parameter :: PI = 4*atan(1.0_dp)
complex(dp), parameter :: j_ = cmplx(0.0_dp,1.0_dp,dp)
real(dp), allocatable :: a(:), da(:)
complex(dp), allocatable :: afreq(:)
real(dp) :: x, L
type(c_ptr) :: pf,pb
integer :: i, n
n = 32
L = 2*PI
allocate(a(n),afreq(n),da(n))
do i = 1, n
x = (i-1)*(L/n)
a(i) = sin(x) + sin(3*x)
da(i) = cos(x) + 3*cos(3*x)
end do
pf = fftw_plan_dft_r2c_1d(n,a,afreq,FFTW_ESTIMATE)
pb = fftw_plan_dft_c2r_1d(n,afreq,a,FFTW_ESTIMATE)
! Forward FFT
call fftw_execute_dft_r2c(pf,a,afreq)
! First derivative
!
! An explanation is given in Section 3 of the document:
! https://math.mit.edu/~stevenj/fft-deriv.pdf
do i = 1, n/2
afreq(i) = j_ * (2*PI*(i-1)/L) * afreq(i)
end do
if (mod(n,2) /= 0) afreq(n/2+1) = 0 ! <-- Only needed when n is odd
! Inverse FFT
call fftw_execute_dft_c2r(pb,afreq,a)
a = a/n
print *, "Maximum difference: ", maxval(abs(da - a))
call fftw_destroy_plan(pf)
call fftw_destroy_plan(pb)
end program
To compile the program I used the following command:
$ gfortran -Wall -I./fftw-3.3.5-dll64 -L./fftw-3.3.5-dll64 -o fftw_demo fftw_demo.f90 -lfftw3-3
and the work folder (current directory) contained the file fftw_demo.f90
and the unzipped FFTW folder.
I also had to edit the PATH environment variable so the linker could find the library at runtime. For a single session, you can achieve this with:
set PATH=%PATH%;C:\path\to\fftw-3.3.5-dll64\
If you’ll be using FFTW more often, you can set the path permanently by following the instructions given here: How to add a folder to `Path` environment variable in Windows 10 (with screenshots) - Stack Overflow
I’d also recommend going through the FFTW documenation on Calling FFTW from Modern Fortran.
To write this answer I used the Quickstart Fortran on Windows.