ede-0.2.9: Templating language with similar syntax and features to Liquid or Jinja2.

Safe HaskellNone
LanguageHaskell2010

Text.EDE

Contents

Description

A (mostly logicless) textual templating language with similar syntax to Liquid or Jinja2.

(ED-E is a character from Fallout New Vegas, pronounced Eddie.)

Synopsis

How to use this library

A simple example of parsing and rendering Text containing a basic conditional expression and variable interpolation follows.

First the Template is defined and parsed in the Result monad:

>>> tmpl <- parse "{% if var %}\nHello, {{ var }}!\n{% else %}\nnegative!\n{% endif %}\n" :: Result Template

Then an Object is defined containing the environment which will be available to the Template during rendering:

>>> let env = fromPairs [ "var" .= "World" ] :: Object

Note: the fromPairs function above is a wrapper over Aeson's object which removes the outer Object Value constructor, exposing the underlying HashMap.

Then, the Template is rendered using the Object environment:

>>> render tmpl env :: Result Text
> Success "Hello, World!"

In this manner, Templates can be pre-compiled to the internal AST and the cost of parsing can be amortised if the same Template is rendered multiple times.

Another example, this time rendering a Template from a file:

import qualified Data.Text.Lazy as LText
import           Text.EDE

main :: IO ()
main = do
    r <- eitherParseFile "template.ede"
    either error print $ r >>= (`eitherRender` env)
  where
    env = fromPairs
        [ "text" .= "Some Text."
        , "int"  .= 1
        , "list" .= [5..10]
        ]

Please see the syntax section for more information about available statements and expressions.

Parsing and Rendering

Parsing and rendering require two separate steps intentionally so that the more expensive (and potentially impure) action of parsing and resolving includes can be embedded and re-used in a pure fashion.

  • Parsing tokenises the input and converts it to an internal AST representation, resolving includes using a custom function. The result is a compiled template which can be cached for future use.
  • Rendering takes a HashMap of custom Funs (functions available in the template context), an Object as the binding environment, and a parsed Template to subsitute the values into. The result is a Lazy Text value containing the rendered output.

data Template Source #

A parsed and compiled template.

Instances

Parsing

parse Source #

Arguments

:: ByteString

Strict ByteString template definition.

-> Result Template 

Parse Lazy Text into a compiled Template.

Because this function is pure and does not resolve includes, encountering an include expression during parsing will result in an Error.

See parseFile or parseWith for mechanisms to deal with include dependencies.

parseIO Source #

Arguments

:: FilePath

Parent directory for relatively pathed includes.

-> ByteString

Strict ByteString template definition.

-> IO (Result Template) 

Parse Text into a compiled Template.

This function handles all include expressions as FilePaths and performs recursive loading/parsing.

parseFile Source #

Arguments

:: FilePath

Path to the template to load and parse.

-> IO (Result Template) 

Load and parse a Template from a file.

This function handles all include expressions as FilePaths and performs recursive loading/parsing, with pathing of includes relatively to the target (unless absolute paths are used).

parseFileWith Source #

Arguments

:: Syntax

Delimiters and parsing options.

-> FilePath

Path to the template to load and parse.

-> IO (Result Template) 

See: parseFile.

parseWith Source #

Arguments

:: Monad m 
=> Syntax

Delimiters and parsing options.

-> Resolver m

Function to resolve includes.

-> Text

Strict Text name.

-> ByteString

Strict ByteString template definition.

-> m (Result Template) 

Parse a Template from a Strict ByteString using a custom function for resolving include expressions.

Two custom include resolvers are supplied:

parseFile for example, is defined as: parseWith includeFile.

Includes

The Resolver used to resolve include expressions determines the purity of Template parsing.

For example, using the includeFile Resolver means parsing is restricted to IO, while pre-caching a HashMap of Templates and supplying them to parseWith using includeMap offers a pure variant for include resolution.

type Resolver m = Syntax -> Id -> Delta -> m (Result Template) Source #

A function to resolve the target of an include expression.

type Id = Text Source #

includeMap Source #

Arguments

:: Monad m 
=> HashMap Id Template

A HashMap of named Templates.

-> Resolver m

Resolver for parseWith.

HashMap resolver for include expressions.

The identifier component of the include expression is treated as a lookup key into the supplied HashMap. If the identifier doesn't exist in the HashMap, an Error is returned.

