Troubles with HStringTemplate (compilation/runtime errors)

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/HomeView... Usage: https://github.com/itsuart/fdc_archivist/blob/master/src/HomeViewFeature.hs#... -- With best regards, Ilya Seleznev

On Sun, Jun 21, 2015 at 7:34 AM, Ilya Seleznev
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
This makes me think you have multiple versions of that package around and your new project has managed to use both, such that it finds an instance in the wrong version of the package which will not be considered compatible with the instance it is looking for. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Looks like my mistake was much more trivial: one of the numerious
*ViewModels of old project did import instances from GenericStandard,
that's why everything was working.
And my crude attempts (with manual 'instance ...') were not adequate.
On Sun, Jun 21, 2015 at 6:12 PM, Brandon Allbery
On Sun, Jun 21, 2015 at 7:34 AM, Ilya Seleznev
wrote: 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
This makes me think you have multiple versions of that package around and your new project has managed to use both, such that it finds an instance in the wrong version of the package which will not be considered compatible with the instance it is looking for.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
-- With best regards, Ilya Seleznev

You probably also need to import Text.StringTemplate.GenericStandard to bring the instance for Data into scope. It was originally exported seperately to be compatible with either syb or syb-with-class. But syb-with-class is no longer supported because it did not come into widespread use. GenericStandard should probably be exported by default these days, especially since orphan instances are more frowned upon than when the package was written. -S On June 21, 2015 at 7:35:14 AM, Ilya Seleznev (itsuart@gmail.com) wrote:
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/HomeView... Usage: https://github.com/itsuart/fdc_archivist/blob/master/src/HomeViewFeature.hs#... -- With best regards, Ilya Seleznev _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Yes! Importing GenericStandard() solved the problem! Thank you very much!
And big thanks for the HStringTemplate itself - awesome library!
On Sun, Jun 21, 2015 at 8:22 PM, S. Clover
You probably also need to import Text.StringTemplate.GenericStandard to bring the instance for Data into scope. It was originally exported seperately to be compatible with either syb or syb-with-class. But syb-with-class is no longer supported because it did not come into widespread use. GenericStandard should probably be exported by default these days, especially since orphan instances are more frowned upon than when the package was written.
-S
On June 21, 2015 at 7:35:14 AM, Ilya Seleznev (itsuart@gmail.com) wrote:
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/HomeView...
Usage:
https://github.com/itsuart/fdc_archivist/blob/master/src/HomeViewFeature.hs#...
-- With best regards, Ilya Seleznev _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- With best regards, Ilya Seleznev
participants (3)
-
Brandon Allbery
-
Ilya Seleznev
-
S. Clover