[Haskell-cafe] [Snap] Argument Substitution in Heist Templates with Splices

Sebastian Fischer mail at sebfisch.de
Thu Sep 20 21:00:41 CEST 2012


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



More information about the Haskell-Cafe mailing list