-- Do not edit! Automatically created with doctest-extract from src/Numeric/BLAS/Matrix/RowMajor.hs {-# LINE 108 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} {-# OPTIONS_GHC -XTypeOperators #-} module Test.ComplexDouble.Numeric.BLAS.Matrix.RowMajor where import Test.DocTest.Base import qualified Test.DocTest.Driver as DocTest {-# LINE 110 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} import Test.ComplexDouble.Numeric.BLAS.Vector.Slice (forSliced, forSliced2) import Test.ComplexDouble.Numeric.BLAS.Vector (genVector, Number_, number_, real_) import Test.Slice (ShapeInt, shapeInt) -- import Test.Utility (approx) import qualified Numeric.BLAS.Matrix.RowMajor.Block as BlockMatrix import qualified Numeric.BLAS.Matrix.RowMajor.Square as Square import qualified Numeric.BLAS.Matrix.RowMajor as Matrix import qualified Numeric.BLAS.Vector.Symbolic as VectorSymb import qualified Numeric.BLAS.Vector.Slice as VectorSlice import qualified Numeric.BLAS.Vector as Vector import qualified Numeric.BLAS.Slice as Slice import qualified Numeric.Netlib.Class as Class import Numeric.BLAS.Matrix.RowMajor.Block ((&===), (&|||)) import Numeric.BLAS.Vector.Slice ((|+|), (.*|)) import Numeric.BLAS.Scalar (RealOf) import Numeric.Netlib.Modifier (Conjugation(NonConjugated, Conjugated)) 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 qualified Data.Array.Comfort.Boxed as BoxedArray import qualified Data.Foldable as Fold import qualified Data.Map as Map import qualified Data.Set as Set import qualified Data.Monoid.HT as Mn import Data.Array.Comfort.Shape ((::+)((::+))) import Data.Map (Map) import Data.Function.HT (Id) import qualified Test.QuickCheck as QC import Test.QuickCheck ((===)) type Matrix = Matrix.Matrix ShapeInt ShapeInt type Real_ = RealOf Number_ maxDim :: Int maxDim = 10 forMatrix :: (QC.Testable prop, QC.Arbitrary a, Class.Floating a, Show a) => QC.Gen a -> (Matrix a -> prop) -> QC.Property forMatrix genElem = QC.forAllShrink (do height <- fmap shapeInt $ QC.choose (0,maxDim) width <- fmap shapeInt $ QC.choose (0,maxDim) genVector (height, width) genElem) (\a -> let (height@(Shape.ZeroBased h), width@(Shape.ZeroBased w)) = Array.shape a in Mn.when (h > 0) [let h2 = div h 2 in Array2.takeTop $ Array.reshape (Shape.ZeroBased h2 ::+ Shape.ZeroBased (h-h2), width) a, Array2.takeTop $ Array.reshape (Shape.ZeroBased (h-1) ::+ (), width) a] ++ Mn.when (w > 0) [let w2 = div w 2 in Array2.takeLeft $ Array.reshape (height, Shape.ZeroBased w2 ::+ Shape.ZeroBased (w-w2)) a, Array2.takeLeft $ Array.reshape (height, Shape.ZeroBased (w-1) ::+ ()) a]) genSplitShape :: ShapeInt -> QC.Gen (ShapeInt ::+ ShapeInt) genSplitShape (Shape.ZeroBased n) = do k <- QC.choose (0, n) return $ Shape.ZeroBased k ::+ Shape.ZeroBased (n-k) genSplitShape3 :: ShapeInt -> QC.Gen (ShapeInt ::+ ShapeInt ::+ ShapeInt) genSplitShape3 (Shape.ZeroBased n) = do k <- QC.choose (0, n) j <- QC.choose (0, n) let a = min k j; b = max k j return $ Shape.ZeroBased a ::+ Shape.ZeroBased (b-a) ::+ Shape.ZeroBased (n-b) maybeConjugate :: (VectorSlice.C v, Shape.C sh, Class.Floating a) => Conjugation -> v sh a -> Array.Array sh a maybeConjugate conj x = case conj of NonConjugated -> VectorSlice.toVector x Conjugated -> VectorSlice.conjugate x test :: DocTest.T () test = do DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:242: " {-# LINE 242 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 242 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.identity (Shape.ZeroBased 0) :: Matrix.Square ShapeInt Real_ ) [ExpectedLine [LineChunk "StorableArray.fromList (ZeroBased {",WildCardChunk,LineChunk " 0},ZeroBased {",WildCardChunk,LineChunk " 0}) []"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:244: " {-# LINE 244 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 244 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.identity (Shape.ZeroBased 3) :: Matrix.Square ShapeInt Real_ ) [ExpectedLine [LineChunk "StorableArray.fromList (ZeroBased {",WildCardChunk,LineChunk " 3},ZeroBased {",WildCardChunk,LineChunk " 3}) [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:280: " {-# LINE 280 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 280 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.transpose a === Matrix.fromRowArray (Matrix.height a) (VectorSlice.slicesVector Slice.columnArray a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:321: " {-# LINE 321 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 321 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} (id :: Id (array (height, Map Char ShapeInt) Number_)) $ Matrix.fromBlockArray (Map.singleton 'A' (shapeInt 2) <> Map.singleton 'B' (shapeInt 3)) Map.empty $ BoxedArray.fromList (Set.fromList "AB", Set.empty) [] ) [ExpectedLine [LineChunk "StorableArray.fromList (fromList [('A',ZeroBased {",WildCardChunk,LineChunk " 2}),('B',ZeroBased {",WildCardChunk,LineChunk " 3})],fromList []) []"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:330: " {-# LINE 330 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 330 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \block -> let height = Map.singleton 'A' $ fst $ Array.shape block in let width = Map.singleton '1' $ snd $ Array.shape block in Array.reshape (height,width) block === Array2.fromBlockArray height width (BoxedArray.replicate (Set.singleton 'A', Set.singleton '1') block) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:341: " {-# LINE 341 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 341 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \blockA1 -> forMatrix number_ $ \blockB3 -> let shapeR0 = fst $ Array.shape blockA1 in let shapeR1 = fst $ Array.shape blockB3 in let shapeC0 = snd $ Array.shape blockA1 in QC.forAll (fmap shapeInt $ QC.choose (0,10)) $ \shapeC1 -> 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 -> let height = Map.fromList [('A',shapeR0),('B',shapeR1)] in let width = Map.fromList [('1',shapeC0),('2',shapeC1),('3',shapeC2)] in Array.reshape (height,width) (BlockMatrix.toMatrix (blockA1 &||| Array2.beside blockA2 blockA3 &=== blockB1 &||| blockB2 &||| blockB3)) === Matrix.fromBlockArray height width (BoxedArray.fromList (Set.fromList "AB", Set.fromList "123") [blockA1, blockA2, blockA3, blockB1, blockB2, blockB3]) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:402: " {-# LINE 402 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 402 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} let shapeR0 = shapeInt 2; shapeR1 = shapeInt 3 in let shapeC0 = shapeInt 3; shapeC1 = shapeInt 2 in let block sh a = Array.replicate sh (a::Real_) in Matrix.fromBlockArray (Map.singleton 'A' shapeR0 <> Map.singleton 'B' shapeR1) (Map.singleton '1' shapeC0 <> Map.singleton '2' shapeC1) $ BoxedArray.fromList (Set.fromList "AB", Set.fromList "12") [block (shapeR0,shapeC0) 0, block (shapeR0,shapeC1) 1, block (shapeR1,shapeC0) 2, block (shapeR1,shapeC1) 3] ) [ExpectedLine [LineChunk "StorableArray.fromList (fromList [('A',ZeroBased {",WildCardChunk,LineChunk " 2}),('B',ZeroBased {",WildCardChunk,LineChunk " 3})],fromList [('1',ZeroBased {",WildCardChunk,LineChunk " 3}),('2',ZeroBased {",WildCardChunk,LineChunk " 2})]) [0.0,0.0,0.0,1.0,1.0,0.0,0.0,0.0,1.0,1.0,2.0,2.0,2.0,3.0,3.0,2.0,2.0,2.0,3.0,3.0,2.0,2.0,2.0,3.0,3.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:415: " {-# LINE 415 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 415 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \blockA1 -> forMatrix number_ $ \blockB2 -> let shapeR0 = fst $ Array.shape blockA1 in let shapeC0 = snd $ Array.shape blockA1 in let shapeR1 = fst $ Array.shape blockB2 in let shapeC1 = snd $ Array.shape blockB2 in QC.forAll (genVector (shapeR0, shapeC1) number_) $ \blockA2 -> QC.forAll (genVector (shapeR1, shapeC0) number_) $ \blockB1 -> let blocked = BoxedArray.fromList (Set.fromList "AB", Set.fromList "12") [blockA1, blockA2, blockB1, blockB2] in Array2.fromNonEmptyBlockArray blocked === Matrix.fromNonEmptyBlockArray blocked ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:433: " {-# LINE 433 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 433 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \blockA1 -> forMatrix number_ $ \blockB2 -> forMatrix number_ $ \blockC3 -> let shapeR0 = fst $ Array.shape blockA1 in let shapeC0 = snd $ Array.shape blockA1 in let shapeR1 = fst $ Array.shape blockB2 in let shapeC1 = snd $ Array.shape blockB2 in let shapeR2 = fst $ Array.shape blockC3 in let shapeC2 = snd $ Array.shape blockC3 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, shapeC2) number_) $ \blockB3 -> QC.forAll (genVector (shapeR2, shapeC0) number_) $ \blockC1 -> QC.forAll (genVector (shapeR2, shapeC1) number_) $ \blockC2 -> let blocked = BoxedArray.fromList (Set.fromList "ABC", Set.fromList "123") [blockA1, blockA2, blockA3, blockB1, blockB2, blockB3, blockC1, blockC2, blockC3] in Array2.fromNonEmptyBlockArray blocked === Matrix.fromNonEmptyBlockArray blocked ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:484: " {-# LINE 484 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 484 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let (height, width) = Array.shape a in QC.forAll (genSplitShape height) $ \splitHeight -> let b = Array.reshape (splitHeight, width) a in b === Matrix.above (Matrix.takeTop b) (Matrix.takeBottom b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:502: " {-# LINE 502 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 502 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let (height, width) = Array.shape a in QC.forAll (genSplitShape width) $ \splitWidth -> let b = Array.reshape (height, splitWidth) a in b === Matrix.beside (Matrix.takeLeft b) (Matrix.takeRight b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:562: " {-# LINE 562 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 562 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let (height, width) = Array.shape a in QC.forAll (genVector width number_) $ \x -> QC.forAll (genSplitShape width) $ \splitWidth -> let b = Array.reshape (height, splitWidth) a in let y = Array.reshape splitWidth x in Matrix.multiplyVectorRight b y === Vector.add (Matrix.multiplyVectorRight (Matrix.takeLeft b) (Vector.takeLeft y)) (Matrix.multiplyVectorRight (Matrix.takeRight b) (Vector.takeRight y)) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:604: " {-# LINE 604 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 604 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \abc0 -> let width = Matrix.width abc0 in QC.forAll (genSplitShape3 width) $ \splitWidth -> let abc = Matrix.reshapeWidth splitWidth abc0 in let a = Matrix.takeLeft abc in let b = Matrix.takeHorizCenter abc in let c = Matrix.takeRight (Matrix.takeRight abc) in abc === BlockMatrix.toMatrix (a &||| b &||| c) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:616: " {-# LINE 616 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 616 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \abc0 -> let width = Matrix.width abc0 in QC.forAll (genSplitShape3 width) $ \splitWidth -> let abc = Matrix.reshapeWidth splitWidth abc0 in Matrix.takeHorizCenter abc === Array2.takeHorizCenter abc ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:653: " {-# LINE 653 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 653 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.transpose (Array.fromList (Shape.Range 'a' 'c', shapeInt 2) [1,2,3,4,5,6::Real_]) ) [ExpectedLine [LineChunk "StorableArray.fromList (ZeroBased {",WildCardChunk,LineChunk "2},Range {rangeFrom = 'a', rangeTo = 'c'}) [1.0,3.0,5.0,2.0,4.0,6.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:656: " {-# LINE 656 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 656 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> a == Matrix.transpose (Matrix.transpose a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:658: " {-# LINE 658 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 658 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.transpose a == Array.reshape (Matrix.width a, Matrix.height a) (VectorSlice.concat (Fold.toList $ fmap VectorSlice.chunk $ VectorSlice.slicesVector Slice.columnArray a)) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:669: " {-# LINE 669 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 669 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> fmap VectorSlice.toVector (VectorSlice.slicesVector Slice.rowArray (Matrix.transpose a)) == fmap VectorSlice.toVector (VectorSlice.slicesVector Slice.columnArray a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:694: " {-# LINE 694 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 694 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs conj -> Matrix.tensorProduct (VectorSymb.conjugate xs) (VectorSymb.maybeConjugate conj $ Vector.one ()) === Matrix.singleColumn (VectorSlice.conjugate xs) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:703: " {-# LINE 703 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 703 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs conj -> Matrix.tensorProduct (VectorSymb.maybeConjugate conj $ Vector.one ()) (VectorSymb.conjugate xs) === Matrix.singleRow (VectorSlice.conjugate xs) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:712: " {-# LINE 712 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 712 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs conjX -> forSliced number_ $ \ys conjY -> Matrix.tensorProduct (VectorSymb.maybeConjugate conjX xs) (VectorSymb.maybeConjugate conjY ys) === Matrix.tensorProduct (maybeConjugate conjX xs) (maybeConjugate conjY ys) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:723: " {-# LINE 723 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 723 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> forSliced number_ $ \ys -> QC.forAll (genVector (VectorSlice.shape ys) number_) $ \zs -> Matrix.multiplyVectorRight (Matrix.tensorProduct xs ys) zs === VectorSlice.dot ys zs .*| xs ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:732: " {-# LINE 732 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 732 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> forSliced number_ $ \ys -> QC.forAll (genVector (VectorSlice.shape xs) number_) $ \zs -> Matrix.multiplyVectorLeft zs (Matrix.tensorProduct xs ys) === VectorSlice.dot xs zs .*| ys ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:741: " {-# LINE 741 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 741 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> forSliced number_ $ \ys -> QC.forAll (genVector (VectorSlice.shape ys) number_) $ \zs -> Matrix.multiplyVectorRight (Matrix.tensorProduct xs (VectorSymb.conjugate ys)) zs === VectorSlice.inner ys zs .*| xs ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:752: " {-# LINE 752 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 752 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> forSliced number_ $ \ys -> QC.forAll (genVector (VectorSlice.shape xs) number_) $ \zs -> Matrix.multiplyVectorLeft zs (Matrix.tensorProduct (VectorSymb.conjugate xs) ys) === VectorSlice.inner xs zs .*| ys ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:843: " {-# LINE 843 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 843 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> a === Matrix.scaleRows (VectorSlice.one (Matrix.height a)) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:848: " {-# LINE 848 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 848 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced2 number_ $ \x y -> QC.forAll (Shape.ZeroBased <$> QC.choose (1,maxDim)) $ \width -> QC.forAll (genVector (VectorSlice.shape x, width) number_) $ \a -> Matrix.scaleRows (x|+|y) a === Matrix.scaleRows x a |+| Matrix.scaleRows y a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:858: " {-# LINE 858 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 858 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (Shape.ZeroBased <$> QC.choose (1,maxDim)) $ \set -> QC.forAll (genVector (Matrix.height a, set) number_) $ \b -> QC.forAll (QC.elements $ Shape.indices set) $ \k -> Matrix.scaleRows (VectorSlice.sliceVector (Slice.column k) b) a === Matrix.scaleRows (Matrix.takeColumn k b) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:894: " {-# LINE 894 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 894 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> a === Matrix.scaleColumns (VectorSlice.one (Matrix.width a)) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:899: " {-# LINE 899 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 899 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced2 number_ $ \x y -> QC.forAll (Shape.ZeroBased <$> QC.choose (1,maxDim)) $ \height -> QC.forAll (genVector (height, VectorSlice.shape x) number_) $ \a -> Matrix.scaleColumns (x|+|y) a === Matrix.scaleColumns x a |+| Matrix.scaleColumns y a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:909: " {-# LINE 909 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 909 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (Shape.ZeroBased <$> QC.choose (1,maxDim)) $ \set -> QC.forAll (genVector (Matrix.width a, set) number_) $ \b -> QC.forAll (QC.elements $ Shape.indices set) $ \k -> Matrix.scaleColumns (VectorSlice.sliceVector (Slice.column k) b) a === Matrix.scaleColumns (Matrix.takeColumn k b) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:953: " {-# LINE 953 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 953 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let (height, _width) = Array.shape a in QC.forAll (genVector height real_) $ \x -> Matrix.scaleRowsReal x a === Matrix.scaleRows (Vector.fromReal x) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:976: " {-# LINE 976 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 976 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let (_height, width) = Array.shape a in QC.forAll (genVector width real_) $ \x -> Matrix.scaleColumnsReal x a === Matrix.scaleColumns (Vector.fromReal x) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1021: " {-# LINE 1021 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1021 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.multiplyVectorLeft (Array.vectorFromList [3,1,4]) (Array.fromList (Shape.ZeroBased (3::Int), Shape.Range 'a' 'b') [0,1,0,0,1,0::Real_]) ) [ExpectedLine [LineChunk "StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [4.0,3.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1024: " {-# LINE 1024 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1024 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> Matrix.multiplyVectorLeft xs (Matrix.identity (VectorSlice.shape xs)) === VectorSlice.toVector xs ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1038: " {-# LINE 1038 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1038 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.multiplyVectorRight (Array.fromList (Shape.Range 'a' 'b', Shape.ZeroBased (3::Int)) [0,0,1,1,0,0]) (Array.vectorFromList [3,1,4::Real_]) ) [ExpectedLine [LineChunk "StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [4.0,3.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1040: " {-# LINE 1040 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1040 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.multiplyVectorRight (Array.fromList (Shape.Range 'a' 'b', Shape.ZeroBased (3::Int)) [2,7,1,8,2,8]) (Array.vectorFromList [3,1,4::Real_]) ) [ExpectedLine [LineChunk "StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [17.0,58.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1043: " {-# LINE 1043 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1043 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forSliced number_ $ \xs -> Matrix.multiplyVectorRight (Matrix.identity (VectorSlice.shape xs)) xs === VectorSlice.toVector xs ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1050: " {-# LINE 1050 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1050 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \x -> Matrix.singleColumn (Matrix.multiplyVectorRight a x) === Matrix.multiply a (Matrix.singleColumn x) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1058: " {-# LINE 1058 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1058 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (fst $ Array.shape a) number_) $ \x -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \y -> Vector.dot x (Matrix.multiplyVectorRight a y) === Vector.dot (Matrix.multiplyVectorLeft x a) y ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1067: " {-# LINE 1067 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1067 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \x -> Matrix.multiplyVectorRight a x === Matrix.multiplyVectorLeft x (Matrix.transpose a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1083: " {-# LINE 1083 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1083 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.multiply (Array.fromList (shapeInt 2, shapeInt 2) [1000,100,10,1]) (Array.fromList (shapeInt 2, shapeInt 3) [0..5::Real_]) ) [ExpectedLine [WildCardChunk,LineChunk " [300.0,1400.0,2500.0,3.0,14.0,25.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1090: " {-# LINE 1090 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1090 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.multiply (Matrix.identity (Matrix.height a)) a == a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1094: " {-# LINE 1094 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1094 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.multiply a (Matrix.identity (Matrix.width a)) == a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1098: " {-# LINE 1098 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1098 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> forMatrix number_ $ \c -> QC.forAll (genVector (Matrix.width a, Matrix.height c) number_) $ \b -> Matrix.multiply a (Matrix.multiply b c) === Matrix.multiply (Matrix.multiply a b) c ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1119: " {-# LINE 1119 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1119 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.sumRows a === Matrix.multiplyVectorRight a (Vector.one $ snd $ Array.shape a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1127: " {-# LINE 1127 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1127 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Vector.sum (Matrix.sumRows a) === Vector.sum (Matrix.sumColumns a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1134: " {-# LINE 1134 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1134 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (fst $ Array.shape a) number_) $ \x -> Vector.dot x (Matrix.sumRows a) === Vector.sum (Matrix.multiplyVectorLeft x a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1203: " {-# LINE 1203 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1203 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.sumColumns a === Matrix.multiplyVectorLeft (Vector.one $ fst $ Array.shape a) a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1211: " {-# LINE 1211 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1211 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> Matrix.sumColumns a === Matrix.sumRows (Matrix.transpose a) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1219: " {-# LINE 1219 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1219 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \x -> Vector.dot (Matrix.sumColumns a) x === Vector.sum (Matrix.multiplyVectorRight a x) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1261: " {-# LINE 1261 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1261 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Array.toBoxed (Matrix.dotRowwise a b) === BoxedArray.zipWith Vector.dot (Matrix.toRowArray a) (Matrix.toRowArray b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1270: " {-# LINE 1270 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1270 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Square.takeDiagonal (Array.mapShape (Shape.Square . fst) (Matrix.multiply a (Matrix.transpose b))) === Matrix.dotRowwise a b ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1281: " {-# LINE 1281 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1281 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let shape = Array.shape a in QC.forAll (genVector shape number_) $ \b -> Matrix.dotRowwise a b === Matrix.sumRows (Vector.mul a b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1291: " {-# LINE 1291 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1291 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Vector.dot a b === Vector.sum (Matrix.dotRowwise a b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1300: " {-# LINE 1300 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1300 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Matrix.dotRowwise a b === Matrix.dotRowwise b a ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1319: " {-# LINE 1319 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1319 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> let shape = Array.shape a in QC.forAll (genVector shape number_) $ \b -> Matrix.innerRowwise a b === Matrix.sumRows (Vector.mulConj a b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1329: " {-# LINE 1329 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1329 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Matrix.innerRowwise a b === Matrix.dotRowwise (Vector.conjugate a) b ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1338: " {-# LINE 1338 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1338 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} forMatrix number_ $ \a -> QC.forAll (genVector (Array.shape a) number_) $ \b -> Vector.inner a b === Vector.sum (Matrix.innerRowwise a b) ) DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1356: " {-# LINE 1356 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1356 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.kronecker (Array.fromList (shapeInt 2, shapeInt 2) [0,1,-1,0::Real_]) (Array.fromList (shapeInt 2, shapeInt 3) [1..6]) ) [ExpectedLine [WildCardChunk,LineChunk " [0.0,0.0,0.0,1.0,2.0,3.0,0.0,0.0,0.0,4.0,5.0,6.0,-1.0,-2.0,-3.0,0.0,0.0,0.0,-4.0,-5.0,-6.0,0.0,0.0,0.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1363: " {-# LINE 1363 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.example( {-# LINE 1363 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} Matrix.kronecker (Array.fromList (shapeInt 2, shapeInt 2) [1,2,3,4::Real_]) (Array.fromList (shapeInt 2, shapeInt 3) [1,2,4,8,16,32]) ) [ExpectedLine [WildCardChunk,LineChunk " [1.0,2.0,4.0,2.0,4.0,8.0,8.0,16.0,32.0,16.0,32.0,64.0,3.0,6.0,12.0,4.0,8.0,16.0,24.0,48.0,96.0,32.0,64.0,128.0]"]] DocTest.printPrefix "Numeric.BLAS.Matrix.RowMajor:1370: " {-# LINE 1370 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} DocTest.property( {-# LINE 1370 "src/Numeric/BLAS/Matrix/RowMajor.hs" #-} QC.forAll (QC.choose (0,5)) $ \m -> QC.forAll (QC.choose (0,5)) $ \n -> Matrix.kronecker (Matrix.identity (shapeInt m)) (Matrix.identity (shapeInt n)) == (Matrix.identity (shapeInt m, shapeInt n) :: Matrix.Square (ShapeInt, ShapeInt) Number_) )