lapack-0.5.0.3: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Symmetric

Synopsis

Documentation

type Symmetric sh = SymmetricP Packed sh Source #

takeUpper :: Symmetric sh a -> Upper sh a Source #

fromUpper :: Upper sh a -> Symmetric sh a Source #

pack :: (Packing pack, C sh, Floating a) => SymmetricP pack sh a -> Symmetric sh a Source #

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

size :: SymmetricP pack sh a -> sh Source #

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

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

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

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

forceOrder :: (Packing pack, C sh, Floating a) => Order -> SymmetricP pack sh a -> SymmetricP pack sh a Source #

transpose :: SymmetricP pack sh a -> SymmetricP pack sh a Source #

adjoint :: (Packing pack, C sh, Floating a) => SymmetricP pack sh a -> SymmetricP pack sh a Source #

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

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

split :: (Packing pack, C sh0, Eq sh0, C sh1, Eq sh1, Floating a) => SymmetricP pack (sh0 ::+ sh1) a -> (SymmetricP pack sh0 a, General sh0 sh1 a, SymmetricP pack sh1 a) Source #

takeTopLeft :: (Packing pack, C sh0, C sh1, Floating a) => SymmetricP pack (sh0 ::+ sh1) a -> SymmetricP pack sh0 a Source #

takeTopRight :: (Packing pack, C sh0, C sh1, Floating a) => SymmetricP pack (sh0 ::+ sh1) a -> General sh0 sh1 a Source #

takeBottomRight :: (Packing pack, C sh0, C sh1, Floating a) => SymmetricP pack (sh0 ::+ sh1) a -> SymmetricP pack sh1 a Source #

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

fromHermitian :: (Packing pack, C neg, C zero, C pos, C sh, Real a) => FlexHermitianP pack neg zero pos sh a -> SymmetricP pack sh a Source #

multiplyVector :: Packing pack => (C sh, Eq sh, Floating a) => SymmetricP pack sh a -> Vector sh a -> Vector sh a Source #

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

square :: (Packing pack, C sh, Floating a) => SymmetricP pack sh a -> SymmetricP pack sh a Source #

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

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

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

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

gramian A = A^T * A

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

gramianTransposed A = A * A^T = gramian (A^T)

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

congruenceDiagonal D A = A^T * D * A

congruenceDiagonalTransposed :: Packing pack => (C height, C width, Eq width, Floating a) => General height width a -> Vector width a -> SymmetricP pack height a Source #

congruenceDiagonalTransposed A D = A * D * A^T

congruence :: Packing pack => (C height, Eq height, C width, Floating a) => SymmetricP pack height a -> General height width a -> SymmetricP pack width a Source #

congruence B A = A^T * B * A

congruenceTransposed :: Packing pack => (C height, C width, Eq width, Floating a) => General height width a -> SymmetricP pack width a -> SymmetricP pack height a Source #

congruenceTransposed B A = A * B * A^T

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 -> SymmetricP pack width a Source #

anticommutator A B = A^T * B + B^T * A

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

anticommutatorTransposed :: (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 -> SymmetricP pack height a Source #

anticommutatorTransposed A B = A * B^T + B * A^T = anticommutator (transpose A) (transpose B)

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

addTransposed A = A^T + A

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

inverse :: (Packing pack, C sh, Floating a) => SymmetricP pack sh a -> SymmetricP pack sh a Source #

determinant :: (Packing pack, C sh, Floating a) => SymmetricP pack sh a -> a Source #