accelerate-fft-1.0.0.0: FFT using the Accelerate library

Copyright[2012..2017] Manuel M T Chakravarty Gabriele Keller Trevor L. McDonell
[2013..2017] Robert Clifton-Everest
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Math.FFT

Description

Computation of a Discrete Fourier Transform using the Cooley-Tuckey algorithm. The time complexity is O(n log n) in the size of the input.

The base (default) implementation uses a naïve divide-and-conquer algorithm whose absolute performance is appalling. It also requires that you know on the Haskell side the size of the data being transformed, and that this is a power-of-two in each dimension.

For performance, compile against the foreign library bindings (using any number of '-fcuda', '-fllvm-gpu', and '-fllvm-cpu' for the accelerate-cuda, accelerate-llvm-ptx, and accelerate-llvm-native backends respectively), which have none of the above restrictions.

Synopsis

Documentation

data Mode Source #

Constructors

Forward

Forward DFT

Reverse

Inverse DFT, un-normalised

Inverse

Inverse DFT, normalised

Instances

Eq Mode Source # 

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Show Mode Source # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

fft1D :: FFTElt e => Mode -> Array DIM1 (Complex e) -> Acc (Array DIM1 (Complex e)) Source #

Discrete Fourier Transform of a vector.

The default implementation requires the array dimension to be a power of two (else error).

fft1D' :: forall e. FFTElt e => Mode -> DIM1 -> Acc (Array DIM1 (Complex e)) -> Acc (Array DIM1 (Complex e)) Source #

Discrete Fourier Transform of a vector.

The default implementation requires the array dimension to be a power of two. The FFI-backed implementations ignore the Haskell-side size parameter (second argument).

fft2D :: FFTElt e => Mode -> Array DIM2 (Complex e) -> Acc (Array DIM2 (Complex e)) Source #

Discrete Fourier Transform of a matrix.

The default implementation requires the array dimensions to be powers of two (else error).

fft2D' :: forall e. FFTElt e => Mode -> DIM2 -> Acc (Array DIM2 (Complex e)) -> Acc (Array DIM2 (Complex e)) Source #

Discrete Fourier Transform of a matrix.

The default implementation requires the array dimensions to be powers of two. The FFI-backed implementations ignore the Haskell-side size parameter (second argument).

fft3D :: FFTElt e => Mode -> Array DIM3 (Complex e) -> Acc (Array DIM3 (Complex e)) Source #

Discrete Fourier Transform of a 3D array.

The default implementation requires the array dimensions to be powers of two (else error).

fft3D' :: forall e. FFTElt e => Mode -> DIM3 -> Acc (Array DIM3 (Complex e)) -> Acc (Array DIM3 (Complex e)) Source #

Discrete Fourier Transform of a 3D array.

The default implementation requires the array dimensions to be powers of two. The FFI-backed implementations ignore the Haskell-side size parameter (second argument).

fft :: forall sh e. (Slice sh, Shape sh, RealFloat e, FromIntegral Int e) => e -> sh -> Int -> Acc (Array (sh :. Int) (Complex e)) -> Acc (Array (sh :. Int) (Complex e)) Source #