[Template-haskell] change in [d| |] and creating instances in template-haskell 2.7
Jeremy Shaw
jeremy at n-heptane.com
Wed Sep 7 21:50:03 CEST 2011
Hello,
I have some code that likes like this, which works in template-haskell
2.5 / GHC 7.0.3:
---------------
{-# Language TemplateHaskell, TypeFamilies #-}
module Show where
import Language.Haskell.TH
class Bar a where
bar :: a -> String
inferBar :: Name -> Q [Dec]
inferBar typeName =
do s <- [d| bar _ = "sucker"
|]
d <- instanceD (return []) (appT (conT ''Bar) (conT typeName))
(map return s)
return [d]
-----------------
$(inferBar ''Bool)
But, in template-haskell 2.6 / GHC 7.2.1, I get an error,
Warning: No explicit method nor default method for `bar'
In the instance declaration for `Bar Bool'
Comparing the output of -ddump-splices we see in GHC 7.0.3/ TH 2.5, we
have:
bar-test.hs:1:1: Splicing declarations
inferBar 'Bool
======>
bar-test.hs:4:3-17
instance Bar Bool where
{ bar _ = "sucker" }
But in GHC 7.2.1 / TH 2.6 we have:
bar-test.hs:1:1: Splicing declarations
inferBar 'Bool
======>
bar-test.hs:4:3-17
instance Bar Bool where
{ bar_acAU _ = "sucker" }
The difference being that instead 'bar' we have 'bar_acAU'. So maybe
that is why it can't find the method 'bar' in the instance
declaration? Though, I would kind of expect an error like,
`bar_acAU' is not a (visible) method of class `Bar'.
Am I doing something wrong? Should I file a bug ?
Thanks!
- jeremy
More information about the template-haskell
mailing list