diff options
Diffstat (limited to 'packages/base/src')
-rw-r--r-- | packages/base/src/Data/Packed/IO.hs | 141 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra.hs | 30 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/LAPACK.hs | 2 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Util.hs | 291 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs | 115 |
5 files changed, 579 insertions, 0 deletions
diff --git a/packages/base/src/Data/Packed/IO.hs b/packages/base/src/Data/Packed/IO.hs new file mode 100644 index 0000000..dbb2943 --- /dev/null +++ b/packages/base/src/Data/Packed/IO.hs | |||
@@ -0,0 +1,141 @@ | |||
1 | ----------------------------------------------------------------------------- | ||
2 | -- | | ||
3 | -- Module : Data.Packed.IO | ||
4 | -- Copyright : (c) Alberto Ruiz 2010 | ||
5 | -- License : BSD3 | ||
6 | -- | ||
7 | -- Maintainer : Alberto Ruiz | ||
8 | -- Stability : provisional | ||
9 | -- | ||
10 | -- Display, formatting and IO functions for numeric 'Vector' and 'Matrix' | ||
11 | -- | ||
12 | ----------------------------------------------------------------------------- | ||
13 | {-# OPTIONS_HADDOCK hide #-} | ||
14 | |||
15 | module Data.Packed.IO ( | ||
16 | dispf, disps, dispcf, vecdisp, latexFormat, format, | ||
17 | readMatrix, fromArray2D | ||
18 | ) where | ||
19 | |||
20 | import Data.Packed | ||
21 | import Data.Packed.Development | ||
22 | import Text.Printf(printf) | ||
23 | import Data.List(intersperse) | ||
24 | import Data.Complex | ||
25 | |||
26 | {- | Creates a string from a matrix given a separator and a function to show each entry. Using | ||
27 | this function the user can easily define any desired display function: | ||
28 | |||
29 | @import Text.Printf(printf)@ | ||
30 | |||
31 | @disp = putStr . format \" \" (printf \"%.2f\")@ | ||
32 | |||
33 | -} | ||
34 | format :: (Element t) => String -> (t -> String) -> Matrix t -> String | ||
35 | format sep f m = table sep . map (map f) . toLists $ m | ||
36 | |||
37 | {- | Show a matrix with \"autoscaling\" and a given number of decimal places. | ||
38 | |||
39 | >>> putStr . disps 2 $ 120 * (3><4) [1..] | ||
40 | 3x4 E3 | ||
41 | 0.12 0.24 0.36 0.48 | ||
42 | 0.60 0.72 0.84 0.96 | ||
43 | 1.08 1.20 1.32 1.44 | ||
44 | |||
45 | -} | ||
46 | disps :: Int -> Matrix Double -> String | ||
47 | disps d x = sdims x ++ " " ++ formatScaled d x | ||
48 | |||
49 | {- | Show a matrix with a given number of decimal places. | ||
50 | |||
51 | >>> dispf 2 (1/3 + ident 3) | ||
52 | "3x3\n1.33 0.33 0.33\n0.33 1.33 0.33\n0.33 0.33 1.33\n" | ||
53 | |||
54 | >>> putStr . dispf 2 $ (3><4)[1,1.5..] | ||
55 | 3x4 | ||
56 | 1.00 1.50 2.00 2.50 | ||
57 | 3.00 3.50 4.00 4.50 | ||
58 | 5.00 5.50 6.00 6.50 | ||
59 | |||
60 | >>> putStr . unlines . tail . lines . dispf 2 . asRow $ linspace 10 (0,1) | ||
61 | 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00 | ||
62 | |||
63 | -} | ||
64 | dispf :: Int -> Matrix Double -> String | ||
65 | dispf d x = sdims x ++ "\n" ++ formatFixed (if isInt x then 0 else d) x | ||
66 | |||
67 | sdims x = show (rows x) ++ "x" ++ show (cols x) | ||
68 | |||
69 | formatFixed d x = format " " (printf ("%."++show d++"f")) $ x | ||
70 | |||
71 | isInt = all lookslikeInt . toList . flatten | ||
72 | |||
73 | formatScaled dec t = "E"++show o++"\n" ++ ss | ||
74 | where ss = format " " (printf fmt. g) t | ||
75 | g x | o >= 0 = x/10^(o::Int) | ||
76 | | otherwise = x*10^(-o) | ||
77 | o | rows t == 0 || cols t == 0 = 0 | ||
78 | | otherwise = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t | ||
79 | fmt = '%':show (dec+3) ++ '.':show dec ++"f" | ||
80 | |||
81 | {- | Show a vector using a function for showing matrices. | ||
82 | |||
83 | >>> putStr . vecdisp (dispf 2) $ linspace 10 (0,1) | ||
84 | 10 |> 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00 | ||
85 | |||
86 | -} | ||
87 | vecdisp :: (Element t) => (Matrix t -> String) -> Vector t -> String | ||
88 | vecdisp f v | ||
89 | = ((show (dim v) ++ " |> ") ++) . (++"\n") | ||
90 | . unwords . lines . tail . dropWhile (not . (`elem` " \n")) | ||
91 | . f . trans . reshape 1 | ||
92 | $ v | ||
93 | |||
94 | {- | Tool to display matrices with latex syntax. | ||
95 | |||
96 | >>> latexFormat "bmatrix" (dispf 2 $ ident 2) | ||
97 | "\\begin{bmatrix}\n1 & 0\n\\\\\n0 & 1\n\\end{bmatrix}" | ||
98 | |||
99 | -} | ||
100 | latexFormat :: String -- ^ type of braces: \"matrix\", \"bmatrix\", \"pmatrix\", etc. | ||
101 | -> String -- ^ Formatted matrix, with elements separated by spaces and newlines | ||
102 | -> String | ||
103 | latexFormat del tab = "\\begin{"++del++"}\n" ++ f tab ++ "\\end{"++del++"}" | ||
104 | where f = unlines . intersperse "\\\\" . map unwords . map (intersperse " & " . words) . tail . lines | ||
105 | |||
106 | -- | Pretty print a complex number with at most n decimal digits. | ||
107 | showComplex :: Int -> Complex Double -> String | ||
108 | showComplex d (a:+b) | ||
109 | | isZero a && isZero b = "0" | ||
110 | | isZero b = sa | ||
111 | | isZero a && isOne b = s2++"i" | ||
112 | | isZero a = sb++"i" | ||
113 | | isOne b = sa++s3++"i" | ||
114 | | otherwise = sa++s1++sb++"i" | ||
115 | where | ||
116 | sa = shcr d a | ||
117 | sb = shcr d b | ||
118 | s1 = if b<0 then "" else "+" | ||
119 | s2 = if b<0 then "-" else "" | ||
120 | s3 = if b<0 then "-" else "+" | ||
121 | |||
122 | shcr d a | lookslikeInt a = printf "%.0f" a | ||
123 | | otherwise = printf ("%."++show d++"f") a | ||
124 | |||
125 | |||
126 | lookslikeInt x = show (round x :: Int) ++".0" == shx || "-0.0" == shx | ||
127 | where shx = show x | ||
128 | |||
129 | isZero x = show x `elem` ["0.0","-0.0"] | ||
130 | isOne x = show x `elem` ["1.0","-1.0"] | ||
131 | |||
132 | -- | Pretty print a complex matrix with at most n decimal digits. | ||
133 | dispcf :: Int -> Matrix (Complex Double) -> String | ||
134 | dispcf d m = sdims m ++ "\n" ++ format " " (showComplex d) m | ||
135 | |||
136 | -------------------------------------------------------------------- | ||
137 | |||
138 | -- | reads a matrix from a string containing a table of numbers. | ||
139 | readMatrix :: String -> Matrix Double | ||
140 | readMatrix = fromLists . map (map read). map words . filter (not.null) . lines | ||
141 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra.hs b/packages/base/src/Numeric/LinearAlgebra.hs new file mode 100644 index 0000000..1db860c --- /dev/null +++ b/packages/base/src/Numeric/LinearAlgebra.hs | |||
@@ -0,0 +1,30 @@ | |||
1 | ----------------------------------------------------------------------------- | ||
2 | {- | | ||
3 | Module : Numeric.LinearAlgebra | ||
4 | Copyright : (c) Alberto Ruiz 2006-10 | ||
5 | License : GPL-style | ||
6 | |||
7 | Maintainer : Alberto Ruiz (aruiz at um dot es) | ||
8 | Stability : provisional | ||
9 | Portability : uses ffi | ||
10 | |||
11 | This module reexports all normally required functions for Linear Algebra applications. | ||
12 | |||
13 | It also provides instances of standard classes 'Show', 'Read', 'Eq', | ||
14 | 'Num', 'Fractional', and 'Floating' for 'Vector' and 'Matrix'. | ||
15 | In arithmetic operations one-component vectors and matrices automatically | ||
16 | expand to match the dimensions of the other operand. | ||
17 | |||
18 | -} | ||
19 | ----------------------------------------------------------------------------- | ||
20 | {-# OPTIONS_HADDOCK hide #-} | ||
21 | |||
22 | module Numeric.LinearAlgebra ( | ||
23 | module Numeric.Container, | ||
24 | module Numeric.LinearAlgebra.Algorithms | ||
25 | ) where | ||
26 | |||
27 | import Numeric.Container | ||
28 | import Numeric.LinearAlgebra.Algorithms | ||
29 | import Numeric.Matrix() | ||
30 | import Numeric.Vector() | ||
diff --git a/packages/base/src/Numeric/LinearAlgebra/LAPACK.hs b/packages/base/src/Numeric/LinearAlgebra/LAPACK.hs index af0c744..9cb67d4 100644 --- a/packages/base/src/Numeric/LinearAlgebra/LAPACK.hs +++ b/packages/base/src/Numeric/LinearAlgebra/LAPACK.hs | |||
@@ -10,6 +10,8 @@ | |||
10 | -- Functional interface to selected LAPACK functions (<http://www.netlib.org/lapack>). | 10 | -- Functional interface to selected LAPACK functions (<http://www.netlib.org/lapack>). |
11 | -- | 11 | -- |
12 | ----------------------------------------------------------------------------- | 12 | ----------------------------------------------------------------------------- |
13 | {-# OPTIONS_HADDOCK hide #-} | ||
14 | |||
13 | 15 | ||
14 | module Numeric.LinearAlgebra.LAPACK ( | 16 | module Numeric.LinearAlgebra.LAPACK ( |
15 | -- * Matrix product | 17 | -- * Matrix product |
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs new file mode 100644 index 0000000..533c54b --- /dev/null +++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs | |||
@@ -0,0 +1,291 @@ | |||
1 | {-# LANGUAGE FlexibleContexts #-} | ||
2 | ----------------------------------------------------------------------------- | ||
3 | {- | | ||
4 | Module : Numeric.LinearAlgebra.Util | ||
5 | Copyright : (c) Alberto Ruiz 2013 | ||
6 | License : GPL | ||
7 | |||
8 | Maintainer : Alberto Ruiz (aruiz at um dot es) | ||
9 | Stability : provisional | ||
10 | |||
11 | -} | ||
12 | ----------------------------------------------------------------------------- | ||
13 | {-# OPTIONS_HADDOCK hide #-} | ||
14 | |||
15 | module Numeric.LinearAlgebra.Util( | ||
16 | |||
17 | -- * Convenience functions | ||
18 | size, disp, | ||
19 | zeros, ones, | ||
20 | diagl, | ||
21 | row, | ||
22 | col, | ||
23 | (&), (¦), (——), (#), | ||
24 | (?), (¿), | ||
25 | cross, | ||
26 | norm, | ||
27 | unitary, | ||
28 | mt, | ||
29 | pairwiseD2, | ||
30 | meanCov, | ||
31 | rowOuters, | ||
32 | null1, | ||
33 | null1sym, | ||
34 | -- * Convolution | ||
35 | -- ** 1D | ||
36 | corr, conv, corrMin, | ||
37 | -- ** 2D | ||
38 | corr2, conv2, separable, | ||
39 | -- * Tools for the Kronecker product | ||
40 | -- | ||
41 | -- | (see A. Fusiello, A matter of notation: Several uses of the Kronecker product in | ||
42 | -- 3d computer vision, Pattern Recognition Letters 28 (15) (2007) 2127-2132) | ||
43 | |||
44 | -- | ||
45 | -- | @`vec` (a \<> x \<> b) == ('trans' b ` 'kronecker' ` a) \<> 'vec' x@ | ||
46 | vec, | ||
47 | vech, | ||
48 | dup, | ||
49 | vtrans, | ||
50 | {- -- * Plot | ||
51 | mplot, | ||
52 | plot, parametricPlot, | ||
53 | splot, mesh, meshdom, | ||
54 | matrixToPGM, imshow, | ||
55 | gnuplotX, gnuplotpdf, gnuplotWin | ||
56 | -} | ||
57 | ) where | ||
58 | |||
59 | import Numeric.Container | ||
60 | import Data.Packed.IO | ||
61 | import Numeric.LinearAlgebra.Algorithms hiding (i) | ||
62 | import Numeric.Matrix() | ||
63 | import Numeric.Vector() | ||
64 | |||
65 | import Numeric.LinearAlgebra.Util.Convolution | ||
66 | --import Graphics.Plot | ||
67 | |||
68 | |||
69 | {- | print a real matrix with given number of digits after the decimal point | ||
70 | |||
71 | >>> disp 5 $ ident 2 / 3 | ||
72 | 2x2 | ||
73 | 0.33333 0.00000 | ||
74 | 0.00000 0.33333 | ||
75 | |||
76 | -} | ||
77 | disp :: Int -> Matrix Double -> IO () | ||
78 | |||
79 | disp n = putStrLn . dispf n | ||
80 | |||
81 | |||
82 | {- | create a real diagonal matrix from a list | ||
83 | |||
84 | >>> diagl [1,2,3] | ||
85 | (3><3) | ||
86 | [ 1.0, 0.0, 0.0 | ||
87 | , 0.0, 2.0, 0.0 | ||
88 | , 0.0, 0.0, 3.0 ] | ||
89 | |||
90 | -} | ||
91 | diagl :: [Double] -> Matrix Double | ||
92 | diagl = diag . fromList | ||
93 | |||
94 | -- | a real matrix of zeros | ||
95 | zeros :: Int -- ^ rows | ||
96 | -> Int -- ^ columns | ||
97 | -> Matrix Double | ||
98 | zeros r c = konst 0 (r,c) | ||
99 | |||
100 | -- | a real matrix of ones | ||
101 | ones :: Int -- ^ rows | ||
102 | -> Int -- ^ columns | ||
103 | -> Matrix Double | ||
104 | ones r c = konst 1 (r,c) | ||
105 | |||
106 | -- | concatenation of real vectors | ||
107 | infixl 3 & | ||
108 | (&) :: Vector Double -> Vector Double -> Vector Double | ||
109 | a & b = vjoin [a,b] | ||
110 | |||
111 | {- | horizontal concatenation of real matrices | ||
112 | |||
113 | (unicode 0x00a6, broken bar) | ||
114 | |||
115 | >>> ident 3 ¦ konst 7 (3,4) | ||
116 | (3><7) | ||
117 | [ 1.0, 0.0, 0.0, 7.0, 7.0, 7.0, 7.0 | ||
118 | , 0.0, 1.0, 0.0, 7.0, 7.0, 7.0, 7.0 | ||
119 | , 0.0, 0.0, 1.0, 7.0, 7.0, 7.0, 7.0 ] | ||
120 | |||
121 | -} | ||
122 | infixl 3 ¦ | ||
123 | (¦) :: Matrix Double -> Matrix Double -> Matrix Double | ||
124 | a ¦ b = fromBlocks [[a,b]] | ||
125 | |||
126 | -- | vertical concatenation of real matrices | ||
127 | -- | ||
128 | -- (unicode 0x2014, em dash) | ||
129 | (——) :: Matrix Double -> Matrix Double -> Matrix Double | ||
130 | infixl 2 —— | ||
131 | a —— b = fromBlocks [[a],[b]] | ||
132 | |||
133 | (#) :: Matrix Double -> Matrix Double -> Matrix Double | ||
134 | infixl 2 # | ||
135 | a # b = fromBlocks [[a],[b]] | ||
136 | |||
137 | -- | create a single row real matrix from a list | ||
138 | row :: [Double] -> Matrix Double | ||
139 | row = asRow . fromList | ||
140 | |||
141 | -- | create a single column real matrix from a list | ||
142 | col :: [Double] -> Matrix Double | ||
143 | col = asColumn . fromList | ||
144 | |||
145 | {- | extract rows | ||
146 | |||
147 | >>> (20><4) [1..] ? [2,1,1] | ||
148 | (3><4) | ||
149 | [ 9.0, 10.0, 11.0, 12.0 | ||
150 | , 5.0, 6.0, 7.0, 8.0 | ||
151 | , 5.0, 6.0, 7.0, 8.0 ] | ||
152 | |||
153 | -} | ||
154 | infixl 9 ? | ||
155 | (?) :: Element t => Matrix t -> [Int] -> Matrix t | ||
156 | (?) = flip extractRows | ||
157 | |||
158 | {- | extract columns | ||
159 | |||
160 | (unicode 0x00bf, inverted question mark, Alt-Gr ?) | ||
161 | |||
162 | >>> (3><4) [1..] ¿ [3,0] | ||
163 | (3><2) | ||
164 | [ 4.0, 1.0 | ||
165 | , 8.0, 5.0 | ||
166 | , 12.0, 9.0 ] | ||
167 | |||
168 | -} | ||
169 | infixl 9 ¿ | ||
170 | (¿) :: Element t => Matrix t -> [Int] -> Matrix t | ||
171 | (¿)= flip extractColumns | ||
172 | |||
173 | |||
174 | cross :: Vector Double -> Vector Double -> Vector Double | ||
175 | -- ^ cross product (for three-element real vectors) | ||
176 | cross x y | dim x == 3 && dim y == 3 = fromList [z1,z2,z3] | ||
177 | | otherwise = error $ "cross ("++show x++") ("++show y++")" | ||
178 | where | ||
179 | [x1,x2,x3] = toList x | ||
180 | [y1,y2,y3] = toList y | ||
181 | z1 = x2*y3-x3*y2 | ||
182 | z2 = x3*y1-x1*y3 | ||
183 | z3 = x1*y2-x2*y1 | ||
184 | |||
185 | norm :: Vector Double -> Double | ||
186 | -- ^ 2-norm of real vector | ||
187 | norm = pnorm PNorm2 | ||
188 | |||
189 | |||
190 | -- | Obtains a vector in the same direction with 2-norm=1 | ||
191 | unitary :: Vector Double -> Vector Double | ||
192 | unitary v = v / scalar (norm v) | ||
193 | |||
194 | -- | ('rows' &&& 'cols') | ||
195 | size :: Matrix t -> (Int, Int) | ||
196 | size m = (rows m, cols m) | ||
197 | |||
198 | -- | trans . inv | ||
199 | mt :: Matrix Double -> Matrix Double | ||
200 | mt = trans . inv | ||
201 | |||
202 | -------------------------------------------------------------------------------- | ||
203 | |||
204 | {- | Compute mean vector and covariance matrix of the rows of a matrix. | ||
205 | |||
206 | >>> meanCov $ gaussianSample 666 1000 (fromList[4,5]) (diagl[2,3]) | ||
207 | (fromList [4.010341078059521,5.0197204699640405], | ||
208 | (2><2) | ||
209 | [ 1.9862461923890056, -1.0127225830525157e-2 | ||
210 | , -1.0127225830525157e-2, 3.0373954915729318 ]) | ||
211 | |||
212 | -} | ||
213 | meanCov :: Matrix Double -> (Vector Double, Matrix Double) | ||
214 | meanCov x = (med,cov) where | ||
215 | r = rows x | ||
216 | k = 1 / fromIntegral r | ||
217 | med = konst k r `vXm` x | ||
218 | meds = konst 1 r `outer` med | ||
219 | xc = x `sub` meds | ||
220 | cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc) | ||
221 | |||
222 | -------------------------------------------------------------------------------- | ||
223 | |||
224 | -- | Matrix of pairwise squared distances of row vectors | ||
225 | -- (using the matrix product trick in blog.smola.org) | ||
226 | pairwiseD2 :: Matrix Double -> Matrix Double -> Matrix Double | ||
227 | pairwiseD2 x y | ok = x2 `outer` oy + ox `outer` y2 - 2* x <> trans y | ||
228 | | otherwise = error $ "pairwiseD2 with different number of columns: " | ||
229 | ++ show (size x) ++ ", " ++ show (size y) | ||
230 | where | ||
231 | ox = one (rows x) | ||
232 | oy = one (rows y) | ||
233 | oc = one (cols x) | ||
234 | one k = constant 1 k | ||
235 | x2 = x * x <> oc | ||
236 | y2 = y * y <> oc | ||
237 | ok = cols x == cols y | ||
238 | |||
239 | -------------------------------------------------------------------------------- | ||
240 | |||
241 | -- | outer products of rows | ||
242 | rowOuters :: Matrix Double -> Matrix Double -> Matrix Double | ||
243 | rowOuters a b = a' * b' | ||
244 | where | ||
245 | a' = kronecker a (ones 1 (cols b)) | ||
246 | b' = kronecker (ones 1 (cols a)) b | ||
247 | |||
248 | -------------------------------------------------------------------------------- | ||
249 | |||
250 | -- | solution of overconstrained homogeneous linear system | ||
251 | null1 :: Matrix Double -> Vector Double | ||
252 | null1 = last . toColumns . snd . rightSV | ||
253 | |||
254 | -- | solution of overconstrained homogeneous symmetric linear system | ||
255 | null1sym :: Matrix Double -> Vector Double | ||
256 | null1sym = last . toColumns . snd . eigSH' | ||
257 | |||
258 | -------------------------------------------------------------------------------- | ||
259 | |||
260 | vec :: Element t => Matrix t -> Vector t | ||
261 | -- ^ stacking of columns | ||
262 | vec = flatten . trans | ||
263 | |||
264 | |||
265 | vech :: Element t => Matrix t -> Vector t | ||
266 | -- ^ half-vectorization (of the lower triangular part) | ||
267 | vech m = vjoin . zipWith f [0..] . toColumns $ m | ||
268 | where | ||
269 | f k v = subVector k (dim v - k) v | ||
270 | |||
271 | |||
272 | dup :: (Num t, Num (Vector t), Element t) => Int -> Matrix t | ||
273 | -- ^ duplication matrix (@'dup' k \<> 'vech' m == 'vec' m@, for symmetric m of 'dim' k) | ||
274 | dup k = trans $ fromRows $ map f es | ||
275 | where | ||
276 | rs = zip [0..] (toRows (ident (k^(2::Int)))) | ||
277 | es = [(i,j) | j <- [0..k-1], i <- [0..k-1], i>=j ] | ||
278 | f (i,j) | i == j = g (k*j + i) | ||
279 | | otherwise = g (k*j + i) + g (k*i + j) | ||
280 | g j = v | ||
281 | where | ||
282 | Just v = lookup j rs | ||
283 | |||
284 | |||
285 | vtrans :: Element t => Int -> Matrix t -> Matrix t | ||
286 | -- ^ generalized \"vector\" transposition: @'vtrans' 1 == 'trans'@, and @'vtrans' ('rows' m) m == 'asColumn' ('vec' m)@ | ||
287 | vtrans p m | r == 0 = fromBlocks . map (map asColumn . takesV (replicate q p)) . toColumns $ m | ||
288 | | otherwise = error $ "vtrans " ++ show p ++ " of matrix with " ++ show (rows m) ++ " rows" | ||
289 | where | ||
290 | (q,r) = divMod (rows m) p | ||
291 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs b/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs new file mode 100644 index 0000000..d04c46b --- /dev/null +++ b/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs | |||
@@ -0,0 +1,115 @@ | |||
1 | {-# LANGUAGE FlexibleContexts #-} | ||
2 | ----------------------------------------------------------------------------- | ||
3 | {- | | ||
4 | Module : Numeric.LinearAlgebra.Util.Convolution | ||
5 | Copyright : (c) Alberto Ruiz 2012 | ||
6 | License : GPL | ||
7 | |||
8 | Maintainer : Alberto Ruiz (aruiz at um dot es) | ||
9 | Stability : provisional | ||
10 | |||
11 | -} | ||
12 | ----------------------------------------------------------------------------- | ||
13 | {-# OPTIONS_HADDOCK hide #-} | ||
14 | |||
15 | module Numeric.LinearAlgebra.Util.Convolution( | ||
16 | corr, conv, corrMin, | ||
17 | corr2, conv2, separable | ||
18 | ) where | ||
19 | |||
20 | import Numeric.LinearAlgebra | ||
21 | |||
22 | |||
23 | vectSS :: Element t => Int -> Vector t -> Matrix t | ||
24 | vectSS n v = fromRows [ subVector k n v | k <- [0 .. dim v - n] ] | ||
25 | |||
26 | |||
27 | corr :: Product t => Vector t -- ^ kernel | ||
28 | -> Vector t -- ^ source | ||
29 | -> Vector t | ||
30 | {- ^ correlation | ||
31 | |||
32 | >>> corr (fromList[1,2,3]) (fromList [1..10]) | ||
33 | fromList [14.0,20.0,26.0,32.0,38.0,44.0,50.0,56.0] | ||
34 | |||
35 | -} | ||
36 | corr ker v | dim ker <= dim v = vectSS (dim ker) v <> ker | ||
37 | | otherwise = error $ "corr: dim kernel ("++show (dim ker)++") > dim vector ("++show (dim v)++")" | ||
38 | |||
39 | |||
40 | conv :: (Product t, Num t) => Vector t -> Vector t -> Vector t | ||
41 | {- ^ convolution ('corr' with reversed kernel and padded input, equivalent to polynomial product) | ||
42 | |||
43 | >>> conv (fromList[1,1]) (fromList [-1,1]) | ||
44 | fromList [-1.0,0.0,1.0] | ||
45 | |||
46 | -} | ||
47 | conv ker v = corr ker' v' | ||
48 | where | ||
49 | ker' = (flatten.fliprl.asRow) ker | ||
50 | v' | dim ker > 1 = vjoin [z,v,z] | ||
51 | | otherwise = v | ||
52 | z = constant 0 (dim ker -1) | ||
53 | |||
54 | corrMin :: (Container Vector t, RealElement t, Product t) | ||
55 | => Vector t | ||
56 | -> Vector t | ||
57 | -> Vector t | ||
58 | -- ^ similar to 'corr', using 'min' instead of (*) | ||
59 | corrMin ker v = minEvery ss (asRow ker) <> ones | ||
60 | where | ||
61 | minEvery a b = cond a b a a b | ||
62 | ss = vectSS (dim ker) v | ||
63 | ones = konst 1 (dim ker) | ||
64 | |||
65 | |||
66 | |||
67 | matSS :: Element t => Int -> Matrix t -> [Matrix t] | ||
68 | matSS dr m = map (reshape c) [ subVector (k*c) n v | k <- [0 .. r - dr] ] | ||
69 | where | ||
70 | v = flatten m | ||
71 | c = cols m | ||
72 | r = rows m | ||
73 | n = dr*c | ||
74 | |||
75 | |||
76 | corr2 :: Product a => Matrix a -> Matrix a -> Matrix a | ||
77 | -- ^ 2D correlation | ||
78 | corr2 ker mat = dims | ||
79 | . concatMap (map (udot ker' . flatten) . matSS c . trans) | ||
80 | . matSS r $ mat | ||
81 | where | ||
82 | r = rows ker | ||
83 | c = cols ker | ||
84 | ker' = flatten (trans ker) | ||
85 | rr = rows mat - r + 1 | ||
86 | rc = cols mat - c + 1 | ||
87 | dims | rr > 0 && rc > 0 = (rr >< rc) | ||
88 | | otherwise = error $ "corr2: dim kernel ("++sz ker++") > dim matrix ("++sz mat++")" | ||
89 | sz m = show (rows m)++"x"++show (cols m) | ||
90 | |||
91 | conv2 :: (Num a, Product a, Container Vector a) => Matrix a -> Matrix a -> Matrix a | ||
92 | -- ^ 2D convolution | ||
93 | conv2 k m = corr2 (fliprl . flipud $ k) pm | ||
94 | where | ||
95 | pm | r == 0 && c == 0 = m | ||
96 | | r == 0 = fromBlocks [[z3,m,z3]] | ||
97 | | c == 0 = fromBlocks [[z2],[m],[z2]] | ||
98 | | otherwise = fromBlocks [[z1,z2,z1] | ||
99 | ,[z3, m,z3] | ||
100 | ,[z1,z2,z1]] | ||
101 | r = rows k - 1 | ||
102 | c = cols k - 1 | ||
103 | h = rows m | ||
104 | w = cols m | ||
105 | z1 = konst 0 (r,c) | ||
106 | z2 = konst 0 (r,w) | ||
107 | z3 = konst 0 (h,c) | ||
108 | |||
109 | -- TODO: could be simplified using future empty arrays | ||
110 | |||
111 | |||
112 | separable :: Element t => (Vector t -> Vector t) -> Matrix t -> Matrix t | ||
113 | -- ^ matrix computation implemented as separated vector operations by rows and columns. | ||
114 | separable f = fromColumns . map f . toColumns . fromRows . map f . toRows | ||
115 | |||