summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/LinearAlgebra/Util.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra/Util.hs')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util.hs58
1 files changed, 8 insertions, 50 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs
index 043aa21..370ca27 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Util.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs
@@ -16,7 +16,6 @@ Stability : provisional
16 16
17-} 17-}
18----------------------------------------------------------------------------- 18-----------------------------------------------------------------------------
19{-# OPTIONS_HADDOCK hide #-}
20 19
21module Numeric.LinearAlgebra.Util( 20module Numeric.LinearAlgebra.Util(
22 21
@@ -53,18 +52,7 @@ module Numeric.LinearAlgebra.Util(
53 -- ** 1D 52 -- ** 1D
54 corr, conv, corrMin, 53 corr, conv, corrMin,
55 -- ** 2D 54 -- ** 2D
56 corr2, conv2, separable, 55 corr2, conv2, separable
57 -- * Tools for the Kronecker product
58 --
59 -- | (see A. Fusiello, A matter of notation: Several uses of the Kronecker product in
60 -- 3d computer vision, Pattern Recognition Letters 28 (15) (2007) 2127-2132)
61
62 --
63 -- | @`vec` (a \<> x \<> b) == ('trans' b ` 'kronecker' ` a) \<> 'vec' x@
64 vec,
65 vech,
66 dup,
67 vtrans
68) where 56) where
69 57
70import Data.Packed.Numeric 58import Data.Packed.Numeric
@@ -227,10 +215,11 @@ infixl 9 ¿
227(¿)= flip extractColumns 215(¿)= flip extractColumns
228 216
229 217
230cross :: Vector Double -> Vector Double -> Vector Double 218cross :: Product t => Vector t -> Vector t -> Vector t
231-- ^ cross product (for three-element real vectors) 219-- ^ cross product (for three-element vectors)
232cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3] 220cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3]
233 | otherwise = error $ "cross ("++show x++") ("++show y++")" 221 | otherwise = error $ "the cross product requires 3-element vectors (sizes given: "
222 ++show (dim x)++" and "++show (dim y)++")"
234 where 223 where
235 [x1,x2,x3] = toList x 224 [x1,x2,x3] = toList x
236 [y1,y2,y3] = toList y 225 [y1,y2,y3] = toList y
@@ -238,6 +227,9 @@ cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3]
238 z2 = x3*y1-x1*y3 227 z2 = x3*y1-x1*y3
239 z3 = x1*y2-x2*y1 228 z3 = x1*y2-x2*y1
240 229
230{-# SPECIALIZE cross :: Vector Double -> Vector Double -> Vector Double #-}
231{-# SPECIALIZE cross :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double) #-}
232
241norm :: Vector Double -> Double 233norm :: Vector Double -> Double
242-- ^ 2-norm of real vector 234-- ^ 2-norm of real vector
243norm = pnorm PNorm2 235norm = pnorm PNorm2
@@ -403,40 +395,6 @@ null1sym = last . toColumns . snd . eigSH'
403 395
404-------------------------------------------------------------------------------- 396--------------------------------------------------------------------------------
405 397
406vec :: Element t => Matrix t -> Vector t
407-- ^ stacking of columns
408vec = flatten . trans
409
410
411vech :: Element t => Matrix t -> Vector t
412-- ^ half-vectorization (of the lower triangular part)
413vech m = vjoin . zipWith f [0..] . toColumns $ m
414 where
415 f k v = subVector k (dim v - k) v
416
417
418dup :: (Num t, Num (Vector t), Element t) => Int -> Matrix t
419-- ^ duplication matrix (@'dup' k \<> 'vech' m == 'vec' m@, for symmetric m of 'dim' k)
420dup k = trans $ fromRows $ map f es
421 where
422 rs = zip [0..] (toRows (ident (k^(2::Int))))
423 es = [(i,j) | j <- [0..k-1], i <- [0..k-1], i>=j ]
424 f (i,j) | i == j = g (k*j + i)
425 | otherwise = g (k*j + i) + g (k*i + j)
426 g j = v
427 where
428 Just v = lookup j rs
429
430
431vtrans :: Element t => Int -> Matrix t -> Matrix t
432-- ^ generalized \"vector\" transposition: @'vtrans' 1 == 'trans'@, and @'vtrans' ('rows' m) m == 'asColumn' ('vec' m)@
433vtrans p m | r == 0 = fromBlocks . map (map asColumn . takesV (replicate q p)) . toColumns $ m
434 | otherwise = error $ "vtrans " ++ show p ++ " of matrix with " ++ show (rows m) ++ " rows"
435 where
436 (q,r) = divMod (rows m) p
437
438--------------------------------------------------------------------------------
439
440infixl 0 ~!~ 398infixl 0 ~!~
441c ~!~ msg = when c (error msg) 399c ~!~ msg = when c (error msg)
442 400