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

Safe HaskellNone
LanguageHaskell2010

Colonnade.Encode

Contents

Description

Most users of this library do not need this module. The functions here are used to build functions that apply a Colonnade to a collection of values, building a table from them. Ultimately, a function that applies a Colonnade Headed MyCell a to data will have roughly the following type:

myTableRenderer :: Foldable g => Colonnade Headed MyCell a -> g a -> MyContent

In the companion packages yesod-colonnade and reflex-dom-colonnade, functions with similar type signatures are readily available. These packages use the functions provided here in the implementations of their rendering functions. It is recommended that users who believe they may need this module look at the source of the companion packages to see an example of how this module's functions are used. Other backends are encouraged to use these functions to build monadic or monoidal content from a Colonnade.

The functions exported here take a Colonnade and convert it to a fragment of content. The functions whose names start with row take at least a Colonnade f c a and an a value to generate a row of content. The functions whose names start with header need the Colonnade f c a but not an a value since a value is not needed to build a header.

Synopsis

Colonnade

Types

newtype Colonnade h a c 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:

            +---- 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 Colonnades are defined at the top-level so that GHC avoids reconstructing them every time they are used.

Constructors

Colonnade 

Fields

Instances

Functor h => Profunctor (Colonnade h) Source # 

Methods

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 => (b -> c) -> Colonnade h a b -> Colonnade h a c #

