-- Do not edit! Automatically created with doctest-extract from src/Numeric/BLAS/Matrix/RowMajor/Block.hs {-# LINE 57 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} {-# OPTIONS_GHC -XTypeOperators #-} module Test.ComplexDouble.Numeric.BLAS.Matrix.RowMajor.Block where import qualified Test.DocTest.Driver as DocTest {-# LINE 59 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} import Test.ComplexDouble.Numeric.BLAS.Matrix.RowMajor (Matrix, forMatrix) import Test.ComplexDouble.Numeric.BLAS.Vector (forVector, genVector, Number_, number_, maxDim) import Test.Slice (ShapeInt, shapeInt) import qualified Numeric.BLAS.Matrix.RowMajor.Block as BlockMatrix import qualified Numeric.BLAS.Matrix.RowMajor as Matrix import qualified Numeric.BLAS.Vector.Slice as VectorSlice import qualified Numeric.BLAS.Vector as Vector import qualified Numeric.BLAS.Subobject.Shape as Subshape import qualified Numeric.BLAS.Slice as Slice import Numeric.BLAS.Matrix.RowMajor.Block ((&===), (&|||)) import Numeric.BLAS.Vector (Vector, (+++)) import qualified Data.Array.Comfort.Boxed.Dim2 as BoxedArray2 import qualified Data.Array.Comfort.Boxed as BoxedArray import qualified Data.Array.Comfort.Storable.Dim2 as Array2 import qualified Data.Array.Comfort.Storable as Array import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Shape ((::+)((::+))) import Control.Monad (replicateM) import Control.Applicative (liftA2) import qualified Test.QuickCheck as QC import Test.QuickCheck ((===)) forPad :: (Shape.C sh, Show sh, QC.Testable prop) => sh -> (Vector (sh, ShapeInt) Number_ -> Vector (sh, ShapeInt) Number_ -> prop) -> QC.Property forPad height prop = QC.forAll (shapeInt <$> QC.choose (0,maxDim)) $ \leftPadShape -> QC.forAll (shapeInt <$> QC.choose (0,maxDim)) $ \rightPadShape -> QC.forAll (genVector (height, leftPadShape) number_) $ \leftPad -> QC.forAll (genVector (height, rightPadShape) number_) $ \rightPad -> prop leftPad rightPad forPadded :: (QC.Testable prop) => (Matrix Number_ -> Vector (Subshape.Submatrix (ShapeInt, ShapeInt)) Number_ -> prop) -> QC.Property forPadded prop = forMatrix number_ $ \a -> let height = Matrix.height a in forVector number_ $ \prefix -> forVector number_ $ \suffix -> forPad height $ \leftPad rightPad -> prop a $ Array.mapShape Subshape.submatrixFromAppend $ prefix +++ Matrix.beside leftPad (Matrix.beside a rightPad) +++ suffix test :: DocTest.T () test = do DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:197: " {-# LINE 197 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 197 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> Matrix.transpose a === BlockMatrix.toMatrix (BlockMatrix.transposed a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:222: " {-# LINE 222 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 222 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> let height = Matrix.height a in QC.forAll (shapeInt <$> QC.choose (0,maxDim)) $ \width -> Matrix.beside a (Vector.zero (height,width)) === BlockMatrix.toMatrix (a &||| BlockMatrix.zero height width) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:257: " {-# LINE 257 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 257 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> a === (Matrix.reshapeHeight (Matrix.height a) $ BlockMatrix.toMatrix $ BlockMatrix.fromBlockColumn (Matrix.width a) $ map BlockMatrix.row $ VectorSlice.slicesVector Slice.rows a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:267: " {-# LINE 267 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 267 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> Matrix.transpose a === (Matrix.reshapeHeight (Matrix.width a) $ BlockMatrix.toMatrix $ BlockMatrix.fromBlockColumn (Matrix.height a) $ map BlockMatrix.row $ VectorSlice.slicesVector Slice.columns a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:287: " {-# LINE 287 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 287 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> a === (Matrix.reshapeWidth (Matrix.width a) $ BlockMatrix.toMatrix $ BlockMatrix.fromBlockRow (Matrix.height a) $ map BlockMatrix.column $ VectorSlice.slicesVector Slice.columns a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:297: " {-# LINE 297 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 297 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \a -> Matrix.transpose a === (Matrix.reshapeWidth (Matrix.height a) $ BlockMatrix.toMatrix $ BlockMatrix.fromBlockRow (Matrix.width a) $ map BlockMatrix.column $ VectorSlice.slicesVector Slice.rows a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:326: " {-# LINE 326 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 326 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forPadded $ \a padded -> BlockMatrix.toMatrix (BlockMatrix.submatrix padded) === a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:334: " {-# LINE 334 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 334 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forPadded $ \a padded -> forPad (Matrix.height a) $ \leftPad rightPad -> let b = BlockMatrix.submatrix padded in BlockMatrix.toMatrix (leftPad &||| b &||| rightPad) === Matrix.beside leftPad (Matrix.beside a rightPad) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:362: " {-# LINE 362 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 362 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forPadded $ \a padded -> BlockMatrix.toMatrix (BlockMatrix.transposedSubmatrix padded) === Matrix.transpose a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:370: " {-# LINE 370 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 370 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forPadded $ \a padded -> forPad (Matrix.width a) $ \leftPad rightPad -> let b = BlockMatrix.transposedSubmatrix padded in BlockMatrix.toMatrix (leftPad &||| b &||| rightPad) === Matrix.beside leftPad (Matrix.beside (Matrix.transpose a) rightPad) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:445: " {-# LINE 445 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 445 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} QC.forAll (shapeInt <$> QC.choose (0,maxDim)) $ \height -> QC.forAll (QC.choose (0,5)) $ \n -> QC.forAll (replicateM n (flip genVector number_ . (,) height . shapeInt =<< QC.choose (0,maxDim))) $ \blocks -> BlockMatrix.toMatrix (BlockMatrix.fromBlockRow height blocks) === BlockMatrix.toMatrix (foldr (\a b -> BlockMatrix.mapWidth (\(shA::+shB) -> shA:shB) $ a&|||b) (BlockMatrix.zero height []) blocks) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:475: " {-# LINE 475 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 475 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} QC.forAll (shapeInt <$> QC.choose (0,maxDim)) $ \width -> QC.forAll (QC.choose (0,5)) $ \n -> QC.forAll (replicateM n (flip genVector number_ . flip (,) width . shapeInt =<< QC.choose (0,maxDim))) $ \blocks -> Matrix.transpose (BlockMatrix.toMatrix (BlockMatrix.fromBlockColumn width blocks)) === BlockMatrix.toMatrix (BlockMatrix.fromBlockRow width $ map BlockMatrix.transposed blocks) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:521: " {-# LINE 521 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 521 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} QC.forAll (QC.choose (0,5)) $ \m -> QC.forAll (replicateM m (shapeInt <$> QC.choose (0,maxDim))) $ \heights -> QC.forAll (QC.choose (0,5)) $ \n -> QC.forAll (replicateM n (shapeInt <$> QC.choose (0,maxDim))) $ \widths -> QC.forAll (traverse (flip genVector number_) $ BoxedArray2.cartesian (BoxedArray.vectorFromList heights) (BoxedArray.vectorFromList widths)) $ \blocks -> Matrix.transpose (BlockMatrix.toMatrix (BlockMatrix.fromBlockEnsemble heights widths blocks)) === BlockMatrix.toMatrix (BlockMatrix.fromBlockEnsemble widths heights $ BoxedArray2.transpose $ fmap BlockMatrix.transposed blocks) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:566: " {-# LINE 566 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 566 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} forMatrix number_ $ \blockA1 -> forMatrix number_ $ \blockB3 -> QC.forAll (liftA2 (\char0 char1 -> Shape.Range (min char0 char1) (max char0 char1)) (QC.choose ('a','k')) (QC.choose ('a','k'))) $ \shapeC1 -> let shapeR0 = fst $ Array.shape blockA1 in let shapeC0 = snd $ Array.shape blockA1 in let shapeR1 = fst $ Array.shape blockB3 in let shapeC2 = snd $ Array.shape blockB3 in QC.forAll (genVector (shapeR0, shapeC1) number_) $ \blockA2 -> QC.forAll (genVector (shapeR0, shapeC2) number_) $ \blockA3 -> QC.forAll (genVector (shapeR1, shapeC0) number_) $ \blockB1 -> QC.forAll (genVector (shapeR1, shapeC1) number_) $ \blockB2 -> BlockMatrix.toMatrix (blockA1 &||| Matrix.beside blockA2 blockA3 &=== blockB1 &||| blockB2 &||| blockB3) === Array2.fromBlockMatrix (blockA1 Array2.&||| blockA2 Array2.&||| blockA3 Array2.&=== blockB1 Array2.&||| blockB2 Array2.&||| blockB3) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor.Block:594: " {-# LINE 594 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} DocTest.property( {-# LINE 594 "src/Numeric/BLAS/Matrix/RowMajor/Block.hs" #-} QC.forAll (liftA2 (\char0 char1 -> Shape.Range (min char0 char1) (max char0 char1)) (QC.choose ('a','k')) (QC.choose ('a','k'))) $ \shapeR0 -> QC.forAll (liftA2 Shape.Shifted (QC.choose (-10,10)) (QC.choose (0,10::Int))) $ \shapeR1 -> let shapeR2 = () in QC.forAll (fmap Shape.ZeroBased (QC.choose (0,10::Int))) $ \shapeC0 -> QC.forAll (fmap Shape.OneBased (QC.choose (0,10::Int))) $ \shapeC1 -> let shapeC2 :: Shape.Enumeration Ordering shapeC2 = Shape.Enumeration in QC.forAll (genVector (shapeR0, shapeC0) number_) $ \blockA1 -> QC.forAll (genVector (shapeR0, shapeC1) number_) $ \blockA2 -> QC.forAll (genVector (shapeC2, shapeR0) number_) $ \blockA3 -> QC.forAll (genVector (shapeR1, shapeC0) number_) $ \blockB1 -> QC.forAll (genVector (shapeR1, shapeC1) number_) $ \blockB2 -> QC.forAll (genVector (shapeR1, shapeC2) number_) $ \blockB3 -> QC.forAll (genVector (shapeR2, shapeC0) number_) $ \blockC1 -> QC.forAll (genVector (shapeR2, shapeC1) number_) $ \blockC2 -> QC.forAll (genVector (shapeR2, shapeC2) number_) $ \blockC3 -> BlockMatrix.toMatrix (blockA1 &||| blockA2 &||| BlockMatrix.transposed blockA3 &=== blockB1 &||| blockB2 &||| blockB3 &=== blockC1 &||| blockC2 &||| blockC3) === Matrix.beside (Matrix.above blockA1 $ Matrix.above blockB1 blockC1) (Matrix.above (Matrix.beside blockA2 $ Matrix.transpose blockA3) (Matrix.beside (Matrix.above blockB2 blockC2) (Matrix.above blockB3 blockC3))) )