-- Do not edit! Automatically created with doctest-extract from private/Numeric/BLAS/Rank1/Unit.hs {-# LINE 33 "private/Numeric/BLAS/Rank1/Unit.hs" #-} {-# OPTIONS_GHC -XTypeFamilies #-} module DocTest.Double.Numeric.BLAS.Rank1.Unit where import qualified Test.DocTest.Driver as DocTest {-# LINE 35 "private/Numeric/BLAS/Rank1/Unit.hs" #-} import Numeric.BLAS.Rank1.Unit import Test.Numeric.FFTW.Extra.Utility import DocTest.Double.Numeric.FFTW.Extra.Rank1.Convolution (complex_) import qualified Numeric.FFTW.Rank1 as Rank1 import qualified Numeric.BLAS.Matrix.RowMajor as Matrix import qualified Numeric.BLAS.Vector.Slice as VectorSlice import qualified Data.Array.Comfort.Shape as Shape import qualified Test.QuickCheck as QC test :: DocTest.T () test = do DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:100: " {-# LINE 100 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 100 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \shape -> let n = Shape.zeroBasedSize shape in let c = 2*pi / fromIntegral n in QC.forAll (chooseLogarithmic n) $ \m i -> VectorSlice.toVector (twiddleVectorCascaded c n shape m i) =~= (twiddleVectorWrap c n shape i &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:197: " {-# LINE 197 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 197 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll (QC.choose (-2*pi,2*pi)) $ \c -> QC.forAll genVectorShape $ \shape -> let n = Shape.zeroBasedSize shape in QC.forAll (chooseLogarithmic n) $ \m -> QC.forAll (QC.choose (1, div n m + 1)) $ \i -> VectorSlice.toVector (twiddleVectorFast c shape m i) =~= (twiddleVector c shape i &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:221: " {-# LINE 221 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 221 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll (QC.choose (-pi,pi)) $ \c -> QC.forAll genVectorShape $ \(Shape.ZeroBased n) -> QC.forAll (QC.choose (-2*n,n)) $ \start -> let shape = Shape.Shifted start n in QC.forAll (chooseLogarithmic n) $ \m -> QC.forAll (QC.choose (1, div n m + 1)) $ \i -> VectorSlice.toVector (twiddleVectorShiftedFast c shape m i) =~= (twiddleVector c shape i &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:273: " {-# LINE 273 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 273 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll (QC.choose (-2*pi,2*pi)) $ \c -> QC.forAll genVectorShape $ \(Shape.ZeroBased nk) -> QC.forAll (chooseLogarithmic nk) $ \k -> let n = div nk k in let width = Shape.ZeroBased k in QC.forAll (QC.choose (-2*n,n)) $ \start -> let height = Shape.intervalFromShifted $ Shape.Shifted start n in QC.forAll (chooseLogarithmic n) $ \m -> let tm = twiddleMatrix c (height, width) &:: complex_ in tm =~= (Matrix.reshapeHeight height $ Matrix.fromRows width $ take n $ twiddleMatrixRowsCascaded c m (height,width)) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:316: " {-# LINE 316 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 316 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \width sign -> let n = Shape.zeroBasedSize width in let cu = 2*pi / fromIntegral n in let c = case sign of Rank1.Forward -> cu; Rank1.Backward -> -cu in QC.forAll (chooseLogarithmic n) $ \m -> let height = Shape.ZeroBased m in (twiddleMatrix c (height, width) &:: complex_) =~= (Matrix.reshapeHeight height $ Matrix.fromRows width $ twiddleMatrixViaChirp sign n (height,width)) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:347: " {-# LINE 347 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 347 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \widthZB fromW sign -> let n = Shape.zeroBasedSize widthZB in let width = Shape.Shifted fromW n in let cu = 2*pi / fromIntegral n in let c = case sign of Rank1.Forward -> cu; Rank1.Backward -> -cu in QC.forAll (chooseLogarithmic n) $ \m fromH -> let height = Shape.Shifted fromH m in (twiddleMatrix c (height, width) &:: complex_) =~= (Matrix.reshapeHeight height $ Matrix.fromRows width $ twiddleMatrixViaChirpShifted sign n (height,width)) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:417: " {-# LINE 417 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 417 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \shape (QC.Positive n) sign -> chirpForShape sign n shape =~= (chirpForShapeScaled sign n 1 shape &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:433: " {-# LINE 433 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 433 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \(Shape.ZeroBased m) (QC.Positive n) sign -> QC.forAll (chooseLogarithmic m) $ \k -> nonNegChirp sign n m =~= (nonNegChirpFast sign n m k &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:469: " {-# LINE 469 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 469 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \(Shape.ZeroBased m) (QC.Positive n) sign -> QC.forAll (chooseLogarithmic m) $ \k -> nonNegChirp sign n m =~= (nonNegChirpChirpy sign n m k &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:495: " {-# LINE 495 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 495 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \(Shape.ZeroBased m) from (QC.Positive n) sign -> QC.forAll (chooseLogarithmic m) $ \k -> let shape = Shape.Shifted from m in chirpForShape sign n shape =~= (chirpForShapeChirpy sign n shape k &:: complex_) ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:541: " {-# LINE 541 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 541 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \shape sign -> let n = Shape.zeroBasedSize shape in forChoose (0,n) $ \to -> forChoose (-n,to) $ \from -> let rng = Shape.Interval from to in VectorSlice.toVector (interval2FromChirp rng (nonNegChirp sign n (n+1))) =~= chirpForShape sign n rng &:: complex_ ) DocTest.printPrefix "Numeric.BLAS.Rank1.Unit:568: " {-# LINE 568 "private/Numeric/BLAS/Rank1/Unit.hs" #-} DocTest.property( {-# LINE 568 "private/Numeric/BLAS/Rank1/Unit.hs" #-} QC.forAll genVectorShape $ \shape sign from (QC.NonNegative offset) -> let n = Shape.zeroBasedSize shape in let to = from+n+offset in let rng = Shape.Interval from to in interval3FromChirp rng (nonNegChirp sign n (n+1)) =~= chirpForShape sign n rng &:: complex_ )