module Numeric.LinearAlgebra.Util(
vector, matrix,
disp,
formatSparse,
approxInt,
dispDots,
dispBlanks,
formatShort,
dispShort,
zeros, ones,
diagl,
row,
col,
(&), (¦), (|||), (——), (===), (#),
(?), (¿),
Indexable(..), size,
Numeric,
rand, randn,
cross,
norm,
ℕ,ℤ,ℝ,ℂ,iC,
Normed(..), norm_Frob, norm_nuclear,
unitary,
mt,
(~!~),
pairwiseD2,
rowOuters,
null1,
null1sym,
corr, conv, corrMin,
corr2, conv2, separable,
vec,
vech,
dup,
vtrans
) where
import Data.Packed.Numeric
import Numeric.LinearAlgebra.Algorithms hiding (i,Normed)
import Numeric.Matrix()
import Numeric.Vector()
import Numeric.LinearAlgebra.Random
import Numeric.LinearAlgebra.Util.Convolution
import Control.Monad(when)
import Text.Printf
import Data.List.Split(splitOn)
import Data.List(intercalate)
type ℝ = Double
type ℕ = Int
type ℤ = Int
type ℂ = Complex Double
iC :: ℂ
iC = 0:+1
vector :: [ℝ] -> Vector ℝ
vector = fromList
matrix
:: Int
-> [ℝ]
-> Matrix ℝ
matrix c = reshape c . fromList
disp :: Int -> Matrix Double -> IO ()
disp n = putStr . dispf n
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 = vjoin [a,b]
infixl 3 |||
(|||) :: Matrix Double -> Matrix Double -> Matrix Double
a ||| b = fromBlocks [[a,b]]
infixl 3 ¦
(¦) :: Matrix Double -> Matrix Double -> Matrix Double
(¦) = (|||)
(===) :: Matrix Double -> Matrix Double -> Matrix Double
infixl 2 ===
a === b = fromBlocks [[a],[b]]
(——) :: Matrix Double -> Matrix Double -> Matrix Double
infixl 2 ——
(——) = (===)
(#) :: 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
(¿)= flip extractColumns
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
class Normed a
where
norm_0 :: a -> ℝ
norm_1 :: a -> ℝ
norm_2 :: a -> ℝ
norm_Inf :: a -> ℝ
instance Normed (Vector ℝ)
where
norm_0 v = sumElements (step (abs v scalar (eps*normInf v)))
norm_1 = pnorm PNorm1
norm_2 = pnorm PNorm2
norm_Inf = pnorm Infinity
instance Normed (Vector ℂ)
where
norm_0 v = sumElements (step (fst (fromComplex (abs v)) scalar (eps*normInf v)))
norm_1 = pnorm PNorm1
norm_2 = pnorm PNorm2
norm_Inf = pnorm Infinity
instance Normed (Matrix ℝ)
where
norm_0 = norm_0 . flatten
norm_1 = pnorm PNorm1
norm_2 = pnorm PNorm2
norm_Inf = pnorm Infinity
instance Normed (Matrix ℂ)
where
norm_0 = norm_0 . flatten
norm_1 = pnorm PNorm1
norm_2 = pnorm PNorm2
norm_Inf = pnorm Infinity
norm_Frob :: (Normed (Vector t), Element t) => Matrix t -> ℝ
norm_Frob = norm_2 . flatten
norm_nuclear :: Field t => Matrix t -> ℝ
norm_nuclear = sumElements . singularValues
unitary :: Vector Double -> Vector Double
unitary v = v / scalar (norm v)
mt :: Matrix Double -> Matrix Double
mt = trans . inv
size :: Container c t => c t -> IndexOf c
size = size'
class Indexable c t | c -> t , t -> c
where
infixl 9 !
(!) :: c -> Int -> t
instance Indexable (Vector Double) Double
where
(!) = (@>)
instance Indexable (Vector Float) Float
where
(!) = (@>)
instance Indexable (Vector (Complex Double)) (Complex Double)
where
(!) = (@>)
instance Indexable (Vector (Complex Float)) (Complex Float)
where
(!) = (@>)
instance Element t => Indexable (Matrix t) (Vector t)
where
m!j = subVector (j*c) c (flatten m)
where
c = cols m
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 = konst 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 = vjoin . 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
infixl 0 ~!~
c ~!~ msg = when c (error msg)
formatSparse :: String -> String -> String -> Int -> Matrix Double -> String
formatSparse zeroI _zeroF sep _ (approxInt -> Just m) = format sep f m
where
f 0 = zeroI
f x = printf "%.0f" x
formatSparse zeroI zeroF sep n m = format sep f m
where
f x | abs (x::Double) < 2*peps = zeroI++zeroF
| abs (fromIntegral (round x::Int) x) / abs x < 2*peps
= printf ("%.0f."++replicate n ' ') x
| otherwise = printf ("%."++show n++"f") x
approxInt m
| norm_Inf (v vi) < 2*peps * norm_Inf v = Just (reshape (cols m) vi)
| otherwise = Nothing
where
v = flatten m
vi = roundVector v
dispDots n = putStr . formatSparse "." (replicate n ' ') " " n
dispBlanks n = putStr . formatSparse "" "" " " n
formatShort sep fmt maxr maxc m = auxm4
where
(rm,cm) = size m
(r1,r2,r3)
| rm <= maxr = (rm,0,0)
| otherwise = (maxr3,rmmaxr+1,2)
(c1,c2,c3)
| cm <= maxc = (cm,0,0)
| otherwise = (maxc3,cmmaxc+1,2)
[ [a,_,b]
,[_,_,_]
,[c,_,d]] = toBlocks [r1,r2,r3]
[c1,c2,c3] m
auxm = fromBlocks [[a,b],[c,d]]
auxm2
| cm > maxc = format "|" fmt auxm
| otherwise = format sep fmt auxm
auxm3
| cm > maxc = map (f . splitOn "|") (lines auxm2)
| otherwise = (lines auxm2)
f items = intercalate sep (take (maxc3) items) ++ " .. " ++
intercalate sep (drop (maxc3) items)
auxm4
| rm > maxr = unlines (take (maxr3) auxm3 ++ vsep : drop (maxr3) auxm3)
| otherwise = unlines auxm3
vsep = map g (head auxm3)
g '.' = ':'
g _ = ' '
dispShort :: Int -> Int -> Int -> Matrix Double -> IO ()
dispShort maxr maxc dec m =
printf "%dx%d\n%s" (rows m) (cols m) (formatShort " " fmt maxr maxc m)
where
fmt = printf ("%."++show dec ++"f")