lapack-0.3.0.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Permutation

Synopsis

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

newtype Shape sh Source #

Constructors

Shape sh 
Instances
Eq sh => Eq (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

(==) :: Shape sh -> Shape sh -> Bool #

(/=) :: Shape sh -> Shape sh -> Bool #

Show sh => Show (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

showsPrec :: Int -> Shape sh -> ShowS #

show :: Shape sh -> String #

showList :: [Shape sh] -> ShowS #

C sh => C (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

size :: Shape sh -> Int #

uncheckedSize :: Shape sh -> Int #

C sh => Indexed (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Associated Types

type Index (Shape sh) :: Type #

Methods

indices :: Shape sh -> [Index (Shape sh)] #

offset :: Shape sh -> Index (Shape sh) -> Int #

uncheckedOffset :: Shape sh -> Index (Shape sh) -> Int #

inBounds :: Shape sh -> Index (Shape sh) -> Bool #

sizeOffset :: Shape sh -> (Int, Index (Shape sh) -> Int) #

uncheckedSizeOffset :: Shape sh -> (Int, Index (Shape sh) -> Int) #

C sh => InvIndexed (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

type Index (Shape sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

type Index (Shape sh) = Element sh

newtype Element sh Source #

Constructors

Element CInt 
Instances
Eq (Element sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

(==) :: Element sh -> Element sh -> Bool #

(/=) :: Element sh -> Element sh -> Bool #

Show (Element sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

showsPrec :: Int -> Element sh -> ShowS #

show :: Element sh -> String #

showList :: [Element sh] -> ShowS #

Storable (Element sh) Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

sizeOf :: Element sh -> Int #

alignment :: Element sh -> Int #

peekElemOff :: Ptr (Element sh) -> Int -> IO (Element sh) #

pokeElemOff :: Ptr (Element sh) -> Int -> Element sh -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Element sh) #

pokeByteOff :: Ptr b -> Int -> Element sh -> IO () #

peek :: Ptr (Element sh) -> IO (Element sh) #

poke :: Ptr (Element sh) -> Element sh -> IO () #

size :: Permutation sh -> sh Source #

identity :: C sh => sh -> Permutation sh Source #

toPivots :: C sh => Inversion -> Permutation sh -> Vector sh (Element sh) Source #

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

data Sign Source #

Constructors

Positive 
Negative 
Instances
Bounded Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Enum Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

succ :: Sign -> Sign #

pred :: Sign -> Sign #

toEnum :: Int -> Sign #

fromEnum :: Sign -> Int #

enumFrom :: Sign -> [Sign] #

enumFromThen :: Sign -> Sign -> [Sign] #

enumFromTo :: Sign -> Sign -> [Sign] #

enumFromThenTo :: Sign -> Sign -> Sign -> [Sign] #

Eq Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

Show Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

Semigroup Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

(<>) :: Sign -> Sign -> Sign #

sconcat :: NonEmpty Sign -> Sign #

stimes :: Integral b => b -> Sign -> Sign #

Monoid Sign Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

mempty :: Sign #

mappend :: Sign -> Sign -> Sign #

mconcat :: [Sign] -> Sign #

numberFromSign :: Floating a => Sign -> a Source #

numberFromSign s == (-1)^fromEnum s

multiply :: (C sh, Eq sh) => Permutation sh -> Permutation sh -> Permutation sh Source #

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