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

Safe HaskellNone
LanguageHaskell2010

Colonnade.Types

Synopsis

Documentation

newtype Encoding f c a Source #

An columnar encoding of a. The type variable f 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.

Internally, an Encoding 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 Encodings are defined at the top-level so that GHC avoid reconstructing them every time they are used.

Constructors

Encoding 

Fields

Instances

Divisible (Encoding f content) Source # 

Methods

divide :: (a -> (b, c)) -> Encoding f content b -> Encoding f content c -> Encoding f content a #

conquer :: Encoding f content a #

Contravariant (Encoding f content) Source # 

Methods

contramap :: (a -> b) -> Encoding f content b -> Encoding f content a #

(>$) :: b -> Encoding f content b -> Encoding f content a #

Monoid (Encoding f c a) Source # 

Methods

mempty :: Encoding f c a #

mappend :: Encoding f c a -> Encoding f c a -> Encoding f c a #

mconcat :: [Encoding f c a] -> Encoding f c a #

data Decoding f content a where Source #

This just actually a specialization of the free applicative. Check out Control.Applicative.Free in the free library to learn more about this. The meanings of the fields are documented slightly more in the source code. Unfortunately, haddock does not play nicely with GADTs.

Constructors

DecodingPure :: !a -> Decoding f content a 
DecodingAp :: !(f content) -> !(content -> Either String a) -> !(Decoding f content (a -> b)) -> Decoding f content b 

Instances

Functor (Decoding f content) Source # 

Methods

fmap :: (a -> b) -> Decoding f content a -> Decoding f content b #

(<$) :: a -> Decoding f content b -> Decoding f content a #

Applicative (Decoding f content) Source # 

Methods

pure :: a -> Decoding f content a #

(<*>) :: Decoding f content (a -> b) -> Decoding f content a -> Decoding f content b #

(*>) :: Decoding f content a -> Decoding f content b -> Decoding f content b #

(<*) :: Decoding f content a -> Decoding f content b -> Decoding f content a #

data OneEncoding f content a Source #

Encodes a header and a cell.

Constructors

OneEncoding 

Fields

Instances

Contravariant (OneEncoding f content) Source # 

Methods

contramap :: (a -> b) -> OneEncoding f content b -> OneEncoding f content a #

(>$) :: b -> OneEncoding f content b -> OneEncoding f content a #

newtype Headed a Source #

This type is isomorphic to Identity.

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 #

This type is isomorphic to Proxy

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 Indexed f a Source #

Constructors

Indexed 

Fields

Instances

Functor f => Functor (Indexed f) Source # 

Methods

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

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

Eq (f a) => Eq (Indexed f a) Source # 

Methods

(==) :: Indexed f a -> Indexed f a -> Bool #

(/=) :: Indexed f a -> Indexed f a -> Bool #

Ord (f a) => Ord (Indexed f a) Source # 

Methods

compare :: Indexed f a -> Indexed f a -> Ordering #

(<) :: Indexed f a -> Indexed f a -> Bool #

(<=) :: Indexed f a -> Indexed f a -> Bool #

(>) :: Indexed f a -> Indexed f a -> Bool #

(>=) :: Indexed f a -> Indexed f a -> Bool #

max :: Indexed f a -> Indexed f a -> Indexed f a #

min :: Indexed f a -> Indexed f a -> Indexed f a #

Read (f a) => Read (Indexed f a) Source # 
Show (f a) => Show (Indexed f a) Source # 

Methods

showsPrec :: Int -> Indexed f a -> ShowS #

show :: Indexed f a -> String #

showList :: [Indexed f a] -> ShowS #

data HeadingErrors content Source #

Constructors

HeadingErrors 

Fields

Instances

Eq content => Eq (HeadingErrors content) Source # 

Methods

(==) :: HeadingErrors content -> HeadingErrors content -> Bool #

(/=) :: HeadingErrors content -> HeadingErrors content -> Bool #

Read content => Read (HeadingErrors content) Source # 
Show content => Show (HeadingErrors content) Source # 

