lapack-0.5.1.1: Numerical Linear Algebra using LAPACK
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.LAPACK.Matrix.Hermitian

Synopsis

Documentation

type FlexHermitian neg zero pos sh = FlexHermitianP Packed neg zero pos sh Source #

The definiteness tags mean:

  • neg == False: There is no x with x^T * A * x < 0.
  • zero == False: There is no x with x^T * A * x = 0.
  • pos == False: There is no x with x^T * A * x > 0.

If a tag is True then this imposes no further restriction on the matrix.

type Hermitian sh = HermitianP Packed sh Source #

type HermitianPosDef sh = HermitianPosDefP Packed sh Source #

type HermitianPosSemidef sh = HermitianPosSemidefP Packed sh Source #

data Transposition #

Constructors

NonTransposed 
Transposed 

Instances

Instances details
Monoid Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Semigroup Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Bounded Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Enum Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Show Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Eq Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

class (C neg, C pos) => Semidefinite neg pos Source #

Instances

Instances details
Semidefinite False True Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Hermitian

Semidefinite True False Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Hermitian

assureFullRank :: (Semidefinite neg pos, C zero) => AnyHermitianP pack neg zero pos bands sh a -> AnyHermitianP pack neg False pos bands sh a Source #

assureAnyRank :: (Semidefinite neg pos, C zero) => AnyHermitianP pack neg True pos bands sh a -> AnyHermitianP pack neg zero pos bands sh a Source #

relaxSemidefinite :: (C neg, C zero, C pos) => AnyHermitianP pack neg False pos bands sh a -> AnyHermitianP pack neg zero pos bands sh a Source #

relaxIndefinite :: (C neg, C zero, C pos) => AnyHermitianP pack neg zero pos bands sh a -> Quadratic pack HermitianUnknownDefiniteness bands bands sh a Source #

assurePositiveDefiniteness :: (C neg, C zero, C pos) => AnyHermitianP pack neg zero pos bands sh a -> Quadratic pack HermitianPositiveDefinite bands bands sh a Source #

relaxDefiniteness :: (C neg, C zero, C pos) => Quadratic pack HermitianPositiveDefinite bands bands sh a -> AnyHermitianP pack neg zero pos bands sh a Source #

pack :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> FlexHermitian neg zero pos sh a Source #

size :: FlexHermitianP pack neg zero pos sh a -> sh Source #

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

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

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

takeDiagonal :: (C neg, C zero, C pos, C sh, Floating a) => FlexHermitian neg zero pos sh a -> Vector sh (RealOf a) Source #

forceOrder :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => Order -> FlexHermitianP pack neg zero pos sh a -> FlexHermitianP pack neg zero pos sh a Source #

