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

Safe HaskellNone

Heist

Contents

Description

This module defines the core data types used by Heist. In practice you will also want to import one or both of Heist.Compiled or Heist.Interpreted to get functions needed for writing splices.

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

Synopsis

Primary Heist initialization functions

loadTemplates :: FilePath -> EitherT [String] IO TemplateRepoSource

Loads templates from disk. This function returns just a template map so you can load multiple directories and combine the maps before initializing your HeistState.

addTemplatePathPrefix :: ByteString -> TemplateRepo -> TemplateRepoSource

Adds a path prefix to a templates in a map returned by loadTemplates. 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 map unchanged.

initHeist :: Monad n => HeistConfig n -> EitherT [String] IO (HeistState n)Source

This is the main Heist initialization function. You pass in a map of all templates and all of your splices and it constructs and returns a HeistState.

We don't provide functions to add either type of loadtime splices to your HeistState after initHeist because it doesn't make any sense unless you re-initialize all templates with the new splices. If you add any old-style runtime heist splices after calling this function, they will still work fine if you use Heist.Interpreted.renderTemplate. If you add any templates later, then those templates will be available for interpreted rendering, but not for compiled rendering.

In the past you could add templates to your HeistState after initialization using its Monoid instance. Due to implementation details, this is no longer possible. All of your templates must be known when you call this function.

initHeistWithCacheTag :: MonadIO n => HeistConfig n -> EitherT [String] IO (HeistState n, CacheTagState)Source

Wrapper around initHeist that also sets up a cache tag. It sets up both compiled and interpreted versions of the cache tag splices. If you need to do configure the cache tag differently than how this function does it, you will still probably want to pattern your approach after this function's implementation.

defaultInterpretedSplices :: MonadIO m => [(Text, Splice m)]Source

The built-in set of static splices. All the splices that used to be enabled by default are included here. To get the normal Heist behavior you should include these in the hcLoadTimeSplices list in your HeistConfig.

defaultLoadTimeSplices :: MonadIO m => [(Text, Splice m)]Source

The built-in set of static splices. All the splices that used to be enabled by default are included here. To get the normal Heist behavior you should include these in the hcLoadTimeSplices list in your HeistConfig.

Core Heist data 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 document fragments that may not have a single root.

type TPath = [ByteString]Source

Reversed list of directories. This holds the path to the template currently being processed.

data HeistConfig m Source

Constructors

HeistConfig 

Fields

hcInterpretedSplices :: [(Text, Splice m)]

Interpreted splices are the splices that Heist has always had. They return a list of nodes and are processed at runtime.

hcLoadTimeSplices :: [(Text, Splice IO)]

Load time splices are like interpreted splices because they return a list of nodes. But they are like compiled splices because they are processed once at load time. All of Heist's built-in splices should be used as load time splices.

hcCompiledSplices :: [(Text, Splice m)]

Compiled splices return a DList of Chunks and are processed at load time to generate a runtime monad action that will be used to render the template.

hcAttributeSplices :: [(Text, AttrSplice m)]

Attribute splices are bound to attribute names and return a list of attributes.

hcTemplates :: TemplateRepo

Templates returned from the loadTemplates function.

Instances

type MIMEType = ByteStringSource

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

data DocumentFile Source

Holds data about templates read from disk.

Constructors

DocumentFile 

Instances

type AttrSplice m = Text -> m [(Text, Text)]Source

Type alias for attribute splices. The function parameter is the value of the bound attribute splice. The return value is a list of attribute key/value pairs that get substituted in the place of the bound attribute.

data RuntimeSplice m a Source

Monad used for runtime splice execution.

data Chunk m Source

Opaque type representing pieces of output from compiled splices.

Instances

Show (Chunk m) 

data HeistState m Source

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

m is the runtime monad

Constructors

HeistState 

Fields

_spliceMap :: HashMap Text (HeistT m m Template)

A mapping of splice names to splice actions

_templateMap :: HashMap TPath DocumentFile

A mapping of template names to templates

_compiledSpliceMap :: HashMap Text (HeistT m IO (DList (Chunk m)))

A mapping of splice names to splice actions

_compiledTemplateMap :: !(HashMap TPath ([Chunk m], MIMEType))

A mapping of template names to templates , _compiledTemplateMap :: HashMap TPath (m Builder, MIMEType)

_attrSpliceMap :: HashMap Text (AttrSplice m)
 
