Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- type BandedHermitian offDiag size = Array (BandedHermitian offDiag size)
- data Transposition
- fromList :: (Natural offDiag, C size, Storable a) => UnaryProxy offDiag -> Order -> size -> [a] -> BandedHermitian offDiag size a
- identity :: (C sh, Floating a) => sh -> Diagonal sh a
- diagonal :: (C sh, Floating a) => Vector sh (RealOf a) -> Diagonal sh a
- takeDiagonal :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Vector size (RealOf a)
- toHermitian :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Hermitian size a
- toBanded :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Square offDiag offDiag size a
- multiplyVector :: (Natural offDiag, C size, Eq size, Floating a) => Transposition -> BandedHermitian offDiag size a -> Vector size a -> Vector size a
- multiplyFull :: (Natural offDiag, C vert, C horiz, C height, Eq height, C width, Eq width, Floating a) => Transposition -> BandedHermitian offDiag height a -> Full vert horiz height width a -> Full vert horiz height width a
- covariance :: (C size, Eq size, Floating a, Natural sub, Natural super) => Square sub super size a -> BandedHermitian (sub :+: super) size a
- sumRank1 :: (Natural k, Indexed sh, Floating a) => Order -> sh -> [(RealOf a, (Index sh, StaticVector (Succ k) a))] -> BandedHermitian k sh a
- eigenvalues :: (Natural offDiag, C sh, Floating a) => BandedHermitian offDiag sh a -> Vector sh (RealOf a)
- eigensystem :: (Natural offDiag, C sh, Floating a) => BandedHermitian offDiag sh a -> (Square sh a, Vector sh (RealOf a))
Documentation
type BandedHermitian offDiag size = Array (BandedHermitian offDiag size) Source #
data Transposition Source #
Instances
Bounded Transposition Source # | |
Defined in Numeric.LAPACK.Matrix.Private | |
Enum Transposition Source # | |
Defined in Numeric.LAPACK.Matrix.Private succ :: Transposition -> Transposition # pred :: Transposition -> Transposition # toEnum :: Int -> Transposition # fromEnum :: Transposition -> Int # enumFrom :: Transposition -> [Transposition] # enumFromThen :: Transposition -> Transposition -> [Transposition] # enumFromTo :: Transposition -> Transposition -> [Transposition] # enumFromThenTo :: Transposition -> Transposition -> Transposition -> [Transposition] # | |
Eq Transposition Source # | |
Defined in Numeric.LAPACK.Matrix.Private (==) :: Transposition -> Transposition -> Bool # (/=) :: Transposition -> Transposition -> Bool # | |
Show Transposition Source # | |
Defined in Numeric.LAPACK.Matrix.Private showsPrec :: Int -> Transposition -> ShowS # show :: Transposition -> String # showList :: [Transposition] -> ShowS # |
fromList :: (Natural offDiag, C size, Storable a) => UnaryProxy offDiag -> Order -> size -> [a] -> BandedHermitian offDiag size a Source #
takeDiagonal :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Vector size (RealOf a) Source #
toHermitian :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Hermitian size a Source #
toBanded :: (Natural offDiag, C size, Floating a) => BandedHermitian offDiag size a -> Square offDiag offDiag size a Source #
multiplyVector :: (Natural offDiag, C size, Eq size, Floating a) => Transposition -> BandedHermitian offDiag size a -> Vector size a -> Vector size a Source #
multiplyFull :: (Natural offDiag, C vert, C horiz, C height, Eq height, C width, Eq width, Floating a) => Transposition -> BandedHermitian offDiag height a -> Full vert horiz height width a -> Full vert horiz height width a Source #
covariance :: (C size, Eq size, Floating a, Natural sub, Natural super) => Square sub super size a -> BandedHermitian (sub :+: super) size a Source #
sumRank1 :: (Natural k, Indexed sh, Floating a) => Order -> sh -> [(RealOf a, (Index sh, StaticVector (Succ k) a))] -> BandedHermitian k sh a Source #
eigenvalues :: (Natural offDiag, C sh, Floating a) => BandedHermitian offDiag sh a -> Vector sh (RealOf a) Source #
eigensystem :: (Natural offDiag, C sh, Floating a) => BandedHermitian offDiag sh a -> (Square sh a, Vector sh (RealOf a)) Source #
For symmetric eigenvalue problems, eigensystem
and schur
coincide.