-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Mustache templates for Haskell
--
-- Mustache templates for Haskell.
@package stache
@version 0.2.0
-- | Types used by the package. You don't usually need to import the
-- module, because Text.Mustache re-exports everything you may
-- need, import that module instead.
module Text.Mustache.Type
-- | Mustache template as name of “top-level” template and a collection of
-- all available templates (partials).
--
-- Template is a Semigroup. This means that you can combine
-- Templates (and their caches) using the
-- (<>) operator, the resulting Template
-- will have the same currently selected template as the left one. Union
-- of caches is also left-biased.
data Template
Template :: PName -> Map PName [Node] -> Template
-- | Name of currently “selected” template (top-level one).
[templateActual] :: Template -> PName
-- | Collection of all templates that are available for interpolation (as
-- partials). The top-level one is also contained here and the “focus”
-- can be switched easily by modifying templateActual.
[templateCache] :: Template -> Map PName [Node]
-- | Structural element of template.
data Node
-- | Plain text contained between tags
TextBlock :: Text -> Node
-- | HTML-escaped variable
EscapedVar :: Key -> Node
-- | Unescaped variable
UnescapedVar :: Key -> Node
-- | Mustache section
Section :: Key -> [Node] -> Node
-- | Inverted section
InvertedSection :: Key -> [Node] -> Node
-- | Partial with indentation level (Nothing means it was inlined)
Partial :: PName -> (Maybe Pos) -> Node
-- | Identifier for values to interpolate.
--
-- The representation is the following:
--
--
-- - [] — empty list means implicit iterators;
-- - [text] — single key is a normal identifier;
-- - [text1, text2] — multiple keys represent dotted
-- names.
--
newtype Key
Key :: [Text] -> Key
[unKey] :: Key -> [Text]
-- | Pretty-print a key, this is helpful, for example, if you want to
-- display an error message.
showKey :: Key -> Text
-- | Identifier for partials. Note that with the OverloadedStrings
-- extension you can use just string literals to create values of this
-- type.
newtype PName
PName :: Text -> PName
[unPName] :: PName -> Text
-- | Exception that is thrown when parsing of a template has failed or
-- referenced values were not provided.
data MustacheException
-- | Template parser has failed. This contains the parse error.
--
-- Before version 0.2.0 it was called MustacheException.
MustacheParserException :: (ParseError Char Dec) -> MustacheException
-- | A referenced value was not provided. The exception provides info about
-- partial in which the issue happened PName and name of the
-- missing key Key.
MustacheRenderException :: PName -> Key -> MustacheException
instance GHC.Generics.Generic Text.Mustache.Type.MustacheException
instance GHC.Show.Show Text.Mustache.Type.MustacheException
instance GHC.Classes.Eq Text.Mustache.Type.MustacheException
instance GHC.Generics.Generic Text.Mustache.Type.Template
instance Data.Data.Data Text.Mustache.Type.Template
instance GHC.Show.Show Text.Mustache.Type.Template
instance GHC.Classes.Ord Text.Mustache.Type.Template
instance GHC.Classes.Eq Text.Mustache.Type.Template
instance GHC.Generics.Generic Text.Mustache.Type.Node
instance Data.Data.Data Text.Mustache.Type.Node
instance GHC.Show.Show Text.Mustache.Type.Node
instance GHC.Classes.Ord Text.Mustache.Type.Node
instance GHC.Classes.Eq Text.Mustache.Type.Node
instance GHC.Generics.Generic Text.Mustache.Type.PName
instance Data.Data.Data Text.Mustache.Type.PName
instance GHC.Show.Show Text.Mustache.Type.PName
instance GHC.Classes.Ord Text.Mustache.Type.PName
instance GHC.Classes.Eq Text.Mustache.Type.PName
instance GHC.Generics.Generic Text.Mustache.Type.Key
instance Data.Data.Data Text.Mustache.Type.Key
instance GHC.Base.Monoid Text.Mustache.Type.Key
instance Data.Semigroup.Semigroup Text.Mustache.Type.Key
instance GHC.Show.Show Text.Mustache.Type.Key
instance GHC.Classes.Ord Text.Mustache.Type.Key
instance GHC.Classes.Eq Text.Mustache.Type.Key
instance Data.Semigroup.Semigroup Text.Mustache.Type.Template
instance Control.DeepSeq.NFData Text.Mustache.Type.Key
instance Data.String.IsString Text.Mustache.Type.PName
instance Control.DeepSeq.NFData Text.Mustache.Type.PName
instance GHC.Exception.Exception Text.Mustache.Type.MustacheException
-- | Functions for rendering Mustache templates. You don't usually need to
-- import the module, because Text.Mustache re-exports everything
-- you may need, import that module instead.
module Text.Mustache.Render
-- | Render a Mustache Template using Aeson's Value to get
-- actual values for interpolation.
--
-- As of version 0.2.0, if referenced values are missing (which almost
-- always indicates some sort of mistake), MustacheRenderException
-- will be thrown. The included Key will indicate full path to
-- missing value and PName will contain the name of active
-- partial.
renderMustache :: Template -> Value -> Text
-- | Megaparsec parser for Mustache templates. You don't usually need to
-- import the module, because Text.Mustache re-exports everything
-- you may need, import that module instead.
module Text.Mustache.Parser
-- | Parse given Mustache template.
parseMustache :: FilePath -> Text -> Either (ParseError Char Dec) [Node]
-- | Mustache Template creation from file or a Text value.
-- You don't usually need to import the module, because
-- Text.Mustache re-exports everything you may need, import that
-- module instead.
module Text.Mustache.Compile
-- | Compile all templates in specified directory and select one. Template
-- files should have extension mustache, (e.g.
-- foo.mustache) to be recognized. This function does not
-- scan the directory recursively.
--
-- The action can throw the same exceptions as
-- getDirectoryContents, and readFile.
compileMustacheDir :: (MonadIO m, MonadThrow m) => PName -> FilePath -> m Template
-- | Compile single Mustache template and select it.
--
-- The action can throw the same exceptions as readFile.
compileMustacheFile :: (MonadIO m, MonadThrow m) => FilePath -> m Template
-- | Compile Mustache template from a lazy Text value. The cache
-- will contain only this template named according to given PName.
compileMustacheText :: PName -> Text -> Either (ParseError Char Dec) Template
-- | Template Haskell helpers to compile Mustache templates at compile
-- time. This module is not imported as part of Text.Mustache, so
-- you need to import it yourself. Qualified import is recommended, but
-- not necessary.
--
-- At the moment, functions in this module only work with GHC 8 (they
-- require at least template-haskell-2.11).
module Text.Mustache.Compile.TH
-- | Compile all templates in specified directory and select one. Template
-- files should have extension mustache, (e.g.
-- foo.mustache) to be recognized. This function does not
-- scan the directory recursively.
--
-- This version compiles the templates at compile time.
compileMustacheDir :: PName -> FilePath -> Q Exp
-- | Compile single Mustache template and select it.
--
-- This version compiles the template at compile time.
compileMustacheFile :: FilePath -> Q Exp
-- | Compile Mustache template from Text value. The cache will
-- contain only this template named according to given Key.
--
-- This version compiles the template at compile time.
compileMustacheText :: PName -> Text -> Q Exp
-- | Compile Mustache using QuasiQuoter. Usage:
--
--
-- {-# LANGUAGE QuasiQuotes #-}
-- import Text.Mustache.Compile.TH (mustache)
--
-- foo :: Template
-- foo = [mustache|This is my inline {{ template }}.|]
--
--
-- Name of created partial is set to "quasi-quoted". You can
-- extend cache of Template created this way using mappend
-- and so work with partials as usual.
mustache :: QuasiQuoter
-- | This is a Haskell implementation of Mustache templates. The
-- implementation conforms to the version 1.1.3 of official Mustache
-- specification https://github.com/mustache/spec. It is extremely
-- simple and straightforward to use with minimal but complete API —
-- three functions to compile templates (from directory, from file, and
-- from lazy text) and one to render them.
--
-- The implementation uses the Megaparsec parsing library to parse the
-- templates which results in superior quality of error messages.
--
-- For rendering you only need to create Aeson's Value where you
-- put the data to interpolate. Since the library re-uses Aeson's
-- instances and most data types in Haskell ecosystem are instances of
-- classes like ToJSON, the whole process is very simple for end
-- user.
--
-- Template Haskell helpers for compilation of templates at compile time
-- are available in the Text.Mustache.Compile.TH module. The
-- helpers are currently available only for GHC 8 users though.
--
-- One feature that is not currently supported is lambdas. The feature is
-- marked as optional in the spec and can be emulated via processing of
-- parsed template representation. The decision to drop lambdas is
-- intentional, for the sake of simplicity and better integration with
-- Aeson.
--
-- Here is an example of basic usage:
--
--
-- {-# LANGUAGE OverloadedStrings #-}
--
-- module Main (main) where
--
-- import Data.Aeson
-- import Data.Text
-- import Text.Megaparsec
-- import Text.Mustache
-- import qualified Data.Text.Lazy.IO as TIO
--
-- main :: IO ()
-- main = do
-- let res = compileMustacheText "foo"
-- "Hi, {{name}}! You have:\n{{#things}}\n * {{.}}\n{{/things}}\n"
-- case res of
-- Left err -> putStrLn (parseErrorPretty err)
-- Right template -> TIO.putStr $ renderMustache template $ object
-- [ "name" .= ("John" :: Text)
-- , "things" .= ["pen" :: Text, "candle", "egg"]
-- ]
--
--
-- If I run the program, it prints the following:
--
--
-- Hi, John! You have:
-- * pen
-- * candle
-- * egg
--
--
-- For more information about Mustache templates the following links may
-- be helpful:
--
--
module Text.Mustache
-- | Mustache template as name of “top-level” template and a collection of
-- all available templates (partials).
--
-- Template is a Semigroup. This means that you can combine
-- Templates (and their caches) using the
-- (<>) operator, the resulting Template
-- will have the same currently selected template as the left one. Union
-- of caches is also left-biased.
data Template
Template :: PName -> Map PName [Node] -> Template
-- | Name of currently “selected” template (top-level one).
[templateActual] :: Template -> PName
-- | Collection of all templates that are available for interpolation (as
-- partials). The top-level one is also contained here and the “focus”
-- can be switched easily by modifying templateActual.
[templateCache] :: Template -> Map PName [Node]
-- | Structural element of template.
data Node
-- | Plain text contained between tags
TextBlock :: Text -> Node
-- | HTML-escaped variable
EscapedVar :: Key -> Node
-- | Unescaped variable
UnescapedVar :: Key -> Node
-- | Mustache section
Section :: Key -> [Node] -> Node
-- | Inverted section
InvertedSection :: Key -> [Node] -> Node
-- | Partial with indentation level (Nothing means it was inlined)
Partial :: PName -> (Maybe Pos) -> Node
-- | Identifier for values to interpolate.
--
-- The representation is the following:
--
--
-- - [] — empty list means implicit iterators;
-- - [text] — single key is a normal identifier;
-- - [text1, text2] — multiple keys represent dotted
-- names.
--
newtype Key
Key :: [Text] -> Key
[unKey] :: Key -> [Text]
-- | Identifier for partials. Note that with the OverloadedStrings
-- extension you can use just string literals to create values of this
-- type.
newtype PName
PName :: Text -> PName
[unPName] :: PName -> Text
-- | Exception that is thrown when parsing of a template has failed or
-- referenced values were not provided.
data MustacheException
-- | Template parser has failed. This contains the parse error.
--
-- Before version 0.2.0 it was called MustacheException.
MustacheParserException :: (ParseError Char Dec) -> MustacheException
-- | A referenced value was not provided. The exception provides info about
-- partial in which the issue happened PName and name of the
-- missing key Key.
MustacheRenderException :: PName -> Key -> MustacheException
-- | Compile all templates in specified directory and select one. Template
-- files should have extension mustache, (e.g.
-- foo.mustache) to be recognized. This function does not
-- scan the directory recursively.
--
-- The action can throw the same exceptions as
-- getDirectoryContents, and readFile.
compileMustacheDir :: (MonadIO m, MonadThrow m) => PName -> FilePath -> m Template
-- | Compile single Mustache template and select it.
--
-- The action can throw the same exceptions as readFile.
compileMustacheFile :: (MonadIO m, MonadThrow m) => FilePath -> m Template
-- | Compile Mustache template from a lazy Text value. The cache
-- will contain only this template named according to given PName.
compileMustacheText :: PName -> Text -> Either (ParseError Char Dec) Template
-- | Render a Mustache Template using Aeson's Value to get
-- actual values for interpolation.
--
-- As of version 0.2.0, if referenced values are missing (which almost
-- always indicates some sort of mistake), MustacheRenderException
-- will be thrown. The included Key will indicate full path to
-- missing value and PName will contain the name of active
-- partial.
renderMustache :: Template -> Value -> Text