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 =
HeistT m [Node]
, and HeistT
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 HeistState
data structure. The
following code demonstrates how this splice would be used.
mySplices = [ ("loginLogout", loginLogoutSplice) ] main = do ets <- loadTemplates "templates" $ bindSplices mySplices emptyHeistState let ts = either error id ets t <- runMyAppMonad $ renderTemplate ts "index" print $ maybe "Page not found" (toByteString . fst) t
Here we build up our HeistState
by starting with emptyHeistState and
applying bindSplice for all the splices we want to add. Then we pass this
to loadTemplates our final HeistState
wrapped in an Either to handle
errors. Then we use this HeistState
to render our templates.
- type Template = [Node]
- type MIMEType = ByteString
- type Splice m = TemplateMonad m Template
- data TemplateMonad m a
- type HeistT = TemplateMonad
- data HeistState m
- type TemplateState = HeistState
- templateNames :: HeistState m -> [TPath]
- spliceNames :: HeistState m -> [Text]
- addTemplate :: Monad m => ByteString -> Template -> Maybe FilePath -> HeistState m -> HeistState m
- addXMLTemplate :: Monad m => ByteString -> Template -> Maybe FilePath -> HeistState m -> HeistState m
- emptyTemplateState :: MonadIO m => HeistState m
- defaultHeistState :: MonadIO m => HeistState m
- bindSplice :: Monad m => Text -> Splice m -> HeistState m -> HeistState m
- bindSplices :: Monad m => [(Text, Splice m)] -> HeistState m -> HeistState m
- lookupSplice :: Monad m => Text -> HeistState m -> Maybe (Splice m)
- setTemplates :: Monad m => TemplateMap -> HeistState m -> HeistState m
- loadTemplates :: Monad m => FilePath -> HeistState m -> IO (Either String (HeistState m))
- hasTemplate :: Monad m => ByteString -> HeistState m -> Bool
- addTemplatePathPrefix :: ByteString -> HeistState m -> HeistState m
- addOnLoadHook :: Monad m => (Template -> IO Template) -> HeistState m -> HeistState m
- addPreRunHook :: Monad m => (Template -> m Template) -> HeistState m -> HeistState m
- addPostRunHook :: Monad m => (Template -> m Template) -> HeistState m -> HeistState m
- stopRecursion :: Monad m => HeistT m ()
- getParamNode :: Monad m => TemplateMonad m Node
- runNodeList :: Monad m => [Node] -> Splice m
- getContext :: Monad m => HeistT m TPath
- getTemplateFilePath :: Monad m => HeistT m (Maybe FilePath)
- localParamNode :: Monad m => (Node -> Node) -> TemplateMonad m a -> TemplateMonad m a
- getsTS :: Monad m => (HeistState m -> r) -> TemplateMonad m r
- getTS :: Monad m => TemplateMonad m (HeistState m)
- putTS :: Monad m => HeistState m -> TemplateMonad m ()
- modifyTS :: Monad m => (HeistState m -> HeistState m) -> TemplateMonad m ()
- restoreTS :: Monad m => HeistState m -> TemplateMonad m ()
- localTS :: Monad m => (HeistState m -> HeistState m) -> TemplateMonad m a -> TemplateMonad m a
- evalTemplate :: Monad m => ByteString -> HeistT m (Maybe Template)
- callTemplate :: Monad m => ByteString -> [(Text, Splice m)] -> HeistT m Template
- callTemplateWithText :: Monad m => ByteString -> [(Text, Text)] -> HeistT m Template
- renderTemplate :: Monad m => HeistState m -> ByteString -> m (Maybe (Builder, MIMEType))
- renderWithArgs :: Monad m => [(Text, Text)] -> HeistState m -> ByteString -> m (Maybe (Builder, MIMEType))
- bindStrings :: Monad m => [(Text, Text)] -> HeistState m -> HeistState m
- bindString :: Monad m => Text -> Text -> HeistState m -> HeistState m
- textSplice :: Monad m => Text -> Splice m
- runChildren :: Monad m => Splice m
- runChildrenWith :: Monad m => [(Text, Splice m)] -> Splice m
- runChildrenWithTrans :: Monad m => (b -> Splice m) -> [(Text, b)] -> Splice m
- runChildrenWithTemplates :: Monad m => [(Text, Template)] -> Splice m
- runChildrenWithText :: Monad m => [(Text, Text)] -> Splice m
- mapSplices :: Monad m => (a -> Splice m) -> [a] -> Splice m
- getDoc :: String -> IO (Either String DocumentFile)
- getXMLDoc :: String -> IO (Either String DocumentFile)
- mkCacheTag :: MonadIO m => IO (HeistState m -> HeistState m, CacheTagState)
- useOldAttributeSyntax :: HeistState m -> HeistState m
Types
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.
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 |
MonadCatchIO m => MonadCatchIO (TemplateMonad m) | MonadCatchIO 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 |
type HeistT = TemplateMonadSource
data HeistState m Source
Holds all the state information needed for template processing. You will
build a HeistState
using any of Heist's HeistState m -> HeistState m
"filter" functions. Then you use the resulting HeistState
in calls to
renderTemplate
.
Eq (HeistState m) | |
Typeable1 m => Typeable (HeistState m) | |
Monad m => Monoid (HeistState m) |
type TemplateState = HeistStateSource
Holds all the state information needed for template processing. You will
build a HeistState
using any of Heist's HeistState m -> HeistState m
"filter" functions. Then you use the resulting HeistState
in calls to
renderTemplate
.
templateNames :: HeistState m -> [TPath]Source
Gets the names of all the templates defined in a HeistState.
spliceNames :: HeistState m -> [Text]Source
Gets the names of all the splices defined in a HeistState.
Functions and declarations on HeistState values
:: Monad m | |
=> ByteString | Path that the template will be referenced by |
-> Template | The template's DOM nodes |
-> Maybe FilePath | An optional path to the actual file on disk where the template is stored |
-> HeistState m | |
-> HeistState m |
Adds an HTML format template to the heist state.
:: Monad m | |
=> ByteString | Path that the template will be referenced by |
-> Template | The template's DOM nodes |
-> Maybe FilePath | An optional path to the actual file on disk where the template is stored |
-> HeistState m | |
-> HeistState m |
Adds an XML format template to the heist state.
emptyTemplateState :: MonadIO m => HeistState 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.
defaultHeistState :: MonadIO m => HeistState mSource
An empty heist state, with Heist's default splices (<apply>
,
<bind>
, <ignore>
, and <markdown>
) mapped. The cache tag is
not mapped here because it must be mapped manually in your application.
:: Monad m | |
=> Text | tag name |
-> Splice m | splice action |
-> HeistState m | source state |
-> HeistState m |
Binds a new splice declaration to a tag name within a HeistState
.
:: Monad m | |
=> [(Text, Splice m)] | splices to bind |
-> HeistState m | start state |
-> HeistState m |
Binds a set of new splice declarations within a HeistState
.
lookupSplice :: Monad m => Text -> HeistState m -> Maybe (Splice m)Source
Convenience function for looking up a splice.
setTemplates :: Monad m => TemplateMap -> HeistState m -> HeistState mSource
Sets the templateMap in a HeistState.
loadTemplates :: Monad m => FilePath -> HeistState m -> IO (Either String (HeistState m))Source
hasTemplate :: Monad m => ByteString -> HeistState m -> BoolSource
Returns True
if the given template can be found in the heist state.
addTemplatePathPrefix :: ByteString -> HeistState m -> HeistState mSource
Adds a path prefix to all the templates in the HeistState
. If you
want to add multiple levels of directories, separate them with slashes as
in foo/bar. Using an empty string as a path prefix will leave the
HeistState
unchanged.
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 HeistState.
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) -> HeistState m -> HeistState mSource
Adds an on-load hook to a HeistState
.
addPreRunHook :: Monad m => (Template -> m Template) -> HeistState m -> HeistState mSource
Adds a pre-run hook to a HeistState
.
addPostRunHook :: Monad m => (Template -> m Template) -> HeistState m -> HeistState mSource
Adds a post-run hook to a HeistState
.
HeistT functions
stopRecursion :: Monad m => HeistT 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 => HeistT m TPathSource
Gets the current context
getTemplateFilePath :: Monad m => HeistT m (Maybe FilePath)Source
Gets the full path to the file holding the template currently being processed. Returns Nothing if the template is not associated with a file on disk or if there is no template being processed.
localParamNode :: Monad m => (Node -> Node) -> TemplateMonad m a -> TemplateMonad m aSource
TemplateMonad's local
.
getsTS :: Monad m => (HeistState m -> r) -> TemplateMonad m rSource
TemplateMonad's gets
.
getTS :: Monad m => TemplateMonad m (HeistState m)Source
TemplateMonad's get
.
putTS :: Monad m => HeistState m -> TemplateMonad m ()Source
TemplateMonad's put
.
modifyTS :: Monad m => (HeistState m -> HeistState m) -> TemplateMonad m ()Source
TemplateMonad's modify
.
restoreTS :: Monad m => HeistState m -> TemplateMonad m ()Source
Restores the HeistState. 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 => (HeistState m -> HeistState m) -> TemplateMonad m a -> TemplateMonad m aSource
Abstracts the common pattern of running a TemplateMonad computation with a modified heist state.
Functions for running splices and templates
evalTemplate :: Monad m => ByteString -> HeistT m (Maybe Template)Source
Looks up a template name evaluates it by calling runNodeList.
:: Monad m | |
=> ByteString | The name of the template |
-> [(Text, Splice m)] | Association list of (name,value) parameter pairs |
-> HeistT m 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. If the template does not exist, this version simply returns an empty list.
:: Monad m | |
=> ByteString | The name of the template |
-> [(Text, Text)] | Association list of (name,value) parameter pairs |
-> HeistT m Template |
Like callTemplate except the splices being bound are constant text splices.
renderTemplate :: Monad m => HeistState m -> ByteString -> m (Maybe (Builder, MIMEType))Source
Renders a template from the specified HeistState 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)] -> HeistState 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)] -> HeistState m -> HeistState mSource
Binds a list of constant string splices.
bindString :: Monad m => Text -> Text -> HeistState m -> HeistState 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.
:: 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.
:: 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.
:: 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
mkCacheTag :: MonadIO m => IO (HeistState m -> HeistState m, CacheTagState)Source
Returns a function that modifies a HeistState to include a "cache"
tag. The cache tag is not bound automatically with the other default Heist
tags. This is because this function also returns CacheTagState, so the
user will be able to clear it with the clearCacheTagState
function.
Temporary functions
useOldAttributeSyntax :: HeistState m -> HeistState mSource
Sets compatibility mode that uses the old $() syntax for splices in attributes. The old syntax conflicts with the ubiquitous jquery function. The new syntax is ${}. This compatibility mode will be removed in the next major release.
See https:github.comsnapframeworkheistissues12 for the discussion.