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.
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