hTensor-0.6.0: Multidimensional arrays and simple tensor computations.Source codeContentsIndex
Numeric.LinearAlgebra.Array.Decomposition
Stabilityprovisional
MaintainerAlberto Ruiz <aruiz@um.es>
Contents
HOSVD
CP
Utilities
Description
Common multidimensional array decompositions. See the paper by Kolda & Balder.
Synopsis
hosvd :: Array Double -> [Array Double]
hosvd' :: Array Double -> ([Array Double], [(Int, Vector Double)])
truncateFactors :: [Int] -> [Array Double] -> [Array Double]
cpAuto :: (Int -> [Array Double]) -> ALSParam None Double -> Array Double -> [Array Double]
cpRun :: [Array Double] -> ALSParam None Double -> Array Double -> ([Array Double], [Double])
cpInitRandom :: Int -> NArray i t -> Int -> [NArray None Double]
cpInitSvd :: [NArray None Double] -> Int -> [NArray None 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
HOSVD
hosvd :: Array Double -> [Array Double]Source

Multilinear Singular Value Decomposition (or Tucker's method, see Lathauwer et al.).

The result is a list with the core (head) and rotations so that t == product (hsvd t).

The core and the rotations are truncated to the rank of each mode.

Use hosvd' to get full transformations and rank information about each mode.

hosvd' :: Array Double -> ([Array Double], [(Int, Vector Double)])Source

Full version of hosvd.

The first element in the result pair is a list with the core (head) and rotations so that t == product (fst (hsvd' t)).

The second element is a list of rank and singular values along each mode, to give some idea about core structure.

truncateFactors :: [Int] -> [Array Double] -> [Array Double]Source
Truncate a hosvd decomposition from the desired number of principal components in each dimension.
CP
cpAutoSource
:: Int -> [Array Double]Initialization function for each rank
-> ALSParam None Doubleoptimization parameters
-> Array Doubleinput array
-> [Array Double]factors

Experimental implementation of the CP decomposition, based on alternating least squares. We try approximations of increasing rank, until the relative reconstruction error is below a desired percent of Frobenius norm (epsilon).

The approximation of rank k is abandoned if the error does not decrease at least delta% in an iteration.

Practical usage can be based on something like this:

cp finit d e t = cpAuto (finit t) defaultParameters {delta = d, epsilon = e} t

cpS = cp (InitSvd . fst . hosvd')
cpR s = cp (cpInitRandom s)

So we can write

 -- initialization based on hosvd
y = cpS 0.01 1E-6 t

-- (pseudo)random initialization
z = cpR seed 0.1 0.1 t
cpRunSource
:: [Array Double]starting point
-> ALSParam None Doubleoptimization parameters
-> Array Doubleinput array
-> ([Array Double], [Double])factors and error history

Basic CP optimization for a given rank. The result includes the obtained sequence of errors.

For example, a rank 3 approximation can be obtained as follows, where initialization is based on the hosvd:

(y,errs) = cpRank 3 t
     where cpRank r t = cpRun (cpInitSvd (fst $ hosvd' t) r) defaultParameters t
cpInitRandomSource
:: Intseed
-> NArray i ttarget array to decompose
-> Intrank
-> [NArray None Double]random starting point
pseudorandom cp initialization from a given seed
cpInitSvdSource
:: [NArray None Double]hosvd decomposition of the target array
-> Intrank
-> [NArray None Double]starting point
cp initialization based on the hosvd
Utilities
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
Produced by Haddock version 2.6.1