{-# LINE 1 "Numeric/FFTW.hsc" #-}
module Numeric.FFTW (
fftwMalloc,
fftwFree,
fftwFreePtr,
fftwAllocReal,
fftwAllocComplex,
Direction(..),
Flag(),
fftwMeasure,
fftwExhaustive,
fftwPatient,
fftwEstimate,
fftwWisdomOnly,
fftwDestroyInput,
fftwUnaligned,
fftwPreserveInput,
FFTWPlan,
planDFT1d,
planDFTR2C1d,
execute,
executeDFT,
executeDFTR2C
) where
import Foreign.C.Types
import Foreign.Ptr
import Data.Word
import Data.Complex
import Control.Monad
import Data.Bits
import Data.Monoid
import Data.Semigroup as Sem
foreign import ccall unsafe "fftw_malloc"
c_fftwMalloc :: CUInt -> IO (Ptr a)
fftwMalloc :: Word32
-> IO (Ptr a)
fftwMalloc = c_fftwMalloc . fromIntegral
foreign import ccall unsafe "fftw_free"
fftwFree :: Ptr a
-> IO ()
foreign import ccall unsafe "&fftw_free"
fftwFreePtr :: FunPtr (Ptr a -> IO ())
foreign import ccall unsafe "fftw_alloc_real"
c_fftwAllocReal :: CUInt -> IO (Ptr CDouble)
fftwAllocReal :: Word32
-> IO (Ptr CDouble)
fftwAllocReal = c_fftwAllocReal . fromIntegral
foreign import ccall unsafe "fftw_alloc_complex"
c_fftwAllocComplex :: CUInt -> IO (Ptr (Complex CDouble))
fftwAllocComplex :: Word32
-> IO (Ptr (Complex CDouble))
fftwAllocComplex = c_fftwAllocComplex . fromIntegral
data Direction = Forward
| Backward
dirToInt :: Direction -> CInt
dirToInt Forward = -1
{-# LINE 109 "Numeric/FFTW.hsc" #-}
dirToInt Backward = 1
{-# LINE 110 "Numeric/FFTW.hsc" #-}
newtype Flag = Flag {unFlag :: CUInt}
instance Sem.Semigroup Flag where
(Flag x) <> (Flag y) = Flag (x .|. y)
instance Monoid Flag where
mempty = Flag 0
{-# LINE 122 "Numeric/FFTW.hsc" #-}
fftwMeasure, fftwExhaustive, fftwPatient, fftwEstimate, fftwWisdomOnly :: Flag
fftwEstimate = Flag 64
{-# LINE 125 "Numeric/FFTW.hsc" #-}
fftwMeasure = Flag 0
{-# LINE 126 "Numeric/FFTW.hsc" #-}
fftwPatient = Flag 32
{-# LINE 127 "Numeric/FFTW.hsc" #-}
fftwExhaustive = Flag 8
{-# LINE 128 "Numeric/FFTW.hsc" #-}
fftwWisdomOnly = Flag 2097152
{-# LINE 129 "Numeric/FFTW.hsc" #-}
fftwDestroyInput, fftwUnaligned, fftwPreserveInput :: Flag
fftwDestroyInput = Flag 1
{-# LINE 132 "Numeric/FFTW.hsc" #-}
fftwUnaligned = Flag 2
{-# LINE 133 "Numeric/FFTW.hsc" #-}
fftwPreserveInput = Flag 16
{-# LINE 134 "Numeric/FFTW.hsc" #-}
data CFFTWPlan
newtype FFTWPlan i o = FFTWPlan (Ptr CFFTWPlan)
foreign import ccall unsafe "fftw_plan_dft_1d"
c_planDFT1d :: CInt -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CUInt -> IO (Ptr CFFTWPlan)
planDFT1d :: Int
-> Ptr (Complex CDouble)
-> Ptr (Complex CDouble)
-> Direction
-> Flag
-> IO (FFTWPlan (Complex CDouble) (Complex CDouble))
planDFT1d n inp out sign flags = liftM FFTWPlan $ c_planDFT1d (fromIntegral n) inp out (dirToInt sign) (unFlag flags)
foreign import ccall unsafe "fftw_plan_dft_r2c_1d"
c_planDFTR2C1d :: CInt -> Ptr CDouble -> Ptr (Complex CDouble) -> CUInt -> IO (Ptr CFFTWPlan)
planDFTR2C1d :: Int
-> Ptr CDouble
-> Ptr (Complex CDouble)
-> Flag
-> IO (FFTWPlan CDouble (Complex CDouble))
planDFTR2C1d n inp out flags = liftM FFTWPlan $ c_planDFTR2C1d (fromIntegral n) inp out (unFlag flags)
foreign import ccall unsafe "fftw_execute"
c_execute :: Ptr CFFTWPlan -> IO ()
execute :: FFTWPlan i o
-> IO ()
execute (FFTWPlan p) = c_execute p
foreign import ccall unsafe "fftw_execute_dft"
c_executeDFT :: Ptr CFFTWPlan -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> IO ()
executeDFT :: FFTWPlan (Complex CDouble) (Complex CDouble)
-> Ptr (Complex CDouble)
-> Ptr (Complex CDouble)
-> IO ()
executeDFT (FFTWPlan p) inp out = c_executeDFT p inp out
foreign import ccall unsafe "fftw_execute_dft_r2c"
c_executeDFTR2C :: Ptr CFFTWPlan -> Ptr CDouble -> Ptr (Complex CDouble) -> IO ()
executeDFTR2C :: FFTWPlan CDouble (Complex CDouble)
-> Ptr CDouble
-> Ptr (Complex CDouble)
-> IO ()
executeDFTR2C (FFTWPlan p) inp out = c_executeDFTR2C p inp out