Copyright | (c) Justus Adam 2015 |
---|---|
License | BSD3 |
Maintainer | dev@justus.science |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
How to use this library
This module exposes some of the most convenient functions for dealing with mustache templates.
Compiling with automatic partial discovery
The easiest way of compiling a file and its potential includes (called partials)
is by using the automaticCompile
function.
main :: IO () main = do let searchSpace = [".", "./templates"] templateName = "main.mustache" compiled <- automaticCompile searchSpace templateName case compiled of Left err -> print err Right template -> return () -- this is where you can start using it
The searchSpace
encompasses all directories in which the compiler should
search for the template source files.
The search itself is conducted in order, from left to right.
Should your search space be only the current working directory, you can use
localAutomaticCompile
.
The templateName
is the relative path of the template to any directory
of the search space.
automaticCompile
not only finds and compiles the template for you, it also
recursively finds any partials included in the template as well,
compiles them and stores them in the partials
hash attached to the resulting
template.
The compiler will throw errors if either the template is malformed
or the source file for a partial or the template itself could not be found
in any of the directories in searchSpace
.
Substituting
In order to substitute data into the template it must be an instance of the ToMustache
typeclass or be of type Value
.
This libray tries to imitate the API of aeson
by allowing you to define conversions of your own custom data types into Value
,
the type used internally by the substitutor via typeclass and a selection of
operators and convenience functions.
Example
data Person = { age :: Int, name :: String } instance ToMustache Person where toMustache person = object [ "age" ~> age person , "name" ~> name person ]
The values to the left of the ~>
operator has to be of type Text
, hence the
OverloadedStrings
can becomes very handy here.
Values to the right of the ~>
operator must be an instance of the ToMustache
typeclass. Alternatively, if your value to the right of the ~>
operator is
not an instance of ToMustache
but an instance of ToJSON
you can use the
~=
operator, which accepts ToJSON
values.
data Person = { age :: Int, name :: String, address :: Address } data Address = ... instance ToJSON Address where ... instance ToMustache Person where toMustache person = object [ "age" ~> age person , "name" ~> name person , "address" ~= address person ]
All operators are also provided in a unicode form, for those that, like me, enjoy unicode operators.
Manual compiling
You can compile templates manually without requiring the IO monad at all, using
the compileTemplate
function. This is the same function internally used by
automaticCompile
and does not check if required partial are present.
More functions for manual compilation can be found in the Compile
module. Including helpers for finding lists of partials in templates.
Additionally the compileTemplateWithCache
function is exposed here which you
may use to automatically compile a template but avoid some of the compilation
overhead by providing already compiled partials as well.
Fundamentals
This library builds on three important data structures/types.
Value
- A data structure almost identical to Data.Aeson.Value extended with lambda functions which represents the data the template is being filled with.
ToMustache
- A typeclass for converting arbitrary types to
Value
, similar to Data.Aeson.ToJSON but with support for lambdas. Template
- Contains the
STree
, the syntax tree, which is basically a list of text blocks and mustache tags. Thename
of the template and itspartials
cache.
Compiling
During the compilation step the template file is located, read, then parsed in a single
pass (compileTemplate
), resulting in a Template
with an empty partials
section.
Subsequenty the STree
of the template is scanned for included partials, any
present TemplateCache
is queried for the partial (compileTemplateWithCache
),
if not found it will be searched for in the searchSpace
, compiled and
inserted into the template's own cache as well as the global cache for the
compilation process.
Internally no partial is compiled twice, as long as the names stay consistent.
Once compiled templates may be used multiple times for substitution or as partial for other templates.
Partials are not being embedded into the templates during compilation, but during
substitution, hence the partials
cache is vital to the template even after
compilation has been completed. Any non existent partial in the cache will
rsubstitute to an empty string.
Substituting
Synopsis
- automaticCompile :: [FilePath] -> FilePath -> IO (Either ParseError Template)
- localAutomaticCompile :: FilePath -> IO (Either ParseError Template)
- compileTemplateWithCache :: [FilePath] -> TemplateCache -> FilePath -> IO (Either ParseError Template)
- compileTemplate :: String -> Text -> Either ParseError Template
- data Template = Template {}
- substitute :: ToMustache k => Template -> k -> Text
- checkedSubstitute :: ToMustache k => Template -> k -> ([SubstitutionError], Text)
- substituteValue :: Template -> Value -> Text
- checkedSubstituteValue :: Template -> Value -> ([SubstitutionError], Text)
- substituteNode :: Node Text -> SubM ()
- substituteAST :: STree -> SubM ()
- catchSubstitute :: SubM a -> SubM (a, Text)
- class ToMustache ω
- toMustache :: ToMustache ω => ω -> Value
- object :: [Pair] -> Value
- (~>) :: ToMustache ω => Text -> ω -> Pair
- (~=) :: ToJSON ι => Text -> ι -> Pair
- overText :: (Text -> Text) -> Value
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.
localAutomaticCompile :: FilePath -> IO (Either ParseError Template) Source #
Compile the template with the search space set to only the current directory
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.
compileTemplate :: String -> Text -> Either ParseError Template Source #
A compiled Template with metadata.
Instances
Show Template Source # | |
Lift Template Source # | |
Lift TemplateCache Source # | |
Defined in Text.Mustache.Internal.Types lift :: TemplateCache -> Q Exp # | |
MonadReader (Context Value, TemplateCache) SubM Source # | |
Defined in Text.Mustache.Internal.Types |
Rendering
Generic
substitute :: ToMustache k => Template -> k -> Text Source #
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.
Equivalent to substituteValue . toMustache
.
checkedSubstitute :: ToMustache k => Template -> k -> ([SubstitutionError], Text) Source #
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure and report any errors and warnings encountered during substitution.
This function always produces results, as in a fully substituted/rendered template, it never halts on errors. It simply reports them in the first part of the tuple. Sites with errors are usually substituted with empty string.
The second value in the tuple is a template rendered with errors ignored. Therefore if you must enforce that there were no errors during substitution you must check that the error list in the first tuple value is empty.
Equivalent to checkedSubstituteValue . toMustache
.
Specialized
substituteValue :: Template -> Value -> Text Source #
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.
checkedSubstituteValue :: Template -> Value -> ([SubstitutionError], Text) Source #
Substitutes all mustache defined tokens (or tags) for values found in the provided data structure and report any errors and warnings encountered during substitution.
This function always produces results, as in a fully substituted/rendered template, it never halts on errors. It simply reports them in the first part of the tuple. Sites with errors are usually substituted with empty string.
The second value in the tuple is a template rendered with errors ignored. Therefore if you must enforce that there were no errors during substitution you must check that the error list in the first tuple value is empty.
In Lambdas
catchSubstitute :: SubM a -> SubM (a, Text) Source #
Catch the results of running the inner substitution.
Data Conversion
class ToMustache ω Source #
Conversion class
Instances
toMustache :: ToMustache ω => ω -> Value Source #
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.