_recurse :: Bool

A flag to control splice recursion

_curContext :: TPath

The path to the template currently being processed.

_recursionDepth :: Int

A counter keeping track of the current recursion depth to prevent infinite loops.

_doctypes :: [DocType]

The doctypes encountered during template processing.

_curTemplateFile :: Maybe FilePath

The full path to the current template's file on disk.

_keygen :: KeyGen

A key generator used to produce new unique Promises.

_preprocessingMode :: Bool

Flag indicating whether we're in preprocessing mode. During preprocessing, errors should stop execution and be reported. During template rendering, it's better to skip the errors and render the page.

Instances

templateNames :: HeistState m -> [TPath]Source

Gets the names of all the templates defined in a HeistState.

compiledTemplateNames :: HeistState m -> [TPath]Source

Gets the names of all the templates defined in a HeistState.

hasTemplate :: ByteString -> HeistState n -> BoolSource

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

spliceNames :: HeistState m -> [Text]Source

Gets the names of all the splices defined in a HeistState.

data HeistT n m a Source

HeistT is the monad transformer used for splice processing. HeistT intentionally does not expose any of its functionality via MonadState or MonadReader functions. We define passthrough instances for the most common types of monads. These instances allow the user to use HeistT in a monad stack without needing calls to lift.

n is the runtime monad (the parameter to HeistState).

m is the monad being run now. In this case, "now" is a variable concept. The type HeistT n n means that "now" is runtime. The type HeistT n IO means that "now" is IO, and more importantly it is NOT runtime. In Heist, the rule of thumb is that IO means load time and n means runtime.

Instances

(Monad (HeistT n m), MonadError e m) => MonadError e (HeistT n m)

MonadError passthrough instance

(Monad (HeistT n m), MonadReader r m) => MonadReader r (HeistT n m)

MonadReader passthrough instance

(Monad (HeistT n m), MonadState s m) => MonadState s (HeistT n m)

MonadState passthrough instance

MonadTrans (HeistT n)

MonadTrans instance

Monad m => Monad (HeistT n m)

Monad instance

Functor m => Functor (HeistT n m)

Functor instance

Typeable1 m => Typeable1 (HeistT n m) 
(Monad (HeistT n m), MonadFix m) => MonadFix (HeistT n m)

MonadFix passthrough instance

(Monad (HeistT n m), MonadPlus m) => MonadPlus (HeistT n m)

MonadPlus passthrough instance

(Functor (HeistT n m), Monad m, Functor m) => Applicative (HeistT n m)

Applicative instance

(MonadIO (HeistT n m), MonadCatchIO m) => MonadCatchIO (HeistT n m)

MonadCatchIO instance

(Applicative (HeistT n m), Functor m, MonadPlus m) => Alternative (HeistT n m)

Alternative passthrough instance

(Monad (HeistT n m), MonadIO m) => MonadIO (HeistT n m)

MonadIO instance

(Monad (HeistT n m), MonadCont m) => MonadCont (HeistT n m)

MonadCont passthrough instance

evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m aSource

Evaluates a template monad as a computation in the underlying monad.

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

getContext :: Monad m => HeistT n m TPathSource

Gets the current context

getTemplateFilePath :: Monad m => HeistT n 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) -> HeistT n m a -> HeistT n m aSource

HeistT's local.

getsHS :: Monad m => (HeistState n -> r) -> HeistT n m rSource

HeistT's gets.

getHS :: Monad m => HeistT n m (HeistState n)Source

HeistT's get.

putHS :: Monad m => HeistState n -> HeistT n m ()Source

HeistT's put.

modifyHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m ()Source

HeistT's modify.

restoreHS :: Monad m => HeistState n -> HeistT n m ()Source

Restores the HeistState. This function is almost like putHS except it preserves the current doctypes. You should use this function instead of putHS 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.

localHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m a -> HeistT n m aSource

Abstracts the common pattern of running a HeistT computation with a modified heist state.

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

Reads an HTML template from disk.

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

Reads an XML template from disk.

orError :: Monad m => HeistT n m b -> String -> HeistT n m bSource

If Heist is running in fail fast mode, then this function will throw an exception with the second argument as the error message. Otherwise, the first argument will be executed to represent silent failure.

This behavior allows us to fail quickly if an error crops up during load-time splice processing or degrade more gracefully if the error occurs while a user request is being processed.