includeFile Source #

Arguments

:: FilePath

Parent directory for relatively pathed includes.

-> Resolver IO 

FilePath resolver for include expressions.

The identifier component of the include expression is treated as a relative FilePath and the template is loaded and parsed using parseFile. If the identifier doesn't exist as a valid FilePath, an Error is returned.

Rendering

render Source #

Arguments

:: Template

Parsed Template to render.

-> Object

Bindings to make available in the environment.

-> Result Text 

Render an Object using the supplied Template.

renderWith Source #

Arguments

:: HashMap Id Term

Filters to make available in the environment.

-> Template

Parsed Template to render.

-> Object

Bindings to make available in the environment.

-> Result Text 

Render an Object using the supplied Template.

Either Variants

Results and Errors

The Result of a parse or render steps can be inspected or analysed using result as follows:

>>> result failure success $ render tmpl env

If you're only interested in dealing with errors as strings, and the positional information contained in Meta is not of use you can use the convenience functions eitherParse, eitherRender, or convert a Result to Either using eitherResult.

>>> either failure success $ eitherParse tmpl

data Delta :: * #

Instances

Eq Delta 

Methods

(==) :: Delta -> Delta -> Bool #

(/=) :: Delta -> Delta -> Bool #

Data Delta 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delta -> c Delta #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delta #

toConstr :: Delta -> Constr #

dataTypeOf :: Delta -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Delta) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delta) #

gmapT :: (forall b. Data b => b -> b) -> Delta -> Delta #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQ :: (forall d. Data d => d -> u) -> Delta -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Delta -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

Ord Delta 

Methods

compare :: Delta -> Delta -> Ordering #

(<) :: Delta -> Delta -> Bool #

(<=) :: Delta -> Delta -> Bool #

(>) :: Delta -> Delta -> Bool #

(>=) :: Delta -> Delta -> Bool #

max :: Delta -> Delta -> Delta #

min :: Delta -> Delta -> Delta #

Show Delta 

Methods

showsPrec :: Int -> Delta -> ShowS #

show :: Delta -> String #

showList :: [Delta] -> ShowS #

Generic Delta 

Associated Types

type Rep Delta :: * -> * #

Methods

from :: Delta -> Rep Delta x #

to :: Rep Delta x -> Delta #

Semigroup Delta 

Methods

(<>) :: Delta -> Delta -> Delta #

sconcat :: NonEmpty Delta -> Delta #

stimes :: Integral b => b -> Delta -> Delta #

Monoid Delta 

Methods

mempty :: Delta #

mappend :: Delta -> Delta -> Delta #

mconcat :: [Delta] -> Delta #

Hashable Delta 

Methods

hashWithSalt :: Int -> Delta -> Int #

hash :: Delta -> Int #

Pretty Delta 

Methods

pretty :: Delta -> Doc #

prettyList :: [Delta] -> Doc #

HasBytes Delta 

Methods

bytes :: Delta -> Int64 #

HasDelta Delta 

Methods

delta :: Delta -> Delta #

Measured Delta Strand 

Methods

measure :: Strand -> Delta #

Measured Delta Rope 

Methods

measure :: Rope -> Delta #

MarkParsing Delta Parser 

Methods

mark :: Parser Delta #

release :: Delta -> Parser () #

Applicative m => Semigroup (Resolver m) # 

Methods

(<>) :: Resolver m -> Resolver m -> Resolver m #

sconcat :: NonEmpty (Resolver m) -> Resolver m #

stimes :: Integral b => b -> Resolver m -> Resolver m #

type Rep Delta 
type Rep Delta = D1 * (MetaData "Delta" "Text.Trifecta.Delta" "trifecta-1.7.1.1-HrJoGmjAESf6gcNNKOzF0c" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Columns" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)))) (C1 * (MetaCons "Tab" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)))))) ((:+:) * (C1 * (MetaCons "Lines" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))))) (C1 * (MetaCons "Directed" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ByteString)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))))))))

data Result a Source #

The result of running parsing or rendering steps.

Constructors

Success a 
Failure Doc 

Instances

Monad Result Source # 

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Foldable Result Source # 

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Alternative Result Source # 

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Applicative m => Semigroup (Resolver m) Source # 

Methods

(<>) :: Resolver m -> Resolver m -> Resolver m #

sconcat :: NonEmpty (Resolver m) -> Resolver m #

stimes :: Integral b => b -> Resolver m -> Resolver m #

Show a => Pretty (Result a) Source # 

Methods

pretty :: Result a -> Doc #

prettyList :: [Result a] -> Doc #

eitherResult :: Result a -> Either String a Source #

Convert a Result to an Either with the Left case holding a formatted error message, and Right being the successful result over which Result is paramterised.

result Source #

Arguments

:: (Doc -> b)

Function to apply to the Failure case.

-> (a -> b)

Function to apply to the Success case.

-> Result a

The Result to map over.

-> b 

Perform a case analysis on a Result.

success :: Monad m => a -> m (Result a) Source #

Convenience for returning a successful Result.

failure :: Monad m => Doc -> m (Result a) Source #

Convenience for returning an error Result.

Input

fromPairs (or fromValue) is a wrapper around Aeson's object function which safely strips the outer Value constructor, providing the correct type signature for input into render.

It is used in combination with the re-exported .= as follows:

>>> render (fromPairs [ "foo" .= "value", "bar" .= 1 ]) :: Template -> Result Text

fromValue :: Value -> Maybe Object Source #

Unwrap a Value to an Object safely.

See Aeson's documentation for more details.

fromPairs :: [Pair] -> Object Source #

Create an Object from a list of name/value Pairs.

See Aeson's documentation for more details.

(.=) :: KeyValue kv => forall v. ToJSON v => Text -> v -> kv infixr 8 #

Version

version :: Version Source #

ED-E Version.

Syntax

data Syntax Source #

Instances

delimPragma :: HasSyntax c => Lens' c Delim Source #

delimInline :: HasSyntax c => Lens' c Delim Source #

delimComment :: HasSyntax c => Lens' c Delim Source #

delimBlock :: HasSyntax c => Lens' c Delim Source #

defaultSyntax :: Syntax Source #

The default ED-E syntax.

Delimiters:

  • Pragma: {! ... !}
  • Inline: {{ ... }}
  • Comments: {}
  • Blocks: {% ... %}

alternateSyntax :: Syntax Source #

An alternate syntax (based on Play/Scala templates) designed to be used when the default is potentially ambiguous due to another encountered smarty based syntax.

Delimiters:

  • Inline: <@ ... @>
  • Comments: @* ... *@
  • Blocks: @( ... )@

Pragmas

Syntax can be modified either via the arguments to parseWith or alternatively by specifying the delimiters via an EDE_SYNTAX pragma.

Note: The pragmas must start on line1. Subsequently encountered pragmas are parsed as textual template contents.

For example:

{! EDE_SYNTAX pragma=("{*", "*}") inline=("#@", "@#") comment=("<#", "#>") block=("$$", "$$") !}
{* EDE_SYNTAX block=("#[", "]#")  *}
...

Would result in the following syntax:

  • Pragmas: {* ... *}
  • Inline: #@ ... @#
  • Comment: <# ... #>
  • Block: #[ ... ]#

Note: EDE_SYNTAX pragmas only take effect for the current template, not child includes. If you want to override the syntax for all templates use parseWith and custom Syntax settings.

Expressions

Expressions behave as any simplistic programming language with a variety of prefix, infix, and postifx operators available. (See: Text.EDE.Filters)

A rough overview of the expression grammar:

expression ::= literal | identifier | '|' filter
filter     ::= identifier
identifier ::= [a-zA-Z_]{1}[0-9A-Za-z_']*
object     ::= '{' pairs '}'
pairs      ::= string ':' literal | string ':' literal ',' pairs
array      ::= '[' elements ']'
elements   ::= literal | literal ',' elements
literal    ::= object | array | boolean | number | string
boolean    ::= true | false
number     ::= integer | double
string     ::= "char+|escape"

Variables

Variables are substituted directly for their renderable representation. An error is raised if the varaible being substituted is not a literal type (ie. an Array or Object) or doesn't exist in the supplied environment.

{{ var }}

Nested variable access is also supported for variables which resolve to an Object. Dot delimiters are used to chain access through multiple nested Objects. The right-most accessor must resolve to a renderable type as with the previous non-nested variable access.

{{ nested.var.access }}

Conditionals

A conditional is introduced and completed with the section syntax:

{% if <expr1> %}
   ... consequent expressions
{% elif <expr2> %}
   ... consequent expressions
{% elif <expr3> %}
   ... consequent expressions
{% else %}
   ... alternate expressions
{% endif %}

The boolean result of the expr determines the branch that is rendered by the template with multiple (or none) elif branches supported, and the else branch being optional.

In the case of a literal it conforms directly to the supported boolean or relation logical operators from Haskell. If a variable is singularly used its existence determines the result of the predicate; the exception to this rule is boolean values which will be substituted into the expression if they exist in the supplied environment.

The following logical expressions are supported as predicates in conditional statements with parameters type checked and an error raised if the left and right hand sides are not type equivalent.

  • And: &&
  • Or: ||
  • Equal: ==
  • Not Equal: != (See: /=)
  • Greater: >
  • Greater Or Equal: >=
  • Less: <
  • Less Or Equal: <=
  • Negation: ! (See: not)

See: Text.EDE.Filters

Case Analysis

To pattern match a literal or variable, you can use the case statement:

{% case var %}
{% when "a" %}
   .. matched expressions
{% when "b" %}
   .. matched expressions
{% else %}
   .. alternate expressions
{% endcase %}

Patterns take the form of variables, literals, or the wild-card '@_@' pattern (which matches anything).

Loops

Iterating over an Array or Object can be acheived using the 'for ... in' section syntax. Attempting to iterate over any other type will raise an error.

Example:

{% for var in list %}
    ... iteration expression
{% else %}
    ... alternate expression
{% endfor %}

The iteration branch is rendering per item with the else branch being (which is optional) being rendered if the {{ list }} variable is empty.

When iterating over an Object, a stable sort using key equivalence is applied, Arrays are unmodified.

The resulting binding within the iteration expression (in this case, {{ var }}) is an Object containing the following keys:

  • key :: Text: They key if the loop target is an Object
  • value :: a: The value of the loop target
  • loop :: Object: Loop metadata.
  • length :: Int: Length of the loop
  • index :: Int: Index of the iteration
  • index0 :: Int: Zero based index of the iteration
  • remainder :: Int: Remaining number of iterations
  • remainder0 :: Int: Zero based remaining number of iterations
  • first :: Bool: Is this the first iteration?
  • last :: Bool: Is this the last iteration?
  • odd :: Bool: Is this an odd iteration?
  • even :: Bool: Is this an even iteration?

For example:

{% for item in items %}
    {{ item.index }}:{{ item.value }}
    {% if !item.last %}

    {% endif %}
{% endfor %}

Will render each item with its (1-based) loop index as a prefix, separated by a blank newline, without a trailing at the end of the document.

Valid loop targets are Objects, Arrays, and Strings, with only Objects having an available {{ var.key }} in scope.

Includes

Includes are a way to reduce the amount of noise in large templates. They can be used to abstract out common snippets and idioms into partials.

If parseFile or the includeFile resolver is used, templates will be loaded using FilePaths. (This is the default.)

For example:

{% include "/var/tmp/partial.ede" %}

Loads partial.ede from the file system.

The current environment is made directly available to the included template. Additional bindings can be created (See: let) which will be additionally available only within the include under a specific identifier:

{% include "/var/tmp/partial.ede" with some_number = 123 %}

Includes can also be resolved using pure Resolvers such as includeMap, which will treat the include expression's identifier as a HashMap key:

{% include "arbitrary_key" %}

Uses lookup to find arbitrary_key in the HashMap supplied to includeMap.

Filters

Filters are typed functions which can be applied to variables and literals. An example of rendering a lower cased boolean would be:

{{ true | show | lower }}

The input is on the LHS and chained filters (delimited by the pipe operator |) are on the RHS, with filters being applied postfix, left associatively.

See: Text.EDE.Filters

Raw

You can disable template processing for blocks of text using the raw section:

{% raw %}
Some {{{ handlebars }}} or {{ mustache }} or {{ jinja2 }} output tags etc.
{% endraw %}

This can be used to avoid parsing expressions which would otherwise be considered valid ED-E syntax.

Comments

Comments are ignored by the parser and omitted from the rendered output.

{# singleline comment #}
{#
   multiline
   comment
#}

Let Expressions

You can also bind an identifier to values which will be available within the following expression scope.

For example:

{% let var = false %}
...
{{ var }}
...
{% endlet %}