| Copyright | (c) Justus Adam, 2015 |
|---|---|
| License | LGPL-3 |
| Maintainer | development@justusadam.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Mustache
Description
- How to use this library
This module exposes some of the most convenient functions for dealing with mustache templates.
The easiest way of compiling a file and its potential includes (called partials)
is by using the compileTemplate function.
@
-- the search space encompasses all directories in which the compiler should
-- search for the template source files
--
-- the search is conducted in order, from left to right.
let searchSpace = [".", "./templates"]
-- the templateName is the relative path of the template to any directory
-- of the search space
templateName = "main.mustache"
compiled <- automaticCompile searchSpace templateName case compiled of -- the compiler will throw errors if either the template is malformed -- or the source file for a partial could not be found Left err -> print err Right template -> return () -- this is where you can start using it @
Should your search space be only the current working directory, you can use
localAutomaticCompile.
- automaticCompile :: [FilePath] -> FilePath -> IO (Either ParseError Template)
- localAutomaticCompile :: FilePath -> IO (Either ParseError Template)
- compileTemplateWithCache :: [FilePath] -> TemplateCache -> FilePath -> IO (Either ParseError Template)
- parseTemplate :: String -> Text -> Either ParseError Template
- data Template = Template {}
- substitute :: ToMustache j => Template -> j -> Text
- substituteValue :: Template -> Value -> Text
- class ToMustache ω where
- toMustache :: ω -> Value
- object :: [Pair] -> Value
- (~>) :: ToMustache ω => Text -> ω -> Pair
- (~=) :: ToJSON ι => Text -> ι -> Pair
- (~~>) :: (Conversion ζ Text, ToMustache ω) => ζ -> ω -> Pair
- (~~=) :: (Conversion ζ Text, ToJSON ι) => ζ -> ι -> Pair
Compiling
Automatic
automaticCompile :: [FilePath] -> FilePath -> IO (Either ParseError Template) Source
Compiles a mustache template provided by name including the mentioned partials.
The same can be done manually using getFile, mustacheParser and getPartials.
This function also ensures each partial is only compiled once even though it may be included by other partials including itself.
A reference to the included template will be found in each including templates
partials section.
Manually
compileTemplateWithCache :: [FilePath] -> TemplateCache -> FilePath -> IO (Either ParseError Template) Source
Compile a mustache template providing a list of precompiled templates that do not have to be recompiled.
parseTemplate :: String -> Text -> Either ParseError Template Source
A compiled Template with metadata.
Rendering
Generic
substitute :: ToMustache j => Template -> j -> Text Source
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.
Equivalent to substituteValue . toMustache.
Specialized
substituteValue :: Template -> Value -> Text Source
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.
Data Conversion
class ToMustache ω where Source
Conversion class
Methods
toMustache :: ω -> Value Source
Instances
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 Source
Map keys to values that provide a ToMustache instance
Recommended in conjunction with the OverloadedStrings extension.
(~=) :: ToJSON ι => Text -> ι -> Pair Source
Map keys to values that provide a ToJSON instance
Recommended in conjunction with the OverloadedStrings extension.
(~~>) :: (Conversion ζ Text, ToMustache ω) => ζ -> ω -> Pair Source
Conceptually similar to ~> but uses arbitrary String-likes as keys.