Skip to content

Commit ceb763a

Browse files
committed
add (i)fft2 interfaces.
add `stdlib/forlab` dependencies for example/test checks.
1 parent ac5fecf commit ceb763a

File tree

8 files changed

+286
-1
lines changed

8 files changed

+286
-1
lines changed

doc/specs/fftpack.md

Lines changed: 99 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -281,6 +281,105 @@ program demo_ifft
281281
end program demo_ifft
282282
```
283283

284+
### `fft2`
285+
286+
#### Description
287+
288+
Computes the rank-2 forward complex discrete fourier transform (the fourier analysis).
289+
290+
#### Status
291+
292+
Experimental.
293+
294+
#### Class
295+
296+
Pure function.
297+
298+
#### Syntax
299+
300+
`result = [[fftpack(module):fft2(interface)]](x)`
301+
302+
#### Argument
303+
304+
`x`: Shall be a `complex` and rank-2 array.
305+
This argument is `intent(in)`.
306+
307+
#### Return value
308+
309+
Returns a `complex` and rank-2 array, the Discrete Fourier Transform (DFT) of `x`.
310+
311+
#### Notes
312+
313+
Within numerical accuracy, `x == ifft2(fft2(x))/(size(x, 1)*size(x, 2))`.
314+
315+
#### Example
316+
317+
```fortran
318+
program demo_fftpack_fft2
319+
320+
use fftpack, only: fft2
321+
use forlab_io, only: disp
322+
323+
complex(kind=8), allocatable :: x(:, :)
324+
x = reshape(spread([1, 2, 3, 4], 1, 4), [4, 4])
325+
call disp(fft2(x), "fft2(x): ")
326+
327+
!! (40.00,0.000) (-8.000,8.000) (-8.000,0.000) (-8.000,-8.000)
328+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
329+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
330+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
331+
332+
end program demo_fftpack_fft2
333+
334+
```
335+
336+
### `ifft2`
337+
338+
#### Description
339+
340+
Unnormalized inverse of `fft2`.
341+
342+
#### Status
343+
344+
Experimental.
345+
346+
#### Class
347+
348+
Pure function.
349+
350+
#### Syntax
351+
352+
`result = [[fftpack(module):ifft(interface)]](x)`
353+
354+
#### Argument
355+
356+
`x`: Shall be a `complex` and rank-2 array.
357+
This argument is `intent(in)`.
358+
359+
#### Return value
360+
361+
Returns a `complex` and rank-2 array, the unnormalized inverse Discrete Fourier Transform (DFT) of `x`.
362+
363+
#### Example
364+
365+
```fortran
366+
program demo_fftpack_ifft2
367+
368+
use fftpack, only: fft2, ifft2
369+
use forlab_io, only: disp
370+
371+
complex(kind=8), allocatable :: x(:, :)
372+
x = reshape(spread([1, 2, 3, 4], 1, 4), [4, 4])
373+
call disp(ifft2(fft2(x))/(size(x, 1)*size(x, 2)), "ifft2(fft2(x))/(size(x, 1)*size(x, 2)): ")
374+
375+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
376+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
377+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
378+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
379+
380+
end program demo_fftpack_ifft2
381+
```
382+
284383
## Fourier transform of double real periodic sequences
285384
### `dffti`
286385

example/demo_fftpack_fft2.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program demo_fftpack_fft2
2+
3+
use fftpack, only: fft2
4+
use forlab_io, only: disp
5+
6+
complex(kind=8), allocatable :: x(:, :)
7+
x = reshape(spread([1, 2, 3, 4], 1, 4), [4, 4])
8+
call disp(fft2(x), "fft2(x): ")
9+
10+
!! (40.00,0.000) (-8.000,8.000) (-8.000,0.000) (-8.000,-8.000)
11+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
12+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
13+
!! (0.000,0.000) (0.000,0.000) (0.000,0.000) (0.000,0.000)
14+
15+
end program demo_fftpack_fft2

example/demo_fftpack_ifft2.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program demo_fftpack_ifft2
2+
3+
use fftpack, only: fft2, ifft2
4+
use forlab_io, only: disp
5+
6+
complex(kind=8), allocatable :: x(:, :)
7+
x = reshape(spread([1, 2, 3, 4], 1, 4), [4, 4])
8+
call disp(ifft2(fft2(x))/(size(x, 1)*size(x, 2)), "ifft2(fft2(x))/(size(x, 1)*size(x, 2)): ")
9+
10+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
11+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
12+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
13+
!! (1.000,0.000) (2.000,0.000) (3.000,0.000) (4.000,0.000)
14+
15+
end program demo_fftpack_ifft2

fpm.toml

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,21 @@ auto-executables = false
1515
auto-tests = false
1616
auto-examples = false
1717

18+
# examples
19+
[[example]]
20+
name = "fftpack_fft2"
21+
source-dir = "example"
22+
main = "demo_fftpack_fft2.f90"
23+
[[example]]
24+
name = "fftpack_ifft2"
25+
source-dir = "example"
26+
main = "demo_fftpack_ifft2.f90"
27+
28+
[dev-dependencies]
29+
stdlib = { git="https://github.com/LKedward/stdlib-fpm.git" }
30+
forlab = { git="https://github.com/fortran-fans/forlab.git" }
31+
32+
1833
# Original test
1934
[[test]]
2035
name = "tstfft"
@@ -32,6 +47,11 @@ name = "fftpack_fft"
3247
source-dir = "test"
3348
main = "test_fftpack_fft.f90"
3449

50+
[[test]]
51+
name = "fftpack_fft2"
52+
source-dir = "test"
53+
main = "test_fftpack_fft2.f90"
54+
3555
[[test]]
3656
name = "fftpack_ifft"
3757
source-dir = "test"

src/fftpack.f90

Lines changed: 23 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module fftpack
55
private
66

77
public :: zffti, zfftf, zfftb
8-
public :: fft, ifft
8+
public :: fft, ifft, fft2, ifft2
99
public :: fftshift, ifftshift
1010

1111
public :: dffti, dfftf, dfftb
@@ -176,6 +176,28 @@ pure module function ifft_dp(x, n) result(result)
176176
end function ifft_dp
177177
end interface ifft
178178

179+
!> Version: experimental
180+
!>
181+
!> Forward transform of a rank-2 and double complex periodic sequence.
182+
!> ([Specifiction](../page/specs/fftpack.html#fft2))
183+
interface fft2
184+
pure module function fft2_dp(x) result(result)
185+
complex(kind=dp), intent(in) :: x(:, :)
186+
complex(kind=dp), allocatable :: result(:, :)
187+
end function fft2_dp
188+
end interface fft2
189+
190+
!> Version: experimental
191+
!>
192+
!> Backward transform of a rank-2 and double complex periodic sequence.
193+
!> ([Specifiction](../page/specs/fftpack.html#ifft2))
194+
interface ifft2
195+
pure module function ifft2_dp(x) result(result)
196+
complex(kind=dp), intent(in) :: x(:, :)
197+
complex(kind=dp), allocatable :: result(:, :)
198+
end function ifft2_dp
199+
end interface ifft2
200+
179201
!> Version: experimental
180202
!>
181203
!> Forward transform of a double real periodic sequence.

src/fftpack_fft2.f90

Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
submodule(fftpack) fftpack_fft2
2+
3+
contains
4+
5+
!> Forward transform of a rank-2 double complex periodic sequence.
6+
!> `fft2` can achieve parallel acceleration through `OpenMP`.
7+
pure module function fft2_dp(x) result(result)
8+
complex(kind=dp), intent(in) :: x(:, :)
9+
complex(kind=dp), allocatable :: result(:, :)
10+
11+
integer :: lendim(rank(x))
12+
integer :: lenseq, lensav, i
13+
real(kind=dp), allocatable :: wsave(:)
14+
15+
lendim = shape(x)
16+
result = x
17+
18+
!! FFT is performed on each dimension of the array in turn,
19+
!! and the scale of the array remains the same after each FFT.
20+
21+
!* First diemnsion:
22+
23+
!> Initialize FFT
24+
lenseq = lendim(1)
25+
lensav = 4*lenseq + 15
26+
allocate(wsave(lensav))
27+
call zffti(lenseq, wsave)
28+
29+
!> Forward transformation
30+
do i = 1, lendim(2)
31+
call zfftf(lenseq, result(:, i), wsave)
32+
end do
33+
34+
deallocate(wsave)
35+
36+
!* Second dimension:
37+
38+
!> Initialize FFT
39+
lenseq = lendim(2)
40+
lensav = 4*lenseq + 15
41+
allocate(wsave(lensav))
42+
call zffti(lenseq, wsave)
43+
44+
!> Forward transformation
45+
do i = 1, lendim(1)
46+
call zfftf(lenseq, result(i, :), wsave)
47+
end do
48+
49+
end function fft2_dp
50+
51+
end submodule fftpack_fft2

src/fftpack_ifft2.f90

Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
submodule(fftpack) fftpack_ifft2
2+
3+
contains
4+
5+
!> Backward transform of a rank-2 double complex periodic sequence.
6+
!> `ifft2` can achieve parallel acceleration through `OpenMP`.
7+
pure module function ifft2_dp(x) result(result)
8+
complex(kind=dp), intent(in) :: x(:, :)
9+
complex(kind=dp), allocatable :: result(:, :)
10+
11+
integer :: lendim(rank(x))
12+
integer :: lenseq, lensav, i
13+
real(kind=dp), allocatable :: wsave(:)
14+
15+
lendim = shape(x)
16+
result = x
17+
18+
!! FFT is performed on each dimension of the array in turn,
19+
!! and the scale of the array remains the same after each FFT.
20+
21+
!* First diemnsion:
22+
23+
!> Initialize FFT
24+
lenseq = lendim(1)
25+
lensav = 4*lenseq + 15
26+
allocate(wsave(lensav))
27+
call zffti(lenseq, wsave)
28+
29+
!> Backward transformation
30+
do i = 1, lendim(2)
31+
call zfftb(lenseq, result(:, i), wsave)
32+
end do
33+
34+
deallocate(wsave)
35+
36+
!* Second dimension:
37+
38+
!> Initialize FFT
39+
lenseq = lendim(2)
40+
lensav = 4*lenseq + 15
41+
allocate(wsave(lensav))
42+
call zffti(lenseq, wsave)
43+
44+
!> Backward transformation
45+
do i = 1, lendim(1)
46+
call zfftb(lenseq, result(i, :), wsave)
47+
end do
48+
49+
end function ifft2_dp
50+
51+
end submodule fftpack_ifft2

test/test_fftpack_fft2.f90

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
program test_fftpack_fft2
2+
use fftpack, only: fft2, ifft2
3+
use forlab_math, only: is_close
4+
use stdlib_error, only: check
5+
6+
complex(kind=8), allocatable :: x(:, :)
7+
x = reshape(spread([1, 2, 3, 4], 1, 4), [4, 4])
8+
9+
call check(all(is_close(ifft2(fft2(x))/16.0_8, x)), msg="`ifft2(fft2(x))` failed.")
10+
print *, "All tests in `test_fftpack_fft2` passed."
11+
12+
end program test_fftpack_fft2

0 commit comments

Comments
 (0)