heist-0.14.0.1: An Haskell template system supporting both HTML5 and XML.

Safe HaskellNone
LanguageHaskell98

Heist.Interpreted

Contents

Description

This module defines the API for writing and working with interpreted splices. It exports some of the same symbols as Heist.Compiled, so you will probably want to import it qualified.

Interpreted splices can be thought of as a function Node -> m [Node]. 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 qualified Heist.Interpreted as I

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 :: I.Splice MyAppMonad
loginLogoutSplice = do
    user <- lift getUser
    return [maybe loginLink logoutLink user]

Synopsis

Documentation

HeistState Functions

addTemplate Source

Arguments

:: 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 n 
-> HeistState n 

Adds an HTML format template to the heist state.

addXMLTemplate Source

Arguments

:: 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 n 
-> HeistState n 

Adds an XML format template to the heist state.

lookupSplice :: Text -> HeistState n -> Maybe (Splice n) Source

Convenience function for looking up a splice.

bindSplice Source

Arguments

:: Text

tag name

-> Splice n

splice action

-> HeistState n

source state

-> HeistState n 

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

bindSplices Source

Arguments

:: Splices (Splice n)

splices to bind

-> HeistState n

start state

-> HeistState n 

Binds a set of new splice declarations within a HeistState.

bindAttributeSplices Source

Arguments

:: Splices (AttrSplice n)

splices to bind

-> HeistState n

start state

-> HeistState n 

Binds a set of new splice declarations within a HeistState.

Functions for creating splices

textSplice :: Monad m => Text -> HeistT n m Template Source

Converts Text to a splice returning a single TextNode.

runChildren :: Monad n => Splice n Source

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.

runChildrenWith Source

Arguments

:: Monad n 
=> Splices (Splice n)

List of splices to bind before running the param nodes.

-> Splice n

Returns the passed in view.

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

runChildrenWithTrans Source

Arguments

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

Splice generating function

-> Splices b

List of tuples to be bound

-> Splice n 

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

runChildrenWithTemplates :: Monad n => Splices Template -> Splice n Source

Like runChildrenWith but using constant templates rather than dynamic splices.

runChildrenWithText :: Monad n => Splices Text -> Splice n Source

Like runChildrenWith but using literal text rather than dynamic splices.

mapSplices Source

Arguments

:: (Monad m, Monoid b) 
=> (a -> m b)

Splice generating function

-> [a]

List of items to generate splices for

-> m b

The result of all splices concatenated together.

Maps a splice generating function over a list and concatenates the results. This function now has a more general type signature so it works with both compiled and interpreted splices. The old type signature was this:

mapSplices :: (Monad n)
        => (a -> Splice n n)
        -> [a]
        -> Splice n n

HeistT functions

stopRecursion :: Monad m => HeistT n 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.

runNode :: Monad n => Node -> Splice n Source

Performs splice processing on a single node.

runAttributes :: Monad n => [(Text, Text)] -> HeistT n n [(Text, Text)] Source

Performs splice processing on a list of attributes. This is useful in situations where you need to stop recursion, but still run splice processing on the node's attributes.

runNodeList :: Monad n => [Node] -> Splice n Source

Performs splice processing on a list of nodes.

evalTemplate :: Monad n => ByteString -> HeistT n n (Maybe Template) Source

Looks up a template name evaluates it by calling runNodeList.

bindStrings :: Monad n => Splices Text -> HeistState n -> HeistState n Source

Binds a list of constant string splices.

bindString :: Monad n => Text -> Text -> HeistState n -> HeistState n Source

Binds a single constant string splice.

callTemplate Source

Arguments

:: Monad n 
=> ByteString

The name of the template

-> Splices (Splice n)

Splices to call the template with

-> HeistT n n 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.

callTemplateWithText Source

Arguments

:: Monad n 
=> ByteString

The name of the template

-> Splices Text

Splices to call the template with

-> HeistT n n Template 

Like callTemplate except the splices being bound are constant text splices.

renderTemplate :: Monad n => HeistState n -> ByteString -> n (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 text/html or text/xml. If a more specific MIME type is needed for a particular XML application, it must be provided by the application.

renderWithArgs :: Monad n => Splices Text -> HeistState n -> ByteString -> n (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.