heist-0.1.1: An xhtml templating systemSource codeContentsIndex
Text.Templating.Heist
Contents
Types
Functions and declarations on TemplateState values
Hook functions
TemplateMonad functions
Functions for running splices and templates
Misc functions
Description

This module contains the core definitions for the Heist template system.

The Heist template system is based on XML/xhtml. It allows you to build custom XML-based markup languages. With Heist you can define your own domain-specific XML tags implemented with Haskell and use them in your templates.

The most important concept in Heist is the Splice. Splices can be thought of as functions that transform a node into a list of nodes. Heist then substitutes the resulting list of nodes into your template in place of the input node. Splice is implemented as a type synonym type Splice m = TemplateMonad m [Node], and TemplateMonad has a function getParamNode that lets you get the input node.

Suppose you have a place on your page where you want to display a link with the text "Logout username" if the user is currently logged in or a link to the login page if no user is logged in. Assume you have a function getUser :: MyAppMonad (Maybe ByteString) that gets the current user. You can implement this functionality with a Splice as follows:

 import Text.XML.Expat.Tree

 link :: ByteString -> ByteString -> Node
 link target text = X.Element "a" [("href", target)] [X.Text text]
 
 loginLink :: Node
 loginLink = link "/login" "Login"
 
 logoutLink :: ByteString -> Node
 logoutLink user = link "/logout" (B.append "Logout " user)
 
 loginLogoutSplice :: Splice MyAppMonad
 loginLogoutSplice = do
     user <- lift getUser
     return $ [maybe loginLink logoutLink user]

Next, you need to bind that splice to an XML tag. Heist stores information about splices and templates in the TemplateState data structure. The following code demonstrates how this splice would be used.

 mySplices = [ ("loginLogout", loginLogoutSplice) ]
 
 main = do
     ets <- loadTemplates "templates" $
            foldr (uncurry bindSplice) emptyTemplateState mySplices
     let ts = either error id ets
     t <- runMyAppMonad $ renderTemplate ts "index"
     print $ maybe "Page not found" id t

Here we build up our TemplateState by starting with emptyTemplateState and applying bindSplice for all the splices we want to add. Then we pass this to loadTemplates our final TemplateState wrapped in an Either to handle errors. Then we use this TemplateState to render our templates.

