ascii-table-0.3.0.2: ASCII table

Safe HaskellNone
LanguageHaskell2010

Data.AsciiTable

Contents

Description

Let's make a table!

> let Just (Value o1) = decode "{\"foo\": \"bar\"}"
> let Just (Value o2) = decode "{\"baz\": 5}"
> let Just (Value o3) = decode "{\"oink\": true}"

> let slice1 = [[Just o1, Just o3], [Just o2, Nothing]]
> let slice2 = [[Nothing, Just o1]]

> pretty (makeTable ["object 1", "object 2"] [slice1, slice2, slice1])
+-----------+------------+
| object 1  | object 2   |
|           |            |
| baz foo   | foo   oink |
+===========+============+
|     "bar" |       True |
| 5.0       |            |
+-----------+------------+
|           | "bar"      |
+-----------+------------+
|     "bar" |       True |
| 5.0       |            |
+-----------+------------+
Synopsis

Documentation

data Table Source #

An opaque data type with a Pretty instance, for printing to a console. Build a table with makeTable, and show it with the pretty-printing functions re-exported from this module.

Instances
Eq Table Source # 
Instance details

Defined in Data.AsciiTable

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Show Table Source # 
Instance details

Defined in Data.AsciiTable

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

Pretty Table Source # 
Instance details

Defined in Data.AsciiTable

Methods

pretty :: Table -> Doc e #

prettyList :: [Table] -> Doc e #

type TableRow a = [Maybe a] Source #

A single horizontal row of a Table. Each row is visually separated from the next by a vertical line. Each row in the table must contain the same number of elements (however, any number of them can be Nothing).

type TableSlice a = [TableRow a] Source #

A single horizontal slice of a Table, containing one or more TableRows. Each slice is visually separated from the next by a horizontal line.

makeTable Source #

Arguments

:: [String]

Headers

-> [TableSlice Object]

Table slices

-> Table 

Make a Table from a list of headers and a list of TableSlices, each of which contains a list of TableRows, each of which contain a list of Values. It is assumed that all dimensions align properly (e.g. each row contains the same number of elements, which is equal to the length of the list of headers).

Each top-level object is flattened into one column per leaf. Note that this means it is not possible to distinguish between e.g. {"foo":{"bar":5}} and {"foo.bar":5}. Hopefully this is not too much of a problem in practice.

Each vertically aligned element need not contain the same set of keys; for example, the table corresponding to

[ [{"foo": "bar"}], [{"baz": "qux"}] ] -- one TableSlice

will simply look like

+-------------+
| foo   baz   |
+=============+
| "bar"       |
|       "qux" |
+-------------+

That is, each missing value is simply not displayed.

makeTableWith Source #

Arguments

:: (Ord key, Hashable key) 
=> (Int -> header -> String)

Header rendering function

-> (Int -> header -> (Int, Int) -> key -> String)

Cell header rendering function

-> (Int -> header -> (Int, Int) -> key -> value -> String)

Cell rendering function

-> [header]

Headers

-> [TableSlice (HashMap key value)]

Table slices

-> Table 

Like makeTable, but takes explicit rendering functions. This is useful for adding ANSI escape codes to color output, or for rendering values depending on what their key is.

For example, you may wish to render Strings with a "timestamp" key without quotation marks.

The Int argument is the header's index. The (Int, Int) argument is the (absolute, relative) index of the key and value. Visually,

+-------------+-------------+
| 0           | 1           |
|             |             |
| (0,0) (1,1) | (2,0) (3,1) |
+=============+=============+
| (0,0) (1,1) | (2,0) (3,1) |
| (0,0) (1,1) | (2,0) (3,1) |
+-------------+-------------+

This function is (unfortunately) String-based as of 0.3.0.0, because the pretty printing and ANSI escape code functions are String-based, too.

Misc. helper functions

prettyValue :: Value -> String Source #

Pretty-print a Value in one line.

flattenObject :: Object -> Object Source #

Flatten an Value so that it contains no top-level Value values.

Re-exports

data Doc e #

The abstract data type Doc represents pretty documents.

Doc is an instance of the Show class. (show doc) pretty prints document doc with a page width of 100 characters and a ribbon width of 40 characters.

show (text "hello" `above` text "world")

Which would return the string "hello\nworld", i.e.

hello
world
Instances
Monad Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

(>>=) :: Doc a -> (a -> Doc b) -> Doc b #

(>>) :: Doc a -> Doc b -> Doc b #

return :: a -> Doc a #

fail :: String -> Doc a #

Functor Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

Applicative Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pure :: a -> Doc a #

(<*>) :: Doc (a -> b) -> Doc a -> Doc b #

liftA2 :: (a -> b -> c) -> Doc a -> Doc b -> Doc c #

(*>) :: Doc a -> Doc b -> Doc b #

(<*) :: Doc a -> Doc b -> Doc a #

Alternative Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

empty :: Doc a #

(<|>) :: Doc a -> Doc a -> Doc a #

some :: Doc a -> Doc [a] #

