Working with FFTW on windows 10

fftw_test.f90 (19.2 KB)

I wanna run the above program but I keep getting the error.
fftw_test.f90:68: Error: Can’t open included file ‘fftw3.f90’

I have downloaded the Precompiled FFTW 3.3.5 Windows DLLs as mentioned there

https://www.fftw.org/install/windows.html

Is there an issue with the command? I am using

gfortran fftw_test.f90 -o fftw_test -lc:\fftw-3.3.5-dll64

As you can see from your picture, there is no file fftw3.f90. Either there is fftw3.f or fftw3.f03. They correspond to different interfaces and do not contain the same procedures.

Depending whether you want to use the the legacy or the modern interface, use one or the other. The issue is inside your code (that you do not show), not in your command.

The code file is attached at the top.

even if I use .f03, the error is there.

You must set your include paths, see the -I flag.

I am confused now. What is the -I path here? Is -Ic not the path?

gfortran fftw_test.f90 -o fftw_test -lc:\fftw-3.3.5-dll64

I am not sure if GCC can understand widows absolute paths. Which distribution of GCC do you use? Msys2, MinGW or Cygwin?

What you have is -l<libraries>, which specifies libraries that get passed to the linker.

The -I<directory> flag is used to specify the path where the compiler searches for include-ed files (including those of the preprocessor statement #include) and precompiled module files.

so if I have precompiled library files, should not it work by this path?

gfortran fftw_test.f90 -o fftw_test -lc:\fftw-3.3.5-dll64

I am even more confused now.

The -l option is for the linker and is used to link the dll libraries only after a successful compilation. The -I option is for the compiler and tells it where to find the include files, here the fftw3.f90.

Note that l is not I and -Ic is not -lc. They look similar, but are different.

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.

2 Likes

It is compatible. It is just based on the legacy interface which is still included in FFTW 3. As I mentioned in my first comment, one has to choose whether one uses the legacy interface or the modern interface and use the appropriate include file.

It is all well documented in the FFTW documentation.

Both work fine, but the modern interface has already been available for more than 10 years. Or at least ~10 years is the age of the first commits from the code where I use it. I incidentally checked that yesterday. However, legacy programs can still use the legacy interface.

1 Like

Thanks for the clarification. I see that the fftw_test page from John Burkardt provides the "fftw3.f90" include file, providing the integer parameters. The subroutines however are called as external routines in agreement with the section “Calling FFTW from Legacy Fortran”.

Initially I replaced include "fftw.f90" with include "fftw.f03" in the John Burkardt example, but this led to a bunch of warnings about missing type definitions, so I assumed something was astray.

In the version downloaded by @Shahid, the integer parameters are in the file "fftw3.f", which can be included in both free- or fixed-form files.

Personally, I find the practice of using the .f, .f90, .f03 extensions for include files confusing. The .f03 extension has been used by FFTW authors, because C interoperability was standardized with Fortran 2003, but I’m afraid it just adds further to the confusion.

Are you working with Spectral Estimation? Are you developing an algorithm? If so, you should read Steven Kay’s textbook ‘Modern Spectral Estimation’ 1988 that has a menu of 10+ spectral estimators to choose from. The results differ dramatically from one estimator to another. Plus, varying input parameters and/or number of points may provide discrepancies. Observe how zero padding effects your results. Manufacturing companies take note! Some estimators can detect signals 50 to 100 dB from main signal. See documented example! The unwritten rule of ‘30 dB is okay’ (i.e. hidden) is no longer true. Download at SpectrumSolvers: Compare 13 Spectral Estimation Algorithms, Spectral Estimation Methods, Signal Analysis, Signal Processing .

1 Like

Thanks for sharing. Actually, I am working on the implementation of a semi-implicit Fourier spectral algorithm as shown here. It is quite comfortable in Matlab. But using Fortran seems a bit tricky!

Are you aware that the FFT is mathematical incorrect? A sampling of data puts a Sinc function convolved with the true PSD. I proved this to NASA, Sandia Labs, & Lockheed (LMSC) back in the late 1980s & 1990. If you have seem Steven Kay’s book where he compares 12 algorithms, would see the differences. The other algorithms try to avoid the Sinc function by different means. I tried to point out this problem to EE profs at Stanford U. but the math was over their head! No school should teach the use of FFTs unless it is for developmentally purpose. Phil