module Statistics.Matrix.Types
(
Vector
, MVector
, Matrix(..)
, MMatrix(..)
, debug
) where
import Data.Char (isSpace)
import Numeric (showFFloat)
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as M
type Vector = U.Vector Double
type MVector s = M.MVector s Double
data Matrix = Matrix {
rows :: {-# UNPACK #-} !Int
, cols :: {-# UNPACK #-} !Int
, _vector :: !Vector
} deriving (Eq)
data MMatrix s = MMatrix
{-# UNPACK #-} !Int
{-# UNPACK #-} !Int
!(MVector s)
instance Show Matrix where
show = debug
debug :: Matrix -> String
debug (Matrix r c vs) = unlines $ zipWith (++) (hdr0 : repeat hdr) rrows
where
rrows = map (cleanEnd . unwords) . split $ zipWith (++) ldone tdone
hdr0 = show (r,c) ++ " "
hdr = replicate (length hdr0) ' '
pad plus k xs = replicate (k - length xs) ' ' `plus` xs
ldone = map (pad (++) (longest lstr)) lstr
tdone = map (pad (flip (++)) (longest tstr)) tstr
(lstr, tstr) = unzip . map (break (=='.') . render) . U.toList $ vs
longest = maximum . map length
render k = reverse . dropWhile (=='.') . dropWhile (=='0') . reverse .
showFFloat (Just 4) k $ ""
split [] = []
split xs = i : split rest where (i, rest) = splitAt c xs
cleanEnd = reverse . dropWhile isSpace . reverse