haiji-0.1.0.0: A typed template engine, subset of jinja2

Copyright2015 Noriyuki OHKAWA
LicenseBSD3
Maintainern.ohkawa@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Haiji

Contents

Description

Haiji is a template engine which is subset of Jinja2. This is designed to free from the unintended rendering result by strictly typed variable interpolation.

Rendering result will be same as Jinja2's one. However, Haiji doesn't aim to be Jinja2. Some feature and built-in Test/Function/Filter of Jinja2 allow rendering time type inspection. Haiji will not support these type unsafe features. Haiji generates a statically typed template by Template Haskell, and check that a given dictionary includes enough information to render template.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE DataKinds #-}
module Main where

import Data.Default
import Text.Haiji
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.IO as LT

main :: IO ()
main = LT.putStr
       $ render $(haijiFile def "example.tmpl")
       $ [key|a_variable|] ("Hello,World!" :: LT.Text) `merge`
         [key|navigation|] [ [key|caption|] cap `merge` [key|href|] href
                           | (cap, href) <- [ ("A", "content/a.html")
                                            , ("B", "content/b.html")
                                            ] :: [ (T.Text, String) ]
                           ] `merge`
         [key|foo|] (1 :: Int) `merge`
         [key|bar|] ("" :: String)

Synopsis

Typed Template

{{ foo }}

For example, this Jinja2 template requires "foo". A dictionary which provides a variable "foo" is required to render it. If a variable "foo" does not exist in a given dictionary, Jinja2 evaluates it to an empty string by default, whereas haiji treats this case as compile error.

data Template dict Source

Haiji template

Generators

haiji :: Environment -> QuasiQuoter Source

QuasiQuoter to generate a Haiji template

haijiFile :: Quasi q => Environment -> FilePath -> q Exp Source

Generate a Haiji template from external file

Renderer

render :: Template dict -> dict -> Text Source

Render Haiji template with given dictionary

Rendering Environment

autoEscape :: Environment -> Bool Source

XML/HTML autoescaping

Dictionary

data Dict kv Source

Type level Dictionary

Instances

ToJSON (Dict s) => Show (Dict s) Source 
(ToJSON (Dict s), ToJSON kv) => ToJSON (Dict ((:) * kv s)) Source 
ToJSON (Dict ([] *)) Source 

empty :: Dict `[]` Source

Empty dictionary

Builder

key :: QuasiQuoter Source

Generate a dictionary with single item

merge :: Mergeable a b => Dict a -> Dict b -> Dict (Merge a b) Source

Merge 2 dictionaries