Copyright | (c) Alberto Ruiz 2009 |
---|---|
License | BSD3 |
Maintainer | Alberto Ruiz |
Stability | experimental |
Safe Haskell | None |
Language | Haskell98 |
Common multidimensional array decompositions. See the paper by Kolda & Balder.
- 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 {}
- 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
:: (Int -> [Array Double]) | Initialization function for each rank |
-> ALSParam None Double | optimization parameters |
-> Array Double | input 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
:: [Array Double] | starting point |
-> ALSParam None Double | optimization parameters |
-> Array Double | input 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
:: Int | seed |
-> NArray i t | target array to decompose |
-> Int | rank |
-> [NArray None Double] | random starting point |
pseudorandom cp initialization from a given seed
:: [NArray None Double] | hosvd decomposition of the target array |
-> Int | rank |
-> [NArray None Double] | starting point |
cp initialization based on the hosvd
Utilities
optimization parameters for alternating least squares
ALSParam | |
|
defaultParameters :: ALSParam i t Source #
nMax = 20, epsilon = 1E-3, delta = 1, post = id, postk = const id, presys = id