stack :: (Packing pack, C sh0, Eq sh0, C sh1, Eq sh1, Floating a) => HermitianP pack sh0 a -> General sh0 sh1 a -> HermitianP pack sh1 a -> HermitianP pack (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.

(*%%%#) :: (Packing pack, C sh0, Eq sh0, C sh1, Eq sh1, Floating a) => (HermitianP pack sh0 a, General sh0 sh1 a) -> HermitianP pack sh1 a -> HermitianP pack (sh0 ::+ sh1) a infixr 2 Source #

split :: (Packing pack, C neg, C zero, C pos, C sh0, C sh1, Floating a) => FlexHermitianP pack neg zero pos (sh0 ::+ sh1) a -> (FlexHermitianP pack neg zero pos sh0 a, General sh0 sh1 a, FlexHermitianP pack neg zero pos sh1 a) Source #

takeTopLeft :: (Packing pack, C neg, C zero, C pos, C sh0, C sh1, Floating a) => FlexHermitianP pack neg zero pos (sh0 ::+ sh1) a -> FlexHermitianP pack neg zero pos sh0 a Source #

Sub-matrices maintain definiteness of the original matrix. Consider x^* A x > 0. Then y^* (take A) y = x^* A x where some components of x are zero.

takeTopRight :: (Packing pack, C neg, C zero, C pos, C sh0, C sh1, Floating a) => FlexHermitianP pack neg zero pos (sh0 ::+ sh1) a -> General sh0 sh1 a Source #

takeBottomRight :: (Packing pack, C neg, C zero, C pos, C sh0, C sh1, Floating a) => FlexHermitianP pack neg zero pos (sh0 ::+ sh1) a -> FlexHermitianP pack neg zero pos sh1 a Source #

toSquare :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> Square sh a Source #

fromSymmetric :: (Packing pack, C sh, Real a) => SymmetricP pack sh a -> HermitianP pack sh a Source #

negate :: (C neg, C zero, C pos, C sh, Floating a) => AnyHermitianP pack neg zero pos bands sh a -> AnyHermitianP pack pos zero neg bands sh a Source #

multiplyVector :: Packing pack => (C neg, C zero, C pos, C sh, Eq sh, Floating a) => Transposition -> FlexHermitianP pack neg zero pos sh a -> Vector sh a -> Vector sh a Source #

multiplyFull :: Packing pack => (C neg, C zero, C pos, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> FlexHermitianP pack neg zero pos height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

square :: Packing pack => (C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> FlexHermitianP pack neg zero pos sh a Source #

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

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

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

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

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

gramian :: Packing pack => (C height, C width, Floating a) => General height width a -> HermitianPosSemidefP pack width a Source #

gramian A = A^H * A

gramianAdjoint :: Packing pack => (C height, C width, Floating a) => General height width a -> HermitianPosSemidefP pack height a Source #

gramianAdjoint A = A * A^H = gramian (A^H)

congruenceDiagonal :: Packing pack => (C height, Eq height, C width, Floating a) => Vector height (RealOf a) -> General height width a -> HermitianP pack width a Source #

congruenceDiagonal D A = A^H * D * A

congruenceDiagonalAdjoint :: Packing pack => (C height, C width, Eq width, Floating a) => General height width a -> Vector width (RealOf a) -> HermitianP pack height a Source #

congruenceDiagonalAdjoint A D = A * D * A^H

congruence :: Packing pack => (C neg, C pos, C height, Eq height, C width, Floating a) => FlexHermitianP pack neg True pos height a -> General height width a -> FlexHermitianP pack neg True pos width a Source #

congruence B A = A^H * B * A

congruenceAdjoint :: Packing pack => (C neg, C pos, C height, C width, Eq width, Floating a) => General height width a -> FlexHermitianP pack neg True pos width a -> FlexHermitianP pack neg True pos height a Source #

congruenceAdjoint B A = A * B * A^H

anticommutator :: Packing pack => (Measure meas, C vert, C horiz, C height, Eq height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Full meas vert horiz height width a -> HermitianP pack width a Source #

anticommutator A B = A^H * B + B^H * A

Not exactly a matrix anticommutator, thus I like to call it Hermitian anticommutator.

anticommutatorAdjoint :: Packing pack => (Measure meas, C vert, C horiz, C height, Eq height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Full meas vert horiz height width a -> HermitianP pack height a Source #

anticommutatorAdjoint A B = A * B^H + B * A^H = anticommutator (adjoint A) (adjoint B)

addAdjoint :: (Packing pack, C sh, Floating a) => Square sh a -> HermitianP pack sh a Source #

addAdjoint A = A^H + A

solve :: Packing pack => (C neg, C zero, C pos, Measure meas, C vert, C horiz, C sh, Eq sh, C nrhs, Floating a) => FlexHermitianP pack neg zero pos sh a -> Full meas vert horiz sh nrhs a -> Full meas vert horiz sh nrhs a Source #

inverse :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> FlexHermitianP pack neg zero pos sh a Source #

determinant :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> RealOf a Source #

eigenvalues :: (Packing pack, C neg, C zero, C pos, Permutable sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> Vector sh (RealOf a) Source #

eigensystem :: (Packing pack, C neg, C zero, C pos, Permutable sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> (Square sh a, Vector sh (RealOf a)) Source #

For symmetric eigenvalue problems, eigensystem and schur coincide.