Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Numeric.LAPACK.Matrix.Hermitian
Synopsis
- type FlexHermitian neg zero pos sh = FlexHermitianP Packed neg zero pos sh
- type Hermitian sh = HermitianP Packed sh
- type HermitianPosDef sh = HermitianPosDefP Packed sh
- type HermitianPosSemidef sh = HermitianPosSemidefP Packed sh
- data Transposition
- class (C neg, C pos) => Semidefinite neg pos
- assureFullRank :: (Semidefinite neg pos, C zero) => AnyHermitianP pack neg zero pos bands sh a -> AnyHermitianP pack neg False pos bands sh a
- assureAnyRank :: (Semidefinite neg pos, C zero) => AnyHermitianP pack neg True pos bands sh a -> AnyHermitianP pack neg zero pos bands sh a
- relaxSemidefinite :: (C neg, C zero, C pos) => AnyHermitianP pack neg False pos bands sh a -> AnyHermitianP pack neg zero pos bands sh a
- relaxIndefinite :: (C neg, C zero, C pos) => AnyHermitianP pack neg zero pos bands sh a -> Quadratic pack HermitianUnknownDefiniteness bands bands sh a
- assurePositiveDefiniteness :: (C neg, C zero, C pos) => AnyHermitianP pack neg zero pos bands sh a -> Quadratic pack HermitianPositiveDefinite bands bands sh a
- relaxDefiniteness :: (C neg, C zero, C pos) => Quadratic pack HermitianPositiveDefinite bands bands sh a -> AnyHermitianP pack neg zero pos bands sh a
- asUnknownDefiniteness :: Id (Quadratic pack HermitianUnknownDefiniteness bands bands sh a)
- 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
- size :: FlexHermitianP pack neg zero pos sh a -> sh
- fromList :: (C sh, Floating a) => Order -> sh -> [a] -> Hermitian sh a
- autoFromList :: Floating a => Order -> [a] -> Hermitian ShapeInt a
- identity :: (C sh, Floating a) => Order -> sh -> HermitianPosDef sh a
- diagonal :: (C sh, Floating a) => Order -> Vector sh (RealOf a) -> Hermitian sh a
- takeDiagonal :: (C neg, C zero, C pos, C sh, Floating a) => FlexHermitian neg zero pos sh a -> Vector sh (RealOf a)
- 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
- 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
- (*%%%#) :: (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
- 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)
- 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
- 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
- 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
- toSquare :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> Square sh a
- fromSymmetric :: (Packing pack, C sh, Real a) => SymmetricP pack sh a -> HermitianP pack sh a
- 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
- 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
- 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
- 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
- outer :: (Packing pack, C sh, Floating a) => Order -> Vector sh a -> HermitianPosSemidefP pack sh a
- sumRank1 :: (Packing pack, C sh, Eq sh, Floating a) => Order -> sh -> [(RealOf a, Vector sh a)] -> HermitianPosSemidefP pack sh a
- sumRank1NonEmpty :: (Packing pack, C sh, Eq sh, Floating a) => Order -> T [] (RealOf a, Vector sh a) -> HermitianPosSemidefP pack sh a
- sumRank2 :: (Packing pack, C sh, Eq sh, Floating a) => Order -> sh -> [(a, (Vector sh a, Vector sh a))] -> HermitianP pack sh a
- sumRank2NonEmpty :: (Packing pack, C sh, Eq sh, Floating a) => Order -> T [] (a, (Vector sh a, Vector sh a)) -> HermitianP pack sh a
- gramian :: Packing pack => (C height, C width, Floating a) => General height width a -> HermitianPosSemidefP pack width a
- gramianAdjoint :: Packing pack => (C height, C width, Floating a) => General height width a -> HermitianPosSemidefP pack height a
- congruenceDiagonal :: Packing pack => (C height, Eq height, C width, Floating a) => Vector height (RealOf a) -> General height width a -> HermitianP pack width a
- congruenceDiagonalAdjoint :: Packing pack => (C height, C width, Eq width, Floating a) => General height width a -> Vector width (RealOf a) -> HermitianP pack height a
- 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
- 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
- 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
- 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
- addAdjoint :: (Packing pack, C sh, Floating a) => Square sh a -> HermitianP pack sh 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
- 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
- determinant :: (Packing pack, C neg, C zero, C pos, C sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> RealOf a
- eigenvalues :: (Packing pack, C neg, C zero, C pos, Permutable sh, Floating a) => FlexHermitianP pack neg zero pos sh a -> Vector sh (RealOf a)
- 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))
Documentation
type FlexHermitian neg zero pos sh = FlexHermitianP Packed neg zero pos sh Source #
The definiteness tags mean:
neg == False
: There is nox
withx^T * A * x < 0
.zero == False
: There is nox
withx^T * A * x = 0
.pos == False
: There is nox
withx^T * A * x > 0
.
If a tag is True
then this imposes no further restriction on the matrix.
type HermitianPosDef sh = HermitianPosDefP Packed sh Source #
type HermitianPosSemidef sh = HermitianPosSemidefP Packed sh Source #
data Transposition #
Constructors
NonTransposed | |
Transposed |
Instances
class (C neg, C pos) => Semidefinite neg pos Source #
Instances
Semidefinite False True Source # | |
Defined in Numeric.LAPACK.Matrix.Array.Hermitian | |
Semidefinite True False Source # | |
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 #
asUnknownDefiniteness :: Id (Quadratic pack HermitianUnknownDefiniteness bands 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 #
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 #