Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Permutation sh
- newtype Shape sh = Shape sh
- newtype Element sh = Element CInt
- size :: Permutation sh -> sh
- identity :: C sh => sh -> Permutation sh
- data Inversion
- fromPivots :: C sh => Inversion -> Vector (Shape sh) (Element sh) -> Permutation sh
- toPivots :: C sh => Inversion -> Permutation sh -> Vector sh (Element sh)
- toMatrix :: (C sh, Floating a) => Permutation sh -> Square sh a
- data Sign
- determinant :: C sh => Permutation sh -> Sign
- numberFromSign :: Floating a => Sign -> a
- transpose :: C sh => Permutation sh -> Permutation sh
- inversionFromTransposition :: Transposition -> Inversion
- multiply :: (C sh, Eq sh) => Permutation sh -> Permutation sh -> Permutation sh
- 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
Documentation
data Permutation sh Source #
Instances
Shape sh |
Instances
Eq sh => Eq (Shape sh) Source # | |
Show sh => Show (Shape sh) Source # | |
C sh => C (Shape sh) Source # | |
Defined in Numeric.LAPACK.Permutation.Private | |
C sh => Indexed (Shape sh) Source # | |
Defined in Numeric.LAPACK.Permutation.Private 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 # | |
Defined in Numeric.LAPACK.Permutation.Private | |
type Index (Shape sh) Source # | |
Defined in Numeric.LAPACK.Permutation.Private |
Instances
Eq (Element sh) Source # | |
Show (Element sh) Source # | |
Storable (Element sh) Source # | |
Defined in Numeric.LAPACK.Permutation.Private |
size :: Permutation sh -> sh Source #
identity :: C sh => sh -> Permutation sh Source #
Instances
Bounded Inversion Source # | |
Enum Inversion Source # | |
Defined in Numeric.LAPACK.Matrix.Modifier succ :: Inversion -> Inversion # pred :: Inversion -> Inversion # fromEnum :: Inversion -> Int # enumFrom :: Inversion -> [Inversion] # enumFromThen :: Inversion -> Inversion -> [Inversion] # enumFromTo :: Inversion -> Inversion -> [Inversion] # enumFromThenTo :: Inversion -> Inversion -> Inversion -> [Inversion] # | |
Eq Inversion Source # | |
Show Inversion Source # | |
Semigroup Inversion Source # | |
Monoid Inversion Source # | |
fromPivots :: C sh => Inversion -> Vector (Shape sh) (Element sh) -> Permutation sh Source #
QC.forAll QC.arbitraryBoundedEnum $ \inv -> QC.forAll (QC.arbitrary >>= genPivots) $ \xs -> Array.toList xs == Array.toList (Perm.toPivots inv (Perm.fromPivots inv xs))
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) -> equating (Array.toList . Perm.toPivots NonInverted) (transpose $ multiply p0 p1) (multiply (transpose p1) (transpose p0))
multiply :: (C sh, Eq sh) => Permutation sh -> Permutation sh -> Permutation sh Source #