fft-0.1.0.1: Bindings to the FFTW library.ContentsIndex
Math.FFT
Portabilitynon-portable
Stabilityexperimental
Maintainerjed@59A2.org
Contents
Data types
Planner flags
Algorithm restriction flags
Planning rigor flags
DFT of complex data
DFT in first dimension only
Multi-dimensional transforms
General transform
Un-normalized general transform
DFT of real data
DFT in first dimension only
Multi-dimensional transforms
General transform
Un-normalized general transform
Real to real transforms (all un-normalized)
Transforms in first dimension only
Multi-dimensional transforms with the same transform type in each dimension
Multi-dimensional transforms with possibly different transforms in each dimension
General transforms
Wisdom
Description

This module exposes an interface to FFTW, the Fastest Fourier Transform in the West.

These bindings present several levels of interface. All the higher level functions (dft, idft, dftN, ...) are easily derived from the general functions (dftG, dftRCG, ...). Only the general functions let you specify planner flags. The higher levels all set estimate so you should not have to wait through time consuming planning (see below for more).

The simplest interface is the one-dimensional transforms. If you supply a multi-dimensional array, these will only transform the first dimension. These functions only take one argument, the array to be transformed.

At the next level, we have multi-dimensional transforms where you specify which dimensions to transform in and the array to transform. For instance

 b = dftRCN [0,2] a

is the real to complex transform in dimensions 0 and 2 of the array a which must be at least rank 3. The array b will be complex valued with the same extent as a in every dimension except 2. If a had extent n in dimension 2 then the b will have extent a div 2 + 1 which consists of all non-negative frequency components in this dimension (the negative frequencies are conjugate to the positive frequencies because of symmetry since a is real valued).

The real to real transforms allow different transform kinds in each transformed dimension. For example,

 b = dftRRN [(0,DHT), (1,REDFT10), (2,RODFT11)] a

is a Discrete Hartley Transform in dimension 0, a discrete cosine transform (DCT-2) in dimension 1, and distrete sine transform (DST-4) in dimension 2 where the array a must have rank at least 3.

The general interface is similar to the multi-dimensional interface, takes as its first argument, a bitwise .|. of planning Flags. (In the complex version, the sign of the transform is first.) For example,

 b = dftG DFTBackward (patient .|. destroy_input) [1,2] a

is an inverse DFT in dimensions 1 and 2 of the complex array a which has rank at least 3. It will use the patient planner to generate a (near) optimal transform. If you compute the same type of transform again, it should be very fast since the plan is cached.

Inverse transforms are typically normalized. The un-normalized inverse transforms are dftGU, dftCRGU and dftCROGU. For example

 b = dftCROGU measure [0,1] a

is an un-normalized inverse DFT in dimensions 0 and 1 of the complex array a (representing the non-negative frequencies, where the negative frequencies are conjugate) which has rank at least 2. Here, dimension 1 is logically odd so if a has extent n in dimension 1, then b will have extent (n - 1) * 2 + 1 in dimension 1. It is more common that the logical dimension is even, in which case we would use dftCRGU in which case b would have extent (n - 1) * 2 in dimension 1.

The FFTW library separates transforms into two steps. First you compute a plan for a given transform, then you execute it. Often the planning stage is quite time-consuming, but subsequent transforms of the same size and type will be extremely fast. The planning phase actually computes transforms, so it overwrites its input array. For many C codes, it is reasonable to re-use the same arrays to compute a given transform on different data. This is not a very useful paradigm from Haskell. Fortunately, FFTW caches its plans so if try to generate a new plan for a transform size which has already been planned, the planner will return immediately. Unfortunately, it is not possible to consult the cache, so if a plan is cached, we may use more memory than is strictly necessary since we must allocate a work array which we expect to be overwritten during planning. FFTW can export its cached plans to a string. This is known as wisdom. For high performance work, it is a good idea to compute plans of the sizes you are interested in, using aggressive options (i.e. patient), use exportWisdomString to get a string representing these plans, and write this to a file. Then for production runs, you can read this in, then add it to the cache with importWisdomString. Now you can use the estimate planner so the Haskell bindings know that FFTW will not overwrite the input array, and you will still get a high quality transform (because it has wisdom).

Synopsis
data Sign
data Kind
destroyInput :: Flag
preserveInput :: Flag
estimate :: Flag
measure :: Flag
patient :: Flag
exhaustive :: Flag
dft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)
idft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)
dftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)
idftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)
dftG :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)
dftGU :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)
dftRC :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i (Complex r)
dftCR :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i r
dftCRO :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i r
dftRCN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i (Complex r)
dftCRN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i r
dftCRON :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i r
dftRCG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i r -> CArray i (Complex r)
dftCRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
dftCROG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
dftCRGU :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
dftCROGU :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
dftRH :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dftHR :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dht :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dct1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dct2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dct3 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dct4 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dst1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dst2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dst3 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dst4 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
dftRHN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dftHRN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dhtN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dct1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dct2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dct3N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dct4N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dst1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dst2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dst3N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dst4N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
dftRRN :: (FFTWReal r, Ix i, Shapable i) => [(Int, Kind)] -> CArray i r -> CArray i r
dftRRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [(Int, Kind)] -> CArray i r -> CArray i r
importWisdomString :: String -> IO Bool
importWisdomSystem :: IO Bool
exportWisdomString :: IO String
Data types
data Sign
Determine which direction of DFT to execute.
show/hide Instances
data Kind
Real to Real transform kinds.
show/hide Instances
Planner flags
Algorithm restriction flags
destroyInput :: Flag

