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

Safe HaskellNone
LanguageHaskell2010

Colonnade

Contents

Description

Build backend-agnostic columnar encodings that can be used to visualize tabular 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)

The data types we wish to encode are:

>>> 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 colPerson :: Colonnade Headed String Person
    colPerson = mconcat
      [ headed "Name" name
      , headed "Age" (show . age)
      ]
:}

The type signature on colPerson 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 colPerson 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 :: Colonnade 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 |
+-------+---------+

data Colonnade h c a Source #

An columnar encoding of a. The type variable h determines what is present in each column in the header row. It is typically instantiated to Headed and occasionally to Headless. There is nothing that restricts it to these two types, although they satisfy the majority of use cases. The type variable c is the content type. This can be Text, String, or ByteString. In the companion libraries reflex-dom-colonnade and yesod-colonnade, additional types that represent HTML with element attributes are provided that serve as the content type. Presented more visually:

            +---- Content (Text, ByteString, Html, etc.)
            |
            v
Colonnade h c a
          ^   ^
          |   |
          |   +-- Value consumed to build a row
          |
          +------ Headedness (Headed or Headless)

Internally, a Colonnade is represented as a Vector of individual column encodings. It is possible to use any collection type with Alternative and Foldable instances. However, Vector was chosen to optimize the data structure for the use case of building the structure once and then folding over it many times. It is recommended that Colonnades are defined at the top-level so that GHC avoids reconstructing them every time they are used.

Instances

Divisible (Colonnade h content) Source # 

Methods

divide :: (a -> (b, c)) -> Colonnade h content b -> Colonnade h content c -> Colonnade h content a #

conquer :: Colonnade h content a #

Contravariant (Colonnade h content) Source # 

Methods

contramap :: (a -> b) -> Colonnade h content b -> Colonnade h content a #

(>$) :: b -> Colonnade h content b -> Colonnade h content a #

Monoid (Colonnade h c a) Source # 

Methods

mempty :: Colonnade h c a #

mappend :: Colonnade h c a -> Colonnade h c a -> Colonnade h c a #

mconcat :: [Colonnade h c a] -> Colonnade h c a #

data Headed a Source #

As the first argument to the Colonnade type constructor, this indictates that the columnar encoding has a header. This type is isomorphic to Identity but is given a new name to clarify its intent:

example :: Colonnade Headed Text Foo

The term example represents a columnar encoding of Foo in which the columns have headings.

Instances

Functor Headed Source # 

Methods

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

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

Foldable Headed Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Headed a -> [a] #

null :: Headed a -> Bool #

length :: Headed a -> Int #

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

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

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

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

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

Eq a => Eq (Headed a) Source # 

Methods

(==) :: Headed a -> Headed a -> Bool #

(/=) :: Headed a -> Headed a -> Bool #

Ord a => Ord (Headed a) Source # 

Methods

compare :: Headed a -> Headed a -> Ordering #

(<) :: Headed a -> Headed a -> Bool #

(<=) :: Headed a -> Headed a -> Bool #

(>) :: Headed a -> Headed a -> Bool #

(>=) :: Headed a -> Headed a -> Bool #

max :: Headed a -> Headed a -> Headed a #

min :: Headed a -> Headed a -> Headed a #

Read a => Read (Headed a) Source # 
Show a => Show (Headed a) Source # 

Methods

showsPrec :: Int -> Headed a -> ShowS #

show :: Headed a -> String #

showList :: [Headed a] -> ShowS #

data Headless a Source #

As the first argument to the Colonnade type constructor, this indictates that the columnar encoding does not have a header. This type is isomorphic to Proxy but is given a new name to clarify its intent:

example :: Colonnade Headless Text Foo

The term example represents a columnar encoding of Foo in which the columns do not have headings.

Instances

Functor Headless Source # 

Methods

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

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

Foldable Headless Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Headless a -> [a] #

null :: Headless a -> Bool #

length :: Headless a -> Int #

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

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

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

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

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

Contravariant Headless Source # 

Methods

contramap :: (a -> b) -> Headless b -> Headless a #

(>$) :: b -> Headless b -> Headless a #

Eq (Headless a) Source # 

Methods

(==) :: Headless a -> Headless a -> Bool #

(/=) :: Headless a -> Headless a -> Bool #

Ord (Headless a) Source # 

Methods

compare :: Headless a -> Headless a -> Ordering #

(<) :: Headless a -> Headless a -> Bool #

(<=) :: Headless a -> Headless a -> Bool #

(>) :: Headless a -> Headless a -> Bool #

(>=) :: Headless a -> Headless a -> Bool #

max :: Headless a -> Headless a -> Headless a #

min :: Headless a -> Headless a -> Headless a #

Read (Headless a) Source # 
Show (Headless a) Source # 

Methods

showsPrec :: Int -> Headless a -> ShowS #

show :: Headless a -> String #

showList :: [Headless a] -> ShowS #

Create

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

A single column with a header.

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

A single column without a header.

singleton :: f c -> (a -> c) -> Colonnade f c a Source #

A single column with any kind of header. This is not typically needed.

Transform

fromMaybe :: c -> Colonnade f c a -> Colonnade 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 colOwners :: Colonnade Headed String (Person,Maybe House)
    colOwners = mconcat
      [ contramap fst colPerson
      , contramap snd (fromMaybe "" encodingHouse)
      ]
:}
>>> putStr (ascii colOwners 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

-> Colonnade 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 :: Colonnade Headed [Char] Color
>>> let encHouse = headed "Price" (showDollar . price) <> contramap color encColor
>>> :t encHouse
encHouse :: Colonnade 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

-> Colonnade f c a 

replaceWhen Source #

Arguments

:: c

New content

-> (a -> Bool)

Row predicate

-> Colonnade f c a

Original Colonnade

-> Colonnade f c a 

Replace the contents of cells in rows whose values satisfy the given predicate. Header content is unaffected.

modifyWhen Source #

Arguments

:: (c -> c)

Content change

-> (a -> Bool)

Row predicate

-> Colonnade f c a

Original Colonnade

-> Colonnade f c a 

Modify the contents of cells in rows whose values satisfy the given predicate. Header content is unaffected. With an HTML backend, this can be used to strikethrough the contents of cells with data that is considered invalid.

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

Colonnade 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.

Ascii Table

ascii Source #

Arguments

:: Foldable f 
=> Colonnade 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 Colonnade. 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.