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

Math.Tensor.LinearAlgebra

Description

Linear algebra for tensor equations.

Synopsis

Linear combinations and polynomials

Data types

newtype Lin a Source #

Linear combination represented as mapping from variable number to prefactor.

Constructors

Lin (IntMap a) 

Instances

Instances details
Eq a => Eq (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

(==) :: Lin a -> Lin a -> Bool #

(/=) :: Lin a -> Lin a -> Bool #

Ord a => Ord (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

compare :: Lin a -> Lin a -> Ordering #

(<) :: Lin a -> Lin a -> Bool #

(<=) :: Lin a -> Lin a -> Bool #

(>) :: Lin a -> Lin a -> Bool #

(>=) :: Lin a -> Lin a -> Bool #

max :: Lin a -> Lin a -> Lin a #

min :: Lin a -> Lin a -> Lin a #

Show a => Show (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

showsPrec :: Int -> Lin a -> ShowS #

show :: Lin a -> String #

showList :: [Lin a] -> ShowS #

Generic (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Associated Types

type Rep (Lin a) :: Type -> Type #

Methods

from :: Lin a -> Rep (Lin a) x #

to :: Rep (Lin a) x -> Lin a #

NFData a => NFData (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

rnf :: Lin a -> () #

type Rep (Lin a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

type Rep (Lin a) = D1 ('MetaData "Lin" "Math.Tensor.LinearAlgebra.Scalar" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'True) (C1 ('MetaCons "Lin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap a))))

data Poly a Source #

Polynomial: Can be constant, affine, or something of higher rank which is not yet implemented.

Constructors

Const !a

constant value

Affine !a !(Lin a)

constant value plus linear term

NotSupported

higher rank

Instances

Instances details
Eq a => Eq (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

(==) :: Poly a -> Poly a -> Bool #

(/=) :: Poly a -> Poly a -> Bool #

(Num a, Eq a) => Num (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

(+) :: Poly a -> Poly a -> Poly a #

(-) :: Poly a -> Poly a -> Poly a #

(*) :: Poly a -> Poly a -> Poly a #

negate :: Poly a -> Poly a #

abs :: Poly a -> Poly a #

signum :: Poly a -> Poly a #

fromInteger :: Integer -> Poly a #

Ord a => Ord (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

compare :: Poly a -> Poly a -> Ordering #

(<) :: Poly a -> Poly a -> Bool #

(<=) :: Poly a -> Poly a -> Bool #

(>) :: Poly a -> Poly a -> Bool #

(>=) :: Poly a -> Poly a -> Bool #

max :: Poly a -> Poly a -> Poly a #

min :: Poly a -> Poly a -> Poly a #

Show a => Show (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

showsPrec :: Int -> Poly a -> ShowS #

show :: Poly a -> String #

showList :: [Poly a] -> ShowS #

Generic (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Associated Types

type Rep (Poly a) :: Type -> Type #

Methods

from :: Poly a -> Rep (Poly a) x #

to :: Rep (Poly a) x -> Poly a #

NFData a => NFData (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

Methods

rnf :: Poly a -> () #

type Rep (Poly a) Source # 
Instance details

Defined in Math.Tensor.LinearAlgebra.Scalar

type Rep (Poly a) = D1 ('MetaData "Poly" "Math.Tensor.LinearAlgebra.Scalar" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'False) (C1 ('MetaCons "Const" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: (C1 ('MetaCons "Affine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Lin a))) :+: C1 ('MetaCons "NotSupported" 'PrefixI 'False) (U1 :: Type -> Type)))

Construction, inspection, modification

singletonPoly Source #

Arguments

:: a

constant

-> Int

variable number

-> a

prefactor

-> Poly a 

Produces an affine value \(c + a\cdot x_i\)

polyMap :: (a -> b) -> Poly a -> Poly b Source #

Maps over Poly

getVars :: Poly a -> [Int] Source #

Returns list of variable numbers present in the polynomial.

shiftVars :: Int -> Poly a -> Poly a Source #

Shifts variable numbers in the polynomial by a constant value.

normalize :: (Fractional a, Eq 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

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).

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.

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.

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.