| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.Ginger.Run.Type
Contents
Description
Synopsis
- data GingerContext p m h = GingerContext {- contextLookup :: VarName -> Run p m h (GVal (Run p m h))
- contextWrite :: h -> Run p m h ()
- contextWarn :: RuntimeError p -> Run p m h ()
- contextEncode :: GVal (Run p m h) -> h
- contextNewlines :: Maybe (Newlines h)
 
- makeContext :: (VarName -> GVal (Run p (Writer Html) Html)) -> GingerContext p (Writer Html) Html
- makeContextM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> GingerContext p m Html
- makeContext' :: Monoid h => (VarName -> GVal (Run p (Writer h) h)) -> (GVal (Run p (Writer h) h) -> h) -> Maybe (Newlines h) -> GingerContext p (Writer h) h
- makeContextM' :: (Monad m, Functor m) => (VarName -> Run p m h (GVal (Run p m h))) -> (h -> m ()) -> (GVal (Run p m h) -> h) -> Maybe (Newlines h) -> GingerContext p m h
- makeContextExM' :: (Monad m, Functor m) => (VarName -> Run p m h (GVal (Run p m h))) -> (h -> m ()) -> (RuntimeError p -> m ()) -> (GVal (Run p m h) -> h) -> Maybe (Newlines h) -> GingerContext p m h
- makeContextHtml :: (VarName -> GVal (Run p (Writer Html) Html)) -> GingerContext p (Writer Html) Html
- makeContextHtmlM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> GingerContext p m Html
- makeContextHtmlExM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> (RuntimeError p -> m ()) -> GingerContext p m Html
- makeContextText :: (VarName -> GVal (Run p (Writer Text) Text)) -> GingerContext p (Writer Text) Text
- makeContextTextM :: (Monad m, Functor m) => (VarName -> Run p m Text (GVal (Run p m Text))) -> (Text -> m ()) -> GingerContext p m Text
- makeContextTextExM :: (Monad m, Functor m) => (VarName -> Run p m Text (GVal (Run p m Text))) -> (Text -> m ()) -> (RuntimeError p -> m ()) -> GingerContext p m Text
- easyContext :: (Monad m, ContextEncodable h, ToGVal (Run p m h) v) => (h -> m ()) -> v -> GingerContext p m h
- class ContextEncodable h where
- liftRun :: Monad m => m a -> Run p m h a
- liftRun2 :: Monad m => (a -> m b) -> a -> Run p m h b
- type Run p m h = ExceptT (RuntimeError p) (StateT (RunState p m h) (ReaderT (GingerContext p m h) m))
- data RunState p m h = RunState {- rsScope :: HashMap VarName (GVal (Run p m h))
- rsCapture :: h
- rsCurrentTemplate :: Template p
- rsCurrentBlockName :: Maybe Text
- rsIndentation :: Maybe [h]
- rsAtLineStart :: Bool
- rsCurrentSourcePos :: p
 
- data RuntimeError p
- runtimeErrorWhat :: RuntimeError p -> Text
- runtimeErrorWhere :: RuntimeError p -> [p]
- runtimeErrorMessage :: RuntimeError p -> Text
- data Newlines h = Newlines {- splitLines :: h -> [h]
- joinLines :: [h] -> h
- stripIndent :: h -> h
- endsWithNewline :: h -> Bool
 
- hoistContext :: Monad m => (h -> t) -> (t -> h) -> GingerContext p m h -> GingerContext p m t
- hoistRun :: Monad m => (h -> t) -> (t -> h) -> Run p m h a -> Run p m t a
- hoistNewlines :: (h -> t) -> (t -> h) -> Newlines h -> Newlines t
- hoistRunState :: Monad m => (h -> t) -> (t -> h) -> RunState p m h -> RunState p m t
- warn :: Monad m => RuntimeError p -> Run p m h ()
- warnFromMaybe :: Monad m => RuntimeError p -> a -> Maybe a -> Run p m h a
- throwHere :: Monad m => RuntimeError p -> Run p m h a
- withSourcePos :: (Monad m, Applicative m, Functor m) => p -> Run p m h a -> Run p m h a
- getSourcePos :: (Monad m, Applicative m, Functor m) => Run p m h p
Documentation
data GingerContext p m h Source #
Execution context. Determines how to look up variables from the environment, and how to write out template output.
Constructors
| GingerContext | |
| Fields 
 | |
makeContext :: (VarName -> GVal (Run p (Writer Html) Html)) -> GingerContext p (Writer Html) Html Source #
Deprecated: Compatibility alias for makeContextHtml
makeContextM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> GingerContext p m Html Source #
Deprecated: Compatibility alias for makeContextHtmlM
makeContext' :: Monoid h => (VarName -> GVal (Run p (Writer h) h)) -> (GVal (Run p (Writer h) h) -> h) -> Maybe (Newlines h) -> GingerContext p (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 p m h (GVal (Run p m h))) -> (h -> m ()) -> (GVal (Run p m h) -> h) -> Maybe (Newlines h) -> GingerContext p 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).
makeContextExM' :: (Monad m, Functor m) => (VarName -> Run p m h (GVal (Run p m h))) -> (h -> m ()) -> (RuntimeError p -> m ()) -> (GVal (Run p m h) -> h) -> Maybe (Newlines h) -> GingerContext p m h Source #
makeContextHtml :: (VarName -> GVal (Run p (Writer Html) Html)) -> GingerContext p (Writer Html) Html Source #
makeContextHtmlM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> GingerContext p m Html Source #
makeContextHtmlExM :: (Monad m, Functor m) => (VarName -> Run p m Html (GVal (Run p m Html))) -> (Html -> m ()) -> (RuntimeError p -> m ()) -> GingerContext p m Html Source #
makeContextText :: (VarName -> GVal (Run p (Writer Text) Text)) -> GingerContext p (Writer Text) Text Source #
makeContextTextM :: (Monad m, Functor m) => (VarName -> Run p m Text (GVal (Run p m Text))) -> (Text -> m ()) -> GingerContext p m Text Source #
makeContextTextExM :: (Monad m, Functor m) => (VarName -> Run p m Text (GVal (Run p m Text))) -> (Text -> m ()) -> (RuntimeError p -> m ()) -> GingerContext p m Text Source #
easyContext :: (Monad m, ContextEncodable h, ToGVal (Run p m h) v) => (h -> m ()) -> v -> GingerContext p m h Source #
class ContextEncodable h where Source #
Typeclass that defines how to encode GVals into a given type.
Minimal complete definition
Instances
| ContextEncodable Text Source # | Encoding to text just takes the text representation without further processing. | 
| ContextEncodable Html Source # | Encoding to Html is implemented as returning the  | 
liftRun :: Monad m => m a -> Run p m h a Source #
Lift a value from the host monad m into the Run monad.
liftRun2 :: Monad m => (a -> m b) -> a -> Run p m h b Source #
Lift a function from the host monad m into the Run monad.
type Run p m h = ExceptT (RuntimeError p) (StateT (RunState p m h) (ReaderT (GingerContext p m h) m)) Source #
Internal type alias for our template-runner monad stack.
Constructors
| RunState | |
| Fields 
 | |
data RuntimeError p Source #
Constructors
| RuntimeError Text | Generic runtime error | 
| UndefinedBlockError Text | Tried to use a block that isn't defined | Invalid arguments to function (function name, explanation) | 
| ArgumentsError (Maybe Text) Text | |
| TypeError [Text] (Maybe Text) | Wrong type, expected one of... | 
| IndexError Text | Invalid index | 
| EvalParseError ParserError | |
| NotAFunctionError | |
| RuntimeErrorAt p (RuntimeError p) | 
Instances
| ToGVal m p => ToGVal m (RuntimeError p) Source # | |
| Defined in Text.Ginger.Run.Type Methods toGVal :: RuntimeError p -> GVal m Source # | |
| Show p => Show (RuntimeError p) Source # | |
| Defined in Text.Ginger.Run.Type Methods showsPrec :: Int -> RuntimeError p -> ShowS # show :: RuntimeError p -> String # showList :: [RuntimeError p] -> ShowS # | |
| Default (RuntimeError p) Source # | |
| Defined in Text.Ginger.Run.Type Methods def :: RuntimeError p # | |
runtimeErrorWhat :: RuntimeError p -> Text Source #
runtimeErrorWhere :: RuntimeError p -> [p] Source #
runtimeErrorMessage :: RuntimeError p -> Text Source #
The Newlines type
Required for handling indentation
A Newlines determines the rules by which a h value can be
 split into lines, how a list of lines can be joined into a single
 value, and how to remove leading whitespace.
Constructors
| Newlines | |
| Fields 
 | |
Hoisting
hoistContext :: Monad m => (h -> t) -> (t -> h) -> GingerContext p m h -> GingerContext p m t Source #
Hoist a context onto a different output type.
 hoistContext fwd rev context returns a context over a different
 output type, applying the fwd and rev projections to convert
 between the original and desired output types.
hoistRun :: Monad m => (h -> t) -> (t -> h) -> Run p m h a -> Run p m t a Source #
Hoist a Run action onto a different output type.
 hoistRun fwd rev action hoists the action from Run p m h a to
 Run p m t a, applying fwd and rev to convert between the output
 types.
hoistNewlines :: (h -> t) -> (t -> h) -> Newlines h -> Newlines t Source #
Hoist a Newlines onto a different output type.
 You don't normally need to use this directly; see hoistRun and/or
 hoistContext.
hoistRunState :: Monad m => (h -> t) -> (t -> h) -> RunState p m h -> RunState p m t Source #
Hoist a RunState onto a different output type.
 You don't normally need to use this directly; see hoistRun and/or
 hoistContext.
warnFromMaybe :: Monad m => RuntimeError p -> a -> Maybe a -> Run p m h a Source #
withSourcePos :: (Monad m, Applicative m, Functor m) => p -> Run p m h a -> Run p m h a Source #
withSourcePos pos action runs action in a context where the
 current source location is set to pos. The original source position is
 restored when action finishes.
getSourcePos :: (Monad m, Applicative m, Functor m) => Run p m h p Source #