{-# LANGUAGE TypeFamilies #-} module Test.Generic where import qualified Test.Generator as Gen import qualified Test.Logic as Logic import Test.Generator ((<#*|>), (<#=#>)) import Test.Utility (approxVector) import qualified Numeric.LAPACK.Matrix.Shape as MatrixShape import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix import qualified Numeric.LAPACK.Matrix as Matrix import Numeric.LAPACK.Matrix.Array (ArrayMatrix) import Numeric.LAPACK.Matrix (ShapeInt, (#*|), (#+#), (#-#)) import Numeric.LAPACK.Vector (Vector, (|+|), (|-|)) import Numeric.LAPACK.Scalar (RealOf) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Shape as Shape import Control.Applicative ((<$>)) forceOrder :: (ArrMatrix.ShapeOrder shape, ArrMatrix.MultiplyVector shape, MatrixShape.HeightOf shape ~ height, Shape.C height, Eq height, MatrixShape.WidthOf shape ~ width, width ~ ShapeInt, Class.Floating a, RealOf a ~ ar, Class.Real ar) => MatrixShape.Order -> (ArrayMatrix shape a, Vector width a) -> Bool forceOrder order (a,x) = let ao = Matrix.forceOrder order a in ArrMatrix.shapeOrder (ArrMatrix.shape ao) == order && approxVector (a #*| x) (ao #*| x) genDistribution :: (Logic.Dim height, Eq height, Logic.Dim width, Eq width, Class.Floating a) => Gen.Matrix height width a matrix -> Gen.Vector height a ((matrix, matrix), Vector width a) genDistribution gen = (,) <$> ((,) <$> gen <#=#> gen) <#*|> Gen.vector addDistributive, subDistributive :: (ArrMatrix.Additive shape, ArrMatrix.MultiplyVector shape, MatrixShape.HeightOf shape ~ height, Shape.C height, Eq height, MatrixShape.WidthOf shape ~ width, width ~ ShapeInt, Class.Floating a, RealOf a ~ ar, Class.Real ar) => ((ArrayMatrix shape a, ArrayMatrix shape a), Vector width a) -> Bool addDistributive ((a,b),x) = approxVector ((a#+#b) #*| x) (a#*|x |+| b#*|x) subDistributive ((a,b),x) = approxVector ((a#-#b) #*| x) (a#*|x |-| b#*|x)