Safe Haskell | None |
---|---|
Language | Haskell2010 |
Build backend-agnostic columnar encodings that can be used to visualize tabular data.
Synopsis
- data Colonnade h a c
- newtype Headed a = Headed {
- getHeaded :: a
- data Headless a = Headless
- class Headedness h where
- headed :: c -> (a -> c) -> Colonnade Headed a c
- headless :: (a -> c) -> Colonnade Headless a c
- singleton :: h c -> (a -> c) -> Colonnade h a c
- fromMaybe :: c -> Colonnade f a c -> Colonnade f (Maybe a) c
- columns :: Foldable g => (b -> a -> c) -> (b -> f c) -> g b -> Colonnade f a c
- bool :: f c -> (a -> Bool) -> (a -> c) -> (a -> c) -> Colonnade f a c
- replaceWhen :: c -> (a -> Bool) -> Colonnade f a c -> Colonnade f a c
- modifyWhen :: (c -> c) -> (a -> Bool) -> Colonnade f a c -> Colonnade f a c
- mapHeaderContent :: Functor h => (c -> c) -> Colonnade h a c -> Colonnade h a c
- mapHeadedness :: (forall x. h x -> h' x) -> Colonnade h a c -> Colonnade h' a c
- toHeadless :: Colonnade h a c -> Colonnade Headless a c
- data Cornice h (p :: Pillar) a c
- data Pillar
- data Fascia (p :: Pillar) r where
- cap :: c -> Colonnade h a c -> Cornice h (Cap Base) a c
- recap :: c -> Cornice h p a c -> Cornice h (Cap p) a c
- ascii :: Foldable f => Colonnade Headed a String -> f a -> String
- asciiCapped :: Foldable f => Cornice Headed p a String -> f a -> String
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.Profunctor (lmap)
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 Person String 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
>>>
colHouse = mconcat [headed "Color" (show . color), headed "Price" (showDollar . price)]
>>>
:t colHouse
colHouse :: Colonnade Headed House [Char]>>>
let houses = [House Green 170000, House Blue 115000, House Green 150000]
>>>
putStr (ascii colHouse houses)
+-------+---------+ | Color | Price | +-------+---------+ | Green | $170000 | | Blue | $115000 | | Green | $150000 | +-------+---------+
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:
+---- Value consumed to build a row | v Colonnade h a c ^ ^ | | | +-- Content (Text, ByteString, Html, etc.) | +------ 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
Colonnade
s are defined at the top-level so that GHC avoids reconstructing
them every time they are used.
Instances
Functor h => Profunctor (Colonnade h) Source # | |
Defined in Colonnade.Encode dimap :: (a -> b) -> (c -> d) -> Colonnade h b c -> Colonnade h a d # lmap :: (a -> b) -> Colonnade h b c -> Colonnade h a c # rmap :: (b -> c) -> Colonnade h a b -> Colonnade h a c # (#.) :: Coercible c b => q b c -> Colonnade h a b -> Colonnade h a c # (.#) :: Coercible b a => Colonnade h b c -> q a b -> Colonnade h a c # | |
Functor h => Functor (Colonnade h a) Source # | |
Semigroup (Colonnade h a c) Source # | |
Monoid (Colonnade h a c) 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 Foo Text
The term example
represents a columnar encoding of Foo
in which the columns have headings.
Instances
Functor Headed Source # | |
Applicative Headed Source # | |
Foldable Headed Source # | |
Defined in Colonnade.Encode 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 # elem :: Eq a => a -> Headed a -> Bool # maximum :: Ord a => Headed a -> a # minimum :: Ord a => Headed a -> a # | |
Headedness Headed Source # | |
Defined in Colonnade.Encode headednessPure :: a -> Headed a Source # headednessExtract :: Maybe (Headed a -> a) Source # headednessExtractForall :: Maybe (ExtractForall Headed) Source # | |
Eq a => Eq (Headed a) Source # | |
Ord a => Ord (Headed a) Source # | |
Defined in Colonnade.Encode | |
Read a => Read (Headed a) Source # | |
Show a => Show (Headed 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 Foo Text
The term example
represents a columnar encoding of Foo
in which the columns do not have headings.
Instances
Functor Headless Source # | |
Applicative Headless Source # | |
Foldable Headless Source # | |
Defined in Colonnade.Encode 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 # elem :: Eq a => a -> Headless a -> Bool # maximum :: Ord a => Headless a -> a # minimum :: Ord a => Headless a -> a # | |
Contravariant Headless Source # | |
Headedness Headless Source # | |
Defined in Colonnade.Encode headednessPure :: a -> Headless a Source # headednessExtract :: Maybe (Headless a -> a) Source # headednessExtractForall :: Maybe (ExtractForall Headless) Source # | |
Eq (Headless a) Source # | |
Ord (Headless a) Source # | |
Read (Headless a) Source # | |
Show (Headless a) Source # | |
Typeclasses
class Headedness h where Source #
This class communicates that a container holds either zero
elements or one element. Furthermore, all inhabitants of
the type must hold the same number of elements. Both
Headed
and Headless
have instances. The following
law accompanies any instances:
maybe x (\f -> f (headednessPure x)) headednessContents == x todo: come up with another law that relates to Traversable
Consequently, there is no instance for Maybe
, which cannot
satisfy the laws since it has inhabitants which hold different
numbers of elements. Nothing
holds 0 elements and Just
holds
1 element.
headednessPure :: a -> h a Source #
headednessExtract :: Maybe (h a -> a) Source #
Instances
Headedness Headless Source # | |
Defined in Colonnade.Encode headednessPure :: a -> Headless a Source # headednessExtract :: Maybe (Headless a -> a) Source # headednessExtractForall :: Maybe (ExtractForall Headless) Source # | |
Headedness Headed Source # | |
Defined in Colonnade.Encode headednessPure :: a -> Headed a Source # headednessExtract :: Maybe (Headed a -> a) Source # headednessExtractForall :: Maybe (ExtractForall Headed) Source # |
Create
singleton :: h c -> (a -> c) -> Colonnade h a c Source #
A single column with any kind of header. This is not typically needed.
Transform
Body
fromMaybe :: c -> Colonnade f a c -> Colonnade f (Maybe a) c 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 (Person,Maybe House) String colOwners = mconcat [ lmap fst colPerson , lmap snd (fromMaybe "" colHouse) ] :}
>>>
putStr (ascii colOwners owners)
+--------+-----+-------+---------+ | Name | Age | Color | Price | +--------+-----+-------+---------+ | Jordan | 18 | | | | Ruth | 25 | Red | $125000 | | Sonia | 12 | Green | $145000 | +--------+-----+-------+---------+
:: Foldable g | |
=> (b -> a -> c) | Cell content function |
-> (b -> f c) | Header content function |
-> g b | Basis for column encodings |
-> Colonnade f a c |
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 Color [Char]>>>
let encHouse = headed "Price" (showDollar . price) <> lmap color encColor
>>>
:t encHouse
encHouse :: Colonnade Headed House [Char]>>>
putStr (ascii encHouse houses)
+---------+-----+-------+------+ | Price | Red | Green | Blue | +---------+-----+-------+------+ | $170000 | | ✓ | | | $115000 | | | ✓ | | $150000 | | ✓ | | +---------+-----+-------+------+
Replace the contents of cells in rows whose values satisfy the given predicate. Header content is unaffected.
:: (c -> c) | Content change |
-> (a -> Bool) | Row predicate |
-> Colonnade f a c | Original |
-> Colonnade f a c |
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.
Header
mapHeadedness :: (forall x. h x -> h' x) -> Colonnade h a c -> Colonnade h' a c Source #
Map over the header type of a Colonnade
.
toHeadless :: Colonnade h a c -> Colonnade Headless a c Source #
Remove the heading from a Colonnade
.
Cornice
Types
data Cornice h (p :: Pillar) a c Source #
Instances
Functor h => Profunctor (Cornice h p) Source # | |
Defined in Colonnade.Encode dimap :: (a -> b) -> (c -> d) -> Cornice h p b c -> Cornice h p a d # lmap :: (a -> b) -> Cornice h p b c -> Cornice h p a c # rmap :: (b -> c) -> Cornice h p a b -> Cornice h p a c # (#.) :: Coercible c b => q b c -> Cornice h p a b -> Cornice h p a c # (.#) :: Coercible b a => Cornice h p b c -> q a b -> Cornice h p a c # | |
Functor h => Functor (Cornice h p a) Source # | |
Semigroup (Cornice h p a c) Source # | |
ToEmptyCornice p => Monoid (Cornice h p a c) Source # | |
Isomorphic to the natural numbers. Only the promoted version of this type is used.
Create
cap :: c -> Colonnade h a c -> Cornice h (Cap Base) a c Source #
Augment a Colonnade
with a header spans over all of the
existing headers. This is best demonstrated by example.
Let's consider how we might encode a pairing of the people
and houses from the initial example:
>>>
let personHomePairs = zip people houses
>>>
let colPersonFst = lmap fst colPerson
>>>
let colHouseSnd = lmap snd colHouse
>>>
putStr (ascii (colPersonFst <> colHouseSnd) personHomePairs)
+-------+-----+-------+---------+ | Name | Age | Color | Price | +-------+-----+-------+---------+ | David | 63 | Green | $170000 | | Ava | 34 | Blue | $115000 | | Sonia | 12 | Green | $150000 | +-------+-----+-------+---------+
This tabular encoding leaves something to be desired. The heading
not indicate that the name and age refer to a person and that
the color and price refer to a house. Without reaching for Cornice
,
we can still improve this situation with mapHeaderContent
:
>>>
let colPersonFst' = mapHeaderContent ("Person " ++) colPersonFst
>>>
let colHouseSnd' = mapHeaderContent ("House " ++) colHouseSnd
>>>
putStr (ascii (colPersonFst' <> colHouseSnd') personHomePairs)
+-------------+------------+-------------+-------------+ | Person Name | Person Age | House Color | House Price | +-------------+------------+-------------+-------------+ | David | 63 | Green | $170000 | | Ava | 34 | Blue | $115000 | | Sonia | 12 | Green | $150000 | +-------------+------------+-------------+-------------+
This is much better, but for longer tables, the redundancy
of prefixing many column headers can become annoying. The solution
that a Cornice
offers is to nest headers:
>>>
let cor = mconcat [cap "Person" colPersonFst, cap "House" colHouseSnd]
>>>
:t cor
cor :: Cornice Headed ('Cap 'Base) (Person, House) [Char]>>>
putStr (asciiCapped cor personHomePairs)
+-------------+-----------------+ | Person | House | +-------+-----+-------+---------+ | Name | Age | Color | Price | +-------+-----+-------+---------+ | David | 63 | Green | $170000 | | Ava | 34 | Blue | $115000 | | Sonia | 12 | Green | $150000 | +-------+-----+-------+---------+
recap :: c -> Cornice h p a c -> Cornice h (Cap p) a c Source #
Add another cap to a cornice. There is no limit to how many times this can be applied:
>>>
data Day = Weekday | Weekend deriving (Show)
>>>
:{
let cost :: Int -> Day -> String cost base w = case w of Weekday -> showDollar base Weekend -> showDollar (base + 1) colStandard = foldMap (\c -> headed c (cost 8)) ["Yt","Ad","Sr"] colSpecial = mconcat [headed "Stud" (cost 6), headed "Mltry" (cost 7)] corStatus = mconcat [ cap "Standard" colStandard , cap "Special" colSpecial ] corShowtime = mconcat [ recap "" (cap "" (headed "Day" show)) , foldMap (\c -> recap c corStatus) ["Matinee","Evening"] ] :}
>>>
putStr (asciiCapped corShowtime [Weekday,Weekend])
+---------+-----------------------------+-----------------------------+ | | Matinee | Evening | +---------+--------------+--------------+--------------+--------------+ | | Standard | Special | Standard | Special | +---------+----+----+----+------+-------+----+----+----+------+-------+ | Day | Yt | Ad | Sr | Stud | Mltry | Yt | Ad | Sr | Stud | Mltry | +---------+----+----+----+------+-------+----+----+----+------+-------+ | Weekday | $8 | $8 | $8 | $6 | $7 | $8 | $8 | $8 | $6 | $7 | | Weekend | $9 | $9 | $9 | $7 | $8 | $9 | $9 | $9 | $7 | $8 | +---------+----+----+----+------+-------+----+----+----+------+-------+
Ascii Table
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 example
code in the haddocks.