classes and template haskell (bug?)
Jeremy Shaw
jeremy.shaw at lindows.com
Tue Dec 30 18:19:07 EST 2003
Hello,
I have loaded the following from a file into ghci 6.2:
module Main where
import Language.Haskell.THSyntax
class Test a where
test :: a -> a
instance Test (a,b,c) where
test x = x
main = putStrLn "Hello, World!"
This works for me:
*Main> runQ [d| instance Test (Int,Int) |] >>= putStrLn . show
[InstanceD [] (AppT (ConT "Main:Test") (AppT (AppT (TupleT 2) (ConT "GHC.Base:Int")) (ConT "GHC.Base:Int"))) []]
But this doesn't:
*Main> runQ [d| instance Test (a,b) |] >>= putStrLn . show
ghc-6.2: panic! (the `impossible' happened, GHC version 6.2):
Failed binder lookup: a {- tv a20x -}
Please report it as a compiler bug to glasgow-haskell-bugs at haskell.org,
or http://sourceforge.net/projects/ghc/.
Am I doing something wrong, or is this a bug?
Thanks!
Jeremy Shaw.
More information about the Glasgow-haskell-users
mailing list