hTensor-0.6.0: Multidimensional arrays and simple tensor computations.Source codeContentsIndex
Numeric.LinearAlgebra.Array.Solve
Stabilityprovisional
MaintainerAlberto Ruiz <aruiz@um.es>
Contents
Linear systems
Multilinear systems
General
Factorized
Utilities
Description
Solution of general multidimensional linear and multilinear systems.
Synopsis
solve :: (Compat i, Coord t) => NArray i t -> NArray i t -> NArray i t
solveHomog :: (Compat i, Coord t) => NArray i t -> [Name] -> Either Double Int -> [NArray i t]
solveHomog1 :: (Compat i, Coord t) => NArray i t -> [Name] -> NArray i t
solveH :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t
solveP :: Tensor Double -> Tensor Double -> Name -> Tensor Double
data ALSParam i t = ALSParam {
nMax :: Int
delta :: Double
epsilon :: Double
post :: [NArray i t] -> [NArray i t]
postk :: Int -> NArray i t -> NArray i t
presys :: Matrix t -> Matrix t
}
defaultParameters :: ALSParam i t
mlSolve :: (Compat i, Coord t, Num (NArray i t), Normed (Vector t)) => ALSParam i t -> [NArray i t] -> [NArray i t] -> NArray i t -> ([NArray i t], [Double])
mlSolveH :: (Compat i, Coord t, Num (NArray i t), Normed (Vector t)) => ALSParam i t -> [NArray i t] -> [NArray i t] -> ([NArray i t], [Double])
mlSolveP :: ALSParam Variant Double -> [Tensor Double] -> [Tensor Double] -> Tensor Double -> Name -> ([Tensor Double], [Double])
solveFactors :: (Coord t, Random t, Compat i, Num (NArray i t), Normed (Vector t)) => Int -> ALSParam i t -> [NArray i t] -> String -> NArray i t -> ([NArray i t], [Double])
solveFactorsH :: (Coord t, Random t, Compat i, Num (NArray i t), Normed (Vector t)) => Int -> ALSParam i t -> [NArray i t] -> String -> ([NArray i t], [Double])
eps :: Double
eqnorm :: (Coord t, Coord (Complex t), Compat i, Num (NArray i t), Normed (Vector t)) => [NArray i t] -> [NArray i t]
infoRank :: Field t => Matrix t -> Matrix t
solve' :: (Coord t, Compat i, Coord t1) => (Matrix t1 -> Matrix t) -> NArray i t1 -> NArray i t -> NArray i t
solveHomog' :: (Coord t1, Compat i, Coord t) => (Matrix t -> Matrix t1) -> NArray i t -> [Name] -> Either Double Int -> [NArray i t1]
solveHomog1' :: (Coord t1, Compat i, Coord t) => (Matrix t -> Matrix t1) -> NArray i t -> [Name] -> NArray i t1
solveP' :: Coord b => (Matrix Double -> Matrix b) -> NArray Variant Double -> NArray Variant Double -> Name -> NArray Variant b
Linear systems
solveSource
:: (Compat i, Coord t)
=> NArray i tcoefficients (a)
-> NArray i ttarget (b)
-> NArray i tresult (x)
Solution of the linear system a x = b, where a and b are general multidimensional arrays. The structure and dimension names of the result are inferred from the arguments.
solveHomogSource
:: (Compat i, Coord t)
=> NArray i tcoefficients (a)
-> [Name]desired dimensions for the result (a subset selected from the target).
-> Either Double IntLeft "numeric zero" (e.g. eps), Right "theoretical" rank
-> [NArray i t]basis for the solutions (x)

Solution of the homogeneous linear system a x = 0, where a is a general multidimensional array.

If the system is overconstrained we may provide the theoretical rank to get a MSE solution.