(.#) :: Coercible * b a => Colonnade h b c -> (a -> b) -> Colonnade h a c #

Functor h => Functor (Colonnade h a) Source # 

Methods

fmap :: (a -> b) -> Colonnade h a a -> Colonnade h a b #

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

Semigroup (Colonnade h a c) Source # 

Methods

(<>) :: Colonnade h a c -> Colonnade h a c -> Colonnade h a c #

sconcat :: NonEmpty (Colonnade h a c) -> Colonnade h a c #

stimes :: Integral b => b -> Colonnade h a c -> Colonnade h a c #

Monoid (Colonnade h a c) Source # 

Methods

mempty :: Colonnade h a c #

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

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

data OneColonnade h a c Source #

Encodes a header and a cell.

Constructors

OneColonnade 

Fields

Instances

Functor h => Profunctor (OneColonnade h) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> OneColonnade h b c -> OneColonnade h a d #

lmap :: (a -> b) -> OneColonnade h b c -> OneColonnade h a c #

rmap :: (b -> c) -> OneColonnade h a b -> OneColonnade h a c #

(#.) :: Coercible * c b => (b -> c) -> OneColonnade h a b -> OneColonnade h a c #

(.#) :: Coercible * b a => OneColonnade h b c -> (a -> b) -> OneColonnade h a c #

Functor h => Functor (OneColonnade h a) Source # 

Methods

fmap :: (a -> b) -> OneColonnade h a a -> OneColonnade h a b #

(<$) :: a -> OneColonnade h a b -> OneColonnade h a a #

newtype 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 Foo Text

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

Constructors

Headed 

Fields

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 Foo Text

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

Constructors

Headless 

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 #

data Sized f a Source #

Constructors

Sized 

Fields

Instances

Functor f => Functor (Sized f) Source # 

Methods

fmap :: (a -> b) -> Sized f a -> Sized f b #

(<$) :: a -> Sized f b -> Sized f a #

Foldable f => Foldable (Sized f) Source # 

Methods

fold :: Monoid m => Sized f m -> m #

foldMap :: Monoid m => (a -> m) -> Sized f a -> m #

foldr :: (a -> b -> b) -> b -> Sized f a -> b #

foldr' :: (a -> b -> b) -> b -> Sized f a -> b #

foldl :: (b -> a -> b) -> b -> Sized f a -> b #

foldl' :: (b -> a -> b) -> b -> Sized f a -> b #

foldr1 :: (a -> a -> a) -> Sized f a -> a #

foldl1 :: (a -> a -> a) -> Sized f a -> a #

toList :: Sized f a -> [a] #

null :: Sized f a -> Bool #

length :: Sized f a -> Int #

elem :: Eq a => a -> Sized f a -> Bool #

maximum :: Ord a => Sized f a -> a #

minimum :: Ord a => Sized f a -> a #

sum :: Num a => Sized f a -> a #

product :: Num a => Sized f a -> a #

Row

row :: (c1 -> c2) -> Colonnade f a c1 -> 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.

rowMonadic :: (Monad m, Monoid b) => Colonnade f a c -> (c -> m b) -> a -> m b Source #

rowMonadic_ :: Monad m => Colonnade f a c -> (c -> m b) -> a -> m () Source #

rowMonadicWith :: Monad m => b -> (b -> b -> b) -> Colonnade f a c -> (c -> m b) -> a -> m b Source #

rowMonoidal :: Monoid m => Colonnade h a c -> (c -> m) -> a -> m Source #

rowMonoidalHeader :: Monoid m => Colonnade h a c -> (h c -> c -> m) -> a -> m Source #

Header

header :: (c1 -> c2) -> Colonnade Headed a c1 -> Vector c2 Source #

headerMonadic :: (Monad m, Monoid b) => Colonnade Headed a c -> (c -> m b) -> m b Source #

headerMonadic_ :: Monad m => Colonnade Headed a c -> (c -> m b) -> m () Source #

headerMonadicGeneral :: (Monad m, Monoid b, Foldable h) => Colonnade h a c -> (c -> m b) -> m b Source #

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

headerMonadicGeneral_ :: (Monad m, Foldable h) => Colonnade h a c -> (c -> m b) -> m () Source #

headerMonoidalGeneral :: (Monoid m, Foldable h) => Colonnade h a c -> (c -> m) -> m Source #

headerMonoidalFull :: Monoid m => Colonnade h a c -> (h c -> m) -> m Source #

Other

bothMonadic_ :: Monad m => Colonnade Headed a c -> (c -> c -> m b) -> a -> m () Source #

sizeColumns Source #

Arguments

:: (Foldable f, Foldable h) 
=> (c -> Int)

Get size from content

-> f a 
-> Colonnade h a c 
-> Colonnade (Sized h) a c 

Cornice

Types

data Cornice p a c where Source #

Constructors

CorniceBase :: !(Colonnade Headed a c) -> Cornice Base a c 
CorniceCap :: !(Vector (OneCornice Cornice p a c)) -> Cornice (Cap p) a c 

Instances

Semigroup (Cornice p a c) Source # 

Methods

(<>) :: Cornice p a c -> Cornice p a c -> Cornice p a c #

sconcat :: NonEmpty (Cornice p a c) -> Cornice p a c #

stimes :: Integral b => b -> Cornice p a c -> Cornice p a c #

ToEmptyCornice p => Monoid (Cornice p a c) Source # 

Methods

mempty :: Cornice p a c #

mappend :: Cornice p a c -> Cornice p a c -> Cornice p a c #

mconcat :: [Cornice p a c] -> Cornice p a c #

data OneCornice k p a c Source #

Constructors

OneCornice 

Fields

data Pillar Source #

Isomorphic to the natural numbers. Only the promoted version of this type is used.

Constructors

Cap !Pillar 
Base 

class ToEmptyCornice p where Source #

Minimal complete definition

toEmptyCornice

Methods

toEmptyCornice :: Cornice p a c Source #

data Fascia p r where Source #

Constructors

FasciaBase :: !r -> Fascia Base r 
FasciaCap :: !r -> Fascia p r -> Fascia (Cap p) r 

Encoding

annotateFinely Source #

Arguments

:: Foldable f 
=> (Int -> Int -> Int)

fold function

-> (Int -> Int)

finalize

-> (c -> Int)

Get size from content

-> f a 
-> Cornice p a c 
-> AnnotatedCornice p a c 

size :: AnnotatedCornice p a c -> Maybe Int Source #

This is an O(1) operation, sort of

endow :: forall p a c. (c -> c -> c) -> Cornice p a c -> Colonnade Headed a c Source #

headersMonoidal Source #

Arguments

:: Monoid m 
=> Maybe (Fascia p r, r -> m -> m)

Apply the Fascia header row content

-> [(Int -> c -> m, m -> m)]

Build content from cell content and size

-> AnnotatedCornice p a c 
-> m 

uncapAnnotated :: forall p a c. AnnotatedCornice p a c -> Colonnade (Sized Headed) a c Source #