Welcome to AE Resources
Converted document FAST FOURIER TRANSFORMS EXAMPLES

FAST FOURIER TRANSFORMS EXAMPLES

This program includes examples of FFT of several functions (some are commented out). Notice that the length of the data must be a function of 2.
PROGRAM FFT_function
!Description:  This program determines the FFT of a
!     given function.  Commented out lines of other functions
!     are also provided.
​
IMPLICIT NONE
REAL, PARAMETER :: pi=4.0*ATAN(1.0)
INTEGER :: i, L
REAL :: fs
INTEGER, DIMENSION(:), ALLOCATABLE :: f
REAL, DIMENSION(:), ALLOCATABLE :: time, myreal, myimag
COMPLEX, DIMENSION(:), ALLOCATABLE :: func
​
!Length of the signal, which should be a multiple of 2
!This makes the math/logarithms nicer
L = 64
!Allocate
ALLOCATE(time(L),myreal(L),myimag(L), f(L/2))
ALLOCATE(func(L))
​
!Notes:
!  w = 2*pi*freq
!  f = 1/T   where T = period
​
!Set time precision
!Implied DO Loop used here!
!time(1:L) = (/((i)*(1/REAL(L)), i=0,L-1)/)  !Time for both cos(2*pi*t)
!time(1:L) = (/((i)*(.5/REAL(L)), i=0,L-1)/)  !Time for both cos(4*pi*t)
time(1:L) = (/((i)*(1/REAL(L)), i=0,L-1)/)  !Time for Step function
​
!Set Sampling Frequency
fs = SIZE(time)/time(SIZE(time))
!Array function used here!
!func = cos(2.*pi*time)  !Code for cos(2.*pi*t) function
!func = cos(4.*pi*time)  !Code for cos(4.*pi*t) function
func = 1. + 0.*time  !Code for STEP function
!func = sin(2.*pi*time)  !Code for sin(2.*pi*t) function
!func = cos(2.*pi*time) + sin(3.*pi*time)
​
!Split up real and imaginary portions of function
myreal(1:L) = REAL(func(1:L))
myimag(1:L) = AIMAG(func(1:L))
​
!Run it through the FFT via scramble and unscramble
CALL scram(L,myreal,myimag)
CALL unscram(L,myreal, myimag)
​
!Store magnitudes by reusing myreal vector
myreal(1:L) = (/(SQRT(myreal(i)**2 + myimag(i)**2), i=1,L)/)
​
!Create frequency axis values
f(1:L/2) = (/(REAL(i)/REAL(SIZE(time)), &
i=0,SIZE(time)*(int(fs/2.)-1),2*int(fs/2.))/)
DO i = 1,L/2
	WRITE(*,*) f(i), myreal(i)
ENDDO
​
​
Next Page →
Next Page →