Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains helpers to make Heist fit in more closely within
Fn
's stance against monad transformers and for regular functions.
In particular, it instantiates the Monad for HeistState to be a StateT that contains our context, so that in the splices we can get the context out (and modify it if needed).
Further, we add splice builders that work similar to our url routing - splices are declared to have certain attributes of specific types, and the splice that correspond is a function that takes those as arguments (and takes the context and the node as well).
- class HeistContext ctxt where
- getHeist :: ctxt -> FnHeistState ctxt
- type FnHeistState ctxt = HeistState (StateT ctxt IO)
- type FnSplice ctxt = Splice (StateT ctxt IO)
- type FnCSplice ctxt = Splice (StateT ctxt IO)
- heistInit :: HeistContext ctxt => [Text] -> Splices (FnSplice ctxt) -> Splices (FnCSplice ctxt) -> IO (Either [String] (FnHeistState ctxt))
- heistServe :: (RequestContext ctxt, HeistContext ctxt) => ctxt -> IO (Maybe Response)
- render :: HeistContext ctxt => ctxt -> Text -> IO (Maybe Response)
- renderWithSplices :: HeistContext ctxt => ctxt -> Text -> Splices (FnSplice ctxt) -> IO (Maybe Response)
- cHeistServe :: (RequestContext ctxt, HeistContext ctxt) => ctxt -> IO (Maybe Response)
- cRender :: HeistContext ctxt => ctxt -> Text -> IO (Maybe Response)
- tag :: Text -> (Node -> k -> Maybe (Node, FnSplice ctxt)) -> (ctxt -> Node -> k) -> Splices (FnSplice ctxt)
- tag' :: Text -> (ctxt -> Node -> FnSplice ctxt) -> Splices (FnSplice ctxt)
- class FromAttribute a where
- fromAttribute :: Text -> Maybe a
- attr :: FromAttribute a => Text -> Node -> (a -> t) -> Maybe (Node, t)
- attrOpt :: FromAttribute a => Text -> Node -> (Maybe a -> t) -> Maybe (Node, t)
- (&=) :: (Node -> k -> Maybe (Node, k')) -> (Node -> k' -> Maybe (Node, a)) -> Node -> k -> Maybe (Node, a)
Types
class HeistContext ctxt where Source
In order to have render be able to get the FnHeistState
out of
our context, we need this helper class.
getHeist :: ctxt -> FnHeistState ctxt Source
type FnHeistState ctxt = HeistState (StateT ctxt IO) Source
The type of our state. We need a StateT to be able to pass the runtime context (which includes the current request) into the splices.
type FnSplice ctxt = Splice (StateT ctxt IO) Source
The type of our splice (interpreted version). We need a StateT to be able to pass the runtime context (which includes the current request) into the splice (and sometimes modify it).
type FnCSplice ctxt = Splice (StateT ctxt IO) Source
The type of our splice (compiled version). We need a StateT to be able to pass the runtime context (which includes the current request) into the splice (and sometimes modify it).
Initializer
heistInit :: HeistContext ctxt => [Text] -> Splices (FnSplice ctxt) -> Splices (FnCSplice ctxt) -> IO (Either [String] (FnHeistState ctxt)) Source
Initialize heist. This takes a list of paths to template
directories, a set of interpreted splices, and a set of compiled
splices (you can pass mempty
as either)
Rendering templates
heistServe :: (RequestContext ctxt, HeistContext ctxt) => ctxt -> IO (Maybe Response) Source
Render interpreted templates according to the request path. Note
that if you have matched some parts of the path, those will not be
included in the path used to find the templates. For example, if
you have foo/bar.tpl
in the directory where you loaded templates
from,
path "foo" ==> heistServe
Will match foo/foo/bar
, but not foo/bar
. To match that, you could:
anything ==> heistServe
This will also try the path followed by "index" if the first
doesn't match, so if you have foo/index.tpl
, the path foo
will
be matched to it.
If no template is found, this will continue routing.
render :: HeistContext ctxt => ctxt -> Text -> IO (Maybe Response) Source
Render a single interpreted heist template by name.
renderWithSplices :: HeistContext ctxt => ctxt -> Text -> Splices (FnSplice ctxt) -> IO (Maybe Response) Source
Render a template, and add additional interpreted splices before doing so.
cHeistServe :: (RequestContext ctxt, HeistContext ctxt) => ctxt -> IO (Maybe Response) Source
Like heistServe
, but for compiled templates.
cRender :: HeistContext ctxt => ctxt -> Text -> IO (Maybe Response) Source
Render a single compiled heist template by name.
Building splices
tag :: Text -> (Node -> k -> Maybe (Node, FnSplice ctxt)) -> (ctxt -> Node -> k) -> Splices (FnSplice ctxt) Source
This declares a new splice. Given a name, an attribute matcher, and a handler function (which takes the context, the node, and the specified attributes), it will pass the handler function the provided attributes or return nothing, if the attributes are missing / not deserializable.
Note that due to the dynamism (the handler function can have any
number of arguments, and the number / type of them is based on the
matcher), the types of this may be a little confusing (in
particular, the k
contains a lot). This continuation-based style
lets us achieve this style, but the types suffer. It may be easier
to see via an example:
tag "posts" (attr "num" & attr "sort") $ \ctxt node num sort -> ...
tag' :: Text -> (ctxt -> Node -> FnSplice ctxt) -> Splices (FnSplice ctxt) Source
A tag with no attributes.
class FromAttribute a where Source
In order to make splice definitions more functional, we declare them and the attributes they need, along with deserialization (if needed). The deserialization is facilitated be this class.
fromAttribute :: Text -> Maybe a Source
attr :: FromAttribute a => Text -> Node -> (a -> t) -> Maybe (Node, t) Source
This specifies that an attribute should be present and convertable to the type indicated by it's type.