| Copyright | 2015 Noriyuki OHKAWA | 
|---|---|
| License | BSD3 | 
| Maintainer | n.ohkawa@gmail.com | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Haiji
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
- data Template dict
- haiji :: Environment -> QuasiQuoter
- haijiFile :: Quasi q => Environment -> FilePath -> q Exp
- render :: Template dict -> dict -> Text
- data Environment
- autoEscape :: Environment -> Bool
- data Dict (kv :: [Type])
- toDict :: (KnownSymbol k, Typeable x) => x -> Dict '[k :-> x]
- empty :: Dict '[]
- key :: QuasiQuoter
- merge :: Dict xs -> Dict ys -> Dict (Merge xs ys)
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.
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
Rendering Environment
data Environment Source #
A template environment
Instances
| Eq Environment Source # | |
| Defined in Text.Haiji.Types | |
| Show Environment Source # | |
| Defined in Text.Haiji.Types Methods showsPrec :: Int -> Environment -> ShowS # show :: Environment -> String # showList :: [Environment] -> ShowS # | |
| Default Environment Source # | |
| Defined in Text.Haiji.Types Methods def :: Environment # | |
autoEscape :: Environment -> Bool Source #
XML/HTML autoescaping
Dictionary
data Dict (kv :: [Type]) Source #
Type level Dictionary
toDict :: (KnownSymbol k, Typeable x) => x -> Dict '[k :-> x] Source #
Create single element dictionary (with TypeApplications extention)
Builder
key :: QuasiQuoter Source #
Generate a dictionary with single item