ert-0.0.2.0: Easy Runtime Templates

PortabilityPOSIX
Stabilityexperimental
Maintainerkayo@illumium.org
Safe HaskellNone

Data.EasyTpl

Contents

Description

This module implements compiler and renderer for easy runtime templates. It can be used for advanced code preprocessing or simple substitution of some variables in string.

Since template engine uses Aeson's Value type, you must use types, which have ToJSON instances, for rendering it. Also you can use Object with variables as fields.

Synopsis

Usage example

 import Data.Aeson
 import Data.EasyTpl (compile, render)
 import Data.ByteString (readFile, writeFile)

 data TplVars = TplVars { ... }

 instance ToJSON TplVars
   ...

 main = do

   template <- readFile "template.tpl" >>=
     either error return . compile

   let result = render Template $ TplVars { ... }

   writeFile "output.txt" result

Template format

Templates consists of:

Control structures
Entities, enclosed by <% and %>.
Substitution expressions
Entities, enclosed by <%= and %>.
Raw content
Anything not controls and literals, interprets as is.

Statements

Control structures:

if control
  <% if expression %>
    The content, which will be displayed, if result of expression evaluation is true.
  <% end %>
for control

Basic form:

  <% for value [, index ] in expression %>
    The content, which will be displayed for each entry in result of expression evaluation.
    Variables value and (optional) index contains entry value and number respectively.
  <% end %>

Alternative form:

  <% for field [, value ] in expression %>
    The content, which will be displayed for each entry in result of expression evaluation.
    Variables field and (optional) value contains entry key and value respectively.
  <% end %>

The expression must be iteratable, like Array or Object.

Expressions

Expressions is:

Constants
Json Values, like string, number, object, array, true, false, null
Variables
Text entities, identified by name
Ranges
Generated arrays of integers
Regexps
Regular expressions, enclosed by / and / with i and m options.
Unary operators
Applied to single expression
Binary operators
Applied to twin expressions

Prefix unary operations:

Get length #
Applied to string, object, array. For anything other gives null.
Stringify @
Converts value to JSON string.
Logical not !
Inverts boolean value.
Numeric negate -
Negates numeric value.
To number +
Forces value to be a numeric.

Postfix unary operations:

Evaluate =
Evaluates string as expression.
Not null ?
Tests value to not be a null.

Generic binary operations:

Equal ==, Not equal !=
Tests values to be an equal.
Compare <, >, <=, >=
Compares values.

Numeric binary operations:

Arithmetic +, -, *, /
Simple calculations.
Integer division :, Extract module %

String binary operations:

Concat +
Concatenates two strings.
Split :
Splits string to array of strings by sepatator.
Repeat *
Repeats string N times.
Regex test ~
Tests string to match regex.
Regex match ~>
Extract matches from string by appling regex.
Regex split ~:
Split string to array of strings by regex.

Logical binary operations:

Logical and &&
Logical or ||

Container indexing operations:

Get field . fieldName
Extracts field, which identified by name.
Get index [ expression ]
Extracts field by number or evaluated name.

This operations applyed sequentially to container types, like string, array, object.

Range expressions:

[ [from] .. to [, step] ]

This expressins generates arrays of numeric values in range from including to by step.

By default from is 0, and step is 1.

Regular expressions:

/ expression / [i] [m]

Posix regular expressions are supported.

  • i-modifier forses case-insensitive mode.
  • m-modifier forces multiline mode.

Template examples

