lapack-0.5.0.3: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Permutation

Synopsis

Documentation

data Permutation sh Source #

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

Defined in Numeric.LAPACK.Permutation.Private

Methods

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

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

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

Defined in Numeric.LAPACK.Permutation.Private

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

Defined in Numeric.LAPACK.Format

Methods

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

newtype Shape sh Source #

Constructors

Shape sh 
Instances
Functor Shape Source # 
Instance details

Defined in Numeric.LAPACK.Permutation.Private

Methods

fmap :: (a -> b) -> Shape a -> Shape b #

(<$) :: a -> Shape b -> Shape a #

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 #

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 #

unifiedOffset :: Checking check => Shape sh -> Index (Shape sh) -> Result check Int #

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

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

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

unifiedSizeOffset :: Checking check => Shape sh -> (Int, Index (Shape sh) -> Result check Int) #

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

Defined in Numeric.LAPACK.Permutation.Private

Methods

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

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

unifiedIndexFromOffset :: Checking check => Shape sh -> Int -> Result check (Index (Shape sh)) #

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 #

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

QC.forAll QC.arbitraryBoundedEnum $ \inv -> QC.forAll (QC.arbitrary >>= genPivots) $ \xs -> xs == Perm.toPivots inv (Perm.fromPivots inv xs)

toPivots :: C sh => Inversion -> Permutation sh -> Vector (Shape 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 #

determinant :: C sh => Permutation sh -> Sign Source #

QC.forAll genPerm2 $ \(p0,p1) -> determinant (multiply p0 p1) == determinant p0 <> determinant p1

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

numberFromSign s == (-1)^fromEnum s

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

QC.forAll genPerm2 $ \(p0,p1) -> transpose (multiply p0 p1) == multiply (transpose p1) (transpose p0)

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

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