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

Safe HaskellNone
LanguageHaskell2010

Colonnade.Internal

Synopsis

Documentation

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

Constructors

Colonnade 

Fields

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 OneColonnade h content a Source #

Encodes a header and a cell.

Constructors

OneColonnade 

Fields

Instances

Contravariant (OneColonnade h content) Source # 

Methods

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

(>$) :: b -> OneColonnade h content b -> OneColonnade h content 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 Text Foo

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

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 #