-- Do not edit! Automatically created with doctest-extract from src/Numeric/FFTW/Extra/Rank1.hs {-# LINE 46 "src/Numeric/FFTW/Extra/Rank1.hs" #-} {-# OPTIONS_GHC -XTypeFamilies #-} module DocTest.Float.Numeric.FFTW.Extra.Rank1 where import qualified Test.DocTest.Driver as DocTest {-# LINE 48 "src/Numeric/FFTW/Extra/Rank1.hs" #-} import Test.Numeric.FFTW.Extra.Utility import Numeric.FFTW.Extra.Rank1 import DocTest.Float.Numeric.FFTW.Extra.Rank1.Convolution (real_, complex_) import Numeric.FFTW.Extra.Utility (padShape, padCyclic, spreadCyclic, cyclicTake) import qualified Numeric.FFTW.Shape as Spectrum import qualified Numeric.FFTW.Rank1 as Rank1 import qualified Numeric.BLAS.Vector as Vector import qualified Data.Array.Comfort.Storable as Array import qualified Data.Array.Comfort.Shape as Shape import qualified Data.Complex as Complex import Data.Array.Comfort.Storable ((//), (!)) import Data.Complex (Complex((:+)), cis) import qualified Test.QuickCheck as QC test :: DocTest.T () test = do DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:98: " {-# LINE 98 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 98 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll (genCyclic complex_) $ \x sign -> QC.forAll (chooseLogarithmic (Shape.cyclicSize $ Array.shape x)) $ \m -> takeFourier sign (Shape.ZeroBased m) x =~= takeShape (Shape.ZeroBased m) (Rank1.fourier sign x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:110: " {-# LINE 110 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 110 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll (genCyclic complex_) $ \x sign -> let n = Shape.cyclicSize $ Array.shape x in forChoose (1,10) $ \m -> Rank1.fourier (Rank1.flipSign sign) (Array.mapShape (Shape.Cyclic . Shape.zeroBasedSize) (takeFourier sign (Shape.ZeroBased n) (upsample m x))) =~= Vector.scaleReal (fromIntegral n) x ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:126: " {-# LINE 126 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 126 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll (genCyclic complex_) $ \x sign -> let n = Shape.size $ Array.shape x in QC.forAll (chooseLogarithmic n) $ \m from -> let shape = Shape.intervalFromShifted $ Shape.Shifted from m in takeFourier sign shape x =~= cyclicTake shape (Rank1.fourier sign x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:195: " {-# LINE 195 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 195 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll (genCyclic real_) $ \x -> QC.forAll (chooseLogarithmic (Shape.size $ Array.shape x)) $ \m -> takeFourierRC m x =~= takeShape (Spectrum.Half m) (Rank1.fourierRC x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:208: " {-# LINE 208 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 208 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll (genCyclic real_) $ \x -> let n = Shape.cyclicSize $ Array.shape x in forChoose (1,10) $ \m -> Rank1.fourierCR (takeFourierRC n (upsample m x)) =~= Vector.scale (fromIntegral n) x ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:225: " {-# LINE 225 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 225 "src/Numeric/FFTW/Extra/Rank1.hs" #-} forChoose (1,100::Int) $ \n k -> forChoose (1, div n 2) $ \m -> let c = - 2*pi / fromIntegral n in takeFourierRC m (Vector.unit (Shape.Cyclic n) k &:: real_) =~= Array.sample (Spectrum.Half m) (\i -> cis (c * fromIntegral (i*k))) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:237: " {-# LINE 237 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 237 "src/Numeric/FFTW/Extra/Rank1.hs" #-} forChoose (1,100::Int) $ \n k -> forChoose (1,n) $ \m -> let c = 2*pi / fromIntegral n in let d = 2*pi / fromIntegral m in Vector.fromReal (Rank1.fourierCR (takeFourierRC m (Vector.unit (Shape.Cyclic n) k))) =~= Array.sample (Shape.Cyclic m) (\j -> (if even m then let m2 = div m 2 in cos (d * fromIntegral (m2*j) - c * fromIntegral (m2*k)) :+ 0 else 0) + (Vector.sum $ Array.sample (Shape.Interval (- div (m-1) 2) (div (m-1) 2)) (\i -> cis (d * fromIntegral (i*j) - c * fromIntegral (i*k))))) &:: complex_ ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:269: " {-# LINE 269 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 269 "src/Numeric/FFTW/Extra/Rank1.hs" #-} forChoose (1,100::Int) $ \n k -> forChoose (1,n) $ \m -> let c = pi / fromIntegral (m*n) in let projectCentric i = let nm2 = div (n*m) 2 (q,r) = divMod (i+nm2) (n*m) in c * fromIntegral (if even q then r-nm2 else nm2-r) in -- numerically stable version of sin (c*m1*i) / sin (c*i) let dirichlet :: Int -> Int -> Float dirichlet m1 i = if mod i (n*m) == 0 then fromIntegral m1 else sin (projectCentric (m1*i)) / sin (projectCentric i) in Rank1.fourierCR (takeFourierRC m (Vector.unit (Shape.Cyclic n) k)) =~= Array.sample (Shape.Cyclic m) (\j -> let i = n*j - m*k (m1,residue) = if even m then (m-1, cos (c * fromIntegral (m*i))) else (m, 0) in residue + dirichlet m1 i) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:380: " {-# LINE 380 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 380 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll genVectorShape $ \shape sign -> let n = Shape.zeroBasedSize shape in QC.forAll (chooseLogarithmic n) $ \m -> QC.forAll (genVectorForShape complex_ (Shape.ZeroBased m)) $ \x -> extendFourier sign n x =~= Rank1.fourier sign (padCyclic n x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:395: " {-# LINE 395 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 395 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll genVectorShape $ \shape sign -> let n = Shape.zeroBasedSize shape in QC.forAll (chooseLogarithmic n) $ \m from -> let rng = Shape.intervalFromShifted $ Shape.Shifted from m in QC.forAll (genVectorForShape complex_ rng) $ \x -> extendFourier sign n x =~= Rank1.fourier sign (spreadCyclic n x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:407: " {-# LINE 407 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 407 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll genVectorShape $ \shape sign -> let n = Shape.zeroBasedSize shape in QC.forAll (chooseLogarithmic n) $ \m -> QC.forAll (genVectorForShape complex_ (Shape.ZeroBased m)) $ \x -> extendFourier sign n x =~= extendFourier sign n (Array.mapShape Shape.intervalFromZeroBased x) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:420: " {-# LINE 420 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 420 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll genVectorShape $ \shape -> let n = Shape.zeroBasedSize shape in n>=3 QC.==> QC.forAll (chooseLogarithmic (n - mod (n+1) 2)) $ \m -> let halfShape = Spectrum.Half m in QC.forAll (genVectorForShape complex_ halfShape) $ \xc -> let x = xc // [(0, Complex.realPart (xc!0) :+ 0)] in let nh = Shape.size halfShape in let xs = Array.reshape (Shape.ZeroBased nh) x in Vector.fromReal (extendFourierCR n x) =~= extendFourier Rank1.Backward n (Array.reshape (Shape.Interval (1-nh) (nh-1)) $ Vector.conjugate (Vector.reverse xs) <> Vector.drop 1 xs) ) DocTest.printPrefix "Numeric.FFTW.Extra.Rank1:471: " {-# LINE 471 "src/Numeric/FFTW/Extra/Rank1.hs" #-} DocTest.property( {-# LINE 471 "src/Numeric/FFTW/Extra/Rank1.hs" #-} QC.forAll genVectorShape $ \shape -> let n = Shape.zeroBasedSize shape in QC.forAll (chooseLogarithmic n) $ \m -> QC.forAll (genVectorForShape complex_ (Spectrum.Half m)) $ \x -> Rank1.fourierCR (padShape (Spectrum.Half n) x) =~= extendFourierCR n x )