[Haskell-cafe] Troubles with HStringTemplate (compilation/runtime errors)

Ilya Seleznev itsuart at gmail.com
Sun Jun 21 11:34:58 UTC 2015


Hello Haskellers,

I hope I chose proper mailing list, if not I apologize. And thanks for
reading this!

I run into a problem with HStringTemplate (
http://hackage.haskell.org/package/HStringTemplate) that I have never seen
before.
Code, similar to

{-# LANGUAGE OverloadedStrings, DeriveDataTypeable, NoImplicitPrelude #-}
module Main where
import Data.Data
import qualified Data.Text as T
import qualified Text.StringTemplate as Template

renderTextTemplate :: (Template.ToSElem a) => T.Text -> a -> IO T.Text
renderTextTemplate name input = do
  templatesGroup <- Template.directoryGroup "templates"
  case Template.getStringTemplate (T.unpack name) templatesGroup of
    Nothing -> return $ "Internal Error: template '" `mappend` name
`mappend` "' can not be rendered"
    Just template  -> return $ Template.render (Template.setAttribute "it"
input (template:: Template.StringTemplate T.Text))

data Foo = Foo {value:: T.Text} deriving (Data, Typeable)

main :: IO ()
main = do
  content <- renderTextTemplate "test" $ Foo {value = "oh hi there!"}
  putStrLn content

with a simple template like this:
Just a test $it.value$!

started to cause complaints from GHC (7.8.2 and 7.8.4 on Linux x86_64):
No instance for (Template.ToSElem Foo)

Problem is - it didn't do that before. What even more confusing, older
project[0] uses same approach, compiles (same machine, same compiler) and
works just fine!
I've exhausted all means to fix the problem that I could think off:
- Adding 'instance Template.ToSElem Foo' allows code to compile but it
doesn't work and prints message in console like this:
  Main.hs:30:10-29: No instance nor default method for class operation
Text.StringTemplate.Classes.toSElem
- Tried to use same version of HStringTemplate deps (syb was different)
- All kinds of desperate messing around (exporting records from modules,
changing field names...)
- Updated ghc from 7.8.2 to 7.8.4
- Googled error messages
to no avail.

I hope almighty All would give me some ideas/directions because I have none
left.

[0] Function:
https://github.com/itsuart/fdc_archivist/blob/master/src/HttpUtils.hs#L59
     Data:
https://github.com/itsuart/fdc_archivist/blob/master/src/ViewModels/HomeViewModel.hs
     Usage:
https://github.com/itsuart/fdc_archivist/blob/master/src/HomeViewFeature.hs#L59
-- 
With best regards,
Ilya Seleznev
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150621/2cc07168/attachment.html>


More information about the Haskell-Cafe mailing list