{-# LANGUAGE TypeFamilies #-} module Numeric.LAPACK.Matrix.Special ( Matrix.Matrix(Scale,Inverse), Scale, Inverse, inverse, ) where import qualified Numeric.LAPACK.Matrix.Inverse as Inverse import qualified Numeric.LAPACK.Matrix.Type as Matrix import qualified Numeric.LAPACK.Matrix.Shape.Omni as Omni import Numeric.LAPACK.Matrix.Layout.Private (Empty, Filled) import Data.Tuple.HT (mapPair) type Scale sh = Matrix.Quadratic Matrix.Scale () () Empty Empty sh type Inverse typ lower upper sh = Matrix.Quadratic (Inverse.Inverse typ) lower upper Filled Filled sh inverse :: (Omni.Strip lower, Inverse.Fill lower ~ lowerf, Omni.Strip upper, Inverse.Fill upper ~ upperf) => Matrix.QuadraticMeas typ xl xu upper lower meas width height a -> Matrix.QuadraticMeas (Inverse.Inverse typ) (xl,lower) (xu,upper) lowerf upperf meas height width a inverse a = case mapPair (Inverse.filledPowerStripFact, Inverse.filledPowerStripFact) $ Matrix.strips a of (Inverse.PowerStripFact, Inverse.PowerStripFact) -> Inverse.Inverse a