heist-0.12.0: An Haskell template system supporting both HTML5 and XML.

Safe HaskellNone

Heist.Compiled

Contents

Description

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.

Synopsis

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 HeistT n IO is the runtime monad. This reveals that the Chunks know about the runtime monad. The second type parameter in HeistT 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 BuilderSource

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 nSource

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

mapSnd :: (b -> c) -> [(d, b)] -> [(d, c)]Source

Helper function for transforming the second element of each of a list of tuples.

applySnd :: a -> [(d, a -> b)] -> [(d, b)]Source

The type signature says it all.

prefixSplices :: Text -> Text -> [(Text, a)] -> [(Text, a)]Source

Adds a prefix to the tag names for a list of splices. If the existing tag name is empty, then the new tag name is just the prefix. Otherwise the new tag name is the prefix followed by the separator followed by the existing name.

namespaceSplices :: Text -> [(Text, a)] -> [(Text, a)]Source

prefixSplices specialized to use a colon as separator in the style of XML namespaces.

textSplices :: [(Text, a -> Text)] -> [(Text, a -> Builder)]Source

Converts pure text splices to pure Builder splices.

htmlSplices :: [(Text, a -> [Node])] -> [(Text, a -> Builder)]Source

Converts pure Node splices to pure Builder splices.

pureSplices :: Monad n => [(d, a -> Builder)] -> [(d, Promise a -> Splice n)]Source

Converts pure Builder splices into monadic splice functions of a Promise.

textSplice :: (a -> Text) -> a -> BuilderSource

Converts a pure text splice function to a pure Builder splice function.

htmlSplice :: (a -> [Node]) -> a -> BuilderSource

Converts a pure Node splice function to a pure Builder splice function.

pureSplice :: Monad n => (a -> Builder) -> Promise a -> Splice nSource

Converts a pure Builder splice function into a monadic splice function that takes a Promise.

repromise :: Monad n => (a -> RuntimeSplice n b) -> [(d, Promise b -> Splice n)] -> [(d, Promise a -> Splice n)]Source

Repromise a list of splices.

repromiseMay :: Monad n => (a -> RuntimeSplice n (Maybe b)) -> [(d, Promise b -> Splice n)] -> [(d, Promise a -> Splice n)]Source

repromiseMay' for a list of splices.

repromise' :: Monad n => (a -> RuntimeSplice n b) -> (Promise b -> Splice n) -> Promise a -> Splice nSource

Change the promise type of a splice function.

repromiseMay' :: Monad n => (a -> RuntimeSplice n (Maybe b)) -> (Promise b -> Splice n) -> Promise a -> Splice nSource

Change the promise type of a splice function with a function that might fail. If a Nothing is encountered, then the splice will generate no output.

defer :: Monad n => (Promise a -> Splice n) -> RuntimeSplice n a -> Splice nSource

Allows you to use deferred Promises in a compiled splice. It takes care of the boilerplate of creating and storing data in a promise to be used at load time when compiled splices are processed. This function is similar to mapPromises but runs on a single value instead of a list.

deferMany :: Monad n => (Promise a -> Splice n) -> RuntimeSplice n [a] -> Splice nSource

Takes a promise function and a runtime action returning a list of items that fit in the promise and returns a Splice that executes the promise function for each item and concatenates the results.

withSplices :: Monad n => Splice n -> [(Text, Promise a -> Splice n)] -> RuntimeSplice n a -> Splice nSource

Another useful way of combining groups of splices. FIXME - We probably need to export this applyDeferred :: Monad n => RuntimeSplice n a -> [(Text, Promise a -> Splice n)] -> [(Text, Splice n)] applyDeferred m = applySnd m . mapSnd defer

This is kind of the opposite of defer. Not sure what to name it yet. FIXME - This is a really common pattern, so I think we do want to expose it deferred :: (Monad n) => (t -> RuntimeSplice n Builder) -> Promise t -> Splice n deferred f p = return $ yieldRuntime $ f =<< getPromise p

Runs a splice computation with a list of splices that are functions of runtime data.

manyWithSplicesSource

Arguments

:: Monad n 
=> Splice n

Splice to run for each of the items in the runtime list. You'll frequently use runChildren here.

-> [(Text, Promise a -> Splice n)]

List of splices to bind

-> RuntimeSplice n [a]

Runtime action returning a list of items to render.

-> Splice n 

Gets a list of items at runtime, then for each item it runs the splice with the list of splices bound. There is no pure variant of this function because the desired behavior can only be achieved as a function of a Promise.

withPureSplices :: Monad n => Splice n -> [(Text, a -> Builder)] -> RuntimeSplice n a -> Splice nSource

Like withSplices, but works for "pure" splices that don't operate in the HeistT monad.

Old compiled splice API

mapPromisesSource

Arguments

:: Monad n 
=> (Promise a -> HeistT n IO (RuntimeSplice n Builder))

Use promiseChildrenWith or a variant to create this function.

-> RuntimeSplice n [a]

Runtime computation returning a list of items

-> Splice n 

Takes a promise function and a runtime action returning a list of items that fit in the promise and returns a Splice that executes the promise function for each item and concatenates the results.

This function works nicely with the promiseChildrenWith family of functions, much like the combination of mapSplices and runChildrenWith for interpreted splices.

promiseChildren :: Monad n => HeistT n IO (RuntimeSplice n Builder)Source

Returns a runtime computation that simply renders the node's children.

promiseChildrenWith :: Monad n => [(Text, a -> Builder)] -> Promise a -> HeistT n IO (RuntimeSplice n Builder)Source

Binds a list of Builder splices before using the children of the spliced node as a view.

promiseChildrenWithTrans :: Monad n => (b -> Builder) -> [(Text, a -> b)] -> Promise a -> HeistT n IO (RuntimeSplice n Builder)Source

Wrapper that composes a transformation function with the second item in each of the tuples before calling promiseChildren.

promiseChildrenWithText :: Monad n => [(Text, a -> Text)] -> Promise a -> HeistT n IO (RuntimeSplice n Builder)Source

Binds a list of Text splices before using the children of the spliced node as a view.

promiseChildrenWithNodes :: Monad n => [(Text, a -> [Node])] -> Promise a -> HeistT n IO (RuntimeSplice n Builder)Source

Binds a list of Node splices before using the children of the spliced node as a view. Note that this will slow down page generation because the nodes generated by the splices must be traversed and rendered into a ByteString at runtime.

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 lever construction of Chunks and DLists of Chunks.

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.

withLocalSplices :: [(Text, Splice n)] -> [(Text, AttrSplice n)] -> HeistT n IO a -> HeistT n IO aSource

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.

Lower level promise functions

data Promise a Source

Promises are used for referencing the results of future runtime computations during load time splice processing.

newEmptyPromise :: HeistT n IO (Promise a)Source

Creates an empty promise.

getPromise :: Monad n => Promise a -> RuntimeSplice n aSource

Gets the result of a promised runtime computation.

putPromise :: Monad n => Promise a -> a -> RuntimeSplice n ()Source

Adds a promise to the runtime splice context.

adjustPromise :: Monad n => Promise a -> (a -> a) -> RuntimeSplice n ()Source

Modifies a promise.

Running nodes and splices

runNodeList :: Monad n => [Node] -> Splice nSource

Returns a computation that performs load-time splice processing on the supplied list of nodes.

runNode :: Monad n => Node -> Splice nSource

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.

runAttributes :: Monad n => [(Text, Text)] -> HeistT n IO [DList (Chunk n)]Source

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.

runAttributesRaw :: Monad n => [(Text, Text)] -> HeistT n IO (RuntimeSplice n [(Text, Text)])Source

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.