error compiling 24 Days of Hackage: heist

Hello, I was trying to compile an example of heist (a template engine) usage from 24 Days of Hackage: heist, but ended up with an error message: src/Main.hs:60:7: `hcTemplateLocations' is not a record selector In the first argument of `initHeist', namely `mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}' In a stmt of a 'do' block: heist <- initHeist (mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}) In the second argument of `($)', namely `do { heist <- initHeist (mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}); Just (output, _) <- renderTemplate heist "billy"; liftIO . BS.putStrLn . toByteString $ output }' src/Main.hs:61:7: `hcInterpretedSplices' is not a record selector In the first argument of `initHeist', namely `mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}' In a stmt of a 'do' block: heist <- initHeist (mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}) In the second argument of `($)', namely `do { heist <- initHeist (mempty {hcTemplateLocations = [loadTemplates "templates"], hcInterpretedSplices = defaultInterpretedSplices}); Just (output, _) <- renderTemplate heist "billy"; liftIO . BS.putStrLn . toByteString $ output }' It's probably something to do with lenses, but I'm not very familiar with it. Four hours of googling didn't give me anything on the subject, so any help? Here is the code(in the state I left it): module Main ( main ) where import Blaze.ByteString.Builder (toByteString) import qualified Data.ByteString.Char8 as BS import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.Trans.Either import Data.Monoid (mempty) import Data.Foldable (forM_) import Heist import Heist.Interpreted import Text.XmlHtml (Node(TextNode), renderHtmlFragment, Encoding(UTF8)) billy :: IO () billy = eitherT (putStrLn . unlines) return $ do heist <- initHeist mempty { hcTemplateLocations = [ loadTemplates "templates" ] , hcInterpretedSplices = defaultInterpretedSplices } Just (output, _) <- renderTemplate heist "billy" liftIO . BS.putStrLn . toByteString $ output main = do putStrLn "---"

On 6 February 2015 at 13:47, hokum
It's probably something to do with lenses, but I'm not very familiar with it. Four hours of googling didn't give me anything on the subject, so any help?
Indeed, hcTemplateLocations is not a record field. Try using lenses instead: initHeist $ mempty & hcTemplateLocations .~ [ loadTemplates "templates" ] & hcInterpretedSplices .~ defaultInterpretedSplices
participants (2)
-
Bas van Dijk
-
hokum