| Copyright | (c) Justus Adam 2015 |
|---|---|
| License | BSD3 |
| Maintainer | dev@justus.science |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Mustache.Types
Description
Synopsis
- type ASTree α = [Node α]
- type STree = ASTree Text
- data Node α
- = TextBlock α
- | Section DataIdentifier (ASTree α)
- | InvertedSection DataIdentifier (ASTree α)
- | Variable Bool DataIdentifier
- | Partial (Maybe α) FilePath
- data DataIdentifier
- data Template = Template {}
- type TemplateCache = HashMap String Template
- data Value
- type Key = Text
- object :: [Pair] -> Value
- (~>) :: ToMustache ω => Text -> ω -> Pair
- (↝) :: ToMustache ω => Text -> ω -> Pair
- (~=) :: ToJSON ι => Text -> ι -> Pair
- (⥱) :: ToJSON ι => Text -> ι -> Pair
- class ToMustache ω
- toMustache :: ToMustache ω => ω -> Value
- mFromJSON :: ToJSON ι => ι -> Value
- type Array = Vector Value
- type Object = HashMap Text Value
- type Pair = (Text, Value)
- data SubM a
- askContext :: SubM (Context Value)
- askPartials :: SubM TemplateCache
- data Context α = Context {
- ctxtParents :: [α]
- ctxtFocus :: α
Types for the Parser / Template
Basic values composing the STree
Constructors
| TextBlock α | |
| Section DataIdentifier (ASTree α) | |
| InvertedSection DataIdentifier (ASTree α) | |
| Variable Bool DataIdentifier | |
| Partial (Maybe α) FilePath |
Instances
| Eq α => Eq (Node α) Source # | |
| Show α => Show (Node α) Source # | |
| Lift α => Lift (Node α) Source # | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> String) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> STree) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (STree -> SubM Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (STree -> SubM STree) Source # | |
Defined in Text.Mustache.Internal.Types | |
data DataIdentifier Source #
Kinds of identifiers for Variables and sections
Instances
| Eq DataIdentifier Source # | |
Defined in Text.Mustache.Internal.Types Methods (==) :: DataIdentifier -> DataIdentifier -> Bool # (/=) :: DataIdentifier -> DataIdentifier -> Bool # | |
| Show DataIdentifier Source # | |
Defined in Text.Mustache.Internal.Types Methods showsPrec :: Int -> DataIdentifier -> ShowS # show :: DataIdentifier -> String # showList :: [DataIdentifier] -> ShowS # | |
| Lift DataIdentifier Source # | |
Defined in Text.Mustache.Internal.Types Methods lift :: DataIdentifier -> Q Exp # | |
A compiled Template with metadata.
Instances
| Show Template Source # | |
| Lift Template Source # | |
| Lift TemplateCache Source # | |
Defined in Text.Mustache.Internal.Types Methods lift :: TemplateCache -> Q Exp # | |
| MonadReader (Context Value, TemplateCache) SubM Source # | |
Defined in Text.Mustache.Internal.Types | |
type TemplateCache = HashMap String Template Source #
A collection of templates with quick access via their hashed names
Types for the Substitution / Data
Internal value representation
Constructors
| Object !Object | |
| Array !Array | |
| Number !Scientific | |
| String !Text | |
| Lambda (STree -> SubM STree) | |
| Bool !Bool | |
| Null |
Instances
| Show Value Source # | |
| ToMustache Value Source # | |
Defined in Text.Mustache.Internal.Types | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> String) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> STree) Source # | |
Defined in Text.Mustache.Render | |
| MonadReader (Context Value, TemplateCache) SubM Source # | |
Defined in Text.Mustache.Internal.Types | |
Converting
object :: [Pair] -> Value Source #
Convenience function for creating Object values.
This function is supposed to be used in conjuction with the ~> and ~= operators.
Examples
data Address = Address { ... }
instance Address ToJSON where
...
data Person = Person { name :: String, address :: Address }
instance ToMustache Person where
toMustache (Person { name, address }) = object
[ "name" ~> name
, "address" ~= address
]
Here we can see that we can use the ~> operator for values that have
themselves a ToMustache instance, or alternatively if they lack such an
instance but provide an instance for the ToJSON typeclass we can use the
~= operator.
(~>) :: ToMustache ω => Text -> ω -> Pair infixr 8 Source #
Map keys to values that provide a ToMustache instance
Recommended in conjunction with the OverloadedStrings extension.
(~=) :: ToJSON ι => Text -> ι -> Pair infixr 8 Source #
Map keys to values that provide a ToJSON instance
Recommended in conjunction with the OverloadedStrings extension.
class ToMustache ω Source #
Conversion class
Minimal complete definition
Instances
toMustache :: ToMustache ω => ω -> Value Source #
mFromJSON :: ToJSON ι => ι -> Value Source #
Converts a value that can be represented as JSON to a Value.
Representation
Instances
| Monad SubM Source # | |
| Functor SubM Source # | |
| Applicative SubM Source # | |
| ToMustache (STree -> SubM Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (STree -> SubM STree) Source # | |
Defined in Text.Mustache.Internal.Types | |
| MonadReader (Context Value, TemplateCache) SubM Source # | |
Defined in Text.Mustache.Internal.Types | |
Representation of stateful context for the substitution process
Constructors
| Context | |
Fields
| |
Instances
| Eq α => Eq (Context α) Source # | |
| Ord α => Ord (Context α) Source # | |
| Show α => Show (Context α) Source # | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> Text) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> String) Source # | |
Defined in Text.Mustache.Render | |
| ToMustache (Context Value -> STree -> STree) Source # | |
Defined in Text.Mustache.Render | |
| MonadReader (Context Value, TemplateCache) SubM Source # | |
Defined in Text.Mustache.Internal.Types | |