
Thanks! For the record, here is how to achieve what I want by
explicitly using `runChildren` and `stopRecursion`:
testSplice :: Splice IO
testSplice = do
input <- getParamNode
kids <- runChildren
stopRecursion
return [input { elementChildren = kids }]
It surprises me that an explicit call to `runChildren` is necessary,
especially after your comment regarding sensitivity to evaulation
order.
Your linked post shows that Heist splices are processed top down,
which reminds me of the `transform` combinator in Uniplate:
http://community.haskell.org/~ndm/downloads/paper-uniform_boilerplate_and_li...
The authors discuss bottom-up and top-down transformations in Sections
2.3 and 2.4 and argue for providing bottom-up transformations and only
a specific form of top-down transformations.
I think Heist's splice processing would be more intuitive (less
sensitive to evaluation order?) if applied bottom up rather than top
down. This only seems to require a slight change in the definition of
`runNode` from the post you linked - to process children before
applying the splice:
runNode :: Monad m => X.Node -> Splice m
runNode (X.Element nm at ch) = do
newAtts <- mapM attSubst at
newKids <- runNodeList ch -- added this line
let n = X.Element nm newAtts newKids -- changed this line
s <- liftM (lookupSplice nm) getTS
maybe n (recurseSplice n) s -- changed this line
-- removed local function `runKids`
runNode n = return [n]
This change would simplify the definition of filter splices which
would not need to call `runChildren` explicitly. It would also make
the definition of substitution splices more uniform, because children
would be already processed when applying the splice - just like
attributes are.
Are Heist splices processed top down intentionally? (Reasons for doing
so are the same reasons people might have for preferring call-by-name
over call-by-value. However, I tend to agree with the discussion in
the Uniplate paper and would prefer "call-by-value" aka bottom-up
transformation.)
Best,
Sebastian
On Fri, Sep 21, 2012 at 6:03 PM, MightyByte
This is one of the more subtle corner cases of Heist. My default, splices are recursively processed. So when testSplice is executed for the <test> tag, the results are fed back into splice processing. I think this is the right thing to do because it makes behavior less sensitive to evaluation order. Obviously this can lead to infinite recursion, so Heist limits the splice call stack to a depth of 50. If this limit is exceeded, then Heist simply stops recursing and returns the nodes unprocessed. I also think this is the right thing to do because it is happening as we're serving a page to the end user, so there's an argument for failing quietly instead of going up in a ball of flames.
In your case, you are returning the same node that was spliced in, so you are hitting the recursion limit and splice processing just stops. I discuss this issue in my blog post about splice subtleties (http://softwaresimply.blogspot.com/2011/04/splice-subtleties.html). Since you're writing a filter splice, you need to call stopRecursion. But if you do that, then the child <arg /> tag won't be processed. So what you need to do is use the runChildren function to process the child nodes, then return them in whatever your constructed node is.
I think the easiest solution to your problem is to not write it as a filter splice. Bind your testSplice function to the <mytest> tag and return a <test> tag. This avoids the infinite recursion and will work the way you want without needing stopRecursion.
On Thu, Sep 20, 2012 at 3:00 PM, Sebastian Fischer
wrote: Hello,
the following program demonstrates that arguments in Heist templates are sometimes not substituted in presence of splices:
{-# LANGUAGE OverloadedStrings #-}
import Blaze.ByteString.Builder (toByteString) import qualified Data.ByteString.Char8 as BS import Data.Functor ((<$>)) import Data.Maybe (fromJust) import Text.Templating.Heist
-- just return input node unchanged testSplice :: Splice IO testSplice = (:[]) <$> getParamNode
main = do writeFile "test.tpl" "<arg /><test attr='${arg}'><arg /></test>" state <- either error id <$> loadTemplates "." defaultHeistState
(builder,_) <- fromJust <$> renderWithArgs [("arg","42")] state "test" BS.putStrLn $ toByteString builder -- 42<test attr='42'>42</test>
let state' = bindSplices [("test",testSplice)] state (builder',_) <- fromJust <$> renderWithArgs [("arg","42")] state' "test" BS.putStrLn $ toByteString builder' -- 42<test attr='42'><arg></arg></test>
Without using splices, all occurrences of 'arg' in the template are substituted. When using a splice, 'arg' is not substituted underneath the input node of the splice. It is substituted in an attribute of the input node.
Is this intentional? How can I ensure substitution also underneath the input node?
Best, Sebastian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe