| Copyright | © 2016–present Stack Builders |
|---|---|
| License | BSD 3 clause |
| Maintainer | Mark Karpov <markkarpov92@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Text.Mustache
Description
This is a Haskell implementation of Mustache templates. The implementation conforms to the version 1.1.3 of the official Mustache specification https://github.com/mustache/spec. It has a 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 Megaparsec parsing library to parse the templates which results in high-quality error messages.
For rendering you only need to create Aeson's Value that is used for interpolation of template variables. Since the library re-uses Aeson's instances and most data types in the Haskell ecosystem are instances of classes like ToJSON, the process is simple for the end user.
Template Haskell helpers for compilation of templates at compile time are available in the Text.Mustache.Compile.TH module.
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 bundle -> putStrLn (errorBundlePretty bundle) 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:
- The official Mustache site: https://mustache.github.io/
- The manual: https://mustache.github.io/mustache.5.html
- The specification: https://github.com/mustache/spec
- Stack Builders Stache tutorial: https://www.stackbuilders.com/tutorials/haskell/mustache-templates/
Synopsis
- data Template = Template {
- templateActual :: PName
- templateCache :: Map PName [Node]
- data Node
- = TextBlock Text
- | EscapedVar Key
- | UnescapedVar Key
- | Section Key [Node]
- | InvertedSection Key [Node]
- | Partial PName (Maybe Pos)
- newtype Key = Key {}
- newtype PName = PName {}
- newtype MustacheException = MustacheParserException (ParseErrorBundle Text Void)
- data MustacheWarning
- displayMustacheWarning :: MustacheWarning -> String
- compileMustacheDir :: MonadIO m => PName -> FilePath -> m Template
- compileMustacheDir' :: MonadIO m => (FilePath -> Bool) -> PName -> FilePath -> m Template
- compileMustacheFile :: MonadIO m => FilePath -> m Template
- compileMustacheText :: PName -> Text -> Either (ParseErrorBundle Text Void) Template
- renderMustache :: Template -> Value -> Text
- renderMustacheW :: Template -> Value -> ([MustacheWarning], Text)
Types
Mustache template as the name of the “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.
Constructors
| Template | |
Fields
| |
Instances
| Data Template Source # | |
Defined in Text.Mustache.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Template -> c Template # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Template # toConstr :: Template -> Constr # dataTypeOf :: Template -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Template) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Template) # gmapT :: (forall b. Data b => b -> b) -> Template -> Template # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Template -> r # gmapQ :: (forall d. Data d => d -> u) -> Template -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Template -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Template -> m Template # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Template -> m Template # | |
| Semigroup Template Source # | |
| Generic Template Source # | |
| Show Template Source # | |
| Eq Template Source # | |
| Ord Template Source # | |
Defined in Text.Mustache.Type | |
| Lift Template Source # | Since: 2.1.0 |
| type Rep Template Source # | |
Defined in Text.Mustache.Type type Rep Template = D1 ('MetaData "Template" "Text.Mustache.Type" "stache-2.3.4-inplace" 'False) (C1 ('MetaCons "Template" 'PrefixI 'True) (S1 ('MetaSel ('Just "templateActual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PName) :*: S1 ('MetaSel ('Just "templateCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PName [Node])))) | |
A structural element of a template.
Constructors
| TextBlock Text | Plain text contained between tags |
| EscapedVar Key | HTML-escaped variable |
| UnescapedVar Key | Unescaped variable |
| Section Key [Node] | Mustache section |
| InvertedSection Key [Node] | Inverted section |
| Partial PName (Maybe Pos) | Partial with indentation level ( |
Instances
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.
Instances
| Data Key Source # | |
Defined in Text.Mustache.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Key -> c Key # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Key # dataTypeOf :: Key -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Key) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key) # gmapT :: (forall b. Data b => b -> b) -> Key -> Key # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r # gmapQ :: (forall d. Data d => d -> u) -> Key -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Key -> m Key # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key # | |
| Monoid Key Source # | |
| Semigroup Key Source # | |
| Generic Key Source # | |
| Show Key Source # | |
| NFData Key Source # | |
Defined in Text.Mustache.Type | |
| Eq Key Source # | |
| Ord Key Source # | |
| Lift Key Source # | Since: 2.1.0 |
| type Rep Key Source # | |
Defined in Text.Mustache.Type | |
Identifier for partials. Note that with the OverloadedStrings extension you can use just string literals to create values of this type.
Instances
| Data PName Source # | |
Defined in Text.Mustache.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PName -> c PName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PName # dataTypeOf :: PName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PName) # gmapT :: (forall b. Data b => b -> b) -> PName -> PName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PName -> r # gmapQ :: (forall d. Data d => d -> u) -> PName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PName -> m PName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PName -> m PName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PName -> m PName # | |
| IsString PName Source # | |
Defined in Text.Mustache.Type Methods fromString :: String -> PName # | |
| Generic PName Source # | |
| Show PName Source # | |
| NFData PName Source # | |
Defined in Text.Mustache.Type | |
| Eq PName Source # | |
| Ord PName Source # | |
| Lift PName Source # | Since: 2.1.0 |
| type Rep PName Source # | |
Defined in Text.Mustache.Type | |
newtype MustacheException Source #
Exception that is thrown when parsing of a template fails or referenced values are not provided.
Constructors
| MustacheParserException (ParseErrorBundle Text Void) | Template parser has failed. This contains the parse error. Before version 0.2.0 it was called The |
Instances
data MustacheWarning Source #
Warning that may be generated during rendering of a Template.
Since: 1.1.1
Constructors
| MustacheVariableNotFound Key | The template contained a variable for which there was no data in the current context. |
| MustacheDirectlyRenderedValue Key | A complex value such as an |
Instances
displayMustacheWarning :: MustacheWarning -> String Source #
Pretty-print a MustacheWarning.
Since: 1.1.1
Compiling
Arguments
| :: MonadIO m | |
| => PName | Which template to select after compiling |
| -> FilePath | Directory with templates |
| -> m Template | The resulting template |
Compile all templates in the specified directory and select one. Template files should have the extension mustache, (e.g. foo.mustache) to be recognized. This function does not scan the directory recursively.
Note that each template/partial will get an identifier which consists of the name of corresponding template file with extension .mustache dropped. This is important for e.g. selecting active template after loading (the first argument).
The action can throw MustacheParserException and the same exceptions as getDirectoryContents, and readFile.
compileMustacheDir = complieMustacheDir' isMustacheFile
Arguments
| :: MonadIO m | |
| => (FilePath -> Bool) | Template selection predicate |
| -> PName | Which template to select after compiling |
| -> FilePath | Directory with templates |
| -> m Template | The resulting template |
The same as compileMustacheDir, but allows using a custom predicate for template selection.
Since: 1.2.0
Compile a Mustache template and select it.
The action can throw MustacheParserException and the same exceptions as readFile.
Rendering
renderMustache :: Template -> Value -> Text Source #
Render a Mustache Template using Aeson's Value to get actual values for interpolation.
renderMustacheW :: Template -> Value -> ([MustacheWarning], Text) Source #
Like renderMustache, but also returns a collection of warnings.
Since: 1.1.1