Assets json

  • Template:
 {<%
   for res, num in assets
     %>
   "<%=
       res.name
     %>": "<%
       if #root>0
         %><%=
           root
         %>/<%
       end
     %><%=
       prefix[res.type]
     %><%=
       res.name
     %><%
       if suffix[res.type]?
         %><%=
           suffix[res.type]
         %><%
       end
     %>"<%
       if num+1<#assets
         %>,<%
       end
     %><%
   end
 %>
 }
  • Compiled template:
 (Template [
   ContentToken "{",
   ControlToken
     (Iteration ("num","res") (Variable "assets"))
     (Template [
       ContentToken "\n  \"",
       LiteralToken
         (BinaryOperation GetField
           (Variable "res")
           (Constant (String "name"))),
       ContentToken "\": \"",
       ControlToken
         (Condition
           (BinaryOperation GreatThan
             (UnaryOperation GetLength
               (Variable "root"))
             (Constant (Number 0))))
         (Template [
           LiteralToken
             (Variable "root"),
           ContentToken "/"
         ]),
       LiteralToken
         (BinaryOperation GetField
           (Variable "prefix")
           (BinaryOperation GetField
             (Variable "res")
             (Constant (String "type")))),
       LiteralToken
         (BinaryOperation GetField
           (Variable "res")
           (Constant (String "name"))),
       ControlToken
         (Condition
           (UnaryOperation NotNull
             (BinaryOperation GetField
               (Variable "suffix")
               (BinaryOperation GetField
                 (Variable "res")
                 (Constant (String "type"))))))
         (Template [
           LiteralToken
             (BinaryOperation GetField
               (Variable "suffix")
               (BinaryOperation GetField
                 (Variable "res")
                 (Constant (String "type"))))]),
       ContentToken "\"",
       ControlToken
         (Condition
           (BinaryOperation LessThan
             (BinaryOperation Append
               (Variable "num")
               (Constant (Number 1)))
             (UnaryOperation GetLength
               (Variable "assets"))))
         (Template [
           ContentToken ","
         ])
     ]),
   ContentToken "\n}\n"
 ])
  • Yaml Dataset:
 prefix:
   script: js/
   style: css/
   image: gfx/
 suffix:
   script: .min.js
   style: .min.css
 assets:
   - type: script
     name: client
   - type: style
     name: styles
   - type: style
     name: bootstrap
   - type: script
     name: react
   - type: image
     name: icons.png
   - type: image
     name: photo.jpg
  • Render result:
 {
   "client": "js/client.min.js",
   "styles": "css/styles.min.css",
   "bootstrap": "css/bootstrap.min.css",
   "react": "js/react.min.js",
   "icons.png": "gfx/icons.png",
   "photo.jpg": "gfx/photo.jpg"
 }

EJS-like template

  • Template:
 <ul><%
   for item in items %>
   <li><%
     if item.url ~ /^http/
       %><a href="<%= item.url %>"<%
         if item.description?
           %> title="<%= item.description %>"<%
         end
         %>><%
         if item.title?
           %><%= item.title %><%
         end
         %><%
         if !(item.title?)
           %><%= (item.url ~> /[^\:]*\:\/\/([^\/]+)/)[0] %><%
         end
       %></a><%
     end
     %><%
     if !(item.url ~ /^http/)
       %><button link="<%= item.url %>"><%= item.title %></button><%
     end
     %></li><%
   end %>
 </ul>
  • Compiled template:
 (Template [
   ContentToken "<ul>",
   ControlToken
     (Iteration ("","item") (Variable "items"))
     (Template [
       ContentToken "\n  <li>",
       ControlToken
         (Condition
           (BinaryOperation RegexTest
             (BinaryOperation GetField
               (Variable "item")
               (Constant (String "url")))
             (Regexp "^http" True False)))
         (Template [
           ContentToken "<a href=\"",
           LiteralToken
             (BinaryOperation GetField
               (Variable "item")
               (Constant (String "url"))),
           ContentToken "\"",
           ControlToken
             (Condition
               (UnaryOperation NotNull
                 (BinaryOperation GetField
                   (Variable "item")
                   (Constant (String "description")))))
             (Template [
               ContentToken " title=\"",
               LiteralToken
                 (BinaryOperation GetField
                   (Variable "item")
                   (Constant (String "description"))),
               ContentToken "\""
             ]),
           ContentToken ">",
           ControlToken
             (Condition
               (UnaryOperation NotNull
                 (BinaryOperation GetField
                   (Variable "item")
                   (Constant (String "title")))))
             (Template [
               LiteralToken
                 (BinaryOperation GetField
                   (Variable "item")
                   (Constant (String "title")))
             ]),
           ControlToken
             (Condition
               (UnaryOperation LogicNot
                 (UnaryOperation NotNull
                   (BinaryOperation GetField
                     (Variable "item")
                     (Constant (String "title"))))))
             (Template [
               LiteralToken
                 (BinaryOperation GetField
                   (BinaryOperation RegexMatch
                     (BinaryOperation GetField
                       (Variable "item")
                       (Constant (String "url")))
                     (Regexp "[^\\:]*\\://([^/]+)" True False))
                   (Constant (Number 0)))
             ]),
           ContentToken "</a>"
         ]),
       ControlToken
         (Condition
           (UnaryOperation LogicNot
             (BinaryOperation RegexTest
               (BinaryOperation GetField
                 (Variable "item")
                 (Constant (String "url")))
               (Regexp "^http" True False))))
         (Template [
            ContentToken "<button link=\"",LiteralToken (BinaryOperation GetField (Variable "item") (Constant (String "url"))),
            ContentToken "\">",
            LiteralToken (BinaryOperation GetField (Variable "item") (Constant (String "title"))),
            ContentToken "</button>"
         ]),
       ContentToken "</li>"
     ]),
   ContentToken "\n</ul>\n"
 ])
  • Yaml Dataset:
 items:
   - url: /
     title: Front page
   - url: http://example.org/
     title: Example site
   - url: https://example.com/example.html
     description: External link
   - url: /about
     title: About
  • Render result:
 <ul>
   <li><button link="/">Front page</button></li>
   <li><a href="http://example.org/">Example site</a></li>
   <li><a href="https://example.com/example.html" title="External link">example.com</a></li>
   <li><button link="/about">About</button></li>
 </ul>

