mustache-0.3.1.0: A mustache template parser library.

Copyright(c) Justus Adam, 2015
LicenseLGPL-3
Maintainerdev@justus.science
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Mustache

Contents

Description

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. Alternatively the ~~> operator can be used, which accepts an arbitrary string-like, converting it to text.

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 AST, the abstract syntax tree, which is basically a list of text blocks and mustache tags. The name of the template and its partials 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 AST 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 searchSpache, 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

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

Compiles a Template directly from Text without checking for missing partials. the result will be a Template with an empty partials cache.

data Template Source

A compiled Template with metadata.

Constructors

Template 

Instances

Rendering

Generic

substitute :: ToMustache κ => Template -> κ -> 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

Note that some instances of this class overlap delierately to provide maximum flexibility instances while preserving maximum efficiency.

Methods

toMustache :: ω -> 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 ω => ToMustache [ω] Source 
ToMustache ω => ToMustache (HashSet ω) Source 
ToMustache ω => ToMustache (Vector ω) Source 
ToMustache (Vector Value) Source 
Conversion θ Text => ToMustache (Context Value -> AST -> θ) Source 
ToMustache (Context Value -> AST -> Text) Source 
ToMustache (Context Value -> AST -> AST) Source 
ToMustache (AST -> Text) Source 
ToMustache (AST -> AST) Source 
(ToMustache α, ToMustache β) => ToMustache (α, β) Source 
(Conversion θ Text, ToMustache ω) => ToMustache (HashMap θ ω) Source 
ToMustache ω => ToMustache (HashMap Text ω) Source 
ToMustache (HashMap Text Value) Source 
(Conversion θ Text, ToMustache ω) => ToMustache (Map θ ω) Source 
(ToMustache α, ToMustache β, ToMustache γ) => ToMustache (α, β, γ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ) => ToMustache (α, β, γ, δ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε) => ToMustache (α, β, γ, δ, ε) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ) => ToMustache (α, β, γ, δ, ε, ζ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η) => ToMustache (α, β, γ, δ, ε, ζ, η) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η, ToMustache θ) => ToMustache (α, β, γ, δ, ε, ζ, η, θ) 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.

(~~>) :: (Conversion ζ Text, ToMustache ω) => ζ -> ω -> Pair infixr 8 Source

Conceptually similar to ~> but uses arbitrary String-likes as keys.

(~~=) :: (Conversion ζ Text, ToJSON ι) => ζ -> ι -> Pair infixr 8 Source

Conceptually similar to ~= but uses arbitrary String-likes as keys.