fft-0.1.1: Bindings to the FFTW library.Source codeContentsIndex
Math.FFT.Base
Synopsis
class (Storable a, RealFloat a) => FFTWReal a where
plan_guru_dft :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex a) -> Ptr (Complex a) -> FFTWSign -> FFTWFlag -> IO Plan
plan_guru_dft_r2c :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr a -> Ptr (Complex a) -> FFTWFlag -> IO Plan
plan_guru_dft_c2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex a) -> Ptr a -> FFTWFlag -> IO Plan
plan_guru_r2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr a -> Ptr a -> Ptr FFTWKind -> FFTWFlag -> IO Plan
withLock :: IO a -> IO a
type Plan = Ptr FFTWPlan
type FFTWPlan = ()
newtype Flag = Flag {
unFlag :: FFTWFlag
}
type FFTWFlag = CUInt
c_measure :: FFTWFlag
c_destroy_input :: FFTWFlag
c_unaligned :: FFTWFlag
c_conserve_memory :: FFTWFlag
c_exhaustive :: FFTWFlag
c_preserve_input :: FFTWFlag
c_patient :: FFTWFlag
nullFlag :: Flag
c_estimate :: FFTWFlag
destroyInput :: Flag
preserveInput :: Flag
unaligned :: Flag
conserveMemory :: Flag
estimate :: Flag
measure :: Flag
patient :: Flag
exhaustive :: Flag
data Sign
= DFTForward
| DFTBackward
type FFTWSign = CInt
c_forward :: FFTWSign
c_backward :: FFTWSign
data Kind
= R2HC
| HC2R
| DHT
| REDFT00
| REDFT10
| REDFT01
| REDFT11
| RODFT00
| RODFT01
| RODFT10
| RODFT11
unKind :: Kind -> FFTWKind
type FFTWKind = CInt
c_r2hc :: FFTWKind
c_hc2r :: FFTWKind
c_dht :: FFTWKind
c_redft00 :: FFTWKind
c_redft10 :: FFTWKind
c_redft01 :: FFTWKind
c_redft11 :: FFTWKind
c_rodft00 :: FFTWKind
data IODim = IODim {
n :: Int
is :: Int
os :: Int
}
c_rodft10 :: FFTWKind
c_rodft01 :: FFTWKind
c_rodft11 :: FFTWKind
type TSpec = ([IODim], [IODim])
data DFT
= CC
| RC
| CR
| CRO
| RR
check :: Plan -> IO ()
execute :: Plan -> IO ()
unsafeNormalize :: (Ix i, Shapable i, Fractional e, Storable e) => [Int] -> CArray i e -> CArray i e
dftG :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex 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
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)
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
dftRRN :: (FFTWReal r, Ix i, Shapable i) => [(Int, Kind)] -> 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
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)
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
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
transformCArray :: (Ix i, Storable a, Storable b) => Flag -> CArray i a -> (i, i) -> (FFTWFlag -> Ptr a -> Ptr b -> IO Plan) -> CArray i b
transformCArray' :: (Ix i, Storable a, Storable b) => Flag -> CArray i a -> (i, i) -> (FFTWFlag -> Ptr a -> Ptr b -> IO Plan) -> CArray i b
dftShape :: (Ix i, Shapable i, IArray CArray e) => DFT -> [Int] -> CArray i e -> ((i, i), TSpec)
withTSpec :: TSpec -> (CInt -> Ptr IODim -> CInt -> Ptr IODim -> IO a) -> IO a
adjust :: (a -> a) -> Int -> [a] -> [a]
dftGU :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)
dftRCG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i r -> CArray i (Complex r)
dftCRG_ :: (FFTWReal r, Ix i, Shapable i) => Bool -> 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
dftRRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [(Int, Kind)] -> CArray i r -> CArray i r
exportWisdomString :: IO String
importWisdomString :: String -> IO Bool
importWisdomSystem :: IO Bool
c_plan_guru_dft :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex Double) -> Ptr (Complex Double) -> FFTWSign -> FFTWFlag -> IO Plan
c_plan_guru_dft_r2c :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr Double -> Ptr (Complex Double) -> FFTWFlag -> IO Plan
c_plan_guru_dft_c2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex Double) -> Ptr Double -> FFTWFlag -> IO Plan
c_plan_guru_r2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr Double -> Ptr Double -> Ptr FFTWKind -> FFTWFlag -> IO Plan
c_execute :: Plan -> IO ()
c_execute_dft :: Plan -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()
c_execute_dft_r2c :: Plan -> Ptr Double -> Ptr (Complex Double) -> IO ()
c_execute_dft_c2r :: Plan -> Ptr (Complex Double) -> Ptr Double -> IO ()
c_execute_r2r :: Plan -> Ptr Double -> Ptr Double -> IO ()
c_export_wisdom_string :: IO CString
c_import_wisdom_string :: CString -> IO CInt
c_import_wisdom_system :: IO CInt
c_free :: Ptr a -> IO ()
Documentation
class (Storable a, RealFloat a) => FFTWReal a whereSource
Our API is polymorphic over the real data type. FFTW, at least in principle, supports single precision Float, double precision Double and long double CLDouble (presumable?).
Methods
plan_guru_dft :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex a) -> Ptr (Complex a) -> FFTWSign -> FFTWFlag -> IO PlanSource
plan_guru_dft_r2c :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr a -> Ptr (Complex a) -> FFTWFlag -> IO PlanSource
plan_guru_dft_c2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex a) -> Ptr a -> FFTWFlag -> IO PlanSource
plan_guru_r2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr a -> Ptr a -> Ptr FFTWKind -> FFTWFlag -> IO PlanSource
show/hide Instances
withLock :: IO a -> IO aSource
This lock must be taken during planning of any transform. The FFTW library is not thread-safe in the planning phase. Thankfully, the lock is not needed during the execute phase.
type Plan = Ptr FFTWPlanSource
A plan is an opaque foreign object.
type FFTWPlan = ()Source
newtype Flag Source
The Flag type is used to influence the kind of plans which are created. To specify multiple flags, use a bitwise .|..
Constructors
Flag
unFlag :: FFTWFlag
show/hide Instances
type FFTWFlag = CUIntSource
c_measure :: FFTWFlagSource
c_destroy_input :: FFTWFlagSource
c_unaligned :: FFTWFlagSource
c_conserve_memory :: FFTWFlagSource
c_exhaustive :: FFTWFlagSource
c_preserve_input :: FFTWFlagSource
c_patient :: FFTWFlagSource
Default flag. For most transforms, this is equivalent to setting measure and preserveInput. The exceptions are complex to real and half-complex to real transforms.
nullFlag :: FlagSource
c_estimate :: FFTWFlagSource
destroyInput :: FlagSource

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 :: FlagSource
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.
unaligned :: FlagSource
Instruct FFTW not to generate a plan which uses SIMD instructions, even if the memory you are planning with is aligned. This should only be needed if you are using the guru interface and want to reuse a plan with memory that may be unaligned (i.e. you constructed the CArray with unsafeForeignPtrToCArray).
conserveMemory :: FlagSource
The header claims that this flag is documented, but in reality, it is not. I don't know what it does and it is here only for completeness.
estimate :: FlagSource

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 :: FlagSource
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 :: FlagSource
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 :: FlagSource
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.
data Sign Source
Determine which direction of DFT to execute.
Constructors
DFTForward
DFTBackward
show/hide Instances
type FFTWSign = CIntSource
c_forward :: FFTWSignSource
c_backward :: FFTWSignSource
data Kind Source
Real to Real transform kinds.
Constructors
R2HC
HC2R
DHT
REDFT00
REDFT10
REDFT01
REDFT11
RODFT00
RODFT01
RODFT10
RODFT11
show/hide Instances
unKind :: Kind -> FFTWKindSource
type FFTWKind = CIntSource
c_r2hc :: FFTWKindSource
c_hc2r :: FFTWKindSource
c_dht :: FFTWKindSource
c_redft00 :: FFTWKindSource
c_redft10 :: FFTWKindSource
c_redft01 :: FFTWKindSource
c_redft11 :: FFTWKindSource
c_rodft00 :: FFTWKindSource
Corresponds to the fftw_iodim structure. It completely describes the layout of each dimension, before and after the transform.
data IODim Source
Constructors
IODim
n :: Int
is :: Int
os :: Int
show/hide Instances
c_rodft10 :: FFTWKindSource
c_rodft01 :: FFTWKindSource
c_rodft11 :: FFTWKindSource
type TSpec = ([IODim], [IODim])Source
Tuple of transform dimensions and non-transform dimensions of the array.
data DFT Source
Types of transforms. Used to control dftShape.
Constructors
CC
RC
CR
CRO
RR
show/hide Instances
check :: Plan -> IO ()Source
Verify that a plan is valid. Thows an exception if not.
execute :: Plan -> IO ()Source
Confirm that the plan is valid, then execute the transform.
unsafeNormalize :: (Ix i, Shapable i, Fractional e, Storable e) => [Int] -> CArray i e -> CArray i eSource
In-place normalization outside of IO. You must be able to prove that no reference to the original can be retained.
dftG :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)Source
Normalized general complex DFT
dftCRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i rSource
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 rSource
Normalized general complex to real DFT where the last transformed dimension is logicall odd.
dftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)Source
Multi-dimensional forward DFT.
idftN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i (Complex r)Source
Multi-dimensional inverse DFT.
dftRCN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i (Complex r)Source
Multi-dimensional forward DFT of real data.
dftCRN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i (Complex r) -> CArray i rSource
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 rSource
Multi-dimensional inverse DFT of Hermitian-symmetric data (where only the non-negative frequencies are given) and the last transformed dimension is logically odd.
dftRRN :: (FFTWReal r, Ix i, Shapable i) => [(Int, Kind)] -> CArray i r -> CArray i rSource
Multi-dimensional real to real transform. The result is not normalized.
dftRHN :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
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 rSource
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 rSource
Multi-dimensional Discrete Hartley Transform. The result is not normalized.
dct1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
Multi-dimensional Type 1 discrete cosine transform.
dct2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
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 rSource
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 rSource
Multi-dimensional Type 4 discrete cosine transform.
dst1N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
Multi-dimensional Type 1 discrete sine transform.
dst2N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
Multi-dimensional Type 2 discrete sine transform.
dst3N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
Multi-dimensional Type 3 discrete sine transform.
dst4N :: (FFTWReal r, Ix i, Shapable i) => [Int] -> CArray i r -> CArray i rSource
Multi-dimensional Type 4 discrete sine transform.
dft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)Source
1-dimensional complex DFT.
idft :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r)Source
1-dimensional complex inverse DFT. Inverse of dft.
dftRC :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i (Complex r)Source
1-dimensional real to complex DFT.
dftCR :: (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i rSource
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 rSource
1-dimensional complex to real DFT with logically odd dimension. Inverse of dftRC.
dftRH :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional real to half-complex DFT.
dftHR :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional half-complex to real DFT. Inverse of dftRH after normalization.
dht :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Discrete Hartley Transform. Self-inverse after normalization.
dct1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Type 1 discrete cosine transform.
dct2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
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 rSource
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 rSource
1-dimensional Type 4 discrete cosine transform.
dst1 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Type 1 discrete sine transform.
dst2 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Type 2 discrete sine transform.
dst3 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Type 3 discrete sine transform.
dst4 :: (FFTWReal r, Ix i, Shapable i) => CArray i r -> CArray i rSource
1-dimensional Type 4 discrete sine transform.
transformCArray :: (Ix i, Storable a, Storable b) => Flag -> CArray i a -> (i, i) -> (FFTWFlag -> Ptr a -> Ptr b -> IO Plan) -> CArray i bSource
Try to transform a CArray with only one memory allocation (for the result). If we can find a way to prove that FFTW already has a sufficiently good plan for this transform size and the input will not be overwritten, then we could call have a version of this that does not require estimate. Since this is not currently the case, we require estimate to be set. Note that we do not check for the preserveInput flag here. This is because the default is to preserve input for all but the C->R and HC->R transforms. Therefore, this function must not be called for those transforms, unless preserveInput is set.
transformCArray' :: (Ix i, Storable a, Storable b) => Flag -> CArray i a -> (i, i) -> (FFTWFlag -> Ptr a -> Ptr b -> IO Plan) -> CArray i bSource
Transform a CArray with two memory allocations. This is entirely safe with all transforms, but it must allocate a temporary array to do the planning in.
dftShape :: (Ix i, Shapable i, IArray CArray e) => DFT -> [Int] -> CArray i e -> ((i, i), TSpec)Source
All the logic for determining shape of resulting array, and how to do the transform.
withTSpec :: TSpec -> (CInt -> Ptr IODim -> CInt -> Ptr IODim -> IO a) -> IO aSource
A simple helper.
adjust :: (a -> a) -> Int -> [a] -> [a]Source
A generally useful list utility
dftGU :: (FFTWReal r, Ix i, Shapable i) => Sign -> Flag -> [Int] -> CArray i (Complex r) -> CArray i (Complex r)Source
Complex to Complex DFT, un-normalized.
dftRCG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i r -> CArray i (Complex r)Source
Real to Complex DFT.
dftCRG_ :: (FFTWReal r, Ix i, Shapable i) => Bool -> Flag -> [Int] -> CArray i (Complex r) -> CArray i rSource
Complex to Real DFT. The first argument determines whether the last transformed dimension is logically odd or even. True implies the dimension is odd.
dftCRGU :: (FFTWReal r, Ix i, Shapable i) => Flag -> [Int] -> CArray i (Complex r) -> CArray i rSource
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 rSource
Complex to Real DFT where last transformed dimension is logically odd.
dftRRG :: (FFTWReal r, Ix i, Shapable i) => Flag -> [(Int, Kind)] -> CArray i r -> CArray i rSource
Real to Real transforms.
exportWisdomString :: IO StringSource
Queries the FFTW cache. The String can be written to a file so the wisdom can be reused on a subsequent run.
importWisdomString :: String -> IO BoolSource
Add wisdom to the FFTW cache. Returns True if it is successful.
importWisdomSystem :: IO BoolSource
Tries to import wisdom from a global source, typically etcfftw/wisdom. Returns True if it was successful.
c_plan_guru_dft :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex Double) -> Ptr (Complex Double) -> FFTWSign -> FFTWFlag -> IO PlanSource
Plan a complex to complex transform using the guru interface.
c_plan_guru_dft_r2c :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr Double -> Ptr (Complex Double) -> FFTWFlag -> IO PlanSource
Plan a real to complex transform using the guru interface.
c_plan_guru_dft_c2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr (Complex Double) -> Ptr Double -> FFTWFlag -> IO PlanSource
Plan a complex to real transform using the guru interface.
c_plan_guru_r2r :: CInt -> Ptr IODim -> CInt -> Ptr IODim -> Ptr Double -> Ptr Double -> Ptr FFTWKind -> FFTWFlag -> IO PlanSource
Plan a real to real transform using the guru interface.
c_execute :: Plan -> IO ()Source
Simple plan execution
c_execute_dft :: Plan -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()Source
c_execute_dft_r2c :: Plan -> Ptr Double -> Ptr (Complex Double) -> IO ()Source
c_execute_dft_c2r :: Plan -> Ptr (Complex Double) -> Ptr Double -> IO ()Source
c_execute_r2r :: Plan -> Ptr Double -> Ptr Double -> IO ()Source
c_export_wisdom_string :: IO CStringSource
c_import_wisdom_string :: CString -> IO CIntSource
c_import_wisdom_system :: IO CIntSource
c_free :: Ptr a -> IO ()Source
Frees memory allocated by fftw_malloc. Currently, we only need this to free the wisdom string.
Produced by Haddock version 2.4.2