module Numeric.LinearAlgebra.Util(
size, disp,
zeros, ones,
diagl,
row,
col,
(&),(!), (¦), (#),
(?),(¿),
rand, randn,
cross,
norm,
unitary,
mt,
pairwiseD2,
rowOuters,
null1,
null1sym,
corr, conv, corrMin,
corr2, conv2, separable,
vec,
vech,
dup,
vtrans
) where
import Numeric.Container
import Numeric.LinearAlgebra.Algorithms hiding (i)
import Numeric.Matrix()
import Numeric.Vector()
import System.Random(randomIO)
import Numeric.LinearAlgebra.Util.Convolution
disp :: Int -> Matrix Double -> IO ()
disp n = putStrLn . dispf n
randm :: RandDist
-> Int
-> Int
-> IO (Matrix Double)
randm d r c = do
seed <- randomIO
return (reshape c $ randomVector seed d (r*c))
rand :: Int -> Int -> IO (Matrix Double)
rand = randm Uniform
randn :: Int -> Int -> IO (Matrix Double)
randn = randm Gaussian
diagl :: [Double] -> Matrix Double
diagl = diag . fromList
zeros :: Int
-> Int
-> Matrix Double
zeros r c = konst 0 (r,c)
ones :: Int
-> Int
-> Matrix Double
ones r c = konst 1 (r,c)
infixl 3 &
(&) :: Vector Double -> Vector Double -> Vector Double
a & b = Numeric.Container.join [a,b]
infixl 3 !
(!) :: Matrix Double -> Matrix Double -> Matrix Double
a ! b = fromBlocks [[a,b]]
infixl 3 ¦
(¦) :: Matrix Double -> Matrix Double -> Matrix Double
a ¦ b = fromBlocks [[a,b]]
(#) :: Matrix Double -> Matrix Double -> Matrix Double
infixl 2 #
a # b = fromBlocks [[a],[b]]
row :: [Double] -> Matrix Double
row = asRow . fromList
col :: [Double] -> Matrix Double
col = asColumn . fromList
infixl 9 ?
(?) :: Element t => Matrix t -> [Int] -> Matrix t
(?) = flip extractRows
infixl 9 ¿
(¿) :: Element t => Matrix t -> [Int] -> Matrix t
m ¿ ks = trans . extractRows ks . trans $ m
cross :: Vector Double -> Vector Double -> Vector Double
cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3]
| otherwise = error $ "cross ("++show x++") ("++show y++")"
where
[x1,x2,x3] = toList x
[y1,y2,y3] = toList y
z1 = x2*y3x3*y2
z2 = x3*y1x1*y3
z3 = x1*y2x2*y1
norm :: Vector Double -> Double
norm = pnorm PNorm2
unitary :: Vector Double -> Vector Double
unitary v = v / scalar (norm v)
size :: Matrix t -> (Int, Int)
size m = (rows m, cols m)
mt :: Matrix Double -> Matrix Double
mt = trans . inv
pairwiseD2 :: Matrix Double -> Matrix Double -> Matrix Double
pairwiseD2 x y | ok = x2 `outer` oy + ox `outer` y2 2* x <> trans y
| otherwise = error $ "pairwiseD2 with different number of columns: "
++ show (size x) ++ ", " ++ show (size y)
where
ox = one (rows x)
oy = one (rows y)
oc = one (cols x)
one k = constant 1 k
x2 = x * x <> oc
y2 = y * y <> oc
ok = cols x == cols y
rowOuters :: Matrix Double -> Matrix Double -> Matrix Double
rowOuters a b = a' * b'
where
a' = kronecker a (ones 1 (cols b))
b' = kronecker (ones 1 (cols a)) b
null1 :: Matrix Double -> Vector Double
null1 = last . toColumns . snd . rightSV
null1sym :: Matrix Double -> Vector Double
null1sym = last . toColumns . snd . eigSH'
vec :: Element t => Matrix t -> Vector t
vec = flatten . trans
vech :: Element t => Matrix t -> Vector t
vech m = Numeric.Container.join . zipWith f [0..] . toColumns $ m
where
f k v = subVector k (dim v k) v
dup :: (Num t, Num (Vector t), Element t) => Int -> Matrix t
dup k = trans $ fromRows $ map f es
where
rs = zip [0..] (toRows (ident (k^(2::Int))))
es = [(i,j) | j <- [0..k1], i <- [0..k1], i>=j ]
f (i,j) | i == j = g (k*j + i)
| otherwise = g (k*j + i) + g (k*i + j)
g j = v
where
Just v = lookup j rs
vtrans :: Element t => Int -> Matrix t -> Matrix t
vtrans p m | r == 0 = fromBlocks . map (map asColumn . takesV (replicate q p)) . toColumns $ m
| otherwise = error $ "vtrans " ++ show p ++ " of matrix with " ++ show (rows m) ++ " rows"
where
(q,r) = divMod (rows m) p