Synopsis
type Node = Node ByteString ByteString
type Splice m = TemplateMonad m Template
type Template = [Node]
data TemplateMonad m a
data TemplateState m
addTemplate :: Monad m => ByteString -> Template -> TemplateState m -> TemplateState m
emptyTemplateState :: MonadIO m => TemplateState m
bindSplice :: Monad m => ByteString -> Splice m -> TemplateState m -> TemplateState m
lookupSplice :: Monad m => ByteString -> TemplateState m -> Maybe (Splice m)
setTemplates :: Monad m => TemplateMap -> TemplateState m -> TemplateState m
loadTemplates :: Monad m => FilePath -> TemplateState m -> IO (Either String (TemplateState m))
addOnLoadHook :: Monad m => (Template -> IO Template) -> TemplateState m -> TemplateState m
addPreRunHook :: Monad m => (Template -> m Template) -> TemplateState m -> TemplateState m
addPostRunHook :: Monad m => (Template -> m Template) -> TemplateState m -> TemplateState m
stopRecursion :: Monad m => TemplateMonad m ()
getParamNode :: Monad m => TemplateMonad m Node
runNodeList :: Monad m => [Node] -> Splice m
getContext :: Monad m => TemplateMonad m TPath
runTemplate :: Monad m => TemplateState m -> ByteString -> m (Maybe [Node])
evalTemplate :: Monad m => ByteString -> TemplateMonad m (Maybe [Node])
callTemplate :: Monad m => ByteString -> [(ByteString, ByteString)] -> TemplateMonad m (Maybe Template)
renderTemplate :: Monad m => TemplateState m -> ByteString -> m (Maybe ByteString)
bindStrings :: Monad m => [(ByteString, ByteString)] -> TemplateState m -> TemplateState m
runSplice :: Monad m => TemplateState m -> Node -> Splice m -> m [Node]
runRawTemplate :: Monad m => TemplateState m -> Template -> m [Node]
getDoc :: String -> IO (Either String Template)
bindStaticTag :: MonadIO m => TemplateState m -> IO (TemplateState m, StaticTagState)
heistExpatOptions :: ParserOptions ByteString ByteString
htmlEntityLookupTable :: Map ByteString ByteString
Types
type Node = Node ByteString ByteStringSource
Heist templates are XML documents. The hexpat library is polymorphic over the type of strings, so here we define a Node alias to fix the string types of the tag names and tag bodies to ByteString.
type Splice m = TemplateMonad m TemplateSource
A Splice is a TemplateMonad computation that returns [Node].
type Template = [Node]Source
A Template is a forest of XML nodes.
data TemplateMonad m a Source
TemplateMonad is a monad transformer that gives you access to the Node being processed (using the MonadReader instance) as well as holding the TemplateState that contains splice and template mappings (accessible using the MonadState instance.
show/hide Instances
data TemplateState m Source

Holds all the state information needed for template processing:

  • a collection of named templates. If you use the <apply template="foo"> tag to include another template by name, "foo" is looked up in here.
  • the mapping from tag names to Splices.
  • a flag to control whether we will recurse during splice processing.

We'll illustrate the recursion flag with a small example template:

 <foo>
   <bar>
     ...
   </bar>
 </foo>

Assume that "foo" is bound to a splice procedure. Running the foo splice will result in a list of nodes L; if the recursion flag is on we will recursively scan L for splices, otherwise L will be included in the output verbatim.

show/hide Instances
Functions and declarations on TemplateState values
addTemplate :: Monad m => ByteString -> Template -> TemplateState m -> TemplateState mSource
Adds a template to the template state.
emptyTemplateState :: MonadIO m => TemplateState mSource
An empty template state, with Heist's default splices (<bind> and <apply>) mapped.
bindSpliceSource
:: Monad m
=> ByteStringtag name
-> Splice msplice action
-> TemplateState msource state
-> TemplateState m
Bind a new splice declaration to a tag name within a TemplateState.
lookupSplice :: Monad m => ByteString -> TemplateState m -> Maybe (Splice m)Source
Convenience function for looking up a splice.
setTemplates :: Monad m => TemplateMap -> TemplateState m -> TemplateState mSource
Sets the templateMap in a TemplateState.
loadTemplates :: Monad m => FilePath -> TemplateState m -> IO (Either String (TemplateState m))Source
Traverses the specified directory structure and builds a TemplateState by loading all the files with a .tpl extension.
Hook functions

Heist hooks allow you to modify templates when they are loaded and before and after they are run. Every time you call one of the addAbcHook functions the hook is added to onto the processing pipeline. The hooks processes the template in the order that they were added to the TemplateState.

The pre-run and post-run hooks are run before and after every template is run/rendered. You should be careful what code you put in these hooks because it can significantly affect the performance of your site.

addOnLoadHook :: Monad m => (Template -> IO Template) -> TemplateState m -> TemplateState mSource
Adds an on-load hook to a TemplateState.
addPreRunHook :: Monad m => (Template -> m Template) -> TemplateState m -> TemplateState mSource
Adds a pre-run hook to a TemplateState.
addPostRunHook :: Monad m => (Template -> m Template) -> TemplateState m -> TemplateState mSource
Adds a post-run hook to a TemplateState.
TemplateMonad functions
stopRecursion :: Monad m => TemplateMonad m ()Source
Stops the recursive processing of splices.
getParamNode :: Monad m => TemplateMonad m NodeSource
Gets the node currently being processed.
runNodeList :: Monad m => [Node] -> Splice mSource
Performs splice processing on a list of nodes.
getContext :: Monad m => TemplateMonad m TPathSource
Gets the current context
Functions for running splices and templates
runTemplate :: Monad m => TemplateState m -> ByteString -> m (Maybe [Node])Source
Looks up a template name in the supplied TemplateState and runs it in the underlying monad.
evalTemplate :: Monad m => ByteString -> TemplateMonad m (Maybe [Node])Source
Looks up a template name evaluates it. Same as runTemplate except it runs in TemplateMonad instead of m.
callTemplateSource
:: Monad m
=> ByteStringThe name of the template
-> [(ByteString, ByteString)]Association list of (name,value) parameter pairs
-> TemplateMonad m (Maybe Template)
Renders a template with the specified parameters. This is the function to use when you want to call a template and pass in parameters from code.
renderTemplate :: Monad m => TemplateState m -> ByteString -> m (Maybe ByteString)Source
Renders a template from the specified TemplateState.
bindStrings :: Monad m => [(ByteString, ByteString)] -> TemplateState m -> TemplateState mSource
Binds a list of constant string splices
Misc functions
runSpliceSource
:: Monad m
=> TemplateState mThe initial template state
-> NodeThe splice's input node
-> Splice mThe splice
-> m [Node]
Runs a splice in the underlying monad. Splices require two parameters, the template state, and an input node.
runRawTemplate :: Monad m => TemplateState m -> Template -> m [Node]Source
Runs a template in the underlying monad. Similar to runSplice except that templates don't require a Node as a parameter.
getDoc :: String -> IO (Either String Template)Source
Reads an XML document from disk.
bindStaticTag :: MonadIO m => TemplateState m -> IO (TemplateState m, StaticTagState)Source
Modifies a TemplateState to include a static tag.
heistExpatOptions :: ParserOptions ByteString ByteStringSource
htmlEntityLookupTable :: Map ByteString ByteStringSource
Produced by Haddock version 2.6.1