{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE EmptyDataDecls #-} module Numeric.LAPACK.Matrix.Inverse where import qualified Numeric.LAPACK.Matrix.Type as Type 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 ((#\|), (-/#)) data Inverse typ newtype instance Type.Matrix (Inverse typ) a = Inverse (Type.Matrix typ a) instance (Type.MultiplySame typ) => Type.MultiplySame (Inverse typ) where multiplySame :: Matrix (Inverse typ) a -> Matrix (Inverse typ) a -> Matrix (Inverse typ) a multiplySame (Inverse a) (Inverse b) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Matrix typ a -> Matrix typ a -> Matrix typ a forall typ a. (MultiplySame typ, Floating a) => Matrix typ a -> Matrix typ a -> Matrix typ a Type.multiplySame Matrix typ a b Matrix typ a a instance (Type.Box typ) => Type.Box (Inverse typ) where type HeightOf (Inverse typ) = Type.HeightOf typ type WidthOf (Inverse typ) = Type.WidthOf typ height :: Matrix (Inverse typ) a -> HeightOf (Inverse typ) height (Inverse m) = Matrix typ a -> HeightOf typ forall typ a. Box typ => Matrix typ a -> HeightOf typ Type.height Matrix typ a m width :: Matrix (Inverse typ) a -> WidthOf (Inverse typ) width (Inverse m) = Matrix typ a -> WidthOf typ forall typ a. Box typ => Matrix typ a -> WidthOf typ Type.width Matrix typ a m instance (MatrixClass.Complex typ) => MatrixClass.Complex (Inverse typ) where conjugate :: Matrix (Inverse typ) a -> Matrix (Inverse typ) a conjugate (Inverse m) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Matrix typ a -> Matrix typ a forall typ a. (Complex typ, Floating a) => Matrix typ a -> Matrix typ a MatrixClass.conjugate Matrix typ a m fromReal :: Matrix (Inverse typ) (RealOf a) -> Matrix (Inverse typ) a fromReal (Inverse m) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Matrix typ (RealOf a) -> Matrix typ a forall typ a. (Complex typ, Floating a) => Matrix typ (RealOf a) -> Matrix typ a MatrixClass.fromReal Matrix typ (RealOf a) m toComplex :: Matrix (Inverse typ) a -> Matrix (Inverse typ) (ComplexOf a) toComplex (Inverse m) = Matrix typ (ComplexOf a) -> Matrix (Inverse typ) (ComplexOf a) forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ (ComplexOf a) -> Matrix (Inverse typ) (ComplexOf a)) -> Matrix typ (ComplexOf a) -> Matrix (Inverse typ) (ComplexOf a) forall a b. (a -> b) -> a -> b $ Matrix typ a -> Matrix typ (ComplexOf a) forall typ a. (Complex typ, Floating a) => Matrix typ a -> Matrix typ (ComplexOf a) MatrixClass.toComplex Matrix typ a m instance (Divide.Solve typ) => Multiply.MultiplyVector (Inverse typ) where matrixVector :: Matrix (Inverse typ) a -> Vector width a -> Vector (HeightOf (Inverse typ)) a matrixVector (Inverse a) Vector width a x = Matrix typ a aMatrix typ a -> Vector width a -> Vector width a forall typ height a. (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Matrix typ a -> Vector height a -> Vector height a #\|Vector width a x vectorMatrix :: Vector height a -> Matrix (Inverse typ) a -> Vector (WidthOf (Inverse typ)) a vectorMatrix Vector height a x (Inverse a) = Vector height a xVector height a -> Matrix typ a -> Vector height a forall typ height a. (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector height a -/#Matrix typ a a instance (Divide.Solve typ) => Multiply.MultiplySquare (Inverse typ) where transposableSquare :: Transposition -> Matrix (Inverse typ) a -> Full vert horiz height width a -> Full vert horiz height width a transposableSquare Transposition trans (Inverse a) Full vert horiz height width a b = Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a forall typ height width vert horiz a. (Solve 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 Divide.solve Transposition trans Matrix typ a a Full vert horiz height width a b squareFull :: Matrix (Inverse typ) a -> Full vert horiz height width a -> Full vert horiz height width a squareFull (Inverse 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. (Solve 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 Divide.solveRight Matrix typ a a Full vert horiz height width a b fullSquare :: Full vert horiz height width a -> Matrix (Inverse typ) a -> Full vert horiz height width a fullSquare Full vert horiz height width a b (Inverse a) = Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a forall typ width height vert horiz a. (Solve 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 Divide.solveLeft Full vert horiz height width a b Matrix typ a a instance (Multiply.Power typ) => Multiply.Power (Inverse typ) where square :: Matrix (Inverse typ) a -> Matrix (Inverse typ) a square (Inverse a) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Matrix typ a -> Matrix typ a forall typ a. (Power typ, Floating a) => Matrix typ a -> Matrix typ a Multiply.square Matrix typ a a power :: Int -> Matrix (Inverse typ) a -> Matrix (Inverse typ) a power Int n (Inverse a) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Int -> Matrix typ a -> Matrix typ a forall typ a. (Power typ, Floating a) => Int -> Matrix typ a -> Matrix typ a Multiply.power Int n Matrix typ a a instance (Divide.Determinant typ) => Divide.Determinant (Inverse typ) where determinant :: Matrix (Inverse typ) 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 $ Matrix typ a -> a forall typ a. (Determinant typ, Floating a) => Matrix typ a -> a Divide.determinant Matrix typ a a instance (Multiply.MultiplySquare typ) => Divide.Solve (Inverse typ) where solve :: Transposition -> Matrix (Inverse typ) a -> Full vert horiz height width a -> Full vert horiz height width a solve Transposition trans (Inverse a) Full vert horiz height width a b = 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 Multiply.transposableSquare Transposition trans Matrix typ a a Full vert horiz height width a b solveRight :: Matrix (Inverse typ) a -> Full vert horiz height width a -> Full vert horiz height width a solveRight (Inverse 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 Multiply.squareFull Matrix typ a a Full vert horiz height width a b solveLeft :: Full vert horiz height width a -> Matrix (Inverse typ) a -> Full vert horiz height width a solveLeft Full vert horiz height width a b (Inverse 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 Multiply.fullSquare Full vert horiz height width a b Matrix typ a a instance (Divide.Inverse typ, Multiply.MultiplySquare typ) => Divide.Inverse (Inverse typ) where inverse :: Matrix (Inverse typ) a -> Matrix (Inverse typ) a inverse (Inverse a) = Matrix typ a -> Matrix (Inverse typ) a forall typ a. Matrix typ a -> Matrix (Inverse typ) a Inverse (Matrix typ a -> Matrix (Inverse typ) a) -> Matrix typ a -> Matrix (Inverse typ) a forall a b. (a -> b) -> a -> b $ Matrix typ a -> Matrix typ a forall typ a. (Inverse typ, Floating a) => Matrix typ a -> Matrix typ a Divide.inverse Matrix typ a a