colonnade-0.4.7: Generic types and functions for columnar encoding and decoding

Safe HaskellNone
LanguageHaskell2010

Colonnade.Encoding

Contents

Description

Build backend-agnostic columnar encodings that can be used to visualize data.

Synopsis

Example

First, let's bring in some neccessary imports that will be used for the remainder of the examples in the docs:

>>> import Data.Monoid (mconcat,(<>))
>>> import Data.Functor.Contravariant (contramap)

Assume that the data we wish to encode is:

>>> data Color = Red | Green | Blue deriving (Show,Eq)
>>> data Person = Person { name :: String, age :: Int }
>>> data House = House { color :: Color, price :: Int }

One potential columnar encoding of a Person would be:

>>> :{
let encodingPerson :: Encoding Headed String Person
    encodingPerson = mconcat
      [ headed "Name" name
      , headed "Age" (show . age)
      ]
:}

The type signature on basicPersonEncoding is not neccessary but is included for clarity. We can feed data into this encoding to build a table:

>>> let people = [Person "David" 63, Person "Ava" 34, Person "Sonia" 12]
>>> putStr (ascii encodingPerson people)
+-------+-----+
| Name  | Age |
+-------+-----+
| David | 63  |
| Ava   | 34  |
| Sonia | 12  |
+-------+-----+

Similarly, we can build a table of houses with:

>>> let showDollar = (('$':) . show) :: Int -> String
>>> :{
let encodingHouse :: Encoding Headed String House
    encodingHouse = mconcat
      [ headed "Color" (show . color)
      , headed "Price" (showDollar . price)
      ]
:}
>>> let houses = [House Green 170000, House Blue 115000, House Green 150000]
>>> putStr (ascii encodingHouse houses)
+-------+---------+
| Color | Price   |
+-------+---------+
| Green | $170000 |
| Blue  | $115000 |
| Green | $150000 |
+-------+---------+

headed :: c -> (a -> c) -> Encoding Headed c a Source #

A single column with a header.

headless :: (a -> c) -> Encoding Headless c a Source #

A single column without a header.

Transform

fromMaybe :: c -> Encoding f c a -> Encoding f c (Maybe a) Source #

Lift a column over a Maybe. For example, if some people have houses and some do not, the data that pairs them together could be represented as:

>>> :{
>>> let owners :: [(Person,Maybe House)]
>>> owners =
>>> [ (Person "Jordan" 18, Nothing)
>>> , (Person "Ruth" 25, Just (House Red 125000))
>>> , (Person "Sonia" 12, Just (House Green 145000))
>>> ]
>>> :}

The column encodings defined earlier can be reused with the help of fromMaybe:

>>> :{
>>> let encodingOwners :: Encoding Headed String (Person,Maybe House)
>>> encodingOwners = mconcat
>>> [ contramap fst encodingPerson
>>> , contramap snd (fromMaybe "" encodingHouse)
>>> ]
>>> :}
>>> putStr (ascii encodingOwners owners)
+--------+-----+-------+---------+
| Name   | Age | Color | Price   |
+--------+-----+-------+---------+
| Jordan | 18  |       |         |
| Ruth   | 25  | Red   | $125000 |
| Sonia  | 12  | Green | $145000 |
+--------+-----+-------+---------+

columns Source #

Arguments

:: Foldable g 
=> (b -> a -> c)

Cell content function

-> (b -> f c)

Header content function

-> g b

Basis for column encodings

-> Encoding f c a 

Convert a collection of b values into a columnar encoding of the same size. Suppose we decide to show a house's color by putting a check mark in the column corresponding to the color instead of by writing out the name of the color:

>>> let allColors = [Red,Green,Blue]
>>> let encColor = columns (\c1 c2 -> if c1 == c2 then "✓" else "") (Headed . show) allColors
>>> :t encColor
encColor :: Encoding Headed [Char] Color
>>> let encHouse = headed "Price" (showDollar . price) <> contramap color encColor
>>> :t encHouse
encHouse :: Encoding Headed [Char] House
>>> putStr (ascii encHouse houses)
+---------+-----+-------+------+
| Price   | Red | Green | Blue |
+---------+-----+-------+------+
| $170000 |     | ✓     |      |
| $115000 |     |       | ✓    |
| $150000 |     | ✓     |      |
+---------+-----+-------+------+

bool Source #

Arguments

:: f c

Heading

-> (a -> Bool)

Predicate

-> (a -> c)

Contents when predicate is false

-> (a -> c)

Contents when predicate is true

-> Encoding f c a 

replaceWhen :: c -> (a -> Bool) -> Encoding f c a -> Encoding f c a Source #

mapContent :: Functor f => (c1 -> c2) -> Encoding f c1 a -> Encoding f c2 a Source #

Encoding is covariant in its content type. Consequently, it can be mapped over. There is no standard typeclass for types that are covariant in their second-to-last argument, so this function is provided for situations that require this.

Render

runRow :: (c1 -> c2) -> Encoding f c1 a -> a -> Vector c2 Source #

Consider providing a variant the produces a list instead. It may allow more things to get inlined in to a loop.

runRowMonadic :: (Monad m, Monoid b) => Encoding f content a -> (content -> m b) -> a -> m b Source #

runRowMonadic_ :: Monad m => Encoding f content a -> (content -> m b) -> a -> m () Source #

runRowMonadicWith :: Monad m => b -> (b -> b -> b) -> Encoding f content a -> (content -> m b) -> a -> m b Source #

runHeader :: (c1 -> c2) -> Encoding Headed c1 a -> Vector c2 Source #

runHeaderMonadic :: (Monad m, Monoid b) => Encoding Headed content a -> (content -> m b) -> m b Source #

runHeaderMonadic_ :: Monad m => Encoding Headed content a -> (content -> m b) -> m () Source #

runHeaderMonadicGeneral :: (Monad m, Monoid b, Foldable h) => Encoding h content a -> (content -> m b) -> m b Source #

This function is a helper for abusing Foldable to optionally render a header. Its future is uncertain.

runHeaderMonadicGeneral_ :: (Monad m, Monoid b, Foldable h) => Encoding h content a -> (content -> m b) -> m () Source #

runBothMonadic_ :: Monad m => Encoding Headed content a -> (content -> content -> m b) -> a -> m () Source #

Ascii Table

ascii Source #

Arguments

:: Foldable f 
=> Encoding Headed String a

columnar encoding

-> f a

rows

-> String 

Render a collection of rows as an ascii table. The table's columns are specified by the given Encoding. This implementation is inefficient and does not provide any wrapping behavior. It is provided so that users can try out colonnade in ghci and so that doctest can verify examples code in the haddocks.