Safe Haskell | None |
---|---|
Language | Haskell98 |
Internal types and accessors. There are no guarantees that heist will preserve backwards compatibility for symbols in this module. If you use them, no complaining when your code breaks.
- type Splices s = MapSyntax Text s
- type Template = [Node]
- type MIMEType = ByteString
- type TPath = [ByteString]
- data DocumentFile = DocumentFile {}
- data Markup
- newtype RuntimeSplice m a = RuntimeSplice {}
- data Chunk m
- = Pure !ByteString
- | RuntimeHtml !(RuntimeSplice m Builder)
- | RuntimeAction !(RuntimeSplice m ())
- showChunk :: Chunk m -> String
- isPureChunk :: Chunk m -> Bool
- type AttrSplice m = Text -> RuntimeSplice m [(Text, Text)]
- data SpliceError = SpliceError {
- spliceHistory :: [(TPath, Maybe FilePath, Text)]
- spliceTemplateFile :: Maybe FilePath
- visibleSplices :: [Text]
- contextNode :: Node
- spliceMsg :: Text
- spliceErrorText :: SpliceError -> Text
- data CompileException = Exception e => CompileException {
- originalException :: e
- exceptionContext :: [SpliceError]
- data HeistState m = HeistState {
- _spliceMap :: HashMap Text (HeistT m m Template)
- _templateMap :: HashMap TPath DocumentFile
- _compiledSpliceMap :: HashMap Text (HeistT m IO (DList (Chunk m)))
- _compiledTemplateMap :: !(HashMap TPath ([Chunk m], MIMEType))
- _attrSpliceMap :: HashMap Text (AttrSplice m)
- _recurse :: Bool
- _curContext :: TPath
- _splicePath :: [(TPath, Maybe FilePath, Text)]
- _recursionDepth :: Int
- _doctypes :: [DocType]
- _curTemplateFile :: Maybe FilePath
- _keygen :: KeyGen
- _preprocessingMode :: Bool
- _curMarkup :: Markup
- _splicePrefix :: Text
- _spliceErrors :: [SpliceError]
- _errorNotBound :: Bool
- _numNamespacedTags :: Int
- newtype HeistT n m a = HeistT {
- runHeistT :: Node -> HeistState n -> m (a, HeistState n)
- templateNames :: HeistState m -> [TPath]
- compiledTemplateNames :: HeistState m -> [TPath]
- spliceNames :: HeistState m -> [Text]
- compiledSpliceNames :: HeistState m -> [Text]
- evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m a
- _liftCatch :: (m (a, HeistState n) -> (e -> m (a, HeistState n)) -> m (a, HeistState n)) -> HeistT n m a -> (e -> HeistT n m a) -> HeistT n m a
- _liftCallCC :: ((((a, HeistState n) -> m (b, HeistState n)) -> m (a, HeistState n)) -> m (a, HeistState n)) -> ((a -> HeistT n m b) -> HeistT n m a) -> HeistT n m a
- getParamNode :: Monad m => HeistT n m Node
- localParamNode :: Monad m => (Node -> Node) -> HeistT n m a -> HeistT n m a
- getsHS :: Monad m => (HeistState n -> r) -> HeistT n m r
- getHS :: Monad m => HeistT n m (HeistState n)
- putHS :: Monad m => HeistState n -> HeistT n m ()
- modifyHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m ()
- restoreHS :: Monad m => HeistState n -> HeistT n m ()
- localHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m a -> HeistT n m a
- modRecursionDepth :: Monad m => (Int -> Int) -> HeistT n m ()
- incNamespacedTags :: Monad m => HeistT n m ()
- data AttAST
- isIdent :: AttAST -> Bool
- type TemplateRepo = HashMap TPath DocumentFile
- type TemplateLocation = IO (Either [String] TemplateRepo)
- lens :: Functor f => (t1 -> t) -> (t1 -> a -> b) -> (t -> f a) -> t1 -> f b
- data SpliceConfig m = SpliceConfig {}
- scInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> SpliceConfig m -> f (SpliceConfig m)
- scCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> SpliceConfig m -> f (SpliceConfig m)
- scTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> SpliceConfig m -> f (SpliceConfig m)
- scCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> SpliceConfig m -> f (SpliceConfig m)
- data HeistConfig m = HeistConfig {}
- hcSpliceConfig :: Functor f => (SpliceConfig m -> f (SpliceConfig m)) -> HeistConfig m -> f (HeistConfig m)
- hcNamespace :: Functor f => (Text -> f Text) -> HeistConfig m -> f (HeistConfig m)
- hcErrorNotBound :: Functor f => (Bool -> f Bool) -> HeistConfig m -> f (HeistConfig m)
- hcInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m)
- hcLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> HeistConfig m -> f (HeistConfig m)
- hcCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m)
- hcAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> HeistConfig m -> f (HeistConfig m)
- hcTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> HeistConfig m -> f (HeistConfig m)
- hcCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> HeistConfig m -> f (HeistConfig m)
Documentation
type Template = [Node] Source #
A Template
is a forest of XML nodes. Here we deviate from the "single
root node" constraint of well-formed XML because we want to allow
templates to contain document fragments that may not have a single root.
type MIMEType = ByteString Source #
MIME Type. The type alias is here to make the API clearer.
type TPath = [ByteString] Source #
Reversed list of directories. This holds the path to the template currently being processed.
data DocumentFile Source #
Holds data about templates read from disk.
newtype RuntimeSplice m a Source #
Monad used for runtime splice execution.
MonadTrans RuntimeSplice Source # | |
Monad m => Monad (RuntimeSplice m) Source # | |
Functor m => Functor (RuntimeSplice m) Source # | |
Monad m => Applicative (RuntimeSplice m) Source # | |
MonadIO m => MonadIO (RuntimeSplice m) Source # | |
(Monad m, Monoid a) => Monoid (RuntimeSplice m a) Source # | |
Opaque type representing pieces of output from compiled splices.
Pure !ByteString | output known at load time |
RuntimeHtml !(RuntimeSplice m Builder) | output computed at run time |
RuntimeAction !(RuntimeSplice m ()) | runtime action used only for its side-effect |
isPureChunk :: Chunk m -> Bool Source #
type AttrSplice m = Text -> RuntimeSplice m [(Text, Text)] Source #
Type alias for attribute splices. The function parameter is the value of the bound attribute splice. The return value is a list of attribute key/value pairs that get substituted in the place of the bound attribute.
data SpliceError Source #
Detailed information about a splice error.
SpliceError | |
|
spliceErrorText :: SpliceError -> Text Source #
Transform a SpliceError record to a Text message.
data CompileException Source #
Exception type for splice compile errors. Wraps the original exception and provides context. data (Exception e) => CompileException e = CompileException
Exception e => CompileException | |
|
data HeistState m Source #
Holds all the state information needed for template processing. You will
build a HeistState
using initHeist
and any of Heist's HeistState ->
HeistState
"filter" functions. Then you use the resulting HeistState
in calls to renderTemplate
.
m is the runtime monad
HeistState | |
|
HeistT is the monad transformer used for splice processing. HeistT
intentionally does not expose any of its functionality via MonadState or
MonadReader functions. We define passthrough instances for the most common
types of monads. These instances allow the user to use HeistT in a monad
stack without needing calls to lift
.
n
is the runtime monad (the parameter to HeistState).
m
is the monad being run now. In this case, "now" is a variable
concept. The type HeistT n n
means that "now" is runtime. The type
HeistT n IO
means that "now" is IO
, and more importantly it is NOT
runtime. In Heist, the rule of thumb is that IO
means load time and n
means runtime.
HeistT | |
|
MonadBase b m => MonadBase b (HeistT n m) Source # | |
MonadBaseControl b m => MonadBaseControl b (HeistT n m) Source # | |
MonadState s m => MonadState s (HeistT n m) Source # | MonadState passthrough instance |
MonadReader r m => MonadReader r (HeistT n m) Source # | MonadReader passthrough instance |
MonadError e m => MonadError e (HeistT n m) Source # | MonadError passthrough instance |
MonadTrans (HeistT n) Source # | MonadTrans instance |
MonadTransControl (HeistT n) Source # | |
Monad m => Monad (HeistT n m) Source # | Monad instance |
Functor m => Functor (HeistT n m) Source # | Functor instance |
MonadFix m => MonadFix (HeistT n m) Source # | MonadFix passthrough instance |
(Monad m, Functor m) => Applicative (HeistT n m) Source # | Applicative instance |
(Functor m, MonadPlus m) => Alternative (HeistT n m) Source # | Alternative passthrough instance |
MonadPlus m => MonadPlus (HeistT n m) Source # | MonadPlus passthrough instance |
MonadIO m => MonadIO (HeistT n m) Source # | MonadIO instance |
MonadCont m => MonadCont (HeistT n m) Source # | MonadCont passthrough instance |
type StT (HeistT n) a Source # | |
type StM (HeistT n m) a Source # | |
templateNames :: HeistState m -> [TPath] Source #
Gets the names of all the templates defined in a HeistState.
compiledTemplateNames :: HeistState m -> [TPath] Source #
Gets the names of all the templates defined in a HeistState.
spliceNames :: HeistState m -> [Text] Source #
Gets the names of all the interpreted splices defined in a HeistState.
compiledSpliceNames :: HeistState m -> [Text] Source #
Gets the names of all the compiled splices defined in a HeistState.
evalHeistT :: Monad m => HeistT n m a -> Node -> HeistState n -> m a Source #
Evaluates a template monad as a computation in the underlying monad.
_liftCatch :: (m (a, HeistState n) -> (e -> m (a, HeistState n)) -> m (a, HeistState n)) -> HeistT n m a -> (e -> HeistT n m a) -> HeistT n m a Source #
Helper for MonadError instance.
_liftCallCC :: ((((a, HeistState n) -> m (b, HeistState n)) -> m (a, HeistState n)) -> m (a, HeistState n)) -> ((a -> HeistT n m b) -> HeistT n m a) -> HeistT n m a Source #
Helper for MonadCont instance.
getParamNode :: Monad m => HeistT n m Node Source #
Gets the node currently being processed.
<speech author="Shakespeare"> To sleep, perchance to dream. </speech>
When you call getParamNode
inside the code for the speech
splice, it
returns the Node for the speech
tag and its children. getParamNode >>=
childNodes
returns a list containing one TextNode
containing part of
Hamlet's speech. liftM (getAttribute "author") getParamNode
would
return Just "Shakespeare"
.
modifyHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m () Source #
HeistT's modify
.
restoreHS :: Monad m => HeistState n -> HeistT n m () Source #
Restores the HeistState. This function is almost like putHS except it
preserves the current doctypes and splice errors. You should use this
function instead of putHS
to restore an old state. This was needed
because doctypes needs to be in a "global scope" as opposed to the template
call "local scope" of state items such as recursionDepth, curContext, and
spliceMap.
localHS :: Monad m => (HeistState n -> HeistState n) -> HeistT n m a -> HeistT n m a Source #
Abstracts the common pattern of running a HeistT computation with a modified heist state.
incNamespacedTags :: Monad m => HeistT n m () Source #
Increments the namespaced tag count
AST to hold attribute parsing structure. This is necessary because attoparsec doesn't support parsers running in another monad.
type TemplateRepo = HashMap TPath DocumentFile Source #
type TemplateLocation = IO (Either [String] TemplateRepo) Source #
An IO action for getting a template repo from this location. By not just using a directory path here, we support templates loaded from a database, retrieved from the network, or anything else you can think of.
lens :: Functor f => (t1 -> t) -> (t1 -> a -> b) -> (t -> f a) -> t1 -> f b Source #
My lens creation function to avoid a dependency on lens.
data SpliceConfig m Source #
The splices and templates Heist will use. To bind a splice simply include it in the appropriate place here.
SpliceConfig | |
|
Monoid (SpliceConfig m) Source # | |
scInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for interpreted splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice m))
scLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for load time splices :: Simple Lens (SpliceConfig m) (Splices (I.Splice IO))
scCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for complied splices :: Simple Lens (SpliceConfig m) (Splices (C.Splice m))
scAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for attribute splices :: Simple Lens (SpliceConfig m) (Splices (AttrSplice m))
scTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for template locations :: Simple Lens (SpliceConfig m) [TemplateLocation]
scCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> SpliceConfig m -> f (SpliceConfig m) Source #
Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)
data HeistConfig m Source #
HeistConfig | |
|
hcSpliceConfig :: Functor f => (SpliceConfig m -> f (SpliceConfig m)) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the SpliceConfig :: Simple Lens (HeistConfig m) (SpliceConfig m)
hcNamespace :: Functor f => (Text -> f Text) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the namespace :: Simple Lens (HeistConfig m) Text
hcErrorNotBound :: Functor f => (Bool -> f Bool) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for the namespace error flag :: Simple Lens (HeistConfig m) Bool
hcInterpretedSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for interpreted splices :: Simple Lens (HeistConfig m) (Splices (I.Splice m))
hcLoadTimeSplices :: Functor f => (Splices (Splice IO) -> f (Splices (Splice IO))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for load time splices :: Simple Lens (HeistConfig m) (Splices (I.Splice IO))
hcCompiledSplices :: Functor f => (Splices (Splice m) -> f (Splices (Splice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for compiled splices :: Simple Lens (HeistConfig m) (Splices (C.Splice m))
hcAttributeSplices :: Functor f => (Splices (AttrSplice m) -> f (Splices (AttrSplice m))) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for attribute splices :: Simple Lens (HeistConfig m) (Splices (AttrSplice m))
hcTemplateLocations :: Functor f => ([TemplateLocation] -> f [TemplateLocation]) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for template locations :: Simple Lens (HeistConfig m) [TemplateLocation]
hcCompiledTemplateFilter :: Functor f => ((TPath -> Bool) -> f (TPath -> Bool)) -> HeistConfig m -> f (HeistConfig m) Source #
Lens for compiled template filter :: Simple Lens (SpliceConfig m) (TBool -> Bool)