vector-fftw-0.1.3.8: A binding to the fftw library for one-dimensional vectors.

Safe HaskellNone
LanguageHaskell98

Numeric.FFT.Vector.Unnormalized

Contents

Description

Raw, unnormalized versions of the transforms in fftw.

Note that the forwards and backwards transforms of this module are not actually inverses. For example, run idft (run dft v) /= v in general.

For more information on the individual transforms, see http://www.fftw.org/fftw3_doc/What-FFTW-Really-Computes.html.

Synopsis

Creating and executing Plans

run :: (Vector v a, Vector v b, Storable a, Storable b) => Transform a b -> v a -> v b Source #

Create and run a Plan for the given transform.

plan :: (Storable a, Storable b) => Transform a b -> Int -> Plan a b Source #

Create a Plan of a specific size. This function is equivalent to planOfType Estimate.

execute :: (Vector v a, Vector v b, Storable a, Storable b) => Plan a b -> v a -> v b Source #

Run a plan on the given Vector.

If planInputSize p /= length v, then calling execute p v will throw an exception.

Complex-to-complex transforms

dft :: Transform (Complex Double) (Complex Double) Source #

A forward discrete Fourier transform. The output and input sizes are the same (n).

y_k = sum_(j=0)^(n-1) x_j e^(-2pi i j k/n)

idft :: Transform (Complex Double) (Complex Double) Source #

A backward discrete Fourier transform. The output and input sizes are the same (n).

y_k = sum_(j=0)^(n-1) x_j e^(2pi i j k/n)

Real-to-complex transforms

dftR2C :: Transform Double (Complex Double) Source #

A forward discrete Fourier transform with real data. If the input size is n, the output size will be n `div` 2 + 1.

dftC2R :: Transform (Complex Double) Double Source #

A backward discrete Fourier transform which produces real data.

This Transform behaves differently than the others:

  • Calling plan dftC2R n creates a Plan whose output size is n, and whose input size is n `div` 2 + 1.
  • If length v == n, then length (run dftC2R v) == 2*(n-1).

Real-to-real transforms

The real-even (DCT) and real-odd (DST) transforms. The input and output sizes are the same (n).

dct1 :: Transform Double Double Source #

A type-1 discrete cosine transform.

y_k = x_0 + (-1)^k x_(n-1) + 2 sum_(j=1)^(n-2) x_j cos(pi j k/(n-1))

dct2 :: Transform Double Double Source #

A type-2 discrete cosine transform.

y_k = 2 sum_(j=0)^(n-1) x_j cos(pi(j+1/2)k/n)

dct3 :: Transform Double Double Source #

A type-3 discrete cosine transform.

y_k = x_0 + 2 sum_(j=1)^(n-1) x_j cos(pi j(k+1/2)/n)

dct4 :: Transform Double Double Source #

A type-4 discrete cosine transform.

y_k = 2 sum_(j=0)^(n-1) x_j cos(pi(j+1/2)(k+1/2)/n)

Discrete sine transforms

dst1 :: Transform Double Double Source #

A type-1 discrete sine transform.

y_k = 2 sum_(j=0)^(n-1) x_j sin(pi(j+1)(k+1)/(n+1))

dst2 :: Transform Double Double Source #

A type-2 discrete sine transform.

y_k = 2 sum_(j=0)^(n-1) x_j sin(pi(j+1/2)(k+1)/n)

dst3 :: Transform Double Double Source #

A type-3 discrete sine transform.

y_k = (-1)^k x_(n-1) + 2 sum_(j=0)^(n-2) x_j sin(pi(j+1)(k+1/2)/n)

dst4 :: Transform Double Double Source #

A type-4 discrete sine transform.

y_k = sum_(j=0)^(n-1) x_j sin(pi(j+1/2)(k+1/2)/n)