Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- loadTemplates :: FilePath -> IO (Either [String] TemplateRepo)
- reloadTemplates :: TemplateRepo -> IO (Either [String] TemplateRepo)
- addTemplatePathPrefix :: ByteString -> TemplateRepo -> TemplateRepo
- initHeist :: Monad n => HeistConfig n -> IO (Either [String] (HeistState n))
- initHeistWithCacheTag :: MonadIO n => HeistConfig n -> IO (Either [String] (HeistState n, CacheTagState))
- defaultInterpretedSplices :: MonadIO m => Splices (Splice m)
- defaultLoadTimeSplices :: MonadIO m => Splices (Splice m)
- emptyHeistConfig :: HeistConfig m
- data SpliceConfig m
- data HeistConfig m
- type TemplateRepo = HashMap TPath DocumentFile
- type TemplateLocation = IO (Either [String] TemplateRepo)
- type Template = [Node]
- type TPath = [ByteString]
- type MIMEType = ByteString
- data DocumentFile = DocumentFile {}
- type AttrSplice m = Text -> RuntimeSplice m [(Text, Text)]
- data RuntimeSplice m a
- data Chunk m
- data HeistState m
- data SpliceError = SpliceError {
- spliceHistory :: [(TPath, Maybe FilePath, Text)]
- spliceTemplateFile :: Maybe FilePath
- visibleSplices :: [Text]
- contextNode :: Node
- spliceMsg :: Text
- data CompileException = Exception e => CompileException {
- originalException :: e
- exceptionContext :: [SpliceError]
- data HeistT n m a
- scInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> SpliceConfig m -> f (SpliceConfig m)
- scCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> SpliceConfig m -> f (SpliceConfig m)
- scCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> SpliceConfig m -> f (SpliceConfig m)
- hcSpliceConfig :: Functor f => (SpliceConfig m -> f (SpliceConfig m)) -> HeistConfig m -> f (HeistConfig m)
- hcNamespace :: Functor f => (Text -> f Text) -> HeistConfig m -> f (HeistConfig m)
- hcErrorNotBound :: Functor f => (Bool -> f Bool) -> HeistConfig m -> f (HeistConfig m)
- hcInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m)
- hcLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> HeistConfig m -> f (HeistConfig m)
- hcCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m)
- hcAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> HeistConfig m -> f (HeistConfig m)
- hcTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> HeistConfig m -> f (HeistConfig m)
- hcCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> HeistConfig m -> f (HeistConfig m)
- templateNames :: HeistState m -> [TPath]
- compiledTemplateNames :: HeistState m -> [TPath]
- hasTemplate :: ByteString -> HeistState n -> Bool
- spliceNames :: HeistState m -> [Text]
- compiledSpliceNames :: HeistState m -> [Text]
- evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m a
- getParamNode :: Monad m => HeistT n m Node
- getContext :: Monad m => HeistT n m TPath
- getTemplateFilePath :: Monad m => HeistT n m (Maybe FilePath)
- localParamNode :: Monad m => (Node -> Node) -> HeistT n m a -> HeistT n m a
- getsHS :: Monad m => (HeistState n -> r) -> HeistT n m r
- getHS :: Monad m => HeistT n m (HeistState n)
- putHS :: Monad m => HeistState n -> HeistT n m ()
- modifyHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m ()
- restoreHS :: Monad m => HeistState n -> HeistT n m ()
- localHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m a -> HeistT n m a
- getDoc :: String -> IO (Either String DocumentFile)
- getXMLDoc :: String -> IO (Either String DocumentFile)
- tellSpliceError :: Monad m => Text -> HeistT n m ()
- spliceErrorText :: SpliceError -> Text
- orError :: Monad m => HeistT n m b -> String -> HeistT n m b
- type Splices s = MapSyntax Text s
Primary Heist initialization functions
loadTemplates :: FilePath -> IO (Either [String] TemplateRepo) Source #
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.
reloadTemplates :: TemplateRepo -> IO (Either [String] TemplateRepo) Source #
Reloads all the templates an an existing TemplateRepo.
addTemplatePathPrefix :: ByteString -> TemplateRepo -> TemplateRepo Source #
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 -> IO (Either [String] (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 -> IO (Either [String] (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 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 => Splices (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 scLoadTimeSplices list in your SpliceConfig.
If you are using interpreted splice mode, then you might also want to bind
the deprecatedContentCheck
splice to the content tag as a load time
splice.
defaultLoadTimeSplices :: MonadIO m => Splices (Splice m) Source #
The built-in set of splices that you should use in compiled splice mode.
This list includes everything from defaultInterpretedSplices
plus a
splice for the content tag that errors out when it sees any instance of the
old content tag, which has now been moved to two separate tags called
apply-content and bind-content.
emptyHeistConfig :: HeistConfig m Source #
An empty HeistConfig that uses the "h" namespace with error checking turned on.
Core Heist data types
data SpliceConfig m Source #
The splices and templates Heist will use. To bind a splice simply include it in the appropriate place here.
Monoid (SpliceConfig m) Source # | |
data HeistConfig m Source #
type TemplateRepo = HashMap TPath DocumentFile Source #
type TemplateLocation = IO (Either [String] TemplateRepo) Source #
An IO action for getting a template repo from this location. By not just using a directory path here, we support templates loaded from a database, retrieved from the network, or anything else you can think of.
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.
type MIMEType = ByteString Source #
MIME Type. The type alias is here to make the API clearer.
data DocumentFile Source #
Holds data about templates read from disk.
type AttrSplice m = Text -> RuntimeSplice 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.
MonadTrans RuntimeSplice Source # | |
Monad m => Monad (RuntimeSplice m) Source # | |
Functor m => Functor (RuntimeSplice m) Source # | |
Monad m => Applicative (RuntimeSplice m) Source # | |
MonadIO m => MonadIO (RuntimeSplice m) Source # | |
(Monad m, Monoid a) => Monoid (RuntimeSplice m a) Source # | |
Opaque type representing pieces of output from compiled splices.
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
data SpliceError Source #
Detailed information about a splice error.
SpliceError | |
|
data CompileException Source #
Exception type for splice compile errors. Wraps the original exception and provides context. data (Exception e) => CompileException e = CompileException
Exception e => CompileException | |
|
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.
MonadBase b m => MonadBase b (HeistT n m) Source # | |
MonadBaseControl b m => MonadBaseControl b (HeistT n m) Source # | |
MonadState s m => MonadState s (HeistT n m) Source # | MonadState passthrough instance |
MonadReader r m => MonadReader r (HeistT n m) Source # | MonadReader passthrough instance |
MonadError e m => MonadError e (HeistT n m) Source # | MonadError passthrough instance |
MonadTrans (HeistT n) Source # | MonadTrans instance |
MonadTransControl (HeistT n) Source # | |
Monad m => Monad (HeistT n m) Source # | Monad instance |
Functor m => Functor (HeistT n m) Source # | Functor instance |
MonadFix m => MonadFix (HeistT n m) Source # | MonadFix passthrough instance |
(Monad m, Functor m) => Applicative (HeistT n m) Source # | Applicative instance |
(Functor m, MonadPlus m) => Alternative (HeistT n m) Source # | Alternative passthrough instance |
MonadPlus m => MonadPlus (HeistT n m) Source # | MonadPlus passthrough instance |
MonadIO m => MonadIO (HeistT n m) Source # | MonadIO instance |
MonadCont m => MonadCont (HeistT n m) Source # | MonadCont passthrough instance |
type StT (HeistT n) a Source # | |
type StM (HeistT n m) a Source # | |
Lenses (can be used with lens or lens-family)
scInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for interpreted splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice m))
scLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for load time splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice IO))
scCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for complied splices :: Simple Lens (SpliceConfig m) (Splices (C.Splice m))
scAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for attribute splices :: Simple Lens (SpliceConfig m) (Splices (AttrSplice m))
scTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for template locations :: Simple Lens (SpliceConfig m) [TemplateLocation]
scCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)
hcSpliceConfig :: Functor f => (SpliceConfig m -> f (SpliceConfig m)) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the SpliceConfig :: Simple Lens (HeistConfig m) (SpliceConfig m)
hcNamespace :: Functor f => (Text -> f Text) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the namespace :: Simple Lens (HeistConfig m) Text
hcErrorNotBound :: Functor f => (Bool -> f Bool) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the namespace error flag :: Simple Lens (HeistConfig m) Bool
hcInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for interpreted splices :: Simple Lens (HeistConfig m) (Splices (I.Splice m))
hcLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for load time splices :: Simple Lens (HeistConfig m) (Splices (I.Splice IO))
hcCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for compiled splices :: Simple Lens (HeistConfig m) (Splices (C.Splice m))
hcAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for attribute splices :: Simple Lens (HeistConfig m) (Splices (AttrSplice m))
hcTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for template locations :: Simple Lens (HeistConfig m) [TemplateLocation]
hcCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)
HeistT functions
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 -> Bool Source #
Returns True
if the given template can be found in the heist state.
spliceNames :: HeistState m -> [Text] Source #
Gets the names of all the interpreted splices defined in a HeistState.
compiledSpliceNames :: HeistState m -> [Text] Source #
Gets the names of all the compiled splices defined in a HeistState.
evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m a Source #
Evaluates a template monad as a computation in the underlying monad.
getParamNode :: Monad m => HeistT n m Node Source #
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"
.
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.
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 and splice errors. 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 a Source #
Abstracts the common pattern of running a HeistT computation with a modified heist state.
tellSpliceError :: Monad m => Text -> HeistT n m () Source #
Adds an error message to the list of splice processing errors.
spliceErrorText :: SpliceError -> Text Source #
Transform a SpliceError record to a Text message.
orError :: Monad m => HeistT n m b -> String -> HeistT n m b Source #
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.