{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Test.Matrix (testsVar) where import qualified Test.Generic as Generic import qualified Test.Indexed as Indexed import qualified Test.Generator as Gen import qualified Test.Utility as Util import Test.Generator ((<.*#>), (<#*#>), (<#*|>), (<-*|>), (<|*->), (<><>), (<|||>), (<===>)) import Test.Utility (equalArray, approx, approxArray, approxMatrix, approxVector, equalVector, genOrder, Tagged(Tagged), TaggedGen, NonEmptyInt, EInt, (!|||), (!===)) import qualified Numeric.LAPACK.Matrix.Triangular as Triangular import qualified Numeric.LAPACK.Matrix.Square as Square import qualified Numeric.LAPACK.Matrix.Shape as MatrixShape import qualified Numeric.LAPACK.Matrix.Extent as Extent import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix import qualified Numeric.LAPACK.Matrix as Matrix import qualified Numeric.LAPACK.Vector as Vector import Numeric.LAPACK.Matrix.Square (Square) import Numeric.LAPACK.Matrix.Array (ArrayMatrix) import Numeric.LAPACK.Matrix (General, ShapeInt, shapeInt, (##*#), (#*#), (#*##), (#*|), (|||), (===)) import Numeric.LAPACK.Vector (Vector, (.*|)) import Numeric.LAPACK.Scalar (RealOf, conjugate) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Boxed as BoxedArray import qualified Data.Array.Comfort.Storable as Array import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Shape ((:+:)) import qualified Control.Monad.Trans.Reader as MR import qualified Control.Functor.HT as FuncHT import Control.Applicative (liftA2, liftA3, pure, (<$>)) import Data.Tuple.HT (mapTriple, mapPair, swap) import qualified Test.QuickCheck as QC genArray :: (Shape.C shape, Class.Floating a) => shape -> QC.Gen (ArrayMatrix shape a) genArray = Util.genArray 10 dotProduct :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (Vector ShapeInt a, Vector ShapeInt a) -> Bool dotProduct (x,y) = approx 1e-5 (Vector.dot x y) (Matrix.toScalar $ Matrix.singleRow MatrixShape.RowMajor x #*# Matrix.singleColumn MatrixShape.ColumnMajor y) innerDot :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (Vector ShapeInt a, Vector ShapeInt a) -> Bool innerDot (x,y) = approx 1e-5 (Vector.inner x y) (Vector.dot (Vector.conjugate x) y) tensorProductTranspose :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool tensorProductTranspose order (x,y) = approxArray (Matrix.transpose (Matrix.tensorProduct order x y)) (Matrix.tensorProduct (MatrixShape.flipOrder order) y x) outerTranspose :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool outerTranspose order (x,y) = approxArray (Matrix.transpose (Matrix.outer order x y)) (Matrix.outer (MatrixShape.flipOrder order) (Vector.conjugate y) (Vector.conjugate x)) tensorProduct :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool tensorProduct order (x,y) = approxArray (Matrix.tensorProduct order x y) (Matrix.singleColumn order x #*# Matrix.singleRow order y) tensorProductMul :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (Triangular.Diagonal ShapeInt a, Matrix.General ShapeInt ShapeInt a, Triangular.Diagonal ShapeInt a) -> Bool tensorProductMul (x,m,y) = let xmy = (x #*## m) ##*# y in approxArray xmy (ArrMatrix.lift2 Vector.mul m (Matrix.tensorProduct (MatrixShape.fullOrder $ ArrMatrix.shape xmy) (Triangular.takeDiagonal x) (Triangular.takeDiagonal y))) outerTensorProduct :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool outerTensorProduct order (x,y) = approxArray (Matrix.outer order x y) (Matrix.tensorProduct order x $ Vector.conjugate y) genScaledVectorPairs :: (Class.Floating a) => Gen.MatrixInt a ((ShapeInt, ShapeInt), [(a, (Vector ShapeInt a, Vector ShapeInt a))]) genScaledVectorPairs = Gen.listOfMatrix ((,) <$> Gen.scalar <.*#> ((,) <$> Gen.vector <|*-> Gen.vector)) sumRank1 :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> ((ShapeInt,ShapeInt), [(a, (Vector ShapeInt a, Vector ShapeInt a))]) -> Bool sumRank1 order (size,xys) = approxArray (case order of MatrixShape.ColumnMajor -> Matrix.sumRank1 size xys MatrixShape.RowMajor -> Matrix.adjoint $ Matrix.sumRank1 (swap size) $ map (mapPair (conjugate, swap)) xys) (Util.addMatrices (uncurry (MatrixShape.general order) size) (map (\(a,(x,y)) -> Matrix.outer order (a.*|x) y) xys)) outerTrace :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool outerTrace order (x,y) = approx 1e-5 (Vector.inner y x) (Square.trace $ Square.fromGeneral $ Matrix.outer order x y) outerInner :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a, Vector ShapeInt a) -> Bool outerInner order (x,y,z) = approxVector (Matrix.outer order x y #*| z) (Vector.inner y z .*| x) tensorTrace :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a) -> Bool tensorTrace order (x,y) = approx 1e-5 (Vector.dot y x) (Square.trace $ Square.fromGeneral $ Matrix.tensorProduct order x y) tensorDot :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (Vector ShapeInt a, Vector ShapeInt a, Vector ShapeInt a) -> Bool tensorDot order (x,y,z) = approxVector (Matrix.tensorProduct order x y #*| z) (Vector.dot y z .*| x) kroneckerTranspose :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool kroneckerTranspose (a,b) = approxArray (Matrix.transpose $ Matrix.kronecker a b) (Matrix.kronecker (Matrix.transpose a) (Matrix.transpose b)) kroneckerTrace :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (Square ShapeInt a, Square ShapeInt a) -> Bool kroneckerTrace (a,b) = approx 1e-5 (Square.trace $ Matrix.kronecker a b) (Square.trace a * Square.trace b) kroneckerProduct :: (Shape.C s0, Shape.C s1, Shape.C s2, Eq s0, Eq s1, Eq s2, Shape.C t0, Shape.C t1, Shape.C t2, Eq t0, Eq t1, Eq t2, Class.Floating a, RealOf a ~ ar, Class.Real ar) => ((General s0 s1 a, General t0 t1 a), (General s1 s2 a, General t1 t2 a)) -> Bool kroneckerProduct ((a,b),(c,d)) = approxArray (Matrix.kronecker a b #*# Matrix.kronecker c d) (Matrix.kronecker (a #*# c) (b #*# d)) kronecker3 :: (Shape.C s0, Shape.C s1, Shape.C s2, Shape.C s3, Eq s0, Eq s1, Eq s2, Eq s3, Class.Floating a, RealOf a ~ ar, Class.Real ar) => (General s0 s1 a, General s1 s2 a, General s2 s3 a) -> Bool kronecker3 (a,b,c) = approxVector (Matrix.kronecker a (Matrix.transpose c) #*| Matrix.toRowMajor b) (Matrix.toRowMajor $ a #*# b #*# c) genZeroColumns :: (Class.Floating a) => TaggedGen a (Matrix.Tall ShapeInt ShapeInt a) genZeroColumns = Tagged $ do height <- shapeInt <$> QC.choose (0,5) order <- genOrder genArray (MatrixShape.tall order height (shapeInt 0)) reverseNoRows :: (Class.Floating a) => Matrix.Wide ShapeInt ShapeInt a -> Bool reverseNoRows x = equalArray x $ Matrix.reverseRows x reverseNoColumns :: (Class.Floating a) => Matrix.Tall ShapeInt ShapeInt a -> Bool reverseNoColumns x = equalArray x $ Matrix.reverseColumns x genMatrix2EqHeight :: (Class.Floating a) => Gen.Matrix ShapeInt (ShapeInt:+:ShapeInt) a (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) genMatrix2EqHeight = (,) <$> Gen.matrix <|||> Gen.matrix genMatrix2EqWidth :: (Class.Floating a) => Gen.Matrix (ShapeInt:+:ShapeInt) ShapeInt a (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) genMatrix2EqWidth = (,) <$> Gen.matrix <===> Gen.matrix reverseRows :: (Class.Floating a) => General ShapeInt ShapeInt a -> Bool reverseRows x = equalArray x $ Matrix.reverseRows (Matrix.reverseRows x) reverseColumns :: (Class.Floating a) => General ShapeInt ShapeInt a -> Bool reverseColumns x = equalArray x $ Matrix.reverseColumns (Matrix.reverseColumns x) -- cf. Vector.genSwapVector genSwapVector :: (Class.Floating a) => Gen.VectorInt a ((EInt,EInt), (General ShapeInt NonEmptyInt a, Vector NonEmptyInt a)) genSwapVector = flip Gen.mapQC ((,) <$> Gen.matrix <#*|> Gen.vector) $ \(m,x) -> do let set = Shape.indices $ Array.shape x ij <- liftA2 (,) (QC.elements set) (QC.elements set) return (ij,(m,x)) swapColumns :: (Eq sh, Shape.Indexed sh, Shape.Index sh ~ ix, Class.Floating a) => ((ix,ix), (General ShapeInt sh a, Vector sh a)) -> Bool swapColumns ((i,j),(m,x)) = equalVector (m#*|x) (Matrix.swapColumns i j m #*| Vector.swap i j x) zeroIntHeight :: (Shape.C height, Shape.C width) => General height width a -> General ShapeInt width a zeroIntHeight = Matrix.mapHeight (shapeInt . Shape.size) zeroIntWidth :: (Shape.C height, Shape.C width) => General height width a -> General height ShapeInt a zeroIntWidth = Matrix.mapWidth (shapeInt . Shape.size) reverseRowsStack :: (Class.Floating a) => (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool reverseRowsStack (x,y) = let above = Matrix.above Matrix.contiguousBias Extent.appendRight in equalArray (Matrix.reverseRows $ zeroIntHeight $ above x y) (zeroIntHeight $ above (Matrix.reverseRows y) (Matrix.reverseRows x)) reverseColumnsStack :: (Class.Floating a) => (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool reverseColumnsStack (x,y) = let beside = Matrix.beside Matrix.contiguousBias Extent.appendRight in equalArray (Matrix.reverseColumns $ zeroIntWidth $ beside x y) (zeroIntWidth $ beside (Matrix.reverseColumns y) (Matrix.reverseColumns x)) data Cut = Take | Drop deriving (Show, Eq, Ord, Enum, Bounded) data Slice = Row | Column deriving (Show, Eq, Ord, Enum, Bounded) cut :: (Class.Floating a) => Cut -> Slice -> Int -> General ShapeInt ShapeInt a -> General ShapeInt ShapeInt a cut Take Row = Matrix.takeRows cut Take Column = Matrix.takeColumns cut Drop Row = Matrix.dropRows cut Drop Column = Matrix.dropColumns cutCommutative :: (Class.Floating a) => ((Cut,Slice),(Int,Int)) -> General ShapeInt ShapeInt a -> Bool cutCommutative (kind,(k,j)) x = let cutK = uncurry cut kind k cutJ = uncurry cut kind j in equalArray (cutK $ cutJ x) (cutJ $ cutK x) cutRowColumnCommutative :: (Class.Floating a) => ((Cut,Int),(Cut,Int)) -> General ShapeInt ShapeInt a -> Bool cutRowColumnCommutative ((cutR,k),(cutC,j)) x = let cutRows = cut cutR Row k cutColumns = cut cutC Column j in equalArray (cutRows $ cutColumns x) (cutColumns $ cutRows x) takeEqually :: (Class.Floating a) => Int -> General ShapeInt ShapeInt a -> Bool takeEqually k x = equalArray (Matrix.takeEqually k x) (Matrix.takeRows k (Matrix.takeColumns k x)) dropEqually :: (Class.Floating a) => Int -> General ShapeInt ShapeInt a -> Bool dropEqually k x = equalArray (Matrix.dropEqually k x) (Matrix.dropRows k (Matrix.dropColumns k x)) takeRowArray :: (Class.Floating a) => [Int] -> General ShapeInt ShapeInt a -> Bool takeRowArray ixs x = Util.equalMatrix (Matrix.fromRows (Matrix.width x) $ map (Matrix.takeRow x) ixs) (Matrix.takeRowArray (BoxedArray.vectorFromList ixs) x) stackSplitRows :: (Class.Floating a) => General (ShapeInt:+:ShapeInt) ShapeInt a -> Bool stackSplitRows x = equalArray x $ Matrix.takeTop x === Matrix.takeBottom x stackSplitColumns :: (Class.Floating a) => General ShapeInt (ShapeInt:+:ShapeInt) a -> Bool stackSplitColumns x = equalArray x $ Matrix.takeLeft x ||| Matrix.takeRight x takeStackRows, dropStackRows :: (Class.Floating a) => (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool takeStackRows (x,y) = equalArray x $ Matrix.takeTop $ x!===y dropStackRows (x,y) = equalArray y $ Matrix.takeBottom $ x===y takeStackColumns, dropStackColumns :: (Class.Floating a) => (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool takeStackColumns (x,y) = equalArray x $ Matrix.takeLeft $ x!|||y dropStackColumns (x,y) = equalArray y $ Matrix.takeRight $ x|||y type BiasMatrix height width a = MR.Reader Matrix.OrderBias (Matrix.General height width a) infixr 3 ?|||? infixr 2 ?===? (?|||?) :: (Shape.C height, Eq height, Shape.C widthA, Shape.C widthB, Class.Floating a) => BiasMatrix height widthA a -> BiasMatrix height widthB a -> BiasMatrix height (widthA:+:widthB) a (?|||?) = liftA3 (flip Matrix.beside Extent.appendAny) MR.ask (?===?) :: (Shape.C width, Eq width, Shape.C heightA, Shape.C heightB, Class.Floating a) => BiasMatrix heightA width a -> BiasMatrix heightB width a -> BiasMatrix (heightA:+:heightB) width a (?===?) = liftA3 (flip Matrix.above Extent.appendAny) MR.ask runWithOrderBias :: (args -> readerArgs) -> (readerArgs -> MR.Reader bias prop) -> bias -> args -> prop runWithOrderBias f prop orderBias args = MR.runReader (prop $ f args) orderBias stackRowsAssociative, stackColumnsAssociative :: (Class.Floating a) => Matrix.OrderBias -> (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a, General ShapeInt ShapeInt a) -> Bool stackRowsAssociative = runWithOrderBias (mapTriple (pure,pure,pure)) $ \(x,y,z) -> liftA2 equalArray (zeroIntHeight <$> ((x?===?y)?===?z)) (zeroIntHeight <$> (x?===?(y?===?z))) stackColumnsAssociative = runWithOrderBias (mapTriple (pure,pure,pure)) $ \(x,y,z) -> liftA2 equalArray (zeroIntWidth <$> ((x?|||?y)?|||?z)) (zeroIntWidth <$> (x?|||?(y?|||?z))) stackRowsColumnsCommutative :: (Class.Floating a) => Matrix.OrderBias -> ((General ShapeInt ShapeInt a, General ShapeInt ShapeInt a), (General ShapeInt ShapeInt a, General ShapeInt ShapeInt a)) -> Bool stackRowsColumnsCommutative = runWithOrderBias (mapPair (mapPair (pure,pure), mapPair (pure,pure))) $ \((x,y),(z,w)) -> liftA2 equalArray ((x?|||?y)?===?(z?|||?w)) ((x?===?z)?|||?(y?===?w)) genOrderBias :: QC.Gen Matrix.OrderBias genOrderBias = QC.elements [Matrix.leftBias, Matrix.rightBias, Matrix.contiguousBias] genLeftRightBias :: QC.Gen Matrix.OrderBias genLeftRightBias = QC.elements [Matrix.leftBias, Matrix.rightBias] rowArgAbsMaximums :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => General ShapeInt (():+:ShapeInt) a -> Bool rowArgAbsMaximums x0 = let x = zeroIntWidth x0 (ixs0,xs0) = Matrix.rowArgAbsMaximums x (ixs1,xs1) = mapPair (Array.fromBoxed, Array.fromBoxed) $ FuncHT.unzip $ fmap Vector.argAbsMaximum $ Matrix.toRowArray x in ixs0==ixs1 && approxVector xs0 xs1 multiplyDiagonalMatrix :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (Triangular.Diagonal ShapeInt a, General ShapeInt ShapeInt a) -> Bool multiplyDiagonalMatrix (x,y) = approxArray (x #*## y) (Triangular.toSquare x #*## y) multiplyMatrixDiagonal :: (Class.Floating a, RealOf a ~ ar, Class.Real ar) => (General ShapeInt ShapeInt a, Triangular.Diagonal ShapeInt a) -> Bool multiplyMatrixDiagonal (x,y) = approxMatrix 1e-5 (x ##*# y) (x ##*# Triangular.toSquare y) checkForAll :: (Show a, QC.Testable test) => Gen.T dim tag a -> (a -> test) -> Tagged tag QC.Property checkForAll gen = Util.checkForAll (Gen.run gen 10 5) checkForAllExtra :: (Show a, Show b, QC.Testable test) => QC.Gen a -> Gen.T dim tag b -> (a -> b -> test) -> Tagged tag QC.Property checkForAllExtra = Gen.withExtra checkForAll testsVar :: (Show a, Class.Floating a, Eq a, RealOf a ~ ar, Class.Real ar) => [(String, Tagged a QC.Property)] testsVar = ("index", checkForAll (Indexed.genMatrixIndex Gen.matrix) Indexed.unitDot) : ("dotProduct", checkForAll ((,) <$> Gen.vector <-*|> Gen.vector) dotProduct) : ("innerDot", checkForAll ((,) <$> Gen.vector <-*|> Gen.vector) innerDot) : ("tensorProductTranspose", checkForAllExtra genOrder ((,) <$> Gen.vector <|*-> Gen.vector) tensorProductTranspose) : ("outerTranspose", checkForAllExtra genOrder ((,) <$> Gen.vector <|*-> Gen.vector) outerTranspose) : ("tensorProduct", checkForAllExtra genOrder ((,) <$> Gen.vector <|*-> Gen.vector) tensorProduct) : ("tensorProductMul", checkForAll ((,,) <$> Gen.diagonal <#*#> Gen.matrix <#*#> Gen.diagonal) tensorProductMul) : ("outerTensorProduct", checkForAllExtra genOrder ((,) <$> Gen.vector <|*-> Gen.vector) outerTensorProduct) : ("sumRank1", checkForAllExtra genOrder genScaledVectorPairs sumRank1) : ("outerTrace", checkForAllExtra genOrder ((,) <$> Gen.vector <-*|> Gen.vector) outerTrace) : ("outerInner", checkForAllExtra genOrder ((,,) <$> Gen.vector <|*-> Gen.vector <#*|> Gen.vector) outerInner) : ("tensorTrace", checkForAllExtra genOrder ((,) <$> Gen.vector <-*|> Gen.vector) tensorTrace) : ("tensorDot", checkForAllExtra genOrder ((,,) <$> Gen.vector <|*-> Gen.vector <#*|> Gen.vector) tensorDot) : ("kroneckerTranspose", checkForAll ((,) <$> Gen.matrix <><> Gen.matrix) kroneckerTranspose) : ("kroneckerTrace", checkForAll ((,) <$> Gen.square <><> Gen.square) kroneckerTrace) : ("kroneckerProduct", checkForAll ((,) <$> ((,) <$> Gen.matrixInt <><> Gen.matrixInt) <#*#> ((,) <$> Gen.matrixInt <><> Gen.matrixInt)) kroneckerProduct) : ("kronecker3", checkForAll ((,,) <$> Gen.matrixInt <#*#> Gen.matrixInt <#*#> Gen.matrixInt) kronecker3) : ("reverseNoRows", Util.checkForAllPlain (fmap Matrix.transpose <$> genZeroColumns) reverseNoRows) : ("reverseNoColumns", Util.checkForAllPlain genZeroColumns reverseNoColumns) : ("reverseRows", checkForAll Gen.matrix reverseRows) : ("reverseColumns", checkForAll Gen.matrix reverseColumns) : ("reverseRowsStack", checkForAll genMatrix2EqWidth reverseRowsStack) : ("reverseColumnsStack", checkForAll genMatrix2EqHeight reverseColumnsStack) : ("cutCommutative", checkForAllExtra (liftA2 (,) (liftA2 (,) QC.arbitraryBoundedEnum QC.arbitraryBoundedEnum) (liftA2 (,) (QC.choose (0,5)) (QC.choose (0,5)))) Gen.matrix cutCommutative) : ("cutRowColumnCommutative", checkForAllExtra (liftA2 (,) (liftA2 (,) QC.arbitraryBoundedEnum (QC.choose (0,5))) (liftA2 (,) QC.arbitraryBoundedEnum (QC.choose (0,5)))) Gen.matrix cutRowColumnCommutative) : ("takeEqually", checkForAllExtra (QC.choose (0,5)) Gen.matrix takeEqually) : ("dropEqually", checkForAllExtra (QC.choose (0,5)) Gen.matrix dropEqually) : ("takeRowArray", checkForAll (Gen.mapQC (\x -> do let set = Shape.indices $ Matrix.height x ixs <- if null set then return [] else QC.listOf $ QC.elements set return (ixs,x)) Gen.matrix) (uncurry takeRowArray)) : ("swapColumns", checkForAll genSwapVector swapColumns) : ("stackSplitRows", checkForAll Gen.matrix stackSplitRows) : ("stackSplitColumns", checkForAll Gen.matrix stackSplitColumns) : ("takeStackRows", checkForAll genMatrix2EqWidth takeStackRows) : ("dropStackRows", checkForAll genMatrix2EqWidth dropStackRows) : ("takeStackColumns", checkForAll genMatrix2EqHeight takeStackColumns) : ("dropStackColumns", checkForAll genMatrix2EqHeight dropStackColumns) : ("stackRowsAssociative", checkForAllExtra genOrderBias ((,,) <$> Gen.matrix <===> Gen.matrix <===> Gen.matrix) stackRowsAssociative) : ("stackColumnsAssociative", checkForAllExtra genOrderBias ((,,) <$> Gen.matrix <|||> Gen.matrix <|||> Gen.matrix) stackColumnsAssociative) : ("stackRowsColumnsCommutative", checkForAllExtra genLeftRightBias ((,) <$> genMatrix2EqHeight <===> genMatrix2EqHeight) stackRowsColumnsCommutative) : ("forceOrder", checkForAllExtra genOrder ((,) <$> Gen.matrixInt <#*|> Gen.vector) Generic.forceOrder) : ("addDistributive", checkForAll (Generic.genDistribution Gen.matrixInt) Generic.addDistributive) : ("subDistributive", checkForAll (Generic.genDistribution Gen.matrixInt) Generic.subDistributive) : ("rowArgAbsMaximums", checkForAll Gen.matrix rowArgAbsMaximums) : ("multiplyDiagonalMatrix", checkForAll ((,) <$> Gen.diagonal <#*#> Gen.matrix) multiplyDiagonalMatrix) : ("multiplyMatrixDiagonal", checkForAll ((,) <$> Gen.matrix <#*#> Gen.diagonal) multiplyMatrixDiagonal) : []