module Numeric.LAPACK.Matrix.Permutation (
Permutation,
size,
identity,
Mod.Inversion(NonInverted,Inverted),
Perm.inversionFromTransposition,
fromPermutation,
toPermutation,
toMatrix,
determinant,
transpose,
multiplyVector,
multiplyFull,
) where
import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix
import qualified Numeric.LAPACK.Matrix.Shape.Private as MatrixShape
import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent
import qualified Numeric.LAPACK.Matrix.Modifier as Mod
import qualified Numeric.LAPACK.Permutation as Perm
import Numeric.LAPACK.Permutation (Permutation)
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
size :: Matrix (Permutation sh) a -> sh
size (Permutation perm) = Perm.size perm
identity :: (Shape.C sh) => sh -> Matrix (Permutation sh) a
identity = Permutation . Perm.identity
fromPermutation ::
(Shape.C sh) => Perm.Permutation sh -> Matrix (Permutation sh) a
fromPermutation = Permutation
toPermutation ::
(Shape.C sh) => Matrix (Permutation sh) a -> Perm.Permutation sh
toPermutation (Permutation perm) = perm
determinant :: (Shape.C sh, Class.Floating a) => Matrix (Permutation sh) a -> a
determinant (Permutation perm) = Perm.numberFromSign $ Perm.determinant perm
transpose ::
(Shape.C sh) => Matrix (Permutation sh) a -> Matrix (Permutation sh) a
transpose (Permutation perm) = Permutation $ Perm.transpose perm
toMatrix ::
(Shape.C sh, Class.Floating a) =>
Matrix (Permutation sh) a -> ArrMatrix.Square sh a
toMatrix (Permutation perm) = Perm.toMatrix perm
multiplyVector ::
(Shape.C size, Eq size, Class.Floating a) =>
Mod.Inversion -> Matrix (Permutation size) a ->
Vector size a -> Vector size a
multiplyVector inverted (Permutation perm) =
ArrMatrix.unliftColumn MatrixShape.ColumnMajor (Perm.apply inverted perm)
multiplyFull ::
(Extent.C vert, Extent.C horiz,
Shape.C height, Eq height, Shape.C width, Class.Floating a) =>
Mod.Inversion -> Matrix (Permutation height) a ->
ArrMatrix.Full vert horiz height width a ->
ArrMatrix.Full vert horiz height width a
multiplyFull inverted (Permutation perm) = Perm.apply inverted perm