-- Do not edit! Automatically created with doctest-extract from src/Numeric/BLAS/Subobject/View/Matrix.hs {-# LINE 23 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} {-# OPTIONS_GHC -XTypeOperators #-} module Test.Numeric.BLAS.Subobject.View.Matrix where import qualified Test.DocTest.Driver as DocTest {-# LINE 26 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} import qualified Numeric.BLAS.Subobject.View.Matrix as ViewMatrix import qualified Numeric.BLAS.Subobject.View as View import qualified Numeric.BLAS.Subobject.Layout as Layout import Test.Slice (shapeInt) import qualified Data.Array.Comfort.Boxed as Array import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Shape ((::+)((::+))) import Data.Array.Comfort.Boxed ((!)) import Control.Applicative (liftA3, pure) import qualified Test.QuickCheck as QC genView :: (height,width) -> QC.Gen (ViewMatrix.T (height,width)) genView sh = liftA3 View.Cons (QC.choose (0,100)) (fmap Layout.Submatrix $ QC.choose (1,100)) (pure sh) type ShapeInt = Shape.ZeroBased Int test :: DocTest.T () test = do DocTest.printPrefix "Numeric.BLAS.Subobject.View.Matrix:105: " {-# LINE 105 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} DocTest.property( {-# LINE 105 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} QC.forAll (QC.choose (1,100)) $ \numRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> QC.forAll (genView (shapeInt numRows, shapeInt numColumns)) $ \view -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numRows) $ \ix -> ViewMatrix.row ix view == ViewMatrix.rowArray view ! ix ) DocTest.printPrefix "Numeric.BLAS.Subobject.View.Matrix:127: " {-# LINE 127 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} DocTest.property( {-# LINE 127 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (QC.choose (1,100)) $ \numColumns -> QC.forAll (genView (shapeInt numRows, shapeInt numColumns)) $ \view -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numColumns) $ \ix -> ViewMatrix.column ix view == ViewMatrix.columnArray view ! ix ) DocTest.printPrefix "Numeric.BLAS.Subobject.View.Matrix:152: " {-# LINE 152 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} DocTest.property( {-# LINE 152 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} QC.forAll (QC.choose (1,100)) $ \numTopRows -> QC.forAll (QC.choose (1,100)) $ \numBottomRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> QC.forAll (genView (shapeInt numTopRows ::+ shapeInt numBottomRows, shapeInt numColumns)) $ \view -> ViewMatrix.rowArray view == Array.append (ViewMatrix.rowArray (ViewMatrix.top view)) (ViewMatrix.rowArray (ViewMatrix.bottom view)) ) DocTest.printPrefix "Numeric.BLAS.Subobject.View.Matrix:178: " {-# LINE 178 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} DocTest.property( {-# LINE 178 "src/Numeric/BLAS/Subobject/View/Matrix.hs" #-} QC.forAll (QC.choose (1,100)) $ \numLeftColumns -> QC.forAll (QC.choose (1,100)) $ \numRightColumns -> QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (genView (shapeInt numRows, shapeInt numLeftColumns ::+ shapeInt numRightColumns)) $ \view -> ViewMatrix.columnArray view == Array.append (ViewMatrix.columnArray (ViewMatrix.left view)) (ViewMatrix.columnArray (ViewMatrix.right view)) )