{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} module Numeric.LAPACK.Matrix.Permutation ( Permutation, size, identity, Mod.Inversion(NonInverted,Inverted), Perm.inversionFromTransposition, fromPermutation, toPermutation, toSquare, determinant, transpose, multiplyVector, multiplyFull, ) where import qualified Numeric.LAPACK.Matrix.Array.Private as ArrMatrix import qualified Numeric.LAPACK.Matrix.Type as Matrix import qualified Numeric.LAPACK.Matrix.Shape.Omni as Omni import qualified Numeric.LAPACK.Matrix.Layout.Private as Layout import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent import qualified Numeric.LAPACK.Matrix.Modifier as Mod import qualified Numeric.LAPACK.Permutation.Private as Plain import qualified Numeric.LAPACK.Permutation as Perm import Numeric.LAPACK.Matrix.Type (Matrix(Permutation)) import Numeric.LAPACK.Vector (Vector) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Shape as Shape type Permutation sh = FlexPermutation Layout.Filled Layout.Filled sh type FlexPermutation lower upper sh = Matrix.Quadratic Matrix.Permutation () () lower upper sh size :: FlexPermutation lower upper sh a -> sh size (Permutation perm) = Perm.size perm identity :: (Shape.C sh) => sh -> FlexPermutation lower upper sh a identity = Permutation . Perm.identity fromPermutation :: (Shape.C sh) => Perm.Permutation sh -> Permutation sh a fromPermutation = Permutation toPermutation :: (Shape.C sh) => FlexPermutation lower upper sh a -> Perm.Permutation sh toPermutation (Permutation perm) = perm determinant :: (Shape.C sh, Class.Floating a) => FlexPermutation lower upper sh a -> a determinant (Permutation perm) = Perm.numberFromSign $ Perm.determinant perm transpose :: (Shape.C sh) => FlexPermutation lower upper sh a -> FlexPermutation upper lower sh a transpose (Permutation perm) = Permutation $ Perm.transpose perm toSquare :: (Omni.Strip lower, Omni.Strip upper, Shape.C sh, Class.Floating a) => FlexPermutation lower upper sh a -> ArrMatrix.Quadratic Layout.Unpacked Omni.Arbitrary lower upper sh a toSquare (Permutation perm) = ArrMatrix.liftUnpacked0 $ Plain.toMatrix perm multiplyVector :: (Shape.C size, Eq size, Class.Floating a) => Mod.Inversion -> FlexPermutation lower upper size a -> Vector size a -> Vector size a multiplyVector inverted (Permutation perm) = ArrMatrix.unliftColumn Layout.ColumnMajor (Perm.apply inverted perm) multiplyFull :: (Extent.Measure meas, Extent.C vert, Extent.C horiz, Shape.C height, Eq height, Shape.C width, Class.Floating a) => Mod.Inversion -> FlexPermutation lower upper height a -> ArrMatrix.Full meas vert horiz height width a -> ArrMatrix.Full meas vert horiz height width a multiplyFull inverted (Permutation perm) = Perm.apply inverted perm