Skip to content

Commit 48b8412

Browse files
committed
doc(example/real): fix comment, better prog name
1 parent b4ed3dd commit 48b8412

File tree

1 file changed

+51
-0
lines changed

1 file changed

+51
-0
lines changed

example/real-transform.f90

Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
program round_trip_transform_of_real_function
2+
!! This program invokes fftpack's rrft function to compute the forward transform of a real function
3+
!! and constructs the resulting complex Fourier coefficients by (re)organizing and normalizing the
4+
!! rfft result according to array element layout described at [1]. The program also demonstrates
5+
!! the inverse transform of the normalized rrft result to recover the original function.
6+
!!
7+
!! [1] https://docs.scipy.org/doc/scipy/reference/generated/scipy.fftpack.rfft.html#scipy.fftpack.rfft
8+
use fftpack, only: rfft, irfft
9+
implicit none
10+
integer j, k
11+
integer, parameter :: N = 8
12+
double precision, parameter :: two_pi = 2.D0*acos(-1.D0), tolerance = 1.0D-06, f_avg = 3.D0, zero=0.D0
13+
double precision, parameter :: x(0:N-1) = [(two_pi*dble(j)/dble(N), j=0,N-1)]
14+
double precision, parameter :: f(0:N-1) = f_avg + cos(x)
15+
!! sample f(x) = 3 + cos(x) uniformly on [0,2*pi)
16+
!! = 3 + (exp(i*x) - exp(-i*x))/2
17+
!! which yields the Fourier coefficients
18+
!! { 3, k = 0
19+
!! f_hat = { 1/2, k = 1
20+
!! { 0, otherwise
21+
double precision, dimension(0:N-1) :: f_round_trip, rfft_f
22+
integer, parameter :: rk = kind(two_pi)
23+
complex(rk) f_hat(0:N/2)
24+
character(len=*), parameter :: real_format = "(a,*(g10.4,:,1x))" !! space-separated values
25+
character(len=*), parameter :: complex_format= "(a,*('(',g10.4,',',g10.4,')',:,1x)))" !! space-separated complex values
26+
27+
call assert(mod(N,2)==0, "the algorithm below requires even N")
28+
29+
rfft_f(:) = rfft(f)/dble(N)
30+
f_hat(:) = [ &
31+
cmplx(rfft_f(0),zero), &
32+
[( cmplx(rfft_f(k),rfft_f(k+1)), k=lbound(rfft_f,1)+1,ubound(rfft_f,1)-1,2)], &
33+
cmplx(zero,rfft_f(N-1)) &
34+
]
35+
f_round_trip(:) = irfft(rfft_f)
36+
37+
print real_format, "f = ", f
38+
print complex_format, "f_hat = ", f_hat
39+
print real_format, "f_round_trip = ",f_round_trip
40+
41+
call assert(all(abs(f_round_trip - f) < tolerance), "inverse of forward FFT must yield the original function")
42+
43+
contains
44+
45+
pure subroutine assert(assertion, description)
46+
logical, intent(in) :: assertion
47+
character(len=*), intent(in) :: description
48+
if (.not. assertion) error stop description
49+
end subroutine
50+
51+
end program

0 commit comments

Comments
 (0)