Types

data Template Source

Compiled template.

Instances

Eq Template 
Show Template 

data TemplateToken Source

Template token.

Instances

Json types

data Value

A JSON value represented as a Haskell value.

Constructors

Object !Object 
Array !Array 
String !Text 
Number !Scientific 
Bool !Bool 
Null 

Instances

Eq Value 
Data Value 
Show Value 
Typeable Value 
IsString Value 
ToJSON Value 
FromJSON Value 
Hashable Value 
NFData Value 

data ByteString

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

data HashMap k v

A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.

Instances

Typeable2 HashMap 
Functor (HashMap k) 
Foldable (HashMap k) 
Traversable (HashMap k) 
(Eq k, Eq v) => Eq (HashMap k v) 
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) 
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) 
(Show k, Show v) => Show (HashMap k v) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap String v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap Text v) 
(Eq k, Hashable k) => Monoid (HashMap k v) 
(NFData k, NFData v) => NFData (HashMap k v) 

data Vector a

Boxed vectors, supporting efficient slicing.

Instances

Monad Vector 
Functor Vector 
Typeable1 Vector 
MonadPlus Vector 
Applicative Vector 
Foldable Vector 
Traversable Vector 
Alternative Vector 
Vector Vector a 
Eq a => Eq (Vector a) 
Data a => Data (Vector a) 
Ord a => Ord (Vector a) 
Read a => Read (Vector a) 
Show a => Show (Vector a) 
ToJSON a => ToJSON (Vector a) 
FromJSON a => FromJSON (Vector a) 
Monoid (Vector a) 
NFData a => NFData (Vector a) 

Functions

Compile and render

compile :: ByteString -> Either String TemplateSource

Compile template from ByteString.

render :: ToJSON e => Template -> e -> ByteStringSource

Render template to ByteString.

compile' :: String -> Either String TemplateSource

Compile template from string.

render' :: ToJSON e => Template -> e -> StringSource

Render template to string.

Parsers

parseTemplate :: Parser TemplateSource

Template parser function. Use this for parsing templates.

parseTemplate' :: Parser TemplateSource

Less template parser. Used internally for parsing subtemplates.

parseExpression :: Parser ExpressionSource

Expression parser. Use this for parsing expressions.

Utily

defaultData :: ValueSource

Default data for render. Empty data for using with standalone render.