module Numeric.LinearAlgebra.Array.Util (
Coord, Compat(..),
NArray, Idx(..), Name,
scalar,
order, names, size, sizes, typeOf, dims, coords,
renameExplicit, (!>), renameO, (!),
parts,
newIndex,
mapArray, zipArray, (|*|), smartProduct, outers,
extract, onIndex, mapTat,
reorder, (~>),
formatArray, formatFixed, formatScaled,
dummyAt, noIdx,
conformable,
sameStructure,
makeConformant,
basisOf,
atT, takeDiagT, diagT,
mkFun, mkAssoc, setType,
renameParts,
resetCoords,
asScalar, asVector, asMatrix, applyAsMatrix,
fibers, matrixator, matrixatorFree, analyzeProduct,
fromVector, fromMatrix, reshapeVector
) where
import Numeric.LinearAlgebra.Array.Internal
import Numeric.LinearAlgebra.Array.Display
import Numeric.LinearAlgebra.HMatrix(Matrix)
import Numeric.LinearAlgebra.Array.Simple
import Data.List(intersperse,sort,foldl1')
diagT :: [Double] -> Int -> Array Double
diagT v n = replicate n k `listArray` concat (intersperse z (map return v))
where k = length v
tot = k^n
nzeros = (tot k) `div` (k1)
z = replicate nzeros 0
(!>) :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t
infixl 9 !>
t !> s = renameExplicit (map f (words s)) t
where
f [a,b] = ([a],[b])
f _ = error "impossible pattern in hTensor (!>)"
renameO :: (Coord t, Compat i)
=> NArray i t
-> [Name]
-> NArray i t
renameO t ns = renameExplicit (zip od ns) t
where od = map iName (sort (dims t))
(!) :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t
infixl 9 !
t ! s = renameExplicit (zip od (map return s)) t
where od = map iName (sort (dims t))
infixl 8 ~>
(~>) :: (Coord t) => NArray i t -> String -> NArray i t
t ~> ns = reorder (map return ns) t
mapTat :: (Coord a, Coord b, Compat i)
=> (NArray i a -> NArray i b)
-> [Name]
-> NArray i a
-> NArray i b
mapTat f [] = f
mapTat f (a:as) = onIndex (map $ mapTat f as) a
outers :: (Coord a, Compat i) => [NArray i a] -> NArray i a
outers = foldl1' (zipArray (*))
mkFun :: [Int] -> ([Int] -> Double) -> Array Double
mkFun ds f = listArray ds $ map f (sequence $ map (enumFromTo 0 . subtract 1. fromIntegral) $ ds)
mkAssoc :: [Int] -> [([Int], Double)] -> Array Double
mkAssoc ds ps = mkFun ds f where
f = maybe 0 id . flip lookup ps
setType :: (Compat i, Coord t) => Name -> i -> NArray i t -> NArray i t
setType n t a = mapDims f a where
f i | iName i == n = i {iType = t}
| otherwise = i
renameParts :: (Compat i, Coord t)
=> Name
-> NArray i t
-> Name
-> String
-> [NArray i t]
renameParts p t x pre = zipWith renameExplicit [[(x,pre ++ show k)] | k<-[1::Int ..] ] (parts t p)
applyAsMatrix :: (Coord t, Compat i) => (Matrix t -> Matrix t) -> (NArray i t -> NArray i t)
applyAsMatrix f t = flip renameRaw nms . fromMatrix r c . f . asMatrix $ t
where [r,c] = map (flip typeOf t) nms
nms = sort . namesR $ t