many :: Doc a -> Doc [a] #

MonadPlus Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

mzero :: Doc a #

mplus :: Doc a -> Doc a -> Doc a #

Plus Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

zero :: Doc a #

Alt Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

(<!>) :: Doc a -> Doc a -> Doc a #

some :: Applicative Doc => Doc a -> Doc [a] #

many :: Applicative Doc => Doc a -> Doc [a] #

Apply Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

(<.>) :: Doc (a -> b) -> Doc a -> Doc b #

(.>) :: Doc a -> Doc b -> Doc b #

(<.) :: Doc a -> Doc b -> Doc a #

liftF2 :: (a -> b -> c) -> Doc a -> Doc b -> Doc c #

Bind Doc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

(>>-) :: Doc a -> (a -> Doc b) -> Doc b #

join :: Doc (Doc a) -> Doc a #

Show (Doc e) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

showsPrec :: Int -> Doc e -> ShowS #

show :: Doc e -> String #

showList :: [Doc e] -> ShowS #

IsString (Doc e) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

fromString :: String -> Doc e #

Semigroup (Doc e) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

(<>) :: Doc e -> Doc e -> Doc e #

sconcat :: NonEmpty (Doc e) -> Doc e #

stimes :: Integral b => b -> Doc e -> Doc e #

Monoid (Doc e) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

mempty :: Doc e #

mappend :: Doc e -> Doc e -> Doc e #

mconcat :: [Doc e] -> Doc e #

Pretty (Doc a) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Doc a -> Doc e #

prettyList :: [Doc a] -> Doc e #

putDoc :: Doc e -> IO () #

The action (putDoc doc) pretty prints document doc to the standard output, with a page width of 100 characters and a ribbon width of 40 characters.

main :: IO ()
main = do{ putDoc (text "hello" <+> text "world") }

Which would output

hello world

hPutDoc :: Handle -> Doc e -> IO () #

(hPutDoc handle doc) pretty prints document doc to the file handle handle with a page width of 100 characters and a ribbon width of 40 characters.

main = do{ handle <- openFile "MyFile" WriteMode
         ; hPutDoc handle (vcat (map text
                           ["vertical","text"]))
         ; hClose handle
         }

class Pretty a where #

The member prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

Minimal complete definition

pretty

Methods

pretty :: a -> Doc e #

prettyList :: [a] -> Doc e #

Instances
Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Bool -> Doc e #

prettyList :: [Bool] -> Doc e #

Pretty Char 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Char -> Doc e #

prettyList :: [Char] -> Doc e #

Pretty Double 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Double -> Doc e #

prettyList :: [Double] -> Doc e #

Pretty Float 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Float -> Doc e #

prettyList :: [Float] -> Doc e #

Pretty Int 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Int -> Doc e #

prettyList :: [Int] -> Doc e #

Pretty Int8 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Int8 -> Doc e #

prettyList :: [Int8] -> Doc e #

Pretty Int16 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Int16 -> Doc e #

prettyList :: [Int16] -> Doc e #

Pretty Int32 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Int32 -> Doc e #

prettyList :: [Int32] -> Doc e #

Pretty Int64 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Int64 -> Doc e #

prettyList :: [Int64] -> Doc e #

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Integer -> Doc e #

prettyList :: [Integer] -> Doc e #

Pretty Natural 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Natural -> Doc e #

prettyList :: [Natural] -> Doc e #

Pretty Word 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word -> Doc e #

prettyList :: [Word] -> Doc e #

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word8 -> Doc e #

prettyList :: [Word8] -> Doc e #

Pretty Word16 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word16 -> Doc e #

prettyList :: [Word16] -> Doc e #

Pretty Word32 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word32 -> Doc e #

prettyList :: [Word32] -> Doc e #

Pretty Word64 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word64 -> Doc e #

prettyList :: [Word64] -> Doc e #

Pretty () 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: () -> Doc e #

prettyList :: [()] -> Doc e #

Pretty ByteString 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: ByteString -> Doc e #

prettyList :: [ByteString] -> Doc e #

Pretty ByteString 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: ByteString -> Doc e #

prettyList :: [ByteString] -> Doc e #

Pretty Text 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Text -> Doc e #

prettyList :: [Text] -> Doc e #

Pretty Text 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Text -> Doc e #

prettyList :: [Text] -> Doc e #

Pretty Table Source # 
Instance details

Defined in Data.AsciiTable

Methods

pretty :: Table -> Doc e #

prettyList :: [Table] -> Doc e #

Pretty a => Pretty [a] 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: [a] -> Doc e #

prettyList :: [[a]] -> Doc e #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Maybe a -> Doc e #

prettyList :: [Maybe a] -> Doc e #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: NonEmpty a -> Doc e #

prettyList :: [NonEmpty a] -> Doc e #

Pretty a => Pretty (Seq a) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Seq a -> Doc e #

prettyList :: [Seq a] -> Doc e #

Pretty (Doc a) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Doc a -> Doc e #

