{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} module Numeric.LAPACK.Matrix.Inverse where import qualified Numeric.LAPACK.Matrix.Type as Matrix import qualified Numeric.LAPACK.Matrix.Layout.Private as Layout import qualified Numeric.LAPACK.Matrix.Shape as MatrixShape import qualified Numeric.LAPACK.Matrix.Shape.Omni as Omni import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent import qualified Numeric.LAPACK.Matrix.Class as MatrixClass import qualified Numeric.LAPACK.Matrix.Divide as Divide import qualified Numeric.LAPACK.Matrix.Multiply as Multiply import Numeric.LAPACK.Matrix.Divide ((#\|), (-/#)) import Numeric.LAPACK.Matrix.Type (Matrix) import qualified Type.Data.Num.Unary as Unary data Inverse typ data instance Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a where Inverse :: (Omni.Strip lower, Fill lower ~ lowerf, Omni.PowerStrip lowerf, Omni.Strip upper, Fill upper ~ upperf, Omni.PowerStrip upperf) => Matrix.QuadraticMeas typ xl xu upper lower meas width height a -> Matrix.QuadraticMeas (Inverse typ) (xl,lower) (xu,upper) lowerf upperf meas height width a type family Fill offDiag type instance Fill (Layout.Bands Unary.Zero) = Layout.Bands Unary.Zero type instance Fill (Layout.Bands (Unary.Succ k)) = Layout.Filled type instance Fill Layout.Filled = Layout.Filled data PowerStripFact c = (Omni.PowerStrip c) => PowerStripFact filledPowerStripFact :: (Omni.Strip c) => Omni.StripSingleton c -> PowerStripFact (Fill c) filledPowerStripFact :: StripSingleton c -> PowerStripFact (Fill c) filledPowerStripFact StripSingleton c w = case StripSingleton c w of StripSingleton c Omni.StripFilled -> PowerStripFact (Fill c) forall c. PowerStrip c => PowerStripFact c PowerStripFact Omni.StripBands HeadSingleton offDiag Unary.Zero -> PowerStripFact (Fill c) forall c. PowerStrip c => PowerStripFact c PowerStripFact Omni.StripBands HeadSingleton offDiag Unary.Succ -> PowerStripFact (Fill c) forall c. PowerStrip c => PowerStripFact c PowerStripFact instance (Matrix.Transpose typ) => Matrix.Transpose (Inverse typ) where transpose :: Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Matrix (Inverse typ) xu xl upper lower meas horiz vert width height a transpose (Inverse a) = QuadraticMeas typ xu xl lower upper meas height width a -> QuadraticMeas (Inverse typ) (xu, upper) (xl, lower) upper lower meas width height a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xu xl lower upper meas height width a -> QuadraticMeas (Inverse typ) (xu, upper) (xl, lower) upper lower meas width height a) -> QuadraticMeas typ xu xl lower upper meas height width a -> QuadraticMeas (Inverse typ) (xu, upper) (xl, lower) upper lower meas width height a forall a b. (a -> b) -> a -> b $ Matrix typ xl xu upper lower meas Small Small width height a -> QuadraticMeas typ xu xl lower upper meas height width a forall typ meas vert horiz width height a xl xu lower upper. (Transpose typ, Measure meas, C vert, C horiz, C width, C height, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xu xl upper lower meas horiz vert width height a Matrix.transpose Matrix typ xl xu upper lower meas Small Small width height a a instance (Matrix.MultiplySame typ xl xu, MatrixShape.PowerStrip lower, MatrixShape.PowerStrip upper) => Matrix.MultiplySame (Inverse typ) (xl,lower) (xu,upper) where multiplySame :: matrix -> matrix -> matrix multiplySame (Inverse a) (Inverse b) = QuadraticMeas typ xl xu upper lower meas sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas sh sh a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower meas sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas sh sh a) -> QuadraticMeas typ xl xu upper lower meas sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas sh sh a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower meas sh sh a -> QuadraticMeas typ xl xu upper lower meas sh sh a -> QuadraticMeas typ xl xu upper lower meas sh sh a forall typ xl xu matrix lower upper meas vert horiz sh a. (MultiplySame typ xl xu, matrix ~ Matrix typ xl xu lower upper meas vert horiz sh sh a, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Matrix.multiplySame QuadraticMeas typ xl xu upper lower meas sh sh a b QuadraticMeas typ xl xu upper lower meas sh sh a QuadraticMeas typ xl xu upper lower meas sh sh a a instance (Matrix.Box typ) => Matrix.Box (Inverse typ) where extent :: Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width extent (Inverse m) = Extent meas Small Small width height -> Extent meas Small Small height width forall meas vert horiz height width. (Measure meas, C vert, C horiz) => Extent meas vert horiz height width -> Extent meas horiz vert width height Extent.transpose (Extent meas Small Small width height -> Extent meas Small Small height width) -> Extent meas Small Small width height -> Extent meas Small Small height width forall a b. (a -> b) -> a -> b $ Matrix typ xl xu upper lower meas Small Small width height a -> Extent meas Small Small width height forall typ meas vert horiz xl xu lower upper height width a. (Box typ, Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Matrix.extent Matrix typ xl xu upper lower meas Small Small width height a m height :: Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> height height (Inverse m) = Matrix typ xl xu upper lower meas Small Small width height a -> height forall typ meas vert horiz xl xu lower upper height width a. (Box typ, Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> width Matrix.width Matrix typ xl xu upper lower meas Small Small width height a m width :: Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> width width (Inverse m) = Matrix typ xl xu upper lower meas Small Small width height a -> width forall typ meas vert horiz xl xu lower upper height width a. (Box typ, Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> height Matrix.height Matrix typ xl xu upper lower meas Small Small width height a m instance (Matrix.ToQuadratic typ) => Matrix.ToQuadratic (Inverse typ) where heightToQuadratic :: QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper height a heightToQuadratic (Inverse m) = QuadraticMeas typ xl xu upper lower Shape height height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape height height a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower Shape height height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape height height a) -> QuadraticMeas typ xl xu upper lower Shape height height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape height height a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas typ xl xu upper lower Shape height height a forall typ meas xl xu lower upper height width a. (ToQuadratic typ, Measure meas) => QuadraticMeas typ xl xu lower upper meas height width a -> Quadratic typ xl xu lower upper width a Matrix.widthToQuadratic QuadraticMeas typ xl xu upper lower meas width height a m widthToQuadratic :: QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper width a widthToQuadratic (Inverse m) = QuadraticMeas typ xl xu upper lower Shape width width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape width width a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower Shape width width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape width width a) -> QuadraticMeas typ xl xu upper lower Shape width width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape width width a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas typ xl xu upper lower Shape width width a forall typ meas xl xu lower upper height width a. (ToQuadratic typ, Measure meas) => QuadraticMeas typ xl xu lower upper meas height width a -> Quadratic typ xl xu lower upper height a Matrix.heightToQuadratic QuadraticMeas typ xl xu upper lower meas width height a m instance (MatrixClass.Complex typ) => MatrixClass.Complex (Inverse typ) where conjugate :: matrix a -> matrix a conjugate (Inverse m) = QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a) -> QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas typ xl xu upper lower meas width height a forall typ xl xu lower upper meas vert horiz height width (matrix :: * -> *) a. (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a MatrixClass.conjugate QuadraticMeas typ xl xu upper lower meas width height a m fromReal :: matrix (RealOf a) -> matrix a fromReal (Inverse m) = QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a) -> QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a forall a b. (a -> b) -> a -> b $ Matrix typ xl xu upper lower meas Small Small width height (RealOf a) -> QuadraticMeas typ xl xu upper lower meas width height a forall typ xl xu lower upper meas vert horiz height width (matrix :: * -> *) a. (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a MatrixClass.fromReal Matrix typ xl xu upper lower meas Small Small width height (RealOf a) m toComplex :: matrix a -> matrix (ComplexOf a) toComplex (Inverse m) = QuadraticMeas typ xl xu upper lower meas width height (ComplexOf a) -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width (ComplexOf a) forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower meas width height (ComplexOf a) -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width (ComplexOf a)) -> QuadraticMeas typ xl xu upper lower meas width height (ComplexOf a) -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width (ComplexOf a) forall a b. (a -> b) -> a -> b $ Matrix typ xl xu upper lower meas Small Small width height a -> QuadraticMeas typ xl xu upper lower meas width height (ComplexOf a) forall typ xl xu lower upper meas vert horiz height width (matrix :: * -> *) a. (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) MatrixClass.toComplex Matrix typ xl xu upper lower meas Small Small width height a m instance (Divide.Solve typ xl xu, Matrix.ToQuadratic typ, Omni.Strip lower, Omni.Strip upper) => Multiply.MultiplyVector (Inverse typ) (xl,lower) (xu,upper) where matrixVector :: Matrix (Inverse typ) (xl, lower) (xu, upper) lower upper meas vert horiz height width a -> Vector width a -> Vector height a matrixVector (Inverse a) Vector width a x = QuadraticMeas typ xl xu upper lower meas width height a aQuadraticMeas typ xl xu upper lower meas width height a -> Vector width a -> Vector height a forall typ xl xu lower upper meas height width a. (Solve typ xl xu, ToQuadratic typ, Strip lower, Strip upper, Measure meas, C height, C width, Eq height, Floating a) => QuadraticMeas typ xl xu lower upper meas height width a -> Vector height a -> Vector width a #\|Vector width a x vectorMatrix :: Vector height a -> Matrix (Inverse typ) (xl, lower) (xu, upper) lower upper meas vert horiz height width a -> Vector width a vectorMatrix Vector height a x (Inverse a) = Vector height a xVector height a -> QuadraticMeas typ xl xu upper lower meas width height a -> Vector width a forall typ xl xu lower upper meas height width a. (Solve typ xl xu, ToQuadratic typ, Strip lower, Strip upper, Measure meas, C height, C width, Eq width, Floating a) => Vector width a -> QuadraticMeas typ xl xu lower upper meas height width a -> Vector height a -/#QuadraticMeas typ xl xu upper lower meas width height a a instance (Divide.Solve typ xl xu, Matrix.ToQuadratic typ, Omni.Strip lower, Omni.Strip upper) => Multiply.MultiplySquare (Inverse typ) (xl,lower) (xu,upper) where transposableSquare :: Transposition -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a transposableSquare Transposition trans (Inverse a) = Transposition -> Quadratic typ xl xu upper lower height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (Solve typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Divide.solve Transposition trans Quadratic typ xl xu upper lower height a a squareFull :: Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a squareFull (Inverse a) Full meas vert horiz height width a b = Quadratic typ xl xu upper lower height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (Solve typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Divide.solveRight Quadratic typ xl xu upper lower height a a Full meas vert horiz height width a b fullSquare :: Full meas vert horiz height width a -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper width a -> Full meas vert horiz height width a fullSquare Full meas vert horiz height width a b (Inverse a) = Full meas vert horiz height width a -> Quadratic typ xl xu upper lower width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (Solve typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic typ xl xu lower upper width a -> Full meas vert horiz height width a Divide.solveLeft Full meas vert horiz height width a b Quadratic typ xl xu upper lower width a a instance (Multiply.Power typ xl xu, MatrixShape.PowerStrip lower, MatrixShape.PowerStrip upper) => Multiply.Power (Inverse typ) (xl,lower) (xu,upper) where square :: Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a square (Inverse a) = QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a) -> QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas typ xl xu upper lower Shape sh sh a forall typ xl xu lower upper sh a. (Power typ xl xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Quadratic typ xl xu lower upper sh a Multiply.square QuadraticMeas typ xl xu upper lower Shape sh sh a a power :: Integer -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a power Integer n (Inverse a) = QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a) -> QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a forall a b. (a -> b) -> a -> b $ Integer -> QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas typ xl xu upper lower Shape sh sh a forall typ xl xu lower upper sh a. (Power typ xl xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic typ xl xu lower upper sh a -> Quadratic typ xl xu lower upper sh a Multiply.power Integer n QuadraticMeas typ xl xu upper lower Shape sh sh a a powers1 :: Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a -> Stream (Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a) powers1 (Inverse a) = (QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a) -> Stream (QuadraticMeas typ xl xu upper lower Shape sh sh a) -> Stream (QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap QuadraticMeas typ xl xu upper lower Shape sh sh a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (Stream (QuadraticMeas typ xl xu upper lower Shape sh sh a) -> Stream (QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a)) -> Stream (QuadraticMeas typ xl xu upper lower Shape sh sh a) -> Stream (QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper Shape sh sh a) forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower Shape sh sh a -> Stream (QuadraticMeas typ xl xu upper lower Shape sh sh a) forall typ xl xu lower upper sh a. (Power typ xl xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Stream (Quadratic typ xl xu lower upper sh a) Multiply.powers1 QuadraticMeas typ xl xu upper lower Shape sh sh a a instance (Divide.Determinant typ xl xu, MatrixShape.PowerStrip lower, MatrixShape.PowerStrip upper) => Divide.Determinant (Inverse typ) (xl,lower) (xu,upper) where determinant :: Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper sh a -> a determinant (Inverse a) = a -> a forall a. Fractional a => a -> a recip (a -> a) -> a -> a forall a b. (a -> b) -> a -> b $ Quadratic typ xl xu upper lower sh a -> a forall typ xl xu lower upper sh a. (Determinant typ xl xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> a Divide.determinant Quadratic typ xl xu upper lower sh a a instance (Multiply.MultiplySquare typ xl xu, Matrix.ToQuadratic typ, MatrixShape.PowerStrip lower, MatrixShape.PowerStrip upper) => Divide.Solve (Inverse typ) (xl,lower) (xu,upper) where solve :: Transposition -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a solve Transposition trans (Inverse a) = Transposition -> Quadratic typ xl xu upper lower height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (MultiplySquare typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Multiply.transposableSquare Transposition trans Quadratic typ xl xu upper lower height a a solveRight :: Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a solveRight (Inverse a) Full meas vert horiz height width a b = Quadratic typ xl xu upper lower height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (MultiplySquare typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Multiply.squareFull Quadratic typ xl xu upper lower height a a Full meas vert horiz height width a b solveLeft :: Full meas vert horiz height width a -> Quadratic (Inverse typ) (xl, lower) (xu, upper) lower upper width a -> Full meas vert horiz height width a solveLeft Full meas vert horiz height width a b (Inverse a) = Full meas vert horiz height width a -> Quadratic typ xl xu upper lower width a -> Full meas vert horiz height width a forall typ xl xu lower upper meas vert horiz height width a. (MultiplySquare typ xl xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic typ xl xu lower upper width a -> Full meas vert horiz height width a Multiply.fullSquare Full meas vert horiz height width a b Quadratic typ xl xu upper lower width a a instance (Divide.Inverse typ xl xu, Multiply.MultiplySquare typ xl xu, Matrix.ToQuadratic typ, MatrixShape.PowerStrip lower, MatrixShape.PowerStrip upper) => Divide.Inverse (Inverse typ) (xl,lower) (xu,upper) where inverse :: QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas width height a inverse (Inverse a) = QuadraticMeas typ xl xu upper lower meas height width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas width height a forall lower lowerf upper upperf typ xl xu meas width height a. (Strip lower, Fill lower ~ lowerf, PowerStrip lowerf, Strip upper, Fill upper ~ upperf, PowerStrip upperf) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lowerf upperf meas height width a Inverse (QuadraticMeas typ xl xu upper lower meas height width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas width height a) -> QuadraticMeas typ xl xu upper lower meas height width a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas width height a forall a b. (a -> b) -> a -> b $ QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas typ xl xu upper lower meas height width a forall typ xl xu lower upper meas height width a. (Inverse typ xl xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas typ xl xu lower upper meas height width a -> QuadraticMeas typ xl xu lower upper meas width height a Divide.inverse QuadraticMeas typ xl xu upper lower meas width height a a