pptable-0.3.0.0: Pretty Print containers in a tabular format

Safe HaskellNone
LanguageHaskell2010

Text.PrettyPrint.Tabulate

Description

Module implements the default methods for Tabulate All examples listed in the document need the following language pragmas and following modules imported

{#- LANGUAGE MultiParamTypeClasses}
{#- LANGUAGE DeriveGeneric}
{#- LANGUAGE DeriveDataTypeable}

import qualified GHC.Generics as G
import Data.Data

Synopsis

Documentation

class Tabulate a flag | a -> flag Source #

Class instance that needs to be instantiated for each record that needs to be printed using printTable

data Stock = Stock {price:: Double, name:: String} derive (Show, G.Generic, Data)
instance Tabulate S ExpandWhenNested

If S is embedded inside another Record type and should be displayed in regular Record Syntax, then

instance Tabulate S DoNotExpandWhenNested

Instances

(~) * flag DoNotExpandWhenNested => Tabulate a flag Source # 

class Boxable b where Source #

Methods

printTable :: (Generic a, GRecordMeta (Rep a)) => b a -> IO () Source #

Used to print a container of Records in a tabular format.

data Stock = Stock {price:: Double, ticker:: String} deriving (Show, Data, G.Generic)
instance Tabulate Stock DoNotExpandWhenNested
-- this can be a Vector or Map
let s =  [Stock 10.0 "yahoo", Stock 12.0 "goog", Stock 10.0 "amz"]
T.printTable s

Nested records can also be printed in tabular format

data FxCode = USD | EUR deriving (Show, Data, G.Generic)
instance CellValueFormatter FxCode

data Price = Price {px:: Double, fxCode:: FxCode} deriving (Show, Data, G.Generic)
instance Tabulate Price ExpandWhenNested
-- since Price will be nested, it also needs an instance of
-- CellValueFormatter
instance CellValueFormatter Price

data Stock = Stock {ticker:: String, price:: Price} deriving (Show, Data, G.Generic)
instance Tabulate Stock DoNotExpandWhenNested

-- this can be a Vector or Map
let s =  [Stock "yahoo" (Price 10.0 USD), Stock "ikea" (Price 11.0 EUR)]
printTable s

renderTable :: (Generic a, GRecordMeta (Rep a)) => b a -> Box Source #

Similar to printTable but rather than return IO (), returns a Box object that can be printed later on, using printBox

printTableWithFlds :: [DisplayFld t] -> b t -> IO () Source #

Used for printing selected fields from Record types This is useful when Records have a large number of fields and only few fields need to be introspected at any time.

Using the example provided under printTables,

printTableWithFlds [DFld (px . price), DFld ticker] s

renderTableWithFlds :: [DisplayFld t] -> b t -> Box Source #

Same as printTableWithFlds but returns a Box object, rather than returning an `IO ()`.

Instances

Boxable [] Source #

Instance methods to render or print a list of records in a tabular format.

Methods

printTable :: (Generic a, GRecordMeta (Rep a)) => [a] -> IO () Source #

renderTable :: (Generic a, GRecordMeta (Rep a)) => [a] -> Box Source #

printTableWithFlds :: [DisplayFld t] -> [t] -> IO () Source #

renderTableWithFlds :: [DisplayFld t] -> [t] -> Box Source #

Boxable Vector Source # 

Methods

printTable :: (Generic a, GRecordMeta (Rep a)) => Vector a -> IO () Source #

renderTable :: (Generic a, GRecordMeta (Rep a)) => Vector a -> Box Source #

printTableWithFlds :: [DisplayFld t] -> Vector t -> IO () Source #

renderTableWithFlds :: [DisplayFld t] -> Vector t -> Box Source #

CellValueFormatter k => Boxable (Map k) Source # 

Methods

printTable :: (Generic a, GRecordMeta (Rep a)) => Map k a -> IO () Source #

renderTable :: (Generic a, GRecordMeta (Rep a)) => Map k a -> Box Source #

printTableWithFlds :: [DisplayFld t] -> Map k t -> IO () Source #

renderTableWithFlds :: [DisplayFld t] -> Map k t -> Box Source #

class CellValueFormatter a Source #

Class that implements formatting using printf. Default instances for String, Char, Int, Integer, Double and Float are provided. For types that are not an instance of this class show is used.

data ExpandWhenNested Source #

Use this flag to expand a Record Type as a table when nested inside another record.

data DoNotExpandWhenNested Source #

Use this flag to not expand a Record type as a table when nested inside another record. The Show instance of the nested record is used by default without expanding. This means that the fields of the nested record are not displayed as separate headers.

data DisplayFld a Source #

Constructors

CellValueFormatter s => DFld (a -> s)