From 899c1f71f64f49c5d3b2c264501565227977cd9c Mon Sep 17 00:00:00 2001 From: Alberto Ruiz Date: Fri, 15 Jun 2012 11:09:15 +0200 Subject: kronecker tools --- lib/Numeric/LinearAlgebra/Util.hs | 56 +++++++++++++++++++++++++-- lib/Numeric/LinearAlgebra/Util/Convolution.hs | 18 ++++----- 2 files changed, 59 insertions(+), 15 deletions(-) (limited to 'lib') diff --git a/lib/Numeric/LinearAlgebra/Util.hs b/lib/Numeric/LinearAlgebra/Util.hs index 79b8774..25eb239 100644 --- a/lib/Numeric/LinearAlgebra/Util.hs +++ b/lib/Numeric/LinearAlgebra/Util.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE FlexibleContexts #-} ----------------------------------------------------------------------------- {- | Module : Numeric.LinearAlgebra.Util @@ -11,6 +12,7 @@ Stability : provisional ----------------------------------------------------------------------------- module Numeric.LinearAlgebra.Util( + -- * Convenience functions for real elements disp, zeros, ones, diagl, @@ -19,11 +21,24 @@ module Numeric.LinearAlgebra.Util( (&),(!), (#), rand, randn, cross, - norm + norm, + -- * Convolution + -- ** 1D + corr, conv, corrMin, + -- ** 2D + corr2, conv2, separable, + -- * Tools for the Kronecker product + -- + -- | @`vec` (a \<> x \<> b) == ('trans' b ` 'kronecker' ` a) \<> 'vec' x@ + vec, + vech, + dup, + vtrans ) where -import Numeric.LinearAlgebra +import Numeric.LinearAlgebra hiding (i) import System.Random(randomIO) +import Numeric.LinearAlgebra.Util.Convolution disp :: Int -> Matrix Double -> IO () @@ -87,7 +102,7 @@ col :: [Double] -> Matrix Double col = asColumn . fromList cross :: Vector Double -> Vector Double -> Vector Double --- ^ cross product of dimension 3 real vectors +-- ^ cross product (for three-element real vectors) cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3] | otherwise = error $ "cross ("++show x++") ("++show y++")" where @@ -98,7 +113,40 @@ cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3] z3 = x1*y2-x2*y1 norm :: Vector Double -> Double --- ^ 2-norm of real vectors +-- ^ 2-norm of real vector norm = pnorm PNorm2 +-------------------------------------------------------------------------------- + +vec :: Element t => Matrix t -> Vector t +-- ^ stacking of columns +vec = flatten . trans + + +vech :: Element t => Matrix t -> Vector t +-- ^ half-vectorization (of the lower triangular part) +vech m = 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 +-- ^ duplication matrix (@'dup' k \<> 'vech' m == 'vec' m@, for symmetric m of 'dim' k) +dup k = trans $ fromRows $ map f es + where + rs = zip [0..] (toRows (ident (k^(2::Int)))) + es = [(i,j) | j <- [0..k-1], i <- [0..k-1], 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 +-- ^ generalized \"vector\" transposition: @'vtrans' 1 == 'trans'@, and @'vtrans' ('rows' m) m == 'asColumn' ('vec' m)@ +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 diff --git a/lib/Numeric/LinearAlgebra/Util/Convolution.hs b/lib/Numeric/LinearAlgebra/Util/Convolution.hs index b64b169..32cb188 100644 --- a/lib/Numeric/LinearAlgebra/Util/Convolution.hs +++ b/lib/Numeric/LinearAlgebra/Util/Convolution.hs @@ -12,12 +12,8 @@ Stability : provisional ----------------------------------------------------------------------------- module Numeric.LinearAlgebra.Util.Convolution( - -- * 1D - corr, conv, - -- * 2D - corr2, conv2, - -- * Misc - separable, corrMin + corr, conv, corrMin, + corr2, conv2, separable ) where import Numeric.LinearAlgebra @@ -32,8 +28,8 @@ corr :: Product t => Vector t -- ^ kernel -> Vector t {- ^ correlation -@\> (fromList[1,2,3]) (fromList [1..10]) -fromList [14.0,20.0,26.0,32.0,38.0,44.0,50.0,56.0]@ +>>> corr (fromList[1,2,3]) (fromList [1..10]) +fromList [14.0,20.0,26.0,32.0,38.0,44.0,50.0,56.0] -} corr ker v | dim ker <= dim v = vectSS (dim ker) v <> ker @@ -43,8 +39,8 @@ corr ker v | dim ker <= dim v = vectSS (dim ker) v <> ker conv :: (Product t, Num t) => Vector t -> Vector t -> Vector t {- ^ convolution ('corr' with reversed kernel and padded input, equivalent to polynomial product) -@\> conv (fromList[1,1]) (fromList [-1,1]) -fromList [-1.0,0.0,1.0]@ +>>> conv (fromList[1,1]) (fromList [-1,1]) +fromList [-1.0,0.0,1.0] -} conv ker v = corr ker' v' @@ -113,6 +109,6 @@ conv2 k m = corr2 (fliprl . flipud $ k) pm separable :: Element t => (Vector t -> Vector t) -> Matrix t -> Matrix t --- ^ 2D process implemented as separated 1D processes by rows and columns. +-- ^ matrix computation implemented as separated vector operations by rows and columns. separable f = fromColumns . map f . toColumns . fromRows . map f . toRows -- cgit v1.2.3