lapack-0.3.2: Numerical Linear Algebra using LAPACK
Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.BandedHermitian

Synopsis

Documentation

type BandedHermitian offDiag sh = Hermitian offDiag sh Source #

data Transposition Source #

Constructors

NonTransposed 
Transposed 

Instances

Instances details
Bounded Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

Enum Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

Eq Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

Show Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

Semigroup Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

Monoid Transposition Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Modifier

size :: BandedHermitian offDiag sh a -> sh Source #

fromList :: (Natural offDiag, C size, Storable a) => UnaryProxy offDiag -> Order -> size -> [a] -> BandedHermitian offDiag size a Source #

identity :: (C sh, Floating a) => sh -> Diagonal sh a Source #

diagonal :: (C sh, Floating a) => Vector sh (RealOf a) -> Diagonal sh 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, Floating a) => Transposition -> BandedHermitian offDiag height a -> Full vert horiz height width a -> Full vert horiz height width a Source #

gramian :: (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 #

The list represents ragged rows of a sparse matrix.

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.