module Text.PrettyPrint.Tabulate
(
Tabulate(..)
, Boxable(..)
, CellValueFormatter
)where
import Data.Data
import Data.Typeable
import Data.Generics.Aliases
import GHC.Generics as G
import GHC.Show
import qualified Data.Map as Map
import qualified Text.PrettyPrint.Boxes as B
import qualified Data.List as List
import Text.Printf
import qualified Data.Vector as V
data TablizeValueFormat = T {floatValueFormat::Maybe (Float -> String),
stringValueFormat::Maybe (String -> String),
integerValueFormat::Maybe (Integer -> String),
intValueFormat::Maybe (Int -> String),
doubleValueFormat::Maybe (Double -> String)}
getDefaultTabulateValueFormat = T {floatValueFormat=Nothing,
stringValueFormat=Nothing,
integerValueFormat=Nothing,
intValueFormat=Nothing,
doubleValueFormat=Nothing}
class GTabulate f where
gprintTable :: f a -> [B.Box]
gprintTableWithStyle :: TablizeValueFormat -> f a -> [B.Box]
instance GTabulate U1 where
gprintTable _ = []
gprintTableWithStyle _ _ = []
instance (GTabulate a, GTabulate b) => GTabulate (a :*: b) where
gprintTable (a :*: b) = gprintTable a ++ gprintTable b
gprintTableWithStyle style (a :*: b) = gprintTableWithStyle style a ++ gprintTableWithStyle style b
instance (GTabulate a, GTabulate b) => GTabulate (a :+: b) where
gprintTable (L1 x) = gprintTable x
gprintTable (R1 x) = gprintTable x
gprintTableWithStyle style (L1 x) = gprintTableWithStyle style x
gprintTableWithStyle style (R1 x) = gprintTableWithStyle style x
instance (GTabulate a) => GTabulate (M1 i c a) where
gprintTable (M1 x) = gprintTable x
gprintTableWithStyle style (M1 x) = gprintTableWithStyle style x
instance (CellValueFormatter a) => GTabulate (K1 i a) where
gprintTable (K1 x) = [B.text $ ppFormatter x]
gprintTableWithStyle style (K1 x) = [B.text $ ppFormatterWithStyle style x]
class CellValueFormatter a where
ppFormatter :: a -> String
ppFormatterWithStyle :: TablizeValueFormat -> a -> String
default ppFormatter :: (Show a) => a -> String
ppFormatter x = show x
default ppFormatterWithStyle :: (Show a) => TablizeValueFormat -> a -> String
ppFormatterWithStyle _ x = "default_" ++ show x
instance CellValueFormatter Integer where
ppFormatter x = printf "%d" x
ppFormatterWithStyle style x = case integerValueFormat style of
Just f -> f x
Nothing -> ppFormatter x
instance CellValueFormatter Int where
ppFormatter x = printf "%d" x
ppFormatterWithStyle style x = case intValueFormat style of
Just f -> f x
Nothing -> ppFormatter x
instance CellValueFormatter Float where
ppFormatter x = printf "%14.9g" x
ppFormatterWithStyle style x = case floatValueFormat style of
Just f -> f x
Nothing -> ppFormatter x
instance CellValueFormatter String where
ppFormatter x = printf "%s" x
ppFormatterWithStyle style x = case stringValueFormat style of
Just f -> f x
Nothing -> ppFormatter x
instance CellValueFormatter Double where
ppFormatter x = printf "%14.9g" x
ppFormatterWithStyle style x = case doubleValueFormat style of
Just f -> f x
Nothing -> ppFormatter x
instance CellValueFormatter Bool
alignBox :: [[B.Box]] -> B.Box
alignBox b = B.hsep 5 B.left cols
where
cols = List.map (B.vcat B.left) $ List.transpose b
isAlgRepConstr t = case dataTypeRep . dataTypeOf $ t of
AlgRep [_] -> True
_ -> False
class Boxable b where
toBox :: (Data a, G.Generic a, GTabulate(Rep a)) => b a -> [[B.Box]]
printTable :: (Data a, G.Generic a, GTabulate(Rep a)) => b a -> IO ()
instance Boxable [] where
toBox a = case a of
[] -> [[B.nullBox]]
x:xs -> gprintTable (from x):toBox xs
printTable m = do
let r = head $ m
let header = constrFields . toConstr $ r
let header_box = List.map (B.text) header
B.printBox $ alignBox $ header_box:toBox m
instance Boxable V.Vector where
toBox v = V.toList $ fmap (\x -> (gprintTable (from x))) v
printTable m = do
let r = m V.! 0
let header = constrFields . toConstr $ r
let header_box = List.map (B.text) header
B.printBox $ alignBox $ header_box:toBox m
instance (Show k) => Boxable (Map.Map k) where
toBox m = Map.elems
(Map.mapWithKey
(\k v -> B.text (show k):gprintTable (from v))
m)
printTable m = do
let r = head . Map.elems $ m
let header = constrFields . toConstr $ r
let header_box = "Key":List.map (B.text) header
B.printBox $ alignBox $ header_box:toBox m
class (Data a) => Tabulate a where
ppTable :: (Boxable f) => f a -> IO()
default ppTable :: (Boxable f, G.Generic a, GTabulate (Rep a)) => f a -> IO ()
ppTable x = printTable x