Copyright | (c) Nils Alex 2020 |
---|---|
License | MIT |
Maintainer | nils.alex@fau.de |
Safe Haskell | None |
Language | Haskell2010 |
Linear algebra for tensor equations.
Synopsis
- newtype Lin a = Lin (IntMap a)
- data Poly a
- = Const !a
- | Affine !a !(Lin a)
- | NotSupported
- singletonPoly :: a -> Int -> a -> Poly a
- polyMap :: (a -> b) -> Poly a -> Poly b
- getVars :: Poly a -> [Int]
- shiftVars :: Int -> Poly a -> Poly a
- normalize :: Fractional a => Poly a -> Poly a
- type Equation a = IntMap a
- tensorToEquations :: Integral a => T (Poly Rational) -> [Equation a]
- tensorsToSparseMat :: Integral a => [T (Poly Rational)] -> [((Int, Int), a)]
- tensorsToMat :: Integral a => [T (Poly Rational)] -> [[a]]
- systemRank :: [T (Poly Rational)] -> Int
- type Solution = IntMap (Poly Rational)
- solveTensor :: Solution -> T (Poly Rational) -> T (Poly Rational)
- solveSystem :: [T (Poly Rational)] -> [T (Poly Rational)] -> [T (Poly Rational)]
- redefineIndets :: [T (Poly v)] -> [T (Poly v)]
- equationFromRational :: forall a. Integral a => Poly Rational -> Equation a
- equationsToSparseMat :: [Equation a] -> [((Int, Int), a)]
- equationsToMat :: Integral a => [Equation a] -> [[a]]
- fromRref :: Matrix Z -> Solution
- fromRow :: forall a. Integral a => [a] -> Maybe (Int, Poly Rational)
- applySolution :: Solution -> Poly Rational -> Poly Rational
Linear combinations and polynomials
Data types
Linear combination represented as mapping from variable number to prefactor.
Polynomial: Can be constant, affine, or something of higher rank which is not yet implemented.
Const !a | constant value |
Affine !a !(Lin a) | constant value plus linear term |
NotSupported | higher rank |
Construction, inspection, modification
Produces an affine value \(c + a\cdot x_i\)
shiftVars :: Int -> Poly a -> Poly a Source #
Shifts variable numbers in the polynomial by a constant value.
normalize :: Fractional a => Poly a -> Poly a Source #
Normalizes a polynomial: \[ \mathrm{normalize}(c) = 1 \\ \mathrm{normalize}(c + a_1\cdot x_1 + a_2\cdot x_2 + \dots + a_n\cdot x_n) = \frac{c}{a_1} + 1\cdot x_1 + \frac{a_2}{a_1}\cdot x_2 + \dots + \frac{a_n}{a_1}\cdot x_n \]
Tensor equations
Extracting tensor equations and matrix representations
type Equation a = IntMap a Source #
A linear equation is a mapping from variable indices to coefficients
tensorToEquations :: Integral a => T (Poly Rational) -> [Equation a] Source #
Extract linear equations from tensor components. The equations are normalized, sorted, and made unique.
tensorsToSparseMat :: Integral a => [T (Poly Rational)] -> [((Int, Int), a)] Source #
Extract sparse matrix representation for the linear system given by a list of existentially quantified tensors with polynomial values.
tensorsToMat :: Integral a => [T (Poly Rational)] -> [[a]] Source #
Extract dense matrix representation for the linear system given by a list of existentially quantified tensors with polynomial values.
Rank of a linear tensor equation system
systemRank :: [T (Poly Rational)] -> Int Source #
Rank of the linear system given by a list of existentially quantified tensors with polynomial values.
Solutions
solveTensor :: Solution -> T (Poly Rational) -> T (Poly Rational) Source #
Apply substitution rules to all components of a tensor.
:: [T (Poly Rational)] | Tensorial linear system |
-> [T (Poly Rational)] | List of indeterminant tensors |
-> [T (Poly Rational)] | Solved indeterminant tensors |
Solve a linear system and apply solution to the tensorial indeterminants.
redefineIndets :: [T (Poly v)] -> [T (Poly v)] Source #
Relabelling of the indeterminants present in a list of tensors.
Redefines the labels of n
indeterminants as [1..n]
, preserving
the previous order.
Internals
equationFromRational :: forall a. Integral a => Poly Rational -> Equation a Source #
Extract linear equation with integral coefficients from polynomial
tensor component with rational coefficients.
Made made integral by multiplying with the lcm
of all denominators.
equationsToSparseMat :: [Equation a] -> [((Int, Int), a)] Source #
Convert list of equations to sparse matrix representation of the linear system.
equationsToMat :: Integral a => [Equation a] -> [[a]] Source #
Convert list of equations to dense matrix representation of the linear system.
fromRref :: Matrix Z -> Solution Source #
Read substitution rules from reduced row echelon form of a linear system.