Safe Haskell | None |
---|---|
Language | Haskell98 |
Compiled splices are similar to the original Heist (interpreted) splices, but without the high performance costs of traversing a DOM at runtime. Compiled splices do all of their DOM processing at load time. They are compiled to produce a runtime computation that generates a ByteString Builder. This preserves the ability to write splices that access runtime information from the HTTP request, database, etc.
If you import both this module and Heist.Interpreted in the same file, then you will need to import them qualified.
- type Splice n = HeistT n IO (DList (Chunk n))
- renderTemplate :: Monad n => HeistState n -> ByteString -> Maybe (n Builder, MIMEType)
- codeGen :: Monad n => DList (Chunk n) -> RuntimeSplice n Builder
- runChildren :: Monad n => Splice n
- textSplice :: (a -> Text) -> a -> Builder
- nodeSplice :: (a -> [Node]) -> a -> Builder
- pureSplice :: Monad n => (a -> Builder) -> RuntimeSplice n a -> Splice n
- deferMany :: Monad n => (RuntimeSplice n a -> Splice n) -> RuntimeSplice n [a] -> Splice n
- deferMap :: Monad n => (a -> RuntimeSplice n b) -> (RuntimeSplice n b -> Splice n) -> RuntimeSplice n a -> Splice n
- mayDeferMap :: Monad n => (a -> RuntimeSplice n (Maybe b)) -> (RuntimeSplice n b -> Splice n) -> RuntimeSplice n a -> Splice n
- bindLater :: Monad n => (a -> RuntimeSplice n Builder) -> RuntimeSplice n a -> Splice n
- withSplices :: Monad n => Splice n -> Splices (RuntimeSplice n a -> Splice n) -> RuntimeSplice n a -> Splice n
- manyWithSplices :: Monad n => Splice n -> Splices (RuntimeSplice n a -> Splice n) -> RuntimeSplice n [a] -> Splice n
- withLocalSplices :: Splices (Splice n) -> Splices (AttrSplice n) -> HeistT n IO a -> HeistT n IO a
- yieldPure :: Builder -> DList (Chunk n)
- yieldRuntime :: RuntimeSplice n Builder -> DList (Chunk n)
- yieldRuntimeEffect :: Monad n => RuntimeSplice n () -> DList (Chunk n)
- yieldPureText :: Text -> DList (Chunk n)
- yieldRuntimeText :: Monad n => RuntimeSplice n Text -> DList (Chunk n)
- runNodeList :: Monad n => [Node] -> Splice n
- runNode :: Monad n => Node -> Splice n
- runAttributes :: Monad n => [(Text, Text)] -> HeistT n IO [DList (Chunk n)]
- runAttributesRaw :: Monad n => [(Text, Text)] -> HeistT n IO (RuntimeSplice n [(Text, Text)])
- callTemplate :: Monad n => ByteString -> HeistT n IO (DList (Chunk n))
High level compiled splice API
type Splice n = HeistT n IO (DList (Chunk n)) Source
A compiled Splice is a HeistT computation that returns a DList
(Chunk m)
.
The more interesting part of the type signature is what comes before the
return value. The first type parameter in
is the runtime
monad. This reveals that the Chunks know about the runtime monad. The
second type parameter in HeistT
n IOHeistT n IO
is IO
. This tells is that the
compiled splices themselves are run in the IO monad, which will usually
mean at load time. Compiled splices run at load time, and they return
computations that run at runtime.
renderTemplate :: Monad n => HeistState n -> ByteString -> Maybe (n Builder, MIMEType) Source
Looks up a compiled template and returns a runtime monad computation that constructs a builder.
codeGen :: Monad n => DList (Chunk n) -> RuntimeSplice n Builder Source
Given a list of output chunks, consolidate turns consecutive runs of
Pure Html
values into maximally-efficient pre-rendered strict
ByteString
chunks.
runChildren :: Monad n => Splice n Source
Runs the parameter node's children and returns the resulting compiled chunks. By itself this function is a simple passthrough splice that makes the spliced node disappear. In combination with locally bound splices, this function makes it easier to pass the desired view into your splices.
Functions for manipulating lists of compiled splices
textSplice :: (a -> Text) -> a -> Builder Source
Converts a pure text splice function to a pure Builder splice function.
nodeSplice :: (a -> [Node]) -> a -> Builder Source
Converts a pure Node splice function to a pure Builder splice function.
pureSplice :: Monad n => (a -> Builder) -> RuntimeSplice n a -> Splice n Source
Converts a pure Builder splice function into a monadic splice function of a RuntimeSplice.
deferMany :: Monad n => (RuntimeSplice n a -> Splice n) -> RuntimeSplice n [a] -> Splice n Source
Similar to mapSplices
in interpreted mode. Gets a runtime list of
items and applies a compiled runtime splice function to each element of the
list.
deferMap :: Monad n => (a -> RuntimeSplice n b) -> (RuntimeSplice n b -> Splice n) -> RuntimeSplice n a -> Splice n Source
Saves the results of a runtme computation in a Promise
so they don't
get recalculated if used more than once.
mayDeferMap :: Monad n => (a -> RuntimeSplice n (Maybe b)) -> (RuntimeSplice n b -> Splice n) -> RuntimeSplice n a -> Splice n Source
Like deferMap, but only runs the result if a Maybe function of the runtime value returns Just. If it returns Nothing, then no output is generated.
This is a good example of how to do more complex flow control with
promises. The generalization of this abstraction is too complex to be
distilled to elegant high-level combinators. If you need to implement your
own special flow control, then you should use functions from the
LowLevel
module similarly to how it is done in the
implementation of this function.
bindLater :: Monad n => (a -> RuntimeSplice n Builder) -> RuntimeSplice n a -> Splice n Source
Converts an RuntimeSplice into a Splice, given a helper function that generates a Builder.
:: Monad n | |
=> Splice n | Splice to be run |
-> Splices (RuntimeSplice n a -> Splice n) | Splices to be bound first |
-> RuntimeSplice n a | Runtime data needed by the above splices |
-> Splice n |
Runs a splice, but first binds splices given by splice functions that need some runtime data.
manyWithSplices :: Monad n => Splice n -> Splices (RuntimeSplice n a -> Splice n) -> RuntimeSplice n [a] -> Splice n Source
Like withSplices, but evaluates the splice repeatedly for each element in a list generated at runtime.
withLocalSplices :: Splices (Splice n) -> Splices (AttrSplice n) -> HeistT n IO a -> HeistT n IO a Source
Adds a list of compiled splices to the splice map. This function is useful because it allows compiled splices to bind other compiled splices during load-time splice processing.
Constructing Chunks
The internals of the Chunk data type are deliberately not exported because
we want to hide the underlying implementation as much as possible. The
yield...
functions give you lower level construction of DLists of Chunks.
Most of the time you will use these functions composed with return to generate a Splice. But we decided not to include the return in these functions to allow you to work with the DLists purely.
yieldPure :: Builder -> DList (Chunk n) Source
Yields a pure Builder known at load time. You should use this and
yieldPureText
as much as possible to maximize the parts of your page that
can be compiled to static ByteStrings.
yieldRuntime :: RuntimeSplice n Builder -> DList (Chunk n) Source
Yields a runtime action that returns a builder.
yieldRuntimeEffect :: Monad n => RuntimeSplice n () -> DList (Chunk n) Source
Yields a runtime action that returns no value and is only needed for its side effect.
yieldPureText :: Text -> DList (Chunk n) Source
A convenience wrapper around yieldPure for working with Text. Roughly
equivalent to textSplice
from Heist.Interpreted.
yieldRuntimeText :: Monad n => RuntimeSplice n Text -> DList (Chunk n) Source
Convenience wrapper around yieldRuntime allowing you to work with Text.
Running nodes and splices
runNodeList :: Monad n => [Node] -> Splice n Source
Returns a computation that performs load-time splice processing on the supplied list of nodes.
runNode :: Monad n => Node -> Splice n Source
Runs a single node. If there is no splice referenced anywhere in the subtree, then it is rendered as a pure chunk, otherwise it calls compileNode to generate the appropriate runtime computation.
Performs splice processing on a list of attributes. This is useful in situations where you need to stop recursion, but still run splice processing on the node's attributes.
Performs splice processing on a list of attributes. This is useful in situations where you need to stop recursion, but still run splice processing on the node's attributes.
callTemplate :: Monad n => ByteString -> HeistT n IO (DList (Chunk n)) Source
Looks up a compiled template and returns a compiled splice.