solveHomog1 :: (Compat i, Coord t) => NArray i t -> [Name] -> NArray i tSource
A simpler way to use solveHomog, which returns just one solution. If the system is overconstrained it returns the MSE solution.
solveH :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i tSource
solveHomog1 for single letter index names.
solvePSource
:: Tensor Doublecoefficients (a)
-> Tensor Doubledesired result (b)
-> Namethe homogeneous dimension
-> Tensor Doubleresult (x)
Solution of the linear system a x = b, where a and b are general multidimensional arrays, with homogeneous equality along a given index.
Multilinear systems
General
data ALSParam i t Source
optimization parameters for alternating least squares
Constructors
ALSParam
nMax :: Intmaximum number of iterations
delta :: Doubleminimum relative improvement in the optimization (percent, e.g. 0.1)
epsilon :: Doublemaximum relative error. For nonhomogeneous problems it is the reconstruction error in percent (e.g. 1E-3), and for homogeneous problems is the frobenius norm of the expected zero structure in the right hand side.
post :: [NArray i t] -> [NArray i t]post-processing function after each full iteration (e.g. id)
postk :: Int -> NArray i t -> NArray i tpost-processing function for the k-th argument (e.g. const id)
presys :: Matrix t -> Matrix tpreprocessing function for the linear systems (eg. id, or infoRank)
defaultParameters :: ALSParam i tSource
nMax = 20, epsilon = 1E-3, delta = 1, post = id, postk = const id, presys = id
mlSolveSource
:: (Compat i, Coord t, Num (NArray i t), Normed (Vector t))
=> ALSParam i toptimization parameters
-> [NArray i t]coefficients (a), given as a list of factors.
-> [NArray i t]initial solution [x,y,z...]
-> NArray i ttarget (b)
-> ([NArray i t], [Double])Solution and error history
Solution of a multilinear system a x y z ... = b based on alternating least squares.
mlSolveHSource
:: (Compat i, Coord t, Num (NArray i t), Normed (Vector t))
=> ALSParam i toptimization parameters
-> [NArray i t]coefficients (a), given as a list of factors.
-> [NArray i t]initial solution [x,y,z...]
-> ([NArray i t], [Double])Solution and error history
Solution of the homogeneous multilinear system a x y z ... = 0 based on alternating least squares.
mlSolvePSource
:: ALSParam Variant Doubleoptimization parameters
-> [Tensor Double]coefficients (a), given as a list of factors.
-> [Tensor Double]initial solution [x,y,z...]
-> Tensor Doubletarget (b)
-> Namehomogeneous index
-> ([Tensor Double], [Double])Solution and error history
Solution of a multilinear system a x y z ... = b, with a homogeneous index, based on alternating least squares.
Factorized
solveFactorsSource
:: (Coord t, Random t, Compat i, Num (NArray i t), Normed (Vector t))
=> Intseed for random initialization
-> ALSParam i toptimization parameters
-> [NArray i t]source (also factorized)
-> Stringindex pairs for the factors separated by spaces
-> NArray i ttarget
-> ([NArray i t], [Double])solution and error history
Given two arrays a (source) and b (target), we try to compute linear transformations x,y,z,... for each dimension, such that product [a,x,y,z,...] == b. (We can use eqnorm for post processing, or id.)
solveFactorsHSource
:: (Coord t, Random t, Compat i, Num (NArray i t), Normed (Vector t))
=> Intseed for random initialization
-> ALSParam i toptimization parameters
-> [NArray i t]coefficient array (a), (also factorized)
-> Stringindex pairs for the factors separated by spaces
-> ([NArray i t], [Double])solution and error history
Homogeneous factorized system. Given an array a, given as a list of factors as, and a list of pairs of indices ["pi","qj", "rk", etc.], we try to compute linear transformations x!"pi", y!"pi", z!"rk", etc. such that product [a,x,y,z,...] == 0.
Utilities
eps :: DoubleSource
The machine precision of a Double: eps = 2.22044604925031e-16 (the value used by GNU-Octave).
eqnorm :: (Coord t, Coord (Complex t), Compat i, Num (NArray i t), Normed (Vector t)) => [NArray i t] -> [NArray i t]Source
post processing function that modifies a list of tensors so that they have equal frobenius norm
infoRank :: Field t => Matrix t -> Matrix tSource
debugging function (e.g. for presys), which shows rows, columns and rank of the coefficient matrix of a linear system.
solve' :: (Coord t, Compat i, Coord t1) => (Matrix t1 -> Matrix t) -> NArray i t1 -> NArray i t -> NArray i tSource
solveHomog' :: (Coord t1, Compat i, Coord t) => (Matrix t -> Matrix t1) -> NArray i t -> [Name] -> Either Double Int -> [NArray i t1]Source
solveHomog1' :: (Coord t1, Compat i, Coord t) => (Matrix t -> Matrix t1) -> NArray i t -> [Name] -> NArray i t1Source
solveP' :: Coord b => (Matrix Double -> Matrix b) -> NArray Variant Double -> NArray Variant Double -> Name -> NArray Variant bSource
Produced by Haddock version 2.6.1