safe-tensor-0.2.0.0: Dependently typed tensor algebra
Copyright(c) Nils Alex 2020
LicenseMIT
Maintainernils.alex@fau.de
Safe HaskellNone
LanguageHaskell2010

Math.Tensor.LinearAlgebra.Equations

Description

Linear tensor equations.

Synopsis

Documentation

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.

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.

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.

systemRank :: [T (Poly Rational)] -> Int Source #

Rank of the linear system given by a list of existentially quantified tensors with polynomial values.

type Solution = IntMap (Poly Rational) Source #

The solution to a linear system is represented as a list of substitution rules, stored as IntMap (Poly Rational).

fromRref :: Matrix Z -> Solution Source #

Read substitution rules from reduced row echelon form of a linear system.

fromRow :: forall a. Integral a => [a] -> Maybe (Int, Poly Rational) Source #

Read single substitution rule from single row of reduced row echelon form.

applySolution :: Solution -> Poly Rational -> Poly Rational Source #

Apply substitution rules to tensor component.

solveTensor :: Solution -> T (Poly Rational) -> T (Poly Rational) Source #

Apply substitution rules to all components of a tensor.

solveSystem Source #

Arguments

:: [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.