heist-0.5.2.1: An xhtml templating system

Text.Templating.Heist

Contents

Description

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

The Heist template system is based on HTML and XML. It allows you to build custom HTML and XML based markup languages. With Heist you can define your own domain-specific HTML and 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 Text) that gets the current user. You can implement this functionality with a Splice as follows:

 import             Blaze.ByteString.Builder
 import             Data.ByteString.Char8 (ByteString)
 import qualified   Data.ByteString.Char8 as B
 import             Data.Text (Text)
 import qualified   Data.Text as T
 import qualified   Text.XmlHtml as X

 import             Text.Templating.Heist

 link :: Text -> Text -> X.Node
 link target text = X.Element "a" [("href", target)] [X.TextNode text]

 loginLink :: X.Node
 loginLink = link "/login" "Login"

 logoutLink :: Text -> X.Node
 logoutLink user = link "/logout" (T.append "Logout " user)

 loginLogoutSplice :: Splice MyAppMonad
 loginLogoutSplice = do
     user <- lift getUser
     return [maybe loginLink logoutLink user]

Next, you need to bind that splice to a 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" $
            bindSplices mySplices (emptyTemplateState "templates")
     let ts = either error id ets
     t <- runMyAppMonad $ renderTemplate ts "index"
     print $ maybe "Page not found" (toByteString . fst) 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

Types

type Template = [Node]Source

A Template is a forest of XML nodes. Here we deviate from the single root node constraint of well-formed XML because we want to allow templates to contain fragments of a document that may not have a single root.

type MIMEType = ByteStringSource

MIME Type. The type alias is here to make the API clearer.

type Splice m = TemplateMonad m TemplateSource

A Splice is a TemplateMonad computation that returns a Template.

data TemplateMonad m a Source

TemplateMonad is the monad used for Splice processing. TemplateMonad provides "passthrough" instances for many of the monads you might use in the inner monad.

Instances

MonadTrans TemplateMonad

MonadTrans instance

MonadError e m => MonadError e (TemplateMonad m)

MonadError passthrough instance

MonadReader r m => MonadReader r (TemplateMonad m)

MonadReader passthrough instance

MonadState s m => MonadState s (TemplateMonad m)

MonadState passthrough instance

Monad m => Monad (TemplateMonad m)

Monad instance

Functor m => Functor (TemplateMonad m)

Functor instance

Typeable1 m => Typeable1 (TemplateMonad m) 
MonadFix m => MonadFix (TemplateMonad m)

MonadFix passthrough instance

MonadPlus m => MonadPlus (TemplateMonad m)

MonadPlus passthrough instance

(Monad m, Functor m) => Applicative (TemplateMonad m)

Applicative instance

(Functor m, MonadPlus m) => Alternative (TemplateMonad m)

Alternative passthrough instance

MonadIO m => MonadIO (TemplateMonad m)

MonadIO instance

MonadCont m => MonadCont (TemplateMonad m)

MonadCont passthrough instance

data TemplateState m Source

Holds all the state information needed for template processing. You will build a TemplateState using any of Heist's TemplateState m -> TemplateState m "filter" functions. Then you use the resulting TemplateState in calls to renderTemplate.

Functions and declarations on TemplateState values

addTemplate :: Monad m => ByteString -> Template -> TemplateState m -> TemplateState mSource

Adds an HTML format template to the template state.

addXMLTemplate :: Monad m => ByteString -> Template -> TemplateState m -> TemplateState mSource

Adds an XML format template to the template state.

emptyTemplateState :: MonadIO m => FilePath -> TemplateState mSource

An empty template state, with Heist's default splices (<apply>, <bind>, <ignore>, and <markdown>) mapped. The static tag is not mapped here because it must be mapped manually in your application.

bindSpliceSource

Arguments

:: Monad m 
=> Text

tag name

-> Splice m

splice action

-> TemplateState m

source state

-> TemplateState m 

Binds a new splice declaration to a tag name within a TemplateState.

bindSplicesSource

Arguments

:: Monad m 
=> [(Text, Splice m)]

splices to bind

-> TemplateState m

start state

-> TemplateState m 

Binds a set of new splice declarations within a TemplateState.

lookupSplice :: Monad m => Text -> 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 or .xtpl extension.

hasTemplate :: Monad m => ByteString -> TemplateState m -> BoolSource

Returns True if the given template can be found in the template state.

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. Consider the following example:

 <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. Normally foo will recursively scan L for splices and run them. If foo calls stopRecursion, L will be included in the output verbatim without running any splices.

getParamNode :: Monad m => TemplateMonad m NodeSource

Gets the node currently being processed.

 <speech author="Shakespeare">
   To sleep, perchance to dream.
 </speech>