Methods

showsPrec :: Int -> HeadingErrors content -> ShowS #

show :: HeadingErrors content -> String #

showList :: [HeadingErrors content] -> ShowS #

Monoid (HeadingErrors content) Source # 

Methods

mempty :: HeadingErrors content #

mappend :: HeadingErrors content -> HeadingErrors content -> HeadingErrors content #

mconcat :: [HeadingErrors content] -> HeadingErrors content #

(Show content, Typeable * content) => Exception (HeadingErrors content) Source # 

data DecodingCellError f content Source #

Instances

(Eq (f content), Eq content) => Eq (DecodingCellError f content) Source # 

Methods

(==) :: DecodingCellError f content -> DecodingCellError f content -> Bool #

(/=) :: DecodingCellError f content -> DecodingCellError f content -> Bool #

(Read (f content), Read content) => Read (DecodingCellError f content) Source # 
(Show (f content), Show content) => Show (DecodingCellError f content) Source # 

Methods

showsPrec :: Int -> DecodingCellError f content -> ShowS #

show :: DecodingCellError f content -> String #

showList :: [DecodingCellError f content] -> ShowS #

data DecodingRowError f content Source #

Constructors

DecodingRowError 

Instances

(Eq (f content), Eq content) => Eq (DecodingRowError f content) Source # 

Methods

(==) :: DecodingRowError f content -> DecodingRowError f content -> Bool #

(/=) :: DecodingRowError f content -> DecodingRowError f content -> Bool #

(Read (f content), Read content) => Read (DecodingRowError f content) Source # 
(Show (f content), Show content) => Show (DecodingRowError f content) Source # 

Methods

showsPrec :: Int -> DecodingRowError f content -> ShowS #

show :: DecodingRowError f content -> String #

showList :: [DecodingRowError f content] -> ShowS #

newtype DecodingCellErrors f content Source #

Instances

(Eq (f content), Eq content) => Eq (DecodingCellErrors f content) Source # 

Methods

(==) :: DecodingCellErrors f content -> DecodingCellErrors f content -> Bool #

(/=) :: DecodingCellErrors f content -> DecodingCellErrors f content -> Bool #

(Read (f content), Read content) => Read (DecodingCellErrors f content) Source # 
(Show (f content), Show content) => Show (DecodingCellErrors f content) Source # 

Methods

showsPrec :: Int -> DecodingCellErrors f content -> ShowS #

show :: DecodingCellErrors f content -> String #

showList :: [DecodingCellErrors f content] -> ShowS #

Monoid (DecodingCellErrors f content) Source # 

Methods

mempty :: DecodingCellErrors f content #

mappend :: DecodingCellErrors f content -> DecodingCellErrors f content -> DecodingCellErrors f content #

mconcat :: [DecodingCellErrors f content] -> DecodingCellErrors f content #

data RowError f content Source #

Constructors

RowErrorParse !String

Error occurred parsing the document into cells

RowErrorDecode !(DecodingCellErrors f content)

Error decoding the content

RowErrorSize !Int !Int

Wrong number of cells in the row

RowErrorHeading !(HeadingErrors content) 
RowErrorMinSize !Int !Int 
RowErrorMalformed !String

Error decoding unicode content

Instances

(Eq (f content), Eq content) => Eq (RowError f content) Source # 

Methods

(==) :: RowError f content -> RowError f content -> Bool #

(/=) :: RowError f content -> RowError f content -> Bool #

(Read (f content), Read content) => Read (RowError f content) Source # 

Methods

readsPrec :: Int -> ReadS (RowError f content) #

readList :: ReadS [RowError f content] #

readPrec :: ReadPrec (RowError f content) #

readListPrec :: ReadPrec [RowError f content] #

(Show (f content), Show content) => Show (RowError f content) Source # 

Methods

showsPrec :: Int -> RowError f content -> ShowS #

show :: RowError f content -> String #

showList :: [RowError f content] -> ShowS #