Safe Haskell | None |
---|---|
Language | Haskell98 |
The Heist snaplet makes it easy to add Heist to your application and use it in other snaplets.
- data Heist b
- class HasHeist b where
- heistInit :: FilePath -> SnapletInit b (Heist b)
- heistInit' :: FilePath -> HeistConfig (Handler b b) -> SnapletInit b (Heist b)
- heistReloader :: Handler b (Heist b) ()
- setInterpreted :: Snaplet (Heist b) -> Initializer b v ()
- getCurHeistConfig :: Snaplet (Heist b) -> Initializer b v (HeistConfig (Handler b b))
- addTemplates :: HasHeist b => Snaplet (Heist b) -> ByteString -> Initializer b v ()
- addTemplatesAt :: HasHeist b => Snaplet (Heist b) -> ByteString -> FilePath -> Initializer b v ()
- addConfig :: Snaplet (Heist b) -> SpliceConfig (Handler b b) -> Initializer b v ()
- getHeistState :: HasHeist b => Handler b v (HeistState (Handler b b))
- modifyHeistState :: HasHeist b => (HeistState (Handler b b) -> HeistState (Handler b b)) -> Initializer b v ()
- withHeistState :: HasHeist b => (HeistState (Handler b b) -> a) -> Handler b v a
- gRender :: HasHeist b => ByteString -> Handler b v ()
- gRenderAs :: HasHeist b => ByteString -> ByteString -> Handler b v ()
- gHeistServe :: HasHeist b => Handler b v ()
- gHeistServeSingle :: HasHeist b => ByteString -> Handler b v ()
- chooseMode :: HasHeist b => Handler b v a -> Handler b v a -> Handler b v a
- cRender :: HasHeist b => ByteString -> Handler b v ()
- cRenderAs :: HasHeist b => ByteString -> ByteString -> Handler b v ()
- cHeistServe :: HasHeist b => Handler b v ()
- cHeistServeSingle :: HasHeist b => ByteString -> Handler b v ()
- render :: HasHeist b => ByteString -> Handler b v ()
- renderAs :: HasHeist b => ByteString -> ByteString -> Handler b v ()
- heistServe :: HasHeist b => Handler b v ()
- heistServeSingle :: HasHeist b => ByteString -> Handler b v ()
- heistLocal :: HasHeist b => (HeistState (Handler b b) -> HeistState (Handler b b)) -> Handler b v a -> Handler b v a
- withSplices :: HasHeist b => Splices (SnapletISplice b) -> Handler b v a -> Handler b v a
- renderWithSplices :: HasHeist b => ByteString -> Splices (SnapletISplice b) -> Handler b v ()
- type SnapletHeist b m a = HeistT (Handler b b) m a
- type SnapletCSplice b = SnapletHeist b IO (DList (Chunk (Handler b b)))
- type SnapletISplice b = SnapletHeist b (Handler b b) Template
- clearHeistCache :: Heist b -> IO ()
Heist and its type class
The state for the Heist snaplet. To use the Heist snaplet in your app
include this in your application state and use heistInit
to initialize
it. The type parameter b will typically be the base state type for your
application.
class HasHeist b where Source #
A single snaplet should never need more than one instance of Heist as a subsnaplet. This type class allows you to make it easy for other snaplets to get the lens that identifies the heist snaplet. Here's an example of how the heist snaplet might be declared:
data App = App { _heist :: Snaplet (Heist App) } makeLenses ''App instance HasHeist App where heistLens = subSnaplet heist appInit = makeSnaplet "app" "" Nothing $ do h <- nestSnaplet "heist" heist $ heistInit "templates" addConfig h heistConfigWithMyAppSplices return $ App h
Initializer Functions
This section contains functions for use in setting up your Heist state during initialization.
:: FilePath | Path to templates |
-> SnapletInit b (Heist b) |
The Initializer
for Heist
. This function is a convenience wrapper
around heistInit'
that uses defaultHeistState and sets up routes for all
the templates. It sets up a "heistReload" route that reloads the heist
templates when you request it from localhost.
:: FilePath | Path to templates |
-> HeistConfig (Handler b b) | Initial HeistConfig |
-> SnapletInit b (Heist b) |
A lower level Initializer
for Heist
. This initializer requires you
to specify the initial HeistConfig. It also does not add any routes for
templates, allowing you complete control over which templates get routed.
heistReloader :: Handler b (Heist b) () Source #
Handler that triggers a template reload. For large sites, this can be desireable because it may be much quicker than the full site reload provided at the adminreload route. This allows you to reload only the heist templates This handler is automatically set up by heistInit, but if you use heistInit', then you can create your own route with it.
setInterpreted :: Snaplet (Heist b) -> Initializer b v () Source #
Sets the snaplet to default to interpreted mode. Initially, the
initializer sets the value to compiled mode. This function allows you to
override that setting. Note that this is just a default. It only has an
effect if you use one of the generic functions: gRender
, gRenderAs
,
gHeistServe
, or gHeistServeSingle
. If you call the non-generic
versions directly, then this value will not be checked and you will get the
mode implemented by the function you called.
getCurHeistConfig :: Snaplet (Heist b) -> Initializer b v (HeistConfig (Handler b b)) Source #
:: HasHeist b | |
=> Snaplet (Heist b) | |
-> ByteString | The url prefix for the template routes |
-> Initializer b v () |
Adds templates to the Heist HeistState. Other snaplets should use this function to add their own templates. The templates are automatically read from the templates directory in the current snaplet's filesystem root.
:: HasHeist b | |
=> Snaplet (Heist b) | |
-> ByteString | URL prefix for template routes |
-> FilePath | Path to templates |
-> Initializer b v () |
Adds templates to the Heist HeistState, and lets you specify where they are found in the filesystem. Note that the path to the template directory is an absolute path. This allows you more flexibility in where your templates are located, but means that you have to explicitly call getSnapletFilePath if you want your snaplet to use templates within its normal directory structure.
addConfig :: Snaplet (Heist b) -> SpliceConfig (Handler b b) -> Initializer b v () Source #
Adds more HeistConfig data using mappend with whatever is currently there. This is the preferred method for adding all four kinds of splices as well as new templates.
getHeistState :: HasHeist b => Handler b v (HeistState (Handler b b)) Source #
More general function allowing arbitrary HeistState modification.
:: HasHeist b | |
=> (HeistState (Handler b b) -> HeistState (Handler b b)) | HeistState modifying function |
-> Initializer b v () |
More general function allowing arbitrary HeistState modification.
:: HasHeist b | |
=> (HeistState (Handler b b) -> a) | HeistState function to run |
-> Handler b v a |
Runs a function on with the Heist snaplet's HeistState
.
Handler Functions
This section contains functions in the Handler
monad that you'll use in
processing requests. Functions beginning with a g
prefix use generic
rendering that checks the preferred rendering mode and chooses
appropriately. Functions beginning with a c
prefix use compiled template
rendering. The other functions use the older interpreted rendering.
Interpreted splices added with addConfig will only work if you use
interpreted rendering.
The generic functions are useful if you are writing general snaplets that use heist, but need to work for applications that use either interpreted or compiled mode.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Generic version of 'render'/'cRender'.
:: HasHeist b | |
=> ByteString | Content type to render with |
-> ByteString | Template name |
-> Handler b v () |
Generic version of 'renderAs'/'cRenderAs'.
gHeistServe :: HasHeist b => Handler b v () Source #
Generic version of 'heistServe'/'cHeistServe'.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Generic version of 'heistServeSingle'/'cHeistServeSingle'.
:: HasHeist b | |
=> Handler b v a | A compiled action |
-> Handler b v a | An interpreted action |
-> Handler b v a |
Chooses between a compiled action and an interpreted action based on the configured default.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Renders a compiled template as text/html. If the given template is not
found, this returns empty
.
:: HasHeist b | |
=> ByteString | Content type to render with |
-> ByteString | Template name |
-> Handler b v () |
Renders a compiled template as the given content type. If the given
template is not found, this returns empty
.
cHeistServe :: HasHeist b => Handler b v () Source #
A compiled version of heistServe
.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Analogous to fileServeSingle
. If the given template is not found,
this throws an error.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Renders a template as text/html. If the given template is not found,
this returns empty
.
:: HasHeist b | |
=> ByteString | Content type to render with |
-> ByteString | Template name |
-> Handler b v () |
Renders a template as the given content type. If the given template
is not found, this returns empty
.
heistServe :: HasHeist b => Handler b v () Source #
A handler that serves all the templates (similar to serveDirectory
).
If the template specified in the request path is not found, it returns
empty
. Also, this function does not serve any templates beginning with
an underscore. This gives you a way to prevent some templates from being
served. For example, you might have a template that contains only the
navbar of your pages, and you probably wouldn't want that template to be
visible to the user as a standalone template. So if you put it in a file
called "_nav.tpl", this function won't serve it.
:: HasHeist b | |
=> ByteString | Template name |
-> Handler b v () |
Handler for serving a single template (similar to fileServeSingle
). If
the given template is not found, this throws an error.
:: HasHeist b | |
=> (HeistState (Handler b b) -> HeistState (Handler b b)) | HeistState modifying function |
-> Handler b v a | Handler to run |
-> Handler b v a |
Runs a handler with a modified HeistState
. You might want to use
this if you had a set of splices which were customised for a specific
action. To do that you would do:
heistLocal (bindSplices mySplices) handlerThatNeedsSplices
:: HasHeist b | |
=> Splices (SnapletISplice b) | Splices to bind |
-> Handler b v a | Handler to run |
-> Handler b v a |
Runs an action with additional splices bound into the Heist
HeistState
.
:: HasHeist b | |
=> ByteString | Template name |
-> Splices (SnapletISplice b) | Splices to bind |
-> Handler b v () |
Renders a template with a given set of splices. This is syntax sugar for a common combination of heistLocal, bindSplices, and render.
Writing Splices
The type signature for SnapletHeist uses (Handler b b)
as the Heist
snaplet's runtime monad. This means that your splices must use the
top-level snaplet's Handler b b
monad. The reasons for this are beyond
the scope of this discussion, but the result is that lift
inside a splice
only works with Handler b b
actions. When you're writing your own
snaplets using some snaplet-specific monad Handler b v
you still have to
use Handler b b
for your splices. If the splices need any of the context
provided by the v
, you must pass it in as a parameter to the splice
function.
type SnapletHeist b m a = HeistT (Handler b b) m a Source #
type SnapletCSplice b = SnapletHeist b IO (DList (Chunk (Handler b b))) Source #
type SnapletISplice b = SnapletHeist b (Handler b b) Template Source #
clearHeistCache :: Heist b -> IO () Source #
Clears data stored by the cache tag. The cache tag automatically reloads its data when the specified TTL expires, but sometimes you may want to trigger a manual reload. This function lets you do that.