module Data.Packed.Matrix (
Matrix,
Element,
rows,cols,
(><),
trans,
reshape, flatten,
fromLists, toLists, buildMatrix,
(@@>),
asRow, asColumn,
fromRows, toRows, fromColumns, toColumns,
fromBlocks, diagBlock, toBlocks, toBlocksEvery,
repmat,
flipud, fliprl,
subMatrix, takeRows, dropRows, takeColumns, dropColumns,
extractRows,
diagRect, takeDiag,
mapMatrix, mapMatrixWithIndex, mapMatrixWithIndexM, mapMatrixWithIndexM_,
liftMatrix, liftMatrix2, liftMatrix2Auto,fromArray2D
) where
import Data.Packed.Internal
import qualified Data.Packed.ST as ST
import Data.Array
import Data.List(transpose,intersperse)
import Foreign.Storable(Storable)
import Control.Monad(liftM)
#ifdef BINARY
import Data.Binary
import Control.Monad(replicateM)
instance (Binary a, Element a, Storable a) => Binary (Matrix a) where
put m = do
let r = rows m
let c = cols m
put r
put c
mapM_ (\i -> mapM_ (\j -> put $ m @@> (i,j)) [0..(c1)]) [0..(r1)]
get = do
r <- get
c <- get
xs <- replicateM r $ replicateM c get
return $ fromLists xs
#endif
instance (Show a, Element a) => (Show (Matrix a)) where
show m = (sizes++) . dsp . map (map show) . toLists $ m
where sizes = "("++show (rows m)++"><"++show (cols m)++")\n"
dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp
where
mt = transpose as
longs = map (maximum . map length) mt
mtp = zipWith (\a b -> map (pad a) b) longs mt
pad n str = replicate (n length str) ' ' ++ str
unwords' = concat . intersperse ", "
instance (Element a, Read a) => Read (Matrix a) where
readsPrec _ s = [((rs><cs) . read $ listnums, rest)]
where (thing,rest) = breakAt ']' s
(dims,listnums) = breakAt ')' thing
cs = read . init . fst. breakAt ')' . snd . breakAt '<' $ dims
rs = read . snd . breakAt '(' .init . fst . breakAt '>' $ dims
breakAt c l = (a++[c],tail b) where
(a,b) = break (==c) l
joinVert :: Element t => [Matrix t] -> Matrix t
joinVert ms = case common cols ms of
Nothing -> error "(impossible) joinVert on matrices with different number of columns"
Just c -> reshape c $ join (map flatten ms)
joinHoriz :: Element t => [Matrix t] -> Matrix t
joinHoriz ms = trans. joinVert . map trans $ ms
fromBlocks :: Element t => [[Matrix t]] -> Matrix t
fromBlocks = fromBlocksRaw . adaptBlocks
fromBlocksRaw mms = joinVert . map joinHoriz $ mms
adaptBlocks ms = ms' where
bc = case common length ms of
Just c -> c
Nothing -> error "fromBlocks requires rectangular [[Matrix]]"
rs = map (compatdim . map rows) ms
cs = map (compatdim . map cols) (transpose ms)
szs = sequence [rs,cs]
ms' = splitEvery bc $ zipWith g szs (concat ms)
g [Just nr,Just nc] m
| nr == r && nc == c = m
| r == 1 && c == 1 = reshape nc (constantD x (nr*nc))
| r == 1 = fromRows (replicate nr (flatten m))
| otherwise = fromColumns (replicate nc (flatten m))
where
r = rows m
c = cols m
x = m@@>(0,0)
g _ _ = error "inconsistent dimensions in fromBlocks"
diagBlock :: (Element t, Num t) => [Matrix t] -> Matrix t
diagBlock ms = fromBlocks $ zipWith f ms [0..]
where
f m k = take n $ replicate k z ++ m : repeat z
n = length ms
z = (1><1) [0]
flipud :: Element t => Matrix t -> Matrix t
flipud m = fromRows . reverse . toRows $ m
fliprl :: Element t => Matrix t -> Matrix t
fliprl m = fromColumns . reverse . toColumns $ m
diagRect :: (Storable t) => t -> Vector t -> Int -> Int -> Matrix t
diagRect z v r c = ST.runSTMatrix $ do
m <- ST.newMatrix z r c
let d = min r c `min` (dim v)
mapM_ (\k -> ST.writeMatrix m k k (v@>k)) [0..d1]
return m
takeDiag :: (Element t) => Matrix t -> Vector t
takeDiag m = fromList [flatten m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) 1]]
(><) :: (Storable a) => Int -> Int -> [a] -> Matrix a
r >< c = f where
f l | dim v == r*c = matrixFromVector RowMajor c v
| otherwise = error $ "inconsistent list size = "
++show (dim v) ++" in ("++show r++"><"++show c++")"
where v = fromList $ take (r*c) l
takeRows :: Element t => Int -> Matrix t -> Matrix t
takeRows n mt = subMatrix (0,0) (n, cols mt) mt
dropRows :: Element t => Int -> Matrix t -> Matrix t
dropRows n mt = subMatrix (n,0) (rows mt n, cols mt) mt
takeColumns :: Element t => Int -> Matrix t -> Matrix t
takeColumns n mt = subMatrix (0,0) (rows mt, n) mt
dropColumns :: Element t => Int -> Matrix t -> Matrix t
dropColumns n mt = subMatrix (0,n) (rows mt, cols mt n) mt
fromLists :: Element t => [[t]] -> Matrix t
fromLists = fromRows . map fromList
asRow :: Storable a => Vector a -> Matrix a
asRow v = reshape (dim v) v
asColumn :: Storable a => Vector a -> Matrix a
asColumn v = reshape 1 v
buildMatrix :: Element a => Int -> Int -> ((Int, Int) -> a) -> Matrix a
buildMatrix rc cc f =
fromLists $ map (map f)
$ map (\ ri -> map (\ ci -> (ri, ci)) [0 .. (cc 1)]) [0 .. (rc 1)]
fromArray2D :: (Storable e) => Array (Int, Int) e -> Matrix e
fromArray2D m = (r><c) (elems m)
where ((r0,c0),(r1,c1)) = bounds m
r = r1r0+1
c = c1c0+1
extractRows :: Element t => [Int] -> Matrix t -> Matrix t
extractRows l m = fromRows $ extract (toRows m) l
where extract l' is = [l'!!i |i<-is]
repmat :: (Element t) => Matrix t -> Int -> Int -> Matrix t
repmat m r c = fromBlocks $ splitEvery c $ replicate (r*c) m
liftMatrix2Auto :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
liftMatrix2Auto f m1 m2
| compat' m1 m2 = lM f m1 m2
| ok = lM f m1' m2'
| otherwise = error $ "nonconformable matrices in liftMatrix2Auto: " ++ shSize m1 ++ ", " ++ shSize m2
where
(r1,c1) = size m1
(r2,c2) = size m2
r = max r1 r2
c = max c1 c2
r0 = min r1 r2
c0 = min c1 c2
ok = r0 == 1 || r1 == r2 && c0 == 1 || c1 == c2
m1' = conformMTo (r,c) m1
m2' = conformMTo (r,c) m2
lM f m1 m2 = reshape (max (cols m1) (cols m2)) (f (flatten m1) (flatten m2))
compat' :: Matrix a -> Matrix b -> Bool
compat' m1 m2 = s1 == (1,1) || s2 == (1,1) || s1 == s2
where
s1 = size m1
s2 = size m2
toBlockRows [r] m | r == rows m = [m]
toBlockRows rs m = map (reshape (cols m)) (takesV szs (flatten m))
where szs = map (* cols m) rs
toBlockCols [c] m | c == cols m = [m]
toBlockCols cs m = map trans . toBlockRows cs . trans $ m
toBlocks :: (Element t) => [Int] -> [Int] -> Matrix t -> [[Matrix t]]
toBlocks rs cs m = map (toBlockCols cs) . toBlockRows rs $ m
toBlocksEvery :: (Element t) => Int -> Int -> Matrix t -> [[Matrix t]]
toBlocksEvery r c m = toBlocks rs cs m where
(qr,rr) = rows m `divMod` r
(qc,rc) = cols m `divMod` c
rs = replicate qr r ++ if rr > 0 then [rr] else []
cs = replicate qc c ++ if rc > 0 then [rc] else []
mk :: Int -> ((Int, Int) -> t) -> (Int -> t)
mk c g = \k -> g (divMod k c)
mapMatrixWithIndexM_
:: (Element a, Num a, Monad m) =>
((Int, Int) -> a -> m ()) -> Matrix a -> m ()
mapMatrixWithIndexM_ g m = mapVectorWithIndexM_ (mk c g) . flatten $ m
where
c = cols m
mapMatrixWithIndexM
:: (Element a, Storable b, Monad m) =>
((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b)
mapMatrixWithIndexM g m = liftM (reshape c) . mapVectorWithIndexM (mk c g) . flatten $ m
where
c = cols m
mapMatrixWithIndex
:: (Element a, Storable b) =>
((Int, Int) -> a -> b) -> Matrix a -> Matrix b
mapMatrixWithIndex g m = reshape c . mapVectorWithIndex (mk c g) . flatten $ m
where
c = cols m
mapMatrix :: (Storable a, Storable b) => (a -> b) -> Matrix a -> Matrix b
mapMatrix f = liftMatrix (mapVector f)