-- Do not edit! Automatically created with doctest-extract from src/Numeric/BLAS/Slice.hs {-# LINE 13 "src/Numeric/BLAS/Slice.hs" #-} module Test.Numeric.BLAS.Slice where import qualified Test.DocTest.Driver as DocTest {-# LINE 14 "src/Numeric/BLAS/Slice.hs" #-} import qualified Numeric.BLAS.Slice as Slice import Test.Slice (shapeInt) import qualified Data.Array.Comfort.Boxed as Array import qualified Data.Array.Comfort.Shape as Shape import qualified Data.Map as Map import Data.Array.Comfort.Shape ((::+)((::+))) import Data.Array.Comfort.Boxed ((!)) import Control.Applicative (liftA3, pure) import qualified Test.QuickCheck as QC genSlice :: sh -> QC.Gen (Slice.T sh) genSlice sh = liftA3 Slice.Cons (QC.choose (0,100)) (QC.choose (1,100)) (pure sh) genSlice2 :: shA -> shB -> QC.Gen (Slice.T shA, Slice.T shB) genSlice2 shA shB = do s <- QC.choose (0,100) k <- QC.choose (1,100) return (Slice.Cons s k shA, Slice.Cons s k shB) test :: DocTest.T () test = do DocTest.printPrefix "Numeric.BLAS.Slice:58: " {-# LINE 58 "src/Numeric/BLAS/Slice.hs" #-} DocTest.property {-# LINE 58 "src/Numeric/BLAS/Slice.hs" #-} (QC.forAll (QC.choose (1,100)) $ \numRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> QC.forAll (genSlice (shapeInt numRows, shapeInt numColumns)) $ \slice -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numRows) $ \ix -> Slice.row ix slice == Slice.rowArray slice ! ix) DocTest.printPrefix "Numeric.BLAS.Slice:70: " {-# LINE 70 "src/Numeric/BLAS/Slice.hs" #-} DocTest.property {-# LINE 70 "src/Numeric/BLAS/Slice.hs" #-} (QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (QC.choose (1,100)) $ \numColumns -> QC.forAll (genSlice (shapeInt numRows, shapeInt numColumns)) $ \slice -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numColumns) $ \ix -> Slice.column ix slice == Slice.columnArray slice ! ix) DocTest.printPrefix "Numeric.BLAS.Slice:145: " {-# LINE 145 "src/Numeric/BLAS/Slice.hs" #-} DocTest.property {-# LINE 145 "src/Numeric/BLAS/Slice.hs" #-} (QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeA -> QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeB -> QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeC -> QC.forAll (genSlice2 (Map.fromList $ ('a', shapeA) : ('b', shapeB) : ('c', shapeC) : []) (shapeA ::+ shapeB ::+ shapeC)) $ \(sliceMap, sliceParted) -> Slice.map sliceMap Map.! 'b' == Slice.left (Slice.right sliceParted)) DocTest.printPrefix "Numeric.BLAS.Slice:147: " {-# LINE 147 "src/Numeric/BLAS/Slice.hs" #-} DocTest.property {-# LINE 147 "src/Numeric/BLAS/Slice.hs" #-} (QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> let rowShape = shapeInt numRows; columnShape = shapeInt numColumns; mapShape = Map.fromList $ map (\k -> (k, columnShape)) (Shape.indices rowShape) in QC.forAll (genSlice2 mapShape (rowShape, columnShape)) $ \(sliceMap, sliceMatrix) -> Map.toAscList (Slice.map sliceMap) == Array.toAssociations (Slice.rowArray sliceMatrix))