prettyList :: [Doc a] -> Doc e #

(Pretty a, Pretty b) => Pretty (a, b) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: (a, b) -> Doc e #

prettyList :: [(a, b)] -> Doc e #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: (a, b, c) -> Doc e #

prettyList :: [(a, b, c)] -> Doc e #

data SimpleDoc e #

The data type SimpleDoc represents rendered documents and is used by the display functions.

The Int in SText contains the length of the string. The Int in SLine contains the indentation for that line. The library provides two default display functions displayS and displayIO. You can provide your own display function by writing a function from a SimpleDoc to your own output format.

Instances
Functor SimpleDoc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

fmap :: (a -> b) -> SimpleDoc a -> SimpleDoc b #

(<$) :: a -> SimpleDoc b -> SimpleDoc a #

Foldable SimpleDoc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

fold :: Monoid m => SimpleDoc m -> m #

foldMap :: Monoid m => (a -> m) -> SimpleDoc a -> m #

foldr :: (a -> b -> b) -> b -> SimpleDoc a -> b #

foldr' :: (a -> b -> b) -> b -> SimpleDoc a -> b #

foldl :: (b -> a -> b) -> b -> SimpleDoc a -> b #

foldl' :: (b -> a -> b) -> b -> SimpleDoc a -> b #

foldr1 :: (a -> a -> a) -> SimpleDoc a -> a #

foldl1 :: (a -> a -> a) -> SimpleDoc a -> a #

toList :: SimpleDoc a -> [a] #

null :: SimpleDoc a -> Bool #

length :: SimpleDoc a -> Int #

elem :: Eq a => a -> SimpleDoc a -> Bool #

maximum :: Ord a => SimpleDoc a -> a #

minimum :: Ord a => SimpleDoc a -> a #

sum :: Num a => SimpleDoc a -> a #

product :: Num a => SimpleDoc a -> a #

Traversable SimpleDoc 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

traverse :: Applicative f => (a -> f b) -> SimpleDoc a -> f (SimpleDoc b) #

sequenceA :: Applicative f => SimpleDoc (f a) -> f (SimpleDoc a) #

mapM :: Monad m => (a -> m b) -> SimpleDoc a -> m (SimpleDoc b) #

sequence :: Monad m => SimpleDoc (m a) -> m (SimpleDoc a) #

renderPretty :: Float -> Int -> Doc e -> SimpleDoc e #

This is the default pretty printer which is used by show, putDoc and hPutDoc. (renderPretty ribbonfrac width x) renders document x with a page width of width and a ribbon width of (ribbonfrac * width) characters. The ribbon width is the maximal amount of non-indentation characters on a line. The parameter ribbonfrac should be between 0.0 and 1.0. If it is lower or higher, the ribbon width will be 0 or width respectively.

renderCompact :: Doc e -> SimpleDoc e #

(renderCompact x) renders document x without adding any indentation. Since no 'pretty' printing is involved, this renderer is very fast. The resulting output contains fewer characters than a pretty printed version and can be used for output that is read by other programs.

renderSmart :: Int -> Doc e -> SimpleDoc e #

A slightly smarter rendering algorithm with more lookahead. It provides provide earlier breaking on deeply nested structures. For example, consider this python-ish pseudocode: fun(fun(fun(fun(fun([abcdefg, abcdefg]))))) If we put a softbreak (+ nesting 2) after each open parenthesis, and align the elements of the list to match the opening brackets, this will render with renderPretty and a page width of 20c as: fun(fun(fun(fun(fun([ | abcdef, | abcdef, ] ))))) | Where the 20c. boundary has been marked with |. Because renderPretty only uses one-line lookahead, it sees that the first line fits, and is stuck putting the second and third lines after the 20c mark. In contrast, renderSmart will continue to check the potential document up to the end of the indentation level. Thus, it will format the document as:

fun(                |
  fun(              |
    fun(            |
      fun(          |
        fun([       |
              abcdef,
              abcdef,
            ]       |
  )))))             |

Which fits within the 20c. mark. In addition, renderSmart uses this lookahead to minimize the number of lines printed, leading to more compact and visually appealing output. Consider this example using the same syntax as above: aaaaaaaaaaa([abc, def, ghi]) When rendered with renderPretty and a page width of 20c, we get: aaaaaaaaaaa([ abc , def , ghi ]) Whereas when rendered with renderSmart and a page width of 20c, we get: aaaaaaaaaaa( [abc, def, ghi])

displayS :: SimpleDoc e -> ShowS #

(displayS simpleDoc) takes the output simpleDoc from a rendering function and transforms it to a ShowS type (for use in the Show class).

showWidth :: Int -> Doc -> String
showWidth w x   = displayS (renderPretty 0.4 w x) ""

displayIO :: Handle -> SimpleDoc e -> IO () #

(displayIO handle simpleDoc) writes simpleDoc to the file handle handle. This function is used for example by hPutDoc:

hPutDoc handle doc  = displayIO handle (renderPretty 0.4 100 doc)