diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
commit | 1925c123d7d8184a1d2ddc0a413e0fd2776e1083 (patch) | |
tree | fad79f909d9c3be53d68e6ebd67202650536d387 /packages/hmatrix/src/Data/Packed/Matrix.hs | |
parent | eb3f702d065a4a967bb754977233e6eec408fd1f (diff) |
empty hmatrix-base
Diffstat (limited to 'packages/hmatrix/src/Data/Packed/Matrix.hs')
-rw-r--r-- | packages/hmatrix/src/Data/Packed/Matrix.hs | 490 |
1 files changed, 490 insertions, 0 deletions
diff --git a/packages/hmatrix/src/Data/Packed/Matrix.hs b/packages/hmatrix/src/Data/Packed/Matrix.hs new file mode 100644 index 0000000..d94d167 --- /dev/null +++ b/packages/hmatrix/src/Data/Packed/Matrix.hs | |||
@@ -0,0 +1,490 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
5 | {-# LANGUAGE CPP #-} | ||
6 | |||
7 | ----------------------------------------------------------------------------- | ||
8 | -- | | ||
9 | -- Module : Data.Packed.Matrix | ||
10 | -- Copyright : (c) Alberto Ruiz 2007-10 | ||
11 | -- License : GPL | ||
12 | -- | ||
13 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
14 | -- Stability : provisional | ||
15 | -- | ||
16 | -- A Matrix representation suitable for numerical computations using LAPACK and GSL. | ||
17 | -- | ||
18 | -- This module provides basic functions for manipulation of structure. | ||
19 | |||
20 | ----------------------------------------------------------------------------- | ||
21 | {-# OPTIONS_HADDOCK hide #-} | ||
22 | |||
23 | module Data.Packed.Matrix ( | ||
24 | Matrix, | ||
25 | Element, | ||
26 | rows,cols, | ||
27 | (><), | ||
28 | trans, | ||
29 | reshape, flatten, | ||
30 | fromLists, toLists, buildMatrix, | ||
31 | (@@>), | ||
32 | asRow, asColumn, | ||
33 | fromRows, toRows, fromColumns, toColumns, | ||
34 | fromBlocks, diagBlock, toBlocks, toBlocksEvery, | ||
35 | repmat, | ||
36 | flipud, fliprl, | ||
37 | subMatrix, takeRows, dropRows, takeColumns, dropColumns, | ||
38 | extractRows, extractColumns, | ||
39 | diagRect, takeDiag, | ||
40 | mapMatrix, mapMatrixWithIndex, mapMatrixWithIndexM, mapMatrixWithIndexM_, | ||
41 | liftMatrix, liftMatrix2, liftMatrix2Auto,fromArray2D | ||
42 | ) where | ||
43 | |||
44 | import Data.Packed.Internal | ||
45 | import qualified Data.Packed.ST as ST | ||
46 | import Data.Array | ||
47 | |||
48 | import Data.List(transpose,intersperse) | ||
49 | import Foreign.Storable(Storable) | ||
50 | import Control.Monad(liftM) | ||
51 | |||
52 | ------------------------------------------------------------------- | ||
53 | |||
54 | #ifdef BINARY | ||
55 | |||
56 | import Data.Binary | ||
57 | import Control.Monad(replicateM) | ||
58 | |||
59 | instance (Binary a, Element a, Storable a) => Binary (Matrix a) where | ||
60 | put m = do | ||
61 | let r = rows m | ||
62 | let c = cols m | ||
63 | put r | ||
64 | put c | ||
65 | mapM_ (\i -> mapM_ (\j -> put $ m @@> (i,j)) [0..(c-1)]) [0..(r-1)] | ||
66 | get = do | ||
67 | r <- get | ||
68 | c <- get | ||
69 | xs <- replicateM r $ replicateM c get | ||
70 | return $ fromLists xs | ||
71 | |||
72 | #endif | ||
73 | |||
74 | ------------------------------------------------------------------- | ||
75 | |||
76 | instance (Show a, Element a) => (Show (Matrix a)) where | ||
77 | show m | rows m == 0 || cols m == 0 = sizes m ++" []" | ||
78 | show m = (sizes m++) . dsp . map (map show) . toLists $ m | ||
79 | |||
80 | sizes m = "("++show (rows m)++"><"++show (cols m)++")\n" | ||
81 | |||
82 | dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp | ||
83 | where | ||
84 | mt = transpose as | ||
85 | longs = map (maximum . map length) mt | ||
86 | mtp = zipWith (\a b -> map (pad a) b) longs mt | ||
87 | pad n str = replicate (n - length str) ' ' ++ str | ||
88 | unwords' = concat . intersperse ", " | ||
89 | |||
90 | ------------------------------------------------------------------ | ||
91 | |||
92 | instance (Element a, Read a) => Read (Matrix a) where | ||
93 | readsPrec _ s = [((rs><cs) . read $ listnums, rest)] | ||
94 | where (thing,rest) = breakAt ']' s | ||
95 | (dims,listnums) = breakAt ')' thing | ||
96 | cs = read . init . fst. breakAt ')' . snd . breakAt '<' $ dims | ||
97 | rs = read . snd . breakAt '(' .init . fst . breakAt '>' $ dims | ||
98 | |||
99 | |||
100 | breakAt c l = (a++[c],tail b) where | ||
101 | (a,b) = break (==c) l | ||
102 | |||
103 | ------------------------------------------------------------------ | ||
104 | |||
105 | -- | creates a matrix from a vertical list of matrices | ||
106 | joinVert :: Element t => [Matrix t] -> Matrix t | ||
107 | joinVert [] = emptyM 0 0 | ||
108 | joinVert ms = case common cols ms of | ||
109 | Nothing -> error "(impossible) joinVert on matrices with different number of columns" | ||
110 | Just c -> matrixFromVector RowMajor (sum (map rows ms)) c $ vjoin (map flatten ms) | ||
111 | |||
112 | -- | creates a matrix from a horizontal list of matrices | ||
113 | joinHoriz :: Element t => [Matrix t] -> Matrix t | ||
114 | joinHoriz ms = trans. joinVert . map trans $ ms | ||
115 | |||
116 | {- | Create a matrix from blocks given as a list of lists of matrices. | ||
117 | |||
118 | Single row-column components are automatically expanded to match the | ||
119 | corresponding common row and column: | ||
120 | |||
121 | @ | ||
122 | disp = putStr . dispf 2 | ||
123 | @ | ||
124 | |||
125 | >>> disp $ fromBlocks [[ident 5, 7, row[10,20]], [3, diagl[1,2,3], 0]] | ||
126 | 8x10 | ||
127 | 1 0 0 0 0 7 7 7 10 20 | ||
128 | 0 1 0 0 0 7 7 7 10 20 | ||
129 | 0 0 1 0 0 7 7 7 10 20 | ||
130 | 0 0 0 1 0 7 7 7 10 20 | ||
131 | 0 0 0 0 1 7 7 7 10 20 | ||
132 | 3 3 3 3 3 1 0 0 0 0 | ||
133 | 3 3 3 3 3 0 2 0 0 0 | ||
134 | 3 3 3 3 3 0 0 3 0 0 | ||
135 | |||
136 | -} | ||
137 | fromBlocks :: Element t => [[Matrix t]] -> Matrix t | ||
138 | fromBlocks = fromBlocksRaw . adaptBlocks | ||
139 | |||
140 | fromBlocksRaw mms = joinVert . map joinHoriz $ mms | ||
141 | |||
142 | adaptBlocks ms = ms' where | ||
143 | bc = case common length ms of | ||
144 | Just c -> c | ||
145 | Nothing -> error "fromBlocks requires rectangular [[Matrix]]" | ||
146 | rs = map (compatdim . map rows) ms | ||
147 | cs = map (compatdim . map cols) (transpose ms) | ||
148 | szs = sequence [rs,cs] | ||
149 | ms' = splitEvery bc $ zipWith g szs (concat ms) | ||
150 | |||
151 | g [Just nr,Just nc] m | ||
152 | | nr == r && nc == c = m | ||
153 | | r == 1 && c == 1 = matrixFromVector RowMajor nr nc (constantD x (nr*nc)) | ||
154 | | r == 1 = fromRows (replicate nr (flatten m)) | ||
155 | | otherwise = fromColumns (replicate nc (flatten m)) | ||
156 | where | ||
157 | r = rows m | ||
158 | c = cols m | ||
159 | x = m@@>(0,0) | ||
160 | g _ _ = error "inconsistent dimensions in fromBlocks" | ||
161 | |||
162 | |||
163 | -------------------------------------------------------------------------------- | ||
164 | |||
165 | {- | create a block diagonal matrix | ||
166 | |||
167 | >>> disp 2 $ diagBlock [konst 1 (2,2), konst 2 (3,5), col [5,7]] | ||
168 | 7x8 | ||
169 | 1 1 0 0 0 0 0 0 | ||
170 | 1 1 0 0 0 0 0 0 | ||
171 | 0 0 2 2 2 2 2 0 | ||
172 | 0 0 2 2 2 2 2 0 | ||
173 | 0 0 2 2 2 2 2 0 | ||
174 | 0 0 0 0 0 0 0 5 | ||
175 | 0 0 0 0 0 0 0 7 | ||
176 | |||
177 | >>> diagBlock [(0><4)[], konst 2 (2,3)] :: Matrix Double | ||
178 | (2><7) | ||
179 | [ 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0 | ||
180 | , 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0 ] | ||
181 | |||
182 | -} | ||
183 | diagBlock :: (Element t, Num t) => [Matrix t] -> Matrix t | ||
184 | diagBlock ms = fromBlocks $ zipWith f ms [0..] | ||
185 | where | ||
186 | f m k = take n $ replicate k z ++ m : repeat z | ||
187 | n = length ms | ||
188 | z = (1><1) [0] | ||
189 | |||
190 | -------------------------------------------------------------------------------- | ||
191 | |||
192 | |||
193 | -- | Reverse rows | ||
194 | flipud :: Element t => Matrix t -> Matrix t | ||
195 | flipud m = extractRows [r-1,r-2 .. 0] $ m | ||
196 | where | ||
197 | r = rows m | ||
198 | |||
199 | -- | Reverse columns | ||
200 | fliprl :: Element t => Matrix t -> Matrix t | ||
201 | fliprl m = extractColumns [c-1,c-2 .. 0] $ m | ||
202 | where | ||
203 | c = cols m | ||
204 | |||
205 | ------------------------------------------------------------ | ||
206 | |||
207 | {- | creates a rectangular diagonal matrix: | ||
208 | |||
209 | >>> diagRect 7 (fromList [10,20,30]) 4 5 :: Matrix Double | ||
210 | (4><5) | ||
211 | [ 10.0, 7.0, 7.0, 7.0, 7.0 | ||
212 | , 7.0, 20.0, 7.0, 7.0, 7.0 | ||
213 | , 7.0, 7.0, 30.0, 7.0, 7.0 | ||
214 | , 7.0, 7.0, 7.0, 7.0, 7.0 ] | ||
215 | |||
216 | -} | ||
217 | diagRect :: (Storable t) => t -> Vector t -> Int -> Int -> Matrix t | ||
218 | diagRect z v r c = ST.runSTMatrix $ do | ||
219 | m <- ST.newMatrix z r c | ||
220 | let d = min r c `min` (dim v) | ||
221 | mapM_ (\k -> ST.writeMatrix m k k (v@>k)) [0..d-1] | ||
222 | return m | ||
223 | |||
224 | -- | extracts the diagonal from a rectangular matrix | ||
225 | takeDiag :: (Element t) => Matrix t -> Vector t | ||
226 | takeDiag m = fromList [flatten m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) -1]] | ||
227 | |||
228 | ------------------------------------------------------------ | ||
229 | |||
230 | {- | An easy way to create a matrix: | ||
231 | |||
232 | >>> (2><3)[2,4,7,-3,11,0] | ||
233 | (2><3) | ||
234 | [ 2.0, 4.0, 7.0 | ||
235 | , -3.0, 11.0, 0.0 ] | ||
236 | |||
237 | This is the format produced by the instances of Show (Matrix a), which | ||
238 | can also be used for input. | ||
239 | |||
240 | The input list is explicitly truncated, so that it can | ||
241 | safely be used with lists that are too long (like infinite lists). | ||
242 | |||
243 | >>> (2><3)[1..] | ||
244 | (2><3) | ||
245 | [ 1.0, 2.0, 3.0 | ||
246 | , 4.0, 5.0, 6.0 ] | ||
247 | |||
248 | |||
249 | -} | ||
250 | (><) :: (Storable a) => Int -> Int -> [a] -> Matrix a | ||
251 | r >< c = f where | ||
252 | f l | dim v == r*c = matrixFromVector RowMajor r c v | ||
253 | | otherwise = error $ "inconsistent list size = " | ||
254 | ++show (dim v) ++" in ("++show r++"><"++show c++")" | ||
255 | where v = fromList $ take (r*c) l | ||
256 | |||
257 | ---------------------------------------------------------------- | ||
258 | |||
259 | -- | Creates a matrix with the first n rows of another matrix | ||
260 | takeRows :: Element t => Int -> Matrix t -> Matrix t | ||
261 | takeRows n mt = subMatrix (0,0) (n, cols mt) mt | ||
262 | -- | Creates a copy of a matrix without the first n rows | ||
263 | dropRows :: Element t => Int -> Matrix t -> Matrix t | ||
264 | dropRows n mt = subMatrix (n,0) (rows mt - n, cols mt) mt | ||
265 | -- |Creates a matrix with the first n columns of another matrix | ||
266 | takeColumns :: Element t => Int -> Matrix t -> Matrix t | ||
267 | takeColumns n mt = subMatrix (0,0) (rows mt, n) mt | ||
268 | -- | Creates a copy of a matrix without the first n columns | ||
269 | dropColumns :: Element t => Int -> Matrix t -> Matrix t | ||
270 | dropColumns n mt = subMatrix (0,n) (rows mt, cols mt - n) mt | ||
271 | |||
272 | ---------------------------------------------------------------- | ||
273 | |||
274 | {- | Creates a 'Matrix' from a list of lists (considered as rows). | ||
275 | |||
276 | >>> fromLists [[1,2],[3,4],[5,6]] | ||
277 | (3><2) | ||
278 | [ 1.0, 2.0 | ||
279 | , 3.0, 4.0 | ||
280 | , 5.0, 6.0 ] | ||
281 | |||
282 | -} | ||
283 | fromLists :: Element t => [[t]] -> Matrix t | ||
284 | fromLists = fromRows . map fromList | ||
285 | |||
286 | -- | creates a 1-row matrix from a vector | ||
287 | -- | ||
288 | -- >>> asRow (fromList [1..5]) | ||
289 | -- (1><5) | ||
290 | -- [ 1.0, 2.0, 3.0, 4.0, 5.0 ] | ||
291 | -- | ||
292 | asRow :: Storable a => Vector a -> Matrix a | ||
293 | asRow v = reshape (dim v) v | ||
294 | |||
295 | -- | creates a 1-column matrix from a vector | ||
296 | -- | ||
297 | -- >>> asColumn (fromList [1..5]) | ||
298 | -- (5><1) | ||
299 | -- [ 1.0 | ||
300 | -- , 2.0 | ||
301 | -- , 3.0 | ||
302 | -- , 4.0 | ||
303 | -- , 5.0 ] | ||
304 | -- | ||
305 | asColumn :: Storable a => Vector a -> Matrix a | ||
306 | asColumn = trans . asRow | ||
307 | |||
308 | |||
309 | |||
310 | {- | creates a Matrix of the specified size using the supplied function to | ||
311 | to map the row\/column position to the value at that row\/column position. | ||
312 | |||
313 | @> buildMatrix 3 4 (\\(r,c) -> fromIntegral r * fromIntegral c) | ||
314 | (3><4) | ||
315 | [ 0.0, 0.0, 0.0, 0.0, 0.0 | ||
316 | , 0.0, 1.0, 2.0, 3.0, 4.0 | ||
317 | , 0.0, 2.0, 4.0, 6.0, 8.0]@ | ||
318 | |||
319 | Hilbert matrix of order N: | ||
320 | |||
321 | @hilb n = buildMatrix n n (\\(i,j)->1/(fromIntegral i + fromIntegral j +1))@ | ||
322 | |||
323 | -} | ||
324 | buildMatrix :: Element a => Int -> Int -> ((Int, Int) -> a) -> Matrix a | ||
325 | buildMatrix rc cc f = | ||
326 | fromLists $ map (map f) | ||
327 | $ map (\ ri -> map (\ ci -> (ri, ci)) [0 .. (cc - 1)]) [0 .. (rc - 1)] | ||
328 | |||
329 | ----------------------------------------------------- | ||
330 | |||
331 | fromArray2D :: (Storable e) => Array (Int, Int) e -> Matrix e | ||
332 | fromArray2D m = (r><c) (elems m) | ||
333 | where ((r0,c0),(r1,c1)) = bounds m | ||
334 | r = r1-r0+1 | ||
335 | c = c1-c0+1 | ||
336 | |||
337 | |||
338 | -- | rearranges the rows of a matrix according to the order given in a list of integers. | ||
339 | extractRows :: Element t => [Int] -> Matrix t -> Matrix t | ||
340 | extractRows [] m = emptyM 0 (cols m) | ||
341 | extractRows l m = fromRows $ extract (toRows m) l | ||
342 | where | ||
343 | extract l' is = [l'!!i | i<- map verify is] | ||
344 | verify k | ||
345 | | k >= 0 && k < rows m = k | ||
346 | | otherwise = error $ "can't extract row " | ||
347 | ++show k++" in list " ++ show l ++ " from matrix " ++ shSize m | ||
348 | |||
349 | -- | rearranges the rows of a matrix according to the order given in a list of integers. | ||
350 | extractColumns :: Element t => [Int] -> Matrix t -> Matrix t | ||
351 | extractColumns l m = trans . extractRows (map verify l) . trans $ m | ||
352 | where | ||
353 | verify k | ||
354 | | k >= 0 && k < cols m = k | ||
355 | | otherwise = error $ "can't extract column " | ||
356 | ++show k++" in list " ++ show l ++ " from matrix " ++ shSize m | ||
357 | |||
358 | |||
359 | |||
360 | {- | creates matrix by repetition of a matrix a given number of rows and columns | ||
361 | |||
362 | >>> repmat (ident 2) 2 3 | ||
363 | (4><6) | ||
364 | [ 1.0, 0.0, 1.0, 0.0, 1.0, 0.0 | ||
365 | , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0 | ||
366 | , 1.0, 0.0, 1.0, 0.0, 1.0, 0.0 | ||
367 | , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0 ] | ||
368 | |||
369 | -} | ||
370 | repmat :: (Element t) => Matrix t -> Int -> Int -> Matrix t | ||
371 | repmat m r c | ||
372 | | r == 0 || c == 0 = emptyM (r*rows m) (c*cols m) | ||
373 | | otherwise = fromBlocks $ replicate r $ replicate c $ m | ||
374 | |||
375 | -- | A version of 'liftMatrix2' which automatically adapt matrices with a single row or column to match the dimensions of the other matrix. | ||
376 | liftMatrix2Auto :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t | ||
377 | liftMatrix2Auto f m1 m2 | ||
378 | | compat' m1 m2 = lM f m1 m2 | ||
379 | | ok = lM f m1' m2' | ||
380 | | otherwise = error $ "nonconformable matrices in liftMatrix2Auto: " ++ shSize m1 ++ ", " ++ shSize m2 | ||
381 | where | ||
382 | (r1,c1) = size m1 | ||
383 | (r2,c2) = size m2 | ||
384 | r = max r1 r2 | ||
385 | c = max c1 c2 | ||
386 | r0 = min r1 r2 | ||
387 | c0 = min c1 c2 | ||
388 | ok = r0 == 1 || r1 == r2 && c0 == 1 || c1 == c2 | ||
389 | m1' = conformMTo (r,c) m1 | ||
390 | m2' = conformMTo (r,c) m2 | ||
391 | |||
392 | -- FIXME do not flatten if equal order | ||
393 | lM f m1 m2 = matrixFromVector | ||
394 | RowMajor | ||
395 | (max (rows m1) (rows m2)) | ||
396 | (max (cols m1) (cols m2)) | ||
397 | (f (flatten m1) (flatten m2)) | ||
398 | |||
399 | compat' :: Matrix a -> Matrix b -> Bool | ||
400 | compat' m1 m2 = s1 == (1,1) || s2 == (1,1) || s1 == s2 | ||
401 | where | ||
402 | s1 = size m1 | ||
403 | s2 = size m2 | ||
404 | |||
405 | ------------------------------------------------------------ | ||
406 | |||
407 | toBlockRows [r] m | r == rows m = [m] | ||
408 | toBlockRows rs m = map (reshape (cols m)) (takesV szs (flatten m)) | ||
409 | where szs = map (* cols m) rs | ||
410 | |||
411 | toBlockCols [c] m | c == cols m = [m] | ||
412 | toBlockCols cs m = map trans . toBlockRows cs . trans $ m | ||
413 | |||
414 | -- | Partition a matrix into blocks with the given numbers of rows and columns. | ||
415 | -- The remaining rows and columns are discarded. | ||
416 | toBlocks :: (Element t) => [Int] -> [Int] -> Matrix t -> [[Matrix t]] | ||
417 | toBlocks rs cs m = map (toBlockCols cs) . toBlockRows rs $ m | ||
418 | |||
419 | -- | Fully partition a matrix into blocks of the same size. If the dimensions are not | ||
420 | -- a multiple of the given size the last blocks will be smaller. | ||
421 | toBlocksEvery :: (Element t) => Int -> Int -> Matrix t -> [[Matrix t]] | ||
422 | toBlocksEvery r c m | ||
423 | | r < 1 || c < 1 = error $ "toBlocksEvery expects block sizes > 0, given "++show r++" and "++ show c | ||
424 | | otherwise = toBlocks rs cs m | ||
425 | where | ||
426 | (qr,rr) = rows m `divMod` r | ||
427 | (qc,rc) = cols m `divMod` c | ||
428 | rs = replicate qr r ++ if rr > 0 then [rr] else [] | ||
429 | cs = replicate qc c ++ if rc > 0 then [rc] else [] | ||
430 | |||
431 | ------------------------------------------------------------------- | ||
432 | |||
433 | -- Given a column number and a function taking matrix indexes, returns | ||
434 | -- a function which takes vector indexes (that can be used on the | ||
435 | -- flattened matrix). | ||
436 | mk :: Int -> ((Int, Int) -> t) -> (Int -> t) | ||
437 | mk c g = \k -> g (divMod k c) | ||
438 | |||
439 | {- | | ||
440 | |||
441 | >>> mapMatrixWithIndexM_ (\(i,j) v -> printf "m[%d,%d] = %.f\n" i j v :: IO()) ((2><3)[1 :: Double ..]) | ||
442 | m[0,0] = 1 | ||
443 | m[0,1] = 2 | ||
444 | m[0,2] = 3 | ||
445 | m[1,0] = 4 | ||
446 | m[1,1] = 5 | ||
447 | m[1,2] = 6 | ||
448 | |||
449 | -} | ||
450 | mapMatrixWithIndexM_ | ||
451 | :: (Element a, Num a, Monad m) => | ||
452 | ((Int, Int) -> a -> m ()) -> Matrix a -> m () | ||
453 | mapMatrixWithIndexM_ g m = mapVectorWithIndexM_ (mk c g) . flatten $ m | ||
454 | where | ||
455 | c = cols m | ||
456 | |||
457 | {- | | ||
458 | |||
459 | >>> mapMatrixWithIndexM (\(i,j) v -> Just $ 100*v + 10*fromIntegral i + fromIntegral j) (ident 3:: Matrix Double) | ||
460 | Just (3><3) | ||
461 | [ 100.0, 1.0, 2.0 | ||
462 | , 10.0, 111.0, 12.0 | ||
463 | , 20.0, 21.0, 122.0 ] | ||
464 | |||
465 | -} | ||
466 | mapMatrixWithIndexM | ||
467 | :: (Element a, Storable b, Monad m) => | ||
468 | ((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b) | ||
469 | mapMatrixWithIndexM g m = liftM (reshape c) . mapVectorWithIndexM (mk c g) . flatten $ m | ||
470 | where | ||
471 | c = cols m | ||
472 | |||
473 | {- | | ||
474 | |||
475 | >>> mapMatrixWithIndex (\\(i,j) v -> 100*v + 10*fromIntegral i + fromIntegral j) (ident 3:: Matrix Double) | ||
476 | (3><3) | ||
477 | [ 100.0, 1.0, 2.0 | ||
478 | , 10.0, 111.0, 12.0 | ||
479 | , 20.0, 21.0, 122.0 ] | ||
480 | |||
481 | -} | ||
482 | mapMatrixWithIndex | ||
483 | :: (Element a, Storable b) => | ||
484 | ((Int, Int) -> a -> b) -> Matrix a -> Matrix b | ||
485 | mapMatrixWithIndex g m = reshape c . mapVectorWithIndex (mk c g) . flatten $ m | ||
486 | where | ||
487 | c = cols m | ||
488 | |||
489 | mapMatrix :: (Storable a, Storable b) => (a -> b) -> Matrix a -> Matrix b | ||
490 | mapMatrix f = liftMatrix (mapVector f) | ||