Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype Colonnade h a c = Colonnade {
- getColonnade :: Vector (OneColonnade h a c)
- data OneColonnade h a c = OneColonnade {
- oneColonnadeHead :: !(h c)
- oneColonnadeEncode :: !(a -> c)
- newtype Headed a = Headed {
- getHeaded :: a
- data Headless a = Headless
- data Sized sz f a = Sized {
- sizedSize :: !sz
- sizedContent :: !(f a)
- newtype ExtractForall h = ExtractForall {
- runExtractForall :: forall a. h a -> a
- class Headedness h where
- row :: (c1 -> c2) -> Colonnade f a c1 -> a -> Vector c2
- rowMonadic :: (Monad m, Monoid b) => Colonnade f a c -> (c -> m b) -> a -> m b
- rowMonadic_ :: Monad m => Colonnade f a c -> (c -> m b) -> a -> m ()
- rowMonadicWith :: Monad m => b -> (b -> b -> b) -> Colonnade f a c -> (c -> m b) -> a -> m b
- rowMonoidal :: Monoid m => Colonnade h a c -> (c -> m) -> a -> m
- rowMonoidalHeader :: Monoid m => Colonnade h a c -> (h c -> c -> m) -> a -> m
- header :: (c1 -> c2) -> Colonnade Headed a c1 -> Vector c2
- headerMonadic :: (Monad m, Monoid b) => Colonnade Headed a c -> (c -> m b) -> m b
- headerMonadic_ :: Monad m => Colonnade Headed a c -> (c -> m b) -> m ()
- headerMonadicGeneral :: (Monad m, Monoid b, Foldable h) => Colonnade h a c -> (c -> m b) -> m b
- headerMonadicGeneral_ :: (Monad m, Headedness h) => Colonnade h a c -> (c -> m b) -> m ()
- headerMonoidalGeneral :: (Monoid m, Foldable h) => Colonnade h a c -> (c -> m) -> m
- headerMonoidalFull :: Monoid m => Colonnade h a c -> (h c -> m) -> m
- bothMonadic_ :: Monad m => Colonnade Headed a c -> (c -> c -> m b) -> a -> m ()
- sizeColumns :: (Foldable f, Foldable h) => (c -> Int) -> f a -> Colonnade h a c -> Colonnade (Sized (Maybe Int) h) a c
- data Cornice h (p :: Pillar) a c where
- CorniceBase :: !(Colonnade h a c) -> Cornice h Base a c
- CorniceCap :: !(Vector (OneCornice (Cornice h) p a c)) -> Cornice h (Cap p) a c
- data AnnotatedCornice sz h (p :: Pillar) a c where
- AnnotatedCorniceBase :: !sz -> !(Colonnade (Sized sz h) a c) -> AnnotatedCornice sz h Base a c
- AnnotatedCorniceCap :: !sz -> !(Vector (OneCornice (AnnotatedCornice sz h) p a c)) -> AnnotatedCornice sz h (Cap p) a c
- data OneCornice k (p :: Pillar) a c = OneCornice {
- oneCorniceHead :: !c
- oneCorniceBody :: !(k p a c)
- data Pillar
- class ToEmptyCornice (p :: Pillar) where
- data Fascia (p :: Pillar) r where
- annotate :: Cornice Headed p a c -> AnnotatedCornice (Maybe Int) Headed p a c
- annotateFinely :: Foldable f => (Int -> Int -> Int) -> (Int -> Int) -> (c -> Int) -> f a -> Cornice Headed p a c -> AnnotatedCornice (Maybe Int) Headed p a c
- size :: AnnotatedCornice sz h p a c -> sz
- endow :: forall p a c. (c -> c -> c) -> Cornice Headed p a c -> Colonnade Headed a c
- discard :: Cornice h p a c -> Colonnade h a c
- headersMonoidal :: forall sz r m c p a h. (Monoid m, Headedness h) => Maybe (Fascia p r, r -> m -> m) -> [(sz -> c -> m, m -> m)] -> AnnotatedCornice sz h p a c -> m
- uncapAnnotated :: forall sz p a c h. AnnotatedCornice sz h p a c -> Colonnade (Sized sz h) a c
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
Colonnade
s are defined at the top-level so that GHC avoids reconstructing
them every time they are used.
Colonnade | |
|
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 # | |
data OneColonnade h a c Source #
Encodes a header and a cell.
OneColonnade | |
|
Instances
Functor h => Profunctor (OneColonnade h) Source # | |
Defined in Colonnade.Encode 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 => q b c -> OneColonnade h a b -> OneColonnade h a c # (.#) :: Coercible b a => OneColonnade h b c -> q a b -> OneColonnade h a c # | |
Functor h => Functor (OneColonnade h a) Source # | |
Defined in Colonnade.Encode fmap :: (a0 -> b) -> OneColonnade h a a0 -> OneColonnade h a b # (<$) :: a0 -> OneColonnade h a b -> OneColonnade h a a0 # |
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 # | |
Sized | |
|
Instances
Functor f => Functor (Sized sz f) Source # | |
Foldable f => Foldable (Sized sz f) Source # | |
Defined in Colonnade.Encode fold :: Monoid m => Sized sz f m -> m # foldMap :: Monoid m => (a -> m) -> Sized sz f a -> m # foldr :: (a -> b -> b) -> b -> Sized sz f a -> b # foldr' :: (a -> b -> b) -> b -> Sized sz f a -> b # foldl :: (b -> a -> b) -> b -> Sized sz f a -> b # foldl' :: (b -> a -> b) -> b -> Sized sz f a -> b # foldr1 :: (a -> a -> a) -> Sized sz f a -> a # foldl1 :: (a -> a -> a) -> Sized sz f a -> a # toList :: Sized sz f a -> [a] # null :: Sized sz f a -> Bool # length :: Sized sz f a -> Int # elem :: Eq a => a -> Sized sz f a -> Bool # maximum :: Ord a => Sized sz f a -> a # minimum :: Ord a => Sized sz f a -> a # |
newtype ExtractForall h Source #
ExtractForall | |
|
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 # |
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 => 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
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, Headedness h) => Colonnade h a c -> (c -> m b) -> m () Source #
headerMonoidalFull :: Monoid m => Colonnade h a c -> (h c -> m) -> m Source #
Other
Cornice
Types
data Cornice h (p :: Pillar) a c where Source #
CorniceBase :: !(Colonnade h a c) -> Cornice h Base a c | |
CorniceCap :: !(Vector (OneCornice (Cornice h) p a c)) -> Cornice h (Cap p) a c |
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 # | |
data AnnotatedCornice sz h (p :: Pillar) a c where Source #
AnnotatedCorniceBase :: !sz -> !(Colonnade (Sized sz h) a c) -> AnnotatedCornice sz h Base a c | |
AnnotatedCorniceCap :: !sz -> !(Vector (OneCornice (AnnotatedCornice sz h) p a c)) -> AnnotatedCornice sz h (Cap p) a c |
data OneCornice k (p :: Pillar) a c Source #
OneCornice | |
|
Instances
Functor (k p a) => Functor (OneCornice k p a) Source # | |
Defined in Colonnade.Encode fmap :: (a0 -> b) -> OneCornice k p a a0 -> OneCornice k p a b # (<$) :: a0 -> OneCornice k p a b -> OneCornice k p a a0 # |
Isomorphic to the natural numbers. Only the promoted version of this type is used.
class ToEmptyCornice (p :: Pillar) where Source #
toEmptyCornice :: Cornice h p a c Source #
Instances
ToEmptyCornice Base Source # | |
Defined in Colonnade.Encode toEmptyCornice :: Cornice h Base a c Source # | |
ToEmptyCornice (Cap p) Source # | |
Defined in Colonnade.Encode toEmptyCornice :: Cornice h (Cap p) a c Source # |
Encoding
size :: AnnotatedCornice sz h p a c -> sz Source #
This is an O(1) operation, sort of
:: (Monoid m, Headedness h) | |
=> Maybe (Fascia p r, r -> m -> m) | Apply the Fascia header row content |
-> [(sz -> c -> m, m -> m)] | Build content from cell content and size |
-> AnnotatedCornice sz h p a c | |
-> m |
uncapAnnotated :: forall sz p a c h. AnnotatedCornice sz h p a c -> Colonnade (Sized sz h) a c Source #