When you call getParamNode inside the code for the speech splice, it returns the Node for the speech tag and its children. getParamNode >>= childNodes returns a list containing one TextNode containing part of Hamlet's speech. liftM (getAttribute "author") getParamNode would return Just Shakespeare.

runNodeList :: Monad m => [Node] -> Splice mSource

Performs splice processing on a list of nodes.

getContext :: Monad m => TemplateMonad m TPathSource

Gets the current context

localParamNode :: Monad m => (Node -> Node) -> TemplateMonad m a -> TemplateMonad m aSource

TemplateMonad's local.

getsTS :: Monad m => (TemplateState m -> r) -> TemplateMonad m rSource

TemplateMonad's gets.

getTS :: Monad m => TemplateMonad m (TemplateState m)Source

TemplateMonad's get.

putTS :: Monad m => TemplateState m -> TemplateMonad m ()Source

TemplateMonad's put.

modifyTS :: Monad m => (TemplateState m -> TemplateState m) -> TemplateMonad m ()Source

TemplateMonad's modify.

restoreTS :: Monad m => TemplateState m -> TemplateMonad m ()Source

Restores the TemplateState. This function is almost like putTS except it preserves the current doctypes. You should use this function instead of putTS to restore an old state. This was needed because doctypes needs to be in a global scope as opposed to the template call local scope of state items such as recursionDepth, curContext, and spliceMap.

localTS :: Monad m => (TemplateState m -> TemplateState m) -> TemplateMonad m a -> TemplateMonad m aSource

Abstracts the common pattern of running a TemplateMonad computation with a modified template state.

Functions for running splices and templates

evalTemplate :: Monad m => ByteString -> TemplateMonad m (Maybe Template)Source

Looks up a template name evaluates it by calling runNodeList.

callTemplateSource

Arguments

:: Monad m 
=> ByteString

The name of the template

-> [(Text, Text)]

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 inside a splice.

renderTemplate :: Monad m => TemplateState m -> ByteString -> m (Maybe (Builder, MIMEType))Source

Renders a template from the specified TemplateState to a Builder. The MIME type returned is based on the detected character encoding, and whether the root template was an HTML or XML format template. It will always be texthtml@ or @textxml. If a more specific MIME type is needed for a particular XML application, it must be provided by the application.

renderWithArgs :: Monad m => [(Text, Text)] -> TemplateState m -> ByteString -> m (Maybe (Builder, MIMEType))Source

Renders a template with the specified arguments passed to it. This is a convenience function for the common pattern of calling renderTemplate after using bindString, bindStrings, or bindSplice to set up the arguments to the template.

bindStrings :: Monad m => [(Text, Text)] -> TemplateState m -> TemplateState mSource

Binds a list of constant string splices.

bindString :: Monad m => Text -> Text -> TemplateState m -> TemplateState mSource

Binds a single constant string splice.

Functions for creating splices

textSplice :: Monad m => Text -> Splice mSource

Converts Text to a splice returning a single TextNode.

runChildren :: Monad m => Splice mSource

Runs the parameter node's children and returns the resulting node list. By itself this function is a simple passthrough splice that makes the spliced node disappear. In combination with locally bound splices, this function makes it easier to pass the desired view into your splices.

runChildrenWithSource

Arguments

:: Monad m 
=> [(Text, Splice m)]

List of splices to bind before running the param nodes.

-> Splice m

Returns the passed in view.

Binds a list of splices before using the children of the spliced node as a view.

runChildrenWithTransSource

Arguments

:: Monad m 
=> (b -> Splice m)

Splice generating function

-> [(Text, b)]

List of tuples to be bound

-> Splice m 

Wrapper around runChildrenWith that applies a transformation function to the second item in each of the tuples before calling runChildrenWith.

runChildrenWithTemplates :: Monad m => [(Text, Template)] -> Splice mSource

Like runChildrenWith but using constant templates rather than dynamic splices.

runChildrenWithText :: Monad m => [(Text, Text)] -> Splice mSource

Like runChildrenWith but using literal text rather than dynamic splices.

mapSplicesSource

Arguments

:: Monad m 
=> (a -> Splice m)

Splice generating function

-> [a]

List of items to generate splices for

-> Splice m

The result of all splices concatenated together.

Maps a splice generating function over a list and concatenates the results.

Misc functions

getDoc :: String -> IO (Either String Document)Source

Reads an HTML template from disk.

getXMLDoc :: String -> IO (Either String Document)Source

Reads an XML template from disk.

bindStaticTag :: MonadIO m => TemplateState m -> IO (TemplateState m, StaticTagState)Source

Modifies a TemplateState to include a "static" tag. The static tag is not bound automatically with the other default Heist tags. This is because this function also returns StaticTagState, so the user will be able to clear it with the clearStaticTagCache function.