lapack-0.2.3.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Hermitian

Synopsis

Documentation

fromList :: (C sh, Storable a) => Order -> sh -> [a] -> Hermitian sh a Source #

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

diagonal :: (C sh, Floating a) => Order -> Vector sh (RealOf a) -> Hermitian sh a Source #

takeDiagonal :: (C sh, Floating a) => Hermitian sh a -> Vector sh (RealOf a) Source #

forceOrder :: (C sh, Floating a) => Order -> Hermitian sh a -> Hermitian sh a Source #

stack :: (C sh0, Eq sh0, C sh1, Eq sh1, Floating a) => Hermitian sh0 a -> General sh0 sh1 a -> Hermitian sh1 a -> Hermitian (sh0 :+: sh1) a Source #

toSquare (stack a b c)

=

toSquare a ||| b
===
adjoint b ||| toSquare c

It holds order (stack a b c) = order b. The function is most efficient when the order of all blocks match.

multiplyVector :: (C sh, Eq sh, Floating a) => Transposition -> Hermitian sh a -> Vector sh a -> Vector sh a Source #

square :: (C sh, Eq sh, Floating a) => Hermitian sh a -> Hermitian sh a Source #

multiplyFull :: (C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Hermitian height a -> Full vert horiz height width a -> Full vert horiz height width a Source #

outer :: (C sh, Floating a) => Order -> Vector sh a -> Hermitian sh a Source #

sumRank1 :: (C sh, Eq sh, Floating a) => Order -> sh -> [(RealOf a, Vector sh a)] -> Hermitian sh a Source #

sumRank1NonEmpty :: (C sh, Eq sh, Floating a) => Order -> T [] (RealOf a, Vector sh a) -> Hermitian sh a Source #

sumRank2 :: (C sh, Eq sh, Floating a) => Order -> sh -> [(a, (Vector sh a, Vector sh a))] -> Hermitian sh a Source #

sumRank2NonEmpty :: (C sh, Eq sh, Floating a) => Order -> T [] (a, (Vector sh a, Vector sh a)) -> Hermitian sh a Source #

toSquare :: (C sh, Floating a) => Hermitian sh a -> Square sh a Source #

covariance :: (C height, C width, Eq width, Floating a) => General height width a -> Hermitian width a Source #

A^H * A

addAdjoint :: (C sh, Floating a) => Square sh a -> Hermitian sh a Source #

A^H + A

solve :: (C vert, C horiz, C sh, Eq sh, C nrhs, Floating a) => Hermitian sh a -> Full vert horiz sh nrhs a -> Full vert horiz sh nrhs a Source #

inverse :: (C sh, Floating a) => Hermitian sh a -> Hermitian sh a Source #

determinant :: (C sh, Floating a) => Hermitian sh a -> RealOf a Source #

eigenvalues :: (C sh, Floating a) => Hermitian sh a -> Vector sh (RealOf a) Source #

eigensystem :: (C sh, Floating a) => Hermitian sh a -> (Square sh a, Vector sh (RealOf a)) Source #

For symmetric eigenvalue problems, eigensystem and schur coincide.