ginger-0.2.5.0: An implementation of the Jinja2 template language in Haskell

Safe HaskellNone
LanguageHaskell2010

Text.Ginger.Run

Description

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

Synopsis

Documentation

runGingerT :: (ToGVal (Run m h) h, Monoid h, Monad m, Functor m) => GingerContext m h -> Template -> m () Source

Monadically run a Ginger template. The m parameter is the carrier monad.

runGinger :: (ToGVal (Run (Writer h) h) h, Monoid h) => GingerContext (Writer h) h -> Template -> h Source

Purely expand a Ginger template. The underlying carrier monad is Writer h, which is used to collect the output and render it into a h value.

data GingerContext m h 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) Html)) -> GingerContext (Writer Html) Html Source

Deprecated: Compatibility alias for makeContextHtml

makeContextM :: (Monad m, Functor m) => (VarName -> Run m Html (GVal (Run m Html))) -> (Html -> m ()) -> GingerContext m Html Source

Deprecated: Compatibility alias for makeContextHtmlM

makeContext' :: Monoid h => (VarName -> GVal (Run (Writer h) h)) -> (GVal (Run (Writer h) h) -> h) -> GingerContext (Writer h) h 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 h (GVal (Run m h))) -> (h -> m ()) -> (GVal (Run m h) -> h) -> GingerContext m h 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 Writers).

makeContextHtmlM :: (Monad m, Functor m) => (VarName -> Run m Html (GVal (Run m Html))) -> (Html -> m ()) -> GingerContext m Html Source

makeContextTextM :: (Monad m, Functor m) => (VarName -> Run m Text (GVal (Run m Text))) -> (Text -> m ()) -> GingerContext m Text Source

type Run m h = StateT (RunState m h) (ReaderT (GingerContext m h) m) Source

Internal type alias for our template-runner monad stack.

liftRun :: Monad m => m a -> Run m h a Source

Lift a value from the host monad m into the Run monad.

liftRun2 :: Monad m => (a -> m b) -> a -> Run m h b Source

Lift a function from the host monad m into the Run monad.