Safe Haskell | None |
---|---|
Language | Haskell2010 |
Colonnade.Types
- newtype Colonnade f c a = Colonnade {
- getColonnade :: Vector (OneColonnade f c a)
- data Decolonnade f content a where
- DecolonnadePure :: !a -> Decolonnade f content a
- DecolonnadeAp :: !(f content) -> !(content -> Either String a) -> !(Decolonnade f content (a -> b)) -> Decolonnade f content b
- data OneColonnade f content a = OneColonnade {
- oneColonnadeHead :: !(f content)
- oneColonnadeEncode :: !(a -> content)
- newtype Headed a = Headed {
- getHeaded :: a
- data Headless a = Headless
- data Indexed f a = Indexed {
- indexedIndex :: !Int
- indexedHeading :: !(f a)
- data HeadingErrors content = HeadingErrors {
- headingErrorsMissing :: Vector content
- headingErrorsDuplicate :: Vector (content, Int)
- data DecolonnadeCellError f content = DecolonnadeCellError {
- decodingCellErrorContent :: !content
- decodingCellErrorHeader :: !(Indexed f content)
- decodingCellErrorMessage :: !String
- data DecolonnadeRowError f content = DecolonnadeRowError {
- decodingRowErrorRow :: !Int
- decodingRowErrorError :: !(RowError f content)
- newtype DecolonnadeCellErrors f content = DecolonnadeCellErrors {
- getDecolonnadeCellErrors :: Vector (DecolonnadeCellError f content)
- data RowError f content
- = RowErrorParse !String
- | RowErrorDecode !(DecolonnadeCellErrors f content)
- | RowErrorSize !Int !Int
- | RowErrorHeading !(HeadingErrors content)
- | RowErrorMinSize !Int !Int
- | RowErrorMalformed !String
Documentation
newtype Colonnade 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, 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 avoid reconstructing
them every time they are used.
Constructors
Colonnade | |
Fields
|
data Decolonnade 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
DecolonnadePure :: !a -> Decolonnade f content a | |
DecolonnadeAp :: !(f content) -> !(content -> Either String a) -> !(Decolonnade f content (a -> b)) -> Decolonnade f content b |
Instances
Functor (Decolonnade f content) Source # | |
Applicative (Decolonnade f content) Source # | |
data OneColonnade f content a Source #
Encodes a header and a cell.
Constructors
OneColonnade | |
Fields
|
Instances
Contravariant (OneColonnade f content) Source # | |
This type is isomorphic to Identity
.
This type is isomorphic to Proxy
Constructors
Headless |
Constructors
Indexed | |
Fields
|
data HeadingErrors content Source #
Constructors
HeadingErrors | |
Fields
|
data DecolonnadeCellError f content Source #
Constructors
DecolonnadeCellError | |
Fields
|
data DecolonnadeRowError f content Source #
Constructors
DecolonnadeRowError | |
Fields
|
newtype DecolonnadeCellErrors f content Source #
Constructors
DecolonnadeCellErrors | |
Fields
|
Instances
data RowError f content Source #
Constructors
RowErrorParse !String | Error occurred parsing the document into cells |
RowErrorDecode !(DecolonnadeCellErrors 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 |