Allows FFTW to overwrite the input array with arbitrary data; this can sometimes allow more efficient algorithms to be employed.

Setting this flag implies that two memory allocations will be done, one for work space, and one for the result. When estimate is not set, we will be doing two memory allocations anyway, so we set this flag as well (since we don't retain the work array anyway).

preserveInput :: Flag
preserveInput specifies that an out-of-place transform must not change its input array. This is ordinarily the default, except for complex to real transforms for which destroyInput is the default. In the latter cases, passing preserveInput will attempt to use algorithms that do not destroy the input, at the expense of worse performance; for multi-dimensional complex to real transforms, however, no input-preserving algorithms are implemented so the Haskell bindings will set destroyInput and do a transform with two memory allocations.
Planning rigor flags
estimate :: Flag

estimate specifies that, instead of actual measurements of different algorithms, a simple heuristic is used to pick a (probably sub-optimal) plan quickly. With this flag, the input/output arrays are not overwritten during planning.

This is the only planner flag for which a single memory allocation is possible.

measure :: Flag
measure tells FFTW to find an optimized plan by actually computing several FFTs and measuring their execution time. Depending on your machine, this can take some time (often a few seconds). measure is the default planning option.
patient :: Flag
patient is like measure, but considers a wider range of algorithms and often produces a more optimal plan (especially for large transforms), but at the expense of several times longer planning time (especially for large transforms).
exhaustive :: Flag
exhaustive is like patient but considers an even wider range of algorithms, including many that we think are unlikely to be fast, to produce the most optimal plan but with a substantially increased planning time.
DFT of complex data
DFT in first dimension only
dft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)
1-dimensional complex DFT.
idft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)
1-dimensional complex inverse DFT. Inverse of dft.
Multi-dimensional transforms
dftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)
Multi-dimensional forward DFT.
idftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)
Multi-dimensional inverse DFT.
General transform
dftG :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)
Normalized general complex DFT
Un-normalized general transform
dftGU :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)
Complex to Complex DFT, un-normalized.
DFT of real data
DFT in first dimension only
dftRC :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i (Complex r)
1-dimensional real to complex DFT.
dftCR :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i r
1-dimensional complex to real DFT with logically even dimension. Inverse of dftRC.
dftCRO :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i r
1-dimensional complex to real DFT with logically odd dimension. Inverse of dftRC.
Multi-dimensional transforms
dftRCN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i (Complex r)
Multi-dimensional forward DFT of real data.
dftCRN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i r
Multi-dimensional inverse DFT of Hermitian-symmetric data (where only the non-negative frequencies are given).
dftCRON :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i r
Multi-dimensional inverse DFT of Hermitian-symmetric data (where only the non-negative frequencies are given) and the last transformed dimension is logically odd.
General transform
dftRCG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i r -> CArray i (Complex r)
Real to Complex DFT.
dftCRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
Normalized general complex to real DFT where the last transformed dimension is logically even.
dftCROG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
Normalized general complex to real DFT where the last transformed dimension is logicall odd.
Un-normalized general transform
dftCRGU :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
Complex to Real DFT where last transformed dimension is logically even.
dftCROGU :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i r
Complex to Real DFT where last transformed dimension is logically odd.
Real to real transforms (all un-normalized)
Transforms in first dimension only
dftRH :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional real to half-complex DFT.
dftHR :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional half-complex to real DFT. Inverse of dftRH after normalization.
dht :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Discrete Hartley Transform. Self-inverse after normalization.
dct1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 1 discrete cosine transform.
dct2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 2 discrete cosine transform. This is commonly known as the DCT.
dct3 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 3 discrete cosine transform. This is commonly known as the inverse DCT.
dct4 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 4 discrete cosine transform.
dst1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 1 discrete sine transform.
dst2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 2 discrete sine transform.
dst3 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 3 discrete sine transform.
dst4 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i r
1-dimensional Type 4 discrete sine transform.
Multi-dimensional transforms with the same transform type in each dimension
dftRHN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional real to half-complex transform. The result is not normalized.
dftHRN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional half-complex to real transform. The result is not normalized.
dhtN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Discrete Hartley Transform. The result is not normalized.
dct1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 1 discrete cosine transform.
dct2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 2 discrete cosine transform. This is commonly known as the DCT.
dct3N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 3 discrete cosine transform. This is commonly known as the inverse DCT. The result is not normalized.
dct4N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 4 discrete cosine transform.
dst1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 1 discrete sine transform.
dst2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 2 discrete sine transform.
dst3N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 3 discrete sine transform.
dst4N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i r
Multi-dimensional Type 4 discrete sine transform.
Multi-dimensional transforms with possibly different transforms in each dimension
dftRRN :: (FFTWReal r, Ix i, Shapable i) => [(Int, Kind)] -> CArray i r -> CArray i r
Multi-dimensional real to real transform. The result is not normalized.
General transforms
dftRRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [(Int, Kind)] -> CArray i r -> CArray i r
Real to Real transforms.
Wisdom
importWisdomString :: String -> IO Bool
Add wisdom to the FFTW cache. Returns True if it is successful.
importWisdomSystem :: IO Bool
Tries to import wisdom from a global source, typically etcfftw/wisdom. Returns True if it was successful.
exportWisdomString :: IO String
Queries the FFTW cache. The String can be written to a file so the wisdom can be reused on a subsequent run.
Produced by Haddock version 2.1.0