| Copyright | (c) Justus Adam, 2015 |
|---|---|
| License | LGPL-3 |
| Maintainer | development@justusadam.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Mustache.Types
Description
- type MustacheAST = [MustacheNode Text]
- data MustacheTemplate = MustacheTemplate {
- name :: String
- ast :: MustacheAST
- partials :: [MustacheTemplate]
- data MustacheNode a
- data Value
- object :: [(Text, Value)] -> Value
- (~>) :: ToMustache m => Text -> m -> KeyValuePair
- (~=) :: ToJSON j => Text -> j -> KeyValuePair
- (~~>) :: (Conversion t Text, ToMustache m) => t -> m -> KeyValuePair
- (~~=) :: (Conversion t Text, ToJSON j) => t -> j -> KeyValuePair
- class ToMustache a where
- toMustache :: a -> Value
- toMustacheText :: Conversion t Text => t -> Value
- mFromJSON :: ToJSON j => j -> Value
- type Array = Vector Value
- type Object = HashMap Text Value
- data Context a = Context [a] a
Types for the Parser / Template
type MustacheAST = [MustacheNode Text] Source
Abstract syntax tree for a mustache template
data MustacheTemplate Source
A compiled Template with metadata.
Constructors
| MustacheTemplate | |
Fields
| |
Instances
data MustacheNode a Source
Basic values composing the AST
Constructors
| MustacheText a | |
| MustacheSection [Text] MustacheAST | |
| MustacheInvertedSection [Text] MustacheAST | |
| MustacheVariable Bool [Text] | |
| MustachePartial FilePath |
Instances
| Eq a => Eq (MustacheNode a) Source | |
| Show a => Show (MustacheNode a) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String Text) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (Context Value -> MustacheAST -> String) Source | |
| ToMustache (Context Value -> MustacheAST -> Text) Source | |
| ToMustache (Context Value -> MustacheAST -> MustacheAST) Source | |
| ToMustache (MustacheAST -> Either String String) Source | |
| ToMustache (MustacheAST -> Either String Text) Source | |
| ToMustache (MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (MustacheAST -> String) Source | |
| ToMustache (MustacheAST -> Text) Source |
Types for the Substitution / Data
Internal value AST
Constructors
| Object Object | |
| Array Array | |
| Number Scientific | |
| String Text | |
| Lambda (Context Value -> MustacheAST -> Either String MustacheAST) | |
| Bool Bool | |
| Null |
Instances
| Show Value Source | |
| ToMustache Value Source | |
| ToMustache (Context Value -> MustacheAST -> Either String Text) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (Context Value -> MustacheAST -> String) Source | |
| ToMustache (Context Value -> MustacheAST -> Text) Source | |
| ToMustache (Context Value -> MustacheAST -> MustacheAST) Source |
Converting
object :: [(Text, Value)] -> 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 m => Text -> m -> KeyValuePair Source
Map keys to values that provide a ToMustache instance
Recommended in conjunction with the OverloadedStrings extension.
(~=) :: ToJSON j => Text -> j -> KeyValuePair Source
Map keys to values that provide a ToJSON instance
Recommended in conjunction with the OverloadedStrings extension.
(~~>) :: (Conversion t Text, ToMustache m) => t -> m -> KeyValuePair Source
Conceptually similar to ~> but uses arbitrary String-likes as keys.
(~~=) :: (Conversion t Text, ToJSON j) => t -> j -> KeyValuePair Source
Conceptually similar to ~= but uses arbitrary String-likes as keys.
class ToMustache a where Source
Conversion class
Methods
toMustache :: a -> Value Source
Instances
| ToMustache Bool Source | |
| ToMustache Char Source | |
| ToMustache () Source | |
| ToMustache Scientific Source | |
| ToMustache Text Source | |
| ToMustache Value Source | |
| ToMustache Text Source | |
| ToMustache Value Source | |
| ToMustache [Char] Source | |
| ToMustache m => ToMustache [m] Source | |
| ToMustache m => ToMustache (Vector m) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String Text) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (Context Value -> MustacheAST -> String) Source | |
| ToMustache (Context Value -> MustacheAST -> Text) Source | |
| ToMustache (Context Value -> MustacheAST -> MustacheAST) Source | |
| ToMustache (MustacheAST -> Either String String) Source | |
| ToMustache (MustacheAST -> Either String Text) Source | |
| ToMustache (MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (MustacheAST -> String) Source | |
| ToMustache (MustacheAST -> Text) Source | |
| ToMustache m => ToMustache (HashMap Text m) Source |
toMustacheText :: Conversion t Text => t -> Value Source
Converts arbitrary String-likes to Values
mFromJSON :: ToJSON j => j -> Value Source
Converts a value that can be represented as JSON to a Value.
Representation
Representation of stateful context for the substitution process
Constructors
| Context [a] a |
Instances
| ToMustache (Context Value -> MustacheAST -> Either String Text) Source | |
| ToMustache (Context Value -> MustacheAST -> Either String MustacheAST) Source | |
| ToMustache (Context Value -> MustacheAST -> String) Source | |
| ToMustache (Context Value -> MustacheAST -> Text) Source | |
| ToMustache (Context Value -> MustacheAST -> MustacheAST) Source |