Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simple templating using HTML5 as the template language. Templates are specified by adding special attributes to tags. During substitution, these attributes are stripped from the HTML. The following attributes are recognized:
insert="identifier"
- replace the tag's contents with the value bound toidentifier
in the substitution context.replace="identifier"
- replace the whole tag and its contents with the value bound toidentifier
in the substitution context.when="identifier"
- only render this tag ifidentifier
is set to true in the substitution context.unless="identifier"
- the dual ofwhen
; only render this tag ifidentifier
is set to false in the substitution context.forall="identifier"
- render this tag and its contents once for each element in the list bound toidentifier
in the substitution context. The contents of the element may refer to the current iteration's value ofidentifier
by that same name.
Substitution can also be performed on the attributes of tags. The following attribute substitutions are recognized:
when:identifier:attr="value"
- only includeattr
isidentifier
is set to true in the substitution context.unless:identifier:attr="value"
- only includeattr
isidentifier
is set to false in the substitution context.insert:identifier:attr="value"
- overwrite the value ofattr
with whateveridentifier
is bound to in the substitution context.
Contexts can be nested, in which case nested keys are separated by
periods, as in parent.child.grandchild
. Keys may be prefixed with a
question mark, in which case they are considered to be "weak keys".
If a weak key does not exist in the context, it will be replaced by a
sensible default value instead of causing an error. The defaults for the
different value types are as follows:
- bool: false
- string: ""
- array: []
- object: {}
As numbers are treated just like strings, they have an empty string as their default value as well.
In general, values used as text must be declared text by the context and so on, but the following coercions are permitted:
- bool to string
- array to bool
Coercion of array to bool, with the empty list being considered false and all other list considered true, is permitted to allow templates to take special action in the case of an empty list.
Contexts may be constructed programatically using the provided
combinators, converted from JSON objects or lists of key-value pairs, or
parsed from a YAML-formatted string using parseContext
.
- data Text :: *
- class Monoid a
- data Template
- data Context
- data Value :: *
- type Key = Text
- parseTemplate :: ByteString -> Template
- replace :: Template -> Context -> Either String ByteString
- add :: Key -> Value -> Context -> Context
- remove :: Key -> Context -> Context
- fromList :: [(Key, Value)] -> Context
- lookup :: Key -> Context -> Maybe Value
- empty :: Context
- size :: Context -> Int
- (<>) :: Monoid m => m -> m -> m
- parseContext :: ByteString -> Either String Context
- compile :: FilePath -> FilePath -> FilePath -> IO ()
Documentation
data Text :: *
A space efficient, packed, unboxed Unicode text type.
IsList Text | |
Eq Text | |
Data Text | This instance preserves data abstraction at the cost of inefficiency. We omit reflection services for the sake of data abstraction. This instance was created by copying the updated behavior of
The original discussion is archived here: could we get a Data instance for Data.Text.Text? The followup discussion that changed the behavior of |
Ord Text | |
Read Text | |
Show Text | |
IsString Text | |
ToJSON Text | |
FromJSON Text | |
Monoid Text | |
Binary Text | |
NFData Text | |
Hashable Text | |
StringLike Text | |
Typeable * Text | |
ToJSON v => ToJSON (HashMap Text v) | |
ToJSON v => ToJSON (Map Text v) | |
FromJSON v => FromJSON (HashMap Text v) | |
FromJSON v => FromJSON (Map Text v) | |
type Item Text = Char |
class Monoid a
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Minimal complete definition: mempty
and mappend
.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Monoid Ordering | |
Monoid () | |
Monoid ByteString | |
Monoid ByteString | |
Monoid Text | |
Monoid Text | |
Monoid All | |
Monoid Any | |
Monoid Context | |
Monoid [a] | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid (Result a) | |
Monoid (Parser a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid (Vector a) | |
Unbox a => Monoid (Vector a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
Monoid a => Monoid (Const a b) | |
Monoid (Proxy * s) | |
Typeable (* -> Constraint) Monoid | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) |
An Unplate context. A simple mapping from keys to values.
data Value :: *
A JSON value represented as a Haskell value.
parseTemplate :: ByteString -> Template Source
Parse an HTML5 string into a template.
replace :: Template -> Context -> Either String ByteString Source
Perform substitutions on the given template using the given context,
returning a ByteString
.
add :: Key -> Value -> Context -> Context Source
Add a new value to the given context. If the value already exists, it is overwritten.
Get the size of the context. Nested contexts count a single element, regardless of their size.
parseContext :: ByteString -> Either String Context Source
Parse a context from a YAML-formatted ByteString
.