comfort-fftw-0.0: High-level interface to FFTW (Fast Fourier Transform) based on comfort-array

Safe HaskellNone
LanguageHaskell98

Numeric.FFTW.Rank3

Synopsis

Documentation

fourier :: (Integral n0, Integral n1, Integral n2, Real a) => Sign -> Array (Cyclic n0, Cyclic n1, Cyclic n2) (Complex a) -> Array (Cyclic n0, Cyclic n1, Cyclic n2) (Complex a) Source #

QC.forAll genCyclicArray3 $ \xs sign-> approxComplex floatTol (adjust xs) (Trafo3.fourier sign (Trafo3.fourier (flipSign sign) xs))
QC.forAll genCyclicArray3 $ \xs sign -> approxComplex doubleTol (adjust xs) (Trafo3.fourier sign (Trafo3.fourier (flipSign sign) xs))
QC.forAll genCyclicArray3 $ \xs sign -> approxComplex floatTol (Trafo3.fourier sign (Array.map Complex.conjugate xs)) (Array.map Complex.conjugate (Trafo3.fourier (flipSign sign) xs))
QC.forAll genCyclicArray3 $ \xs sign -> approxComplex doubleTol (Trafo3.fourier sign (Array.map Complex.conjugate xs)) (Array.map Complex.conjugate (Trafo3.fourier (flipSign sign) xs))
QC.forAll genCyclicArray3 $ \xys sign -> let (xs,ys) = split xys in approxComplex floatTol (Trafo3.fourier sign $ Array.zipWith (+) xs ys) (Array.zipWith (+) (Trafo3.fourier sign xs) (Trafo3.fourier sign ys))
QC.forAll genCyclicArray3 $ \xys sign -> let (xs,ys) = split xys in approxComplex doubleTol (Trafo3.fourier sign $ Array.zipWith (+) xs ys) (Array.zipWith (+) (Trafo3.fourier sign xs) (Trafo3.fourier sign ys))
QC.forAll genCyclicArray3 $ \xys sign -> let (xs,ys) = split xys in Complex.magnitude (scalarProduct (adjust xs) ys - scalarProduct (Trafo3.fourier sign xs) (Trafo3.fourier sign ys)) <= floatTol * normInf Complex.magnitude (adjust xs) * normInf Complex.magnitude ys
QC.forAll genCyclicArray3 $ \xys sign -> let (xs,ys) = split xys in Complex.magnitude (scalarProduct (adjust xs) ys - scalarProduct (Trafo3.fourier sign xs) (Trafo3.fourier sign ys)) <= doubleTol * normInf Complex.magnitude (adjust xs) * normInf Complex.magnitude ys
\sign -> QC.forAll genCyclicArray3 $ immutable (Trafo3.fourier sign) . arrayComplexFloat
\sign -> QC.forAll genCyclicArray3 $ immutable (Trafo3.fourier sign) . arrayComplexDouble

data Sign Source #

Order is chosen such that the numeric sign is (-1) ^ fromEnum sign.

Constructors

Backward 
Forward 
Instances
Enum Sign Source # 
Instance details

Defined in Numeric.FFTW.Private

Methods

succ :: Sign -> Sign #

pred :: Sign -> Sign #

toEnum :: Int -> Sign #

fromEnum :: Sign -> Int #

enumFrom :: Sign -> [Sign] #

enumFromThen :: Sign -> Sign -> [Sign] #

enumFromTo :: Sign -> Sign -> [Sign] #

enumFromThenTo :: Sign -> Sign -> Sign -> [Sign] #

Eq Sign Source # 
Instance details

Defined in Numeric.FFTW.Private

Methods

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

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

Ord Sign Source # 
Instance details

Defined in Numeric.FFTW.Private

Methods

compare :: Sign -> Sign -> Ordering #

(<) :: Sign -> Sign -> Bool #

(<=) :: Sign -> Sign -> Bool #

(>) :: Sign -> Sign -> Bool #

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

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 
Instance details

Defined in Numeric.FFTW.Private

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

Arbitrary Sign Source # 
Instance details

Defined in Numeric.FFTW.Private

Methods

arbitrary :: Gen Sign #

shrink :: Sign -> [Sign] #

fourierRC :: (Integral n0, Integral n1, Integral n2, Real a) => Array (Cyclic n0, Cyclic n1, Cyclic n2) a -> Array (Cyclic n0, Cyclic n1, Half n2) (Complex a) Source #

QC.forAll genCyclicArray3 $ \xs -> approxReal floatTol (adjust xs) (Trafo3.fourierCR (Trafo3.fourierRC xs))
QC.forAll genCyclicArray3 $ \xs -> approxReal doubleTol (adjust xs) (Trafo3.fourierCR (Trafo3.fourierRC xs))
QC.forAll genCyclicArray3 $ immutable Trafo3.fourierRC . arrayFloat
QC.forAll genCyclicArray3 $ immutable Trafo3.fourierRC . arrayDouble

fourierCR :: (Integral n0, Integral n1, Integral n2, Real a) => Array (Cyclic n0, Cyclic n1, Half n2) (Complex a) -> Array (Cyclic n0, Cyclic n1, Cyclic n2) a Source #

QC.forAll (fmap Trafo3.fourierRC genCyclicArray3) $ immutable Trafo3.fourierCR . arrayComplexFloat
QC.forAll (fmap Trafo3.fourierRC genCyclicArray3) $ immutable Trafo3.fourierCR . arrayComplexDouble