Safe Haskell | None |
---|---|
Language | Haskell2010 |
Execute Ginger templates in an arbitrary monad.
Usage example:
render :: Template -> Text -> Text -> Text render template -> username imageURL = do let contextLookup varName = case varName of "username" -> toGVal username "imageURL" -> toGVal imageURL _ -> def -- def for GVal is equivalent to a NULL value context = makeContext contextLookup in htmlSource $ runGinger context template
- runGingerT :: (Monad m, Functor m) => GingerContext m -> Template -> m ()
- runGinger :: GingerContext (Writer Html) -> Template -> Html
- data GingerContext m
- makeContext :: (VarName -> GVal (Run (Writer Html))) -> GingerContext (Writer Html)
- makeContextM :: (Monad m, Functor m) => (VarName -> Run m (GVal (Run m))) -> (Html -> m ()) -> GingerContext m
- type Run m = StateT (RunState m) (ReaderT (GingerContext m) m)
- liftRun :: Monad m => m a -> Run m a
- liftRun2 :: Monad m => (a -> m b) -> a -> Run m b
Documentation
runGingerT :: (Monad m, Functor m) => GingerContext m -> Template -> m () Source
Monadically run a Ginger template. The m
parameter is the carrier monad.
data GingerContext m Source
Execution context. Determines how to look up variables from the environment, and how to write out template output.
makeContext :: (VarName -> GVal (Run (Writer Html))) -> GingerContext (Writer Html) Source
Create an execution context for runGinger.
The argument is a lookup function that maps top-level context keys to ginger
values. makeContext
is a specialized version of makeContextM
, targeting
the Writer
Html
monad (which is what is used for the non-monadic
template interpreter runGinger
).
The type of the lookup function may look intimidating, but in most cases,
marshalling values from Haskell to Ginger is a matter of calling toGVal
on them, so the 'GVal (Run (Writer Html))' part can usually be ignored.
See the GVal
module for details.
makeContextM :: (Monad m, Functor m) => (VarName -> Run m (GVal (Run m))) -> (Html -> m ()) -> GingerContext m Source
Create an execution context for runGingerT.
Takes a lookup function, which returns ginger values into the carrier monad
based on a lookup key, and a writer function (outputting HTML by whatever
means the carrier monad provides, e.g. putStr
for IO
, or tell
for
Writer
s).
type Run m = StateT (RunState m) (ReaderT (GingerContext m) m) Source
Internal type alias for our template-runner monad stack.