mustache-0.1.0.0: A mustache template parser library.

Copyright(c) Justus Adam, 2015
LicenseLGPL-3
Maintainerdevelopment@justusadam.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Mustache

Contents

Description

 

Synopsis

Compiling

Automatic

compileTemplate :: [FilePath] -> FilePath -> IO (Either ParseError MustacheTemplate) 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] -> [MustacheTemplate] -> FilePath -> IO (Either ParseError MustacheTemplate) Source

Compile a mustache template providing a list of precompiled templates that do not have to be recompiled.

data MustacheTemplate Source

A compiled Template with metadata.

Rendering

Generic

substitute :: ToMustache j => MustacheTemplate -> j -> Either String Text Source

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.

Equivalent to substituteValue . toMustache.

Specialized

substituteValue :: MustacheTemplate -> Value -> Either String Text Source

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.

Data Conversion

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.

Util

These are functions used internally by the parser and renderer. Whether these will continue to be exposed is to be seen.

getFile :: [FilePath] -> FilePath -> EitherT ParseError IO Text Source

getFile searchSpace file iteratively searches all directories in searchSpace for a file returning it if found or raising an error if none of the directories contain the file.

This trows ParseErrors to be compatible with the internal Either Monad of compileTemplateWithCache.

getPartials :: MustacheAST -> [FilePath] Source

Find the names of all included partials in a mustache AST.

Same as join . fmap getPartials'

getPartials' :: MustacheNode Text -> [FilePath] Source

Find partials in a single MustacheNode