{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} module Numeric.LAPACK.Matrix.Multiply where import qualified Numeric.LAPACK.Matrix.Plain.Multiply as ArrMultiply import qualified Numeric.LAPACK.Matrix.Array.Basic as Basic import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix import qualified Numeric.LAPACK.Matrix.Permutation as PermMatrix import qualified Numeric.LAPACK.Matrix.Type as Type import qualified Numeric.LAPACK.Matrix.Modifier as Mod import qualified Numeric.LAPACK.Matrix.Shape.Box as Box import qualified Numeric.LAPACK.Matrix.Extent as Extent import qualified Numeric.LAPACK.Permutation.Private as Perm import qualified Numeric.LAPACK.Vector as Vector import Numeric.LAPACK.Matrix.Array (Full) import Numeric.LAPACK.Matrix.Type (Matrix, scaleWithCheck) import Numeric.LAPACK.Matrix.Modifier (Transposition(NonTransposed,Transposed)) import Numeric.LAPACK.Vector (Vector) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Storable as Array import qualified Data.Array.Comfort.Shape as Shape infixl 7 -*# infixr 7 #*| (#*|) :: (MultiplyVector typ, Type.WidthOf typ ~ width, Eq width, Class.Floating a) => Matrix typ a -> Vector width a -> Vector (Type.HeightOf typ) a #*| :: Matrix typ a -> Vector width a -> Vector (HeightOf typ) a (#*|) = Matrix typ a -> Vector width a -> Vector (HeightOf typ) a forall typ width a. (MultiplyVector typ, WidthOf typ ~ width, Eq width, Floating a) => Matrix typ a -> Vector width a -> Vector (HeightOf typ) a matrixVector (-*#) :: (MultiplyVector typ, Type.HeightOf typ ~ height, Eq height, Class.Floating a) => Vector height a -> Matrix typ a -> Vector (Type.WidthOf typ) a -*# :: Vector height a -> Matrix typ a -> Vector (WidthOf typ) a (-*#) = Vector height a -> Matrix typ a -> Vector (WidthOf typ) a forall typ height a. (MultiplyVector typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector (WidthOf typ) a vectorMatrix class (Type.Box typ) => MultiplyVector typ where matrixVector :: (Type.WidthOf typ ~ width, Eq width, Class.Floating a) => Matrix typ a -> Vector width a -> Vector (Type.HeightOf typ) a vectorMatrix :: (Type.HeightOf typ ~ height, Eq height, Class.Floating a) => Vector height a -> Matrix typ a -> Vector (Type.WidthOf typ) a instance (Shape.C shape) => MultiplyVector (Type.Scale shape) where matrixVector :: Matrix (Scale shape) a -> Vector width a -> Vector (HeightOf (Scale shape)) a matrixVector = String -> (Vector width a -> width) -> (a -> Vector width a -> Vector width a) -> Matrix (Scale width) a -> Vector width a -> Vector width a forall shape b a c. Eq shape => String -> (b -> shape) -> (a -> b -> c) -> Matrix (Scale shape) a -> b -> c scaleWithCheck String "Matrix.Multiply.matrixVector Scale" Vector width a -> width forall sh a. Array sh a -> sh Array.shape a -> Vector width a -> Vector width a forall sh a. (C sh, Floating a) => a -> Vector sh a -> Vector sh a Vector.scale vectorMatrix :: Vector height a -> Matrix (Scale shape) a -> Vector (WidthOf (Scale shape)) a vectorMatrix = (Matrix (Scale shape) a -> Array shape a -> Array shape a) -> Array shape a -> Matrix (Scale shape) a -> Array shape a forall a b c. (a -> b -> c) -> b -> a -> c flip ((Matrix (Scale shape) a -> Array shape a -> Array shape a) -> Array shape a -> Matrix (Scale shape) a -> Array shape a) -> (Matrix (Scale shape) a -> Array shape a -> Array shape a) -> Array shape a -> Matrix (Scale shape) a -> Array shape a forall a b. (a -> b) -> a -> b $ String -> (Array shape a -> shape) -> (a -> Array shape a -> Array shape a) -> Matrix (Scale shape) a -> Array shape a -> Array shape a forall shape b a c. Eq shape => String -> (b -> shape) -> (a -> b -> c) -> Matrix (Scale shape) a -> b -> c scaleWithCheck String "Matrix.Multiply.vectorMatrix Scale" Array shape a -> shape forall sh a. Array sh a -> sh Array.shape a -> Array shape a -> Array shape a forall sh a. (C sh, Floating a) => a -> Vector sh a -> Vector sh a Vector.scale instance (Shape.C shape) => MultiplyVector (PermMatrix.Permutation shape) where matrixVector :: Matrix (Permutation shape) a -> Vector width a -> Vector (HeightOf (Permutation shape)) a matrixVector = Inversion -> Matrix (Permutation width) a -> Vector width a -> Vector width a forall size a. (C size, Eq size, Floating a) => Inversion -> Matrix (Permutation size) a -> Vector size a -> Vector size a PermMatrix.multiplyVector Inversion Mod.NonInverted vectorMatrix :: Vector height a -> Matrix (Permutation shape) a -> Vector (WidthOf (Permutation shape)) a vectorMatrix = (Matrix (Permutation shape) a -> Vector shape a -> Vector shape a) -> Vector shape a -> Matrix (Permutation shape) a -> Vector shape a forall a b c. (a -> b -> c) -> b -> a -> c flip ((Matrix (Permutation shape) a -> Vector shape a -> Vector shape a) -> Vector shape a -> Matrix (Permutation shape) a -> Vector shape a) -> (Matrix (Permutation shape) a -> Vector shape a -> Vector shape a) -> Vector shape a -> Matrix (Permutation shape) a -> Vector shape a forall a b. (a -> b) -> a -> b $ Inversion -> Matrix (Permutation shape) a -> Vector shape a -> Vector shape a forall size a. (C size, Eq size, Floating a) => Inversion -> Matrix (Permutation size) a -> Vector size a -> Vector size a PermMatrix.multiplyVector Inversion Mod.Inverted instance (ArrMultiply.MultiplyVector shape) => MultiplyVector (ArrMatrix.Array shape) where matrixVector :: Matrix (Array shape) a -> Vector width a -> Vector (HeightOf (Array shape)) a matrixVector (ArrMatrix.Array a) Vector width a x = Array shape a -> Vector width a -> Vector (HeightOf shape) a forall shape width a. (MultiplyVector shape, WidthOf shape ~ width, Eq width, Floating a) => Array shape a -> Vector width a -> Vector (HeightOf shape) a ArrMultiply.matrixVector Array shape a a Vector width a x vectorMatrix :: Vector height a -> Matrix (Array shape) a -> Vector (WidthOf (Array shape)) a vectorMatrix Vector height a x (ArrMatrix.Array a) = Vector height a -> Array shape a -> Vector (WidthOf shape) a forall shape height a. (MultiplyVector shape, HeightOf shape ~ height, Eq height, Floating a) => Vector height a -> Array shape a -> Vector (WidthOf shape) a ArrMultiply.vectorMatrix Vector height a x Array shape a a class (Type.Box typ, Type.HeightOf typ ~ Type.WidthOf typ) => MultiplySquare typ where {-# MINIMAL transposableSquare | fullSquare,squareFull #-} transposableSquare :: (Type.HeightOf typ ~ height, Eq height, Shape.C width, Extent.C vert, Extent.C horiz, Class.Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare Transposition NonTransposed Matrix typ a a Full vert horiz height width a b = Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a forall typ height width vert horiz a. (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C vert, C horiz, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a squareFull Matrix typ a a Full vert horiz height width a b transposableSquare Transposition Transposed Matrix typ a a Full vert horiz height width a b = Full horiz vert width height a -> Full vert horiz height width a forall vert horiz height width a. (C vert, C horiz) => Full vert horiz height width a -> Full horiz vert width height a Basic.transpose (Full horiz vert width height a -> Full vert horiz height width a) -> Full horiz vert width height a -> Full vert horiz height width a forall a b. (a -> b) -> a -> b $ Full horiz vert width height a -> Matrix typ a -> Full horiz vert width height a forall typ width height vert horiz a. (MultiplySquare typ, WidthOf typ ~ width, Eq width, C height, C vert, C horiz, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a fullSquare (Full vert horiz height width a -> Full horiz vert width height a forall vert horiz height width a. (C vert, C horiz) => Full vert horiz height width a -> Full horiz vert width height a Basic.transpose Full vert horiz height width a b) Matrix typ a a squareFull :: (Type.HeightOf typ ~ height, Eq height, Shape.C width, Extent.C vert, Extent.C horiz, Class.Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a squareFull = Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a forall typ height width vert horiz a. (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C vert, C horiz, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare Transposition NonTransposed fullSquare :: (Type.WidthOf typ ~ width, Eq width, Shape.C height, Extent.C vert, Extent.C horiz, Class.Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a fullSquare Full vert horiz height width a b Matrix typ a a = Full horiz vert width height a -> Full vert horiz height width a forall vert horiz height width a. (C vert, C horiz) => Full vert horiz height width a -> Full horiz vert width height a Basic.transpose (Full horiz vert width height a -> Full vert horiz height width a) -> Full horiz vert width height a -> Full vert horiz height width a forall a b. (a -> b) -> a -> b $ Transposition -> Matrix typ a -> Full horiz vert width height a -> Full horiz vert width height a forall typ height width vert horiz a. (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C vert, C horiz, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare Transposition Transposed Matrix typ a a (Full horiz vert width height a -> Full horiz vert width height a) -> Full horiz vert width height a -> Full horiz vert width height a forall a b. (a -> b) -> a -> b $ Full vert horiz height width a -> Full horiz vert width height a forall vert horiz height width a. (C vert, C horiz) => Full vert horiz height width a -> Full horiz vert width height a Basic.transpose Full vert horiz height width a b infixl 7 ##*#, #*# infixr 7 #*## (#*##) :: (MultiplySquare typ, Type.HeightOf typ ~ height, Eq height, Shape.C width, Extent.C vert, Extent.C horiz, Class.Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a #*## :: Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a (#*##) = Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a forall typ height width vert horiz a. (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C vert, C horiz, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a squareFull (##*#) :: (MultiplySquare typ, Type.WidthOf typ ~ width, Eq width, Shape.C height, Extent.C vert, Extent.C horiz, Class.Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a ##*# :: Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a (##*#) = Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a forall typ width height vert horiz a. (MultiplySquare typ, WidthOf typ ~ width, Eq width, C height, C vert, C horiz, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a fullSquare instance (Shape.C shape) => MultiplySquare (Type.Scale shape) where transposableSquare :: Transposition -> Matrix (Scale shape) a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare Transposition _trans = String -> (Full vert horiz height width a -> shape) -> (a -> Full vert horiz height width a -> Full vert horiz height width a) -> Matrix (Scale shape) a -> Full vert horiz height width a -> Full vert horiz height width a forall shape b a c. Eq shape => String -> (b -> shape) -> (a -> b -> c) -> Matrix (Scale shape) a -> b -> c scaleWithCheck String "Matrix.Multiply.transposableSquare" Full vert horiz height width a -> shape forall typ a. Box typ => Matrix typ a -> HeightOf typ Type.height ((a -> Full vert horiz height width a -> Full vert horiz height width a) -> Matrix (Scale shape) a -> Full vert horiz height width a -> Full vert horiz height width a) -> (a -> Full vert horiz height width a -> Full vert horiz height width a) -> Matrix (Scale shape) a -> Full vert horiz height width a -> Full vert horiz height width a forall a b. (a -> b) -> a -> b $ (Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Full vert horiz height width a -> Full vert horiz height width a forall shA a shB b. (Array shA a -> Array shB b) -> ArrayMatrix shA a -> ArrayMatrix shB b ArrMatrix.lift1 ((Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Full vert horiz height width a -> Full vert horiz height width a) -> (a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> a -> Full vert horiz height width a -> Full vert horiz height width a forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a forall sh a. (C sh, Floating a) => a -> Vector sh a -> Vector sh a Vector.scale instance (Shape.C shape) => MultiplySquare (PermMatrix.Permutation shape) where transposableSquare :: Transposition -> Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare = Inversion -> Matrix (Permutation height) a -> Full vert horiz height width a -> Full vert horiz height width a forall vert horiz height width a. (C vert, C horiz, C height, Eq height, C width, Floating a) => Inversion -> Matrix (Permutation height) a -> Full vert horiz height width a -> Full vert horiz height width a PermMatrix.multiplyFull (Inversion -> Matrix (Permutation height) a -> Full vert horiz height width a -> Full vert horiz height width a) -> (Transposition -> Inversion) -> Transposition -> Matrix (Permutation height) a -> Full vert horiz height width a -> Full vert horiz height width a forall b c a. (b -> c) -> (a -> b) -> a -> c . Transposition -> Inversion Perm.inversionFromTransposition instance (ArrMultiply.MultiplySquare shape) => MultiplySquare (ArrMatrix.Array shape) where transposableSquare :: Transposition -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare = (Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a forall shA a shB b shC c. (Array shA a -> Array shB b -> Array shC c) -> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c ArrMatrix.lift2 ((Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a) -> (Transposition -> Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Transposition -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a forall b c a. (b -> c) -> (a -> b) -> a -> c . Transposition -> Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a forall shape height width vert horiz a. (MultiplySquare shape, HeightOf shape ~ height, Eq height, C width, C vert, C horiz, Floating a) => Transposition -> Array shape a -> Full vert horiz height width a -> Full vert horiz height width a ArrMultiply.transposableSquare fullSquare :: Full vert horiz height width a -> Matrix (Array shape) a -> Full vert horiz height width a fullSquare = (Array (Full vert horiz height width) a -> Array shape a -> Array (Full vert horiz height width) a) -> Full vert horiz height width a -> Matrix (Array shape) a -> Full vert horiz height width a forall shA a shB b shC c. (Array shA a -> Array shB b -> Array shC c) -> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c ArrMatrix.lift2 Array (Full vert horiz height width) a -> Array shape a -> Array (Full vert horiz height width) a forall shape width height vert horiz a. (MultiplySquare shape, WidthOf shape ~ width, Eq width, C height, C vert, C horiz, Floating a) => Full vert horiz height width a -> Array shape a -> Full vert horiz height width a ArrMultiply.fullSquare squareFull :: Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a squareFull = (Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a) -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a forall shA a shB b shC c. (Array shA a -> Array shB b -> Array shC c) -> ArrayMatrix shA a -> ArrayMatrix shB b -> ArrayMatrix shC c ArrMatrix.lift2 Array shape a -> Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a forall shape height width vert horiz a. (MultiplySquare shape, HeightOf shape ~ height, Eq height, C width, C vert, C horiz, Floating a) => Array shape a -> Full vert horiz height width a -> Full vert horiz height width a ArrMultiply.squareFull class (Type.Box typ, Type.HeightOf typ ~ Type.WidthOf typ) => Power typ where square :: (Class.Floating a) => Matrix typ a -> Matrix typ a power :: (Class.Floating a) => Int -> Matrix typ a -> Matrix typ a instance (Shape.C shape) => Power (Type.Scale shape) where square :: Matrix (Scale shape) a -> Matrix (Scale shape) a square (Type.Scale sh a) = shape -> a -> Matrix (Scale shape) a forall shape a. shape -> a -> Matrix (Scale shape) a Type.Scale shape sh (a aa -> a -> a forall a. Num a => a -> a -> a *a a) power :: Int -> Matrix (Scale shape) a -> Matrix (Scale shape) a power Int n (Type.Scale sh a) = shape -> a -> Matrix (Scale shape) a forall shape a. shape -> a -> Matrix (Scale shape) a Type.Scale shape sh (a aa -> Int -> a forall a b. (Num a, Integral b) => a -> b -> a ^Int n) instance (Shape.C shape) => Power (PermMatrix.Permutation shape) where square :: Matrix (Permutation shape) a -> Matrix (Permutation shape) a square (Type.Permutation p) = Permutation shape -> Matrix (Permutation shape) a forall sh a. Permutation sh -> Matrix (Permutation sh) a Type.Permutation (Permutation shape -> Matrix (Permutation shape) a) -> Permutation shape -> Matrix (Permutation shape) a forall a b. (a -> b) -> a -> b $ Permutation shape -> Permutation shape forall sh. C sh => Permutation sh -> Permutation sh Perm.square Permutation shape p power :: Int -> Matrix (Permutation shape) a -> Matrix (Permutation shape) a power Int n (Type.Permutation p) = Permutation shape -> Matrix (Permutation shape) a forall sh a. Permutation sh -> Matrix (Permutation sh) a Type.Permutation (Permutation shape -> Matrix (Permutation shape) a) -> Permutation shape -> Matrix (Permutation shape) a forall a b. (a -> b) -> a -> b $ Integer -> Permutation shape -> Permutation shape forall sh. C sh => Integer -> Permutation sh -> Permutation sh Perm.power (Int -> Integer forall a b. (Integral a, Num b) => a -> b fromIntegral Int n) Permutation shape p instance (ArrMatrix.Power shape) => Power (ArrMatrix.Array shape) where square :: Matrix (Array shape) a -> Matrix (Array shape) a square = (Array shape a -> Array shape a) -> Matrix (Array shape) a -> Matrix (Array shape) a forall shA a shB b. (Array shA a -> Array shB b) -> ArrayMatrix shA a -> ArrayMatrix shB b ArrMatrix.lift1 Array shape a -> Array shape a forall shape a. (Power shape, Floating a) => Array shape a -> Array shape a ArrMultiply.square power :: Int -> Matrix (Array shape) a -> Matrix (Array shape) a power = (Array shape a -> Array shape a) -> Matrix (Array shape) a -> Matrix (Array shape) a forall shA a shB b. (Array shA a -> Array shB b) -> ArrayMatrix shA a -> ArrayMatrix shB b ArrMatrix.lift1 ((Array shape a -> Array shape a) -> Matrix (Array shape) a -> Matrix (Array shape) a) -> (Int -> Array shape a -> Array shape a) -> Int -> Matrix (Array shape) a -> Matrix (Array shape) a forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Array shape a -> Array shape a forall shape a. (Power shape, Floating a) => Int -> Array shape a -> Array shape a ArrMultiply.power (#*#) :: (Multiply typA typB, Class.Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a #*# :: Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a (#*#) = Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a forall typA typB a. (Multiply typA typB, Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a matrixMatrix class (Type.Box typA, Type.Box typB) => Multiply typA typB where type Multiplied typA typB matrixMatrix :: (Class.Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a instance (Box.Box shapeA, Box.Box shapeB, ArrMultiply.Multiply shapeA shapeB) => Multiply (ArrMatrix.Array shapeA) (ArrMatrix.Array shapeB) where type Multiplied (ArrMatrix.Array shapeA) (ArrMatrix.Array shapeB) = ArrMatrix.Array (ArrMultiply.Multiplied shapeA shapeB) matrixMatrix :: Matrix (Array shapeA) a -> Matrix (Array shapeB) a -> Matrix (Multiplied (Array shapeA) (Array shapeB)) a matrixMatrix (ArrMatrix.Array a) (ArrMatrix.Array b) = Array (Multiplied shapeA shapeB) a -> Matrix (Array (Multiplied shapeA shapeB)) a forall shape a. Array shape a -> Matrix (Array shape) a ArrMatrix.Array (Array (Multiplied shapeA shapeB) a -> Matrix (Array (Multiplied shapeA shapeB)) a) -> Array (Multiplied shapeA shapeB) a -> Matrix (Array (Multiplied shapeA shapeB)) a forall a b. (a -> b) -> a -> b $ Array shapeA a -> Array shapeB a -> Array (Multiplied shapeA shapeB) a forall shapeA shapeB a. (Multiply shapeA shapeB, Floating a) => Array shapeA a -> Array shapeB a -> Array (Multiplied shapeA shapeB) a ArrMultiply.matrixMatrix Array shapeA a a Array shapeB a b instance (Shape.C shapeA, Eq shapeA, shapeA ~ shapeB, Shape.C shapeB) => Multiply (Type.Scale shapeA) (Type.Scale shapeB) where type Multiplied (Type.Scale shapeA) (Type.Scale shapeB) = Type.Scale shapeB matrixMatrix :: Matrix (Scale shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Multiplied (Scale shapeA) (Scale shapeB)) a matrixMatrix = Matrix (Scale shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Multiplied (Scale shapeA) (Scale shapeB)) a forall typ a. (MultiplySame typ, Floating a) => Matrix typ a -> Matrix typ a -> Matrix typ a Type.multiplySame instance (Shape.C shapeA, Eq shapeA, shapeA ~ Box.HeightOf shapeB, Box.Box shapeB, ArrMultiply.Scale shapeB) => Multiply (Type.Scale shapeA) (ArrMatrix.Array shapeB) where type Multiplied (Type.Scale shapeA) (ArrMatrix.Array shapeB) = ArrMatrix.Array shapeB matrixMatrix :: Matrix (Scale shapeA) a -> Matrix (Array shapeB) a -> Matrix (Multiplied (Scale shapeA) (Array shapeB)) a matrixMatrix = String -> (Matrix (Array shapeB) a -> shapeA) -> (a -> Matrix (Array shapeB) a -> Matrix (Array shapeB) a) -> Matrix (Scale shapeA) a -> Matrix (Array shapeB) a -> Matrix (Array shapeB) a forall shape b a c. Eq shape => String -> (b -> shape) -> (a -> b -> c) -> Matrix (Scale shape) a -> b -> c scaleWithCheck String "Matrix.Multiply.multiply Scale" Matrix (Array shapeB) a -> shapeA forall typ a. Box typ => Matrix typ a -> HeightOf typ Type.height a -> Matrix (Array shapeB) a -> Matrix (Array shapeB) a forall shape a. (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a ArrMatrix.scale instance (Box.Box shapeA, ArrMultiply.Scale shapeA, Box.WidthOf shapeA ~ shapeB, Shape.C shapeB, Eq shapeB) => Multiply (ArrMatrix.Array shapeA) (Type.Scale shapeB) where type Multiplied (ArrMatrix.Array shapeA) (Type.Scale shapeB) = ArrMatrix.Array shapeA matrixMatrix :: Matrix (Array shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Multiplied (Array shapeA) (Scale shapeB)) a matrixMatrix = (Matrix (Scale shapeB) a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a) -> Matrix (Array shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Array shapeA) a forall a b c. (a -> b -> c) -> b -> a -> c flip ((Matrix (Scale shapeB) a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a) -> Matrix (Array shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Array shapeA) a) -> (Matrix (Scale shapeB) a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a) -> Matrix (Array shapeA) a -> Matrix (Scale shapeB) a -> Matrix (Array shapeA) a forall a b. (a -> b) -> a -> b $ String -> (Matrix (Array shapeA) a -> shapeB) -> (a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a) -> Matrix (Scale shapeB) a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a forall shape b a c. Eq shape => String -> (b -> shape) -> (a -> b -> c) -> Matrix (Scale shape) a -> b -> c scaleWithCheck String "Matrix.Multiply.multiply Scale" Matrix (Array shapeA) a -> shapeB forall typ a. Box typ => Matrix typ a -> WidthOf typ Type.width a -> Matrix (Array shapeA) a -> Matrix (Array shapeA) a forall shape a. (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a ArrMatrix.scale instance (Shape.C shapeA, Eq shapeA, shapeA ~ shapeB, Shape.C shapeB) => Multiply (Perm.Permutation shapeA) (Perm.Permutation shapeB) where type Multiplied (Perm.Permutation shapeA) (Perm.Permutation shapeB) = Perm.Permutation shapeB matrixMatrix :: Matrix (Permutation shapeA) a -> Matrix (Permutation shapeB) a -> Matrix (Multiplied (Permutation shapeA) (Permutation shapeB)) a matrixMatrix = Matrix (Permutation shapeA) a -> Matrix (Permutation shapeB) a -> Matrix (Multiplied (Permutation shapeA) (Permutation shapeB)) a forall typ a. (MultiplySame typ, Floating a) => Matrix typ a -> Matrix typ a -> Matrix typ a Type.multiplySame