lapack-0.3.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Permutation

Documentation

data Permutation sh Source #

Instances
(C sh, Show sh) => Show (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Box (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

Associated Types

type HeightOf (Permutation sh) :: Type Source #

type WidthOf (Permutation sh) :: Type Source #

C sh => FormatMatrix (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

Methods

formatMatrix :: (Floating a, Output out) => String -> Matrix (Permutation sh) a -> out Source #

C sh => Format (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Format

Methods

format :: Output out => String -> Permutation sh -> out Source #

Indexed size => Indexed (Permutation size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: Floating a => Matrix (Permutation size) a -> (Index (HeightOf (Permutation size)), Index (WidthOf (Permutation size))) -> a Source #

C sh => SquareShape (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

toSquare :: (HeightOf (Permutation sh) ~ sh0, Floating a) => Matrix (Permutation sh) a -> Square sh0 a Source #

identityOrder :: (HeightOf (Permutation sh) ~ sh0, Floating a) => Order -> sh0 -> Matrix (Permutation sh) a

takeDiagonal :: (HeightOf (Permutation sh) ~ sh0, Floating a) => Matrix (Permutation sh) a -> Vector sh0 a Source #

C shape => Complex (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

conjugate :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source #

fromReal :: Floating a => Matrix (Permutation shape) (RealOf a) -> Matrix (Permutation shape) a Source #

toComplex :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) (ComplexOf a) Source #

C shape => Power (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

square :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source #

power :: Floating a => Int -> Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source #

C shape => MultiplySquare (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

transposableSquare :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a

squareFull :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a

fullSquare :: (WidthOf (Permutation shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Permutation shape) a -> Full vert horiz height width a

C shape => MultiplyVector (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

matrixVector :: (WidthOf (Permutation shape) ~ width, Eq width, Floating a) => Matrix (Permutation shape) a -> Vector width a -> Vector (HeightOf (Permutation shape)) a

vectorMatrix :: (HeightOf (Permutation shape) ~ height, Eq height, Floating a) => Vector height a -> Matrix (Permutation shape) a -> Vector (WidthOf (Permutation shape)) a

C shape => Inverse (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

inverse :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source #

C shape => Solve (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

solve :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source #

solveRight :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source #

solveLeft :: (WidthOf (Permutation shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Permutation shape) a -> Full vert horiz height width a Source #

C shape => Determinant (Permutation shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

determinant :: Floating a => Matrix (Permutation shape) a -> a Source #

(C shapeA, Eq shapeA, shapeA ~ shapeB, C shapeB) => Multiply (Permutation shapeA) (Permutation shapeB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied (Permutation shapeA) (Permutation shapeB) :: Type

Methods

matrixMatrix :: Floating a => Matrix (Permutation shapeA) a -> Matrix (Permutation shapeB) a -> Matrix (Multiplied (Permutation shapeA) (Permutation shapeB)) a

(C sh, Show sh) => Show (Matrix (Permutation sh) a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

Methods

showsPrec :: Int -> Matrix (Permutation sh) a -> ShowS #

show :: Matrix (Permutation sh) a -> String #

showList :: [Matrix (Permutation sh) a] -> ShowS #

type HeightOf (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

type HeightOf (Permutation sh) = sh
type WidthOf (Permutation sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

type WidthOf (Permutation sh) = sh
newtype Matrix (Permutation sh) a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type

size :: Matrix (Permutation sh) a -> sh Source #

identity :: C sh => sh -> Matrix (Permutation sh) a Source #

toMatrix :: (C sh, Floating a) => Matrix (Permutation sh) a -> Square sh a Source #

determinant :: (C sh, Floating a) => Matrix (Permutation sh) a -> a Source #

multiplyVector :: (C size, Eq size, Floating a) => Inversion -> Matrix (Permutation size) a -> Vector size a -> Vector size a Source #

multiplyFull :: (C vert, C horiz, C height, Eq height, C width, Floating a) => Inversion -> Matrix (Permutation height) a -> Full vert horiz height width a -> Full vert horiz height width a Source #