RE: classes and template haskell (bug?)

In GHC 6.2, Template Haskell has various bugs. I think they are all fixed in the HEAD, so you can either build from source or grab a development snapshot from the GHC site. The HEAD version of TH has a slightly different programming interface too -- see http://research.microsoft.com/~simonpj/tmp/notes2.ps Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Jeremy Shaw | Sent: 31 December 2003 02:19 | To: glasgow-haskell-users@haskell.org | Subject: classes and template haskell (bug?) | | 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@haskell.org, | or http://sourceforge.net/projects/ghc/. | | | Am I doing something wrong, or is this a bug? | | Thanks! | Jeremy Shaw. | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Hello,
I attempted to build cvs head but it died with the following error:
/usr/bin/ghc6 -H16m -O -istage1/utils -istage1/basicTypes -istage1/types -istage1/hsSyn -istage1/prelude -istage1/rename -istage1/typecheck -istage1/deSugar -istage1/coreSyn -istage1/specialise -istage1/simplCore -istage1/stranal -istage1/stgSyn -istage1/simplStg -istage1/codeGen -istage1/absCSyn -istage1/main -istage1/profiling -istage1/parser -istage1/cprAnalysis -istage1/compMan -istage1/ndpFlatten -istage1/cbits -istage1/iface -istage1/nativeGen -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser -package concurrent -package posix -package util -recomp -Rghc-timing -H16M '-#include "hschooks.h"' -fno-warn-incomplete-patterns -fvia-C -Onot -fno-ignore-interface-pragmas -c parser/Parser.hs -o stage1/parser/Parser.o -ohi stage1/parser/Parser.hi
parser/Parser.hs:1878: Variable not in scope: `$>'
parser/Parser.hs:1887: Variable not in scope: `$>'
parser/Parser.hs:1899: Variable not in scope: `$>'
parser/Parser.hs:1908: Variable not in scope: `$>'
parser/Parser.hs:2019: Variable not in scope: `$>'
<snip> <snip> <snip> <snip> <snip>
parser/Parser.hs:5284: Variable not in scope: `$>'
parser/Parser.hs:5301: Variable not in scope: `$>'
<
In GHC 6.2, Template Haskell has various bugs. I think they are all fixed in the HEAD, so you can either build from source or grab a development snapshot from the GHC site.
The HEAD version of TH has a slightly different programming interface too -- see http://research.microsoft.com/~simonpj/tmp/notes2.ps
Simon
| -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Jeremy Shaw | Sent: 31 December 2003 02:19 | To: glasgow-haskell-users@haskell.org | Subject: classes and template haskell (bug?) | | 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@haskell.org, | or http://sourceforge.net/projects/ghc/. | | | Am I doing something wrong, or is this a bug? | | Thanks! | Jeremy Shaw. | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Jeremy Shaw wrote:
I attempted to build cvs head but it died with the following error:
/usr/bin/ghc6 -H16m -O -istage1/utils -istage1/basicTypes -istage1/types -istage1/hsSyn -istage1/prelude -istage1/rename -istage1/typecheck -istage1/deSugar -istage1/coreSyn -istage1/specialise -istage1/simplCore -istage1/stranal -istage1/stgSyn -istage1/simplStg -istage1/codeGen -istage1/absCSyn -istage1/main -istage1/profiling -istage1/parser -istage1/cprAnalysis -istage1/compMan -istage1/ndpFlatten -istage1/cbits -istage1/iface -istage1/nativeGen -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser -package concurrent -package posix -package util -recomp -Rghc-timing -H16M '-#include "hschooks.h"' -fno-warn-incomplete-patterns -fvia-C -Onot -fno-ignore-interface-pragmas -c parser/Parser.hs -o stage1/parser/Parser.o -ohi stage1/parser/Parser.hi
parser/Parser.hs:1878: Variable not in scope: `$>' [...]
You need a rather recent version of Happy from CVS to compile the HEAD. Cheers, S.

Hello, No dice. Using cvs head from 12/31, I get the same behavior, (plus a new bug). Using the same test as before (after updating the import line): *Main> runQ [d| instance Test (a,b) |] >>= putStrLn . show ghc-6.3: panic! (the `impossible' happened, GHC version 6.3): Failed binder lookup: a{tv} {- tv a2jx -} Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org, or http://sourceforge.net/projects/ghc/. Also, a new bug has appeared (then again, it is cvs head) -- If I start ghci, and then do this: Prelude> let n = 1 Prelude> n *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive patterns in record update Prelude> b *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive patterns in record update Prelude> a *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive patterns in record update Prelude> 3 + 4 *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive patterns in record update Or similarily: *Main> runQ [d| instance Test (Int,Int) |] >>= putStrLn . show Loading package haskell98 ... linking ... done. Loading package haskell-src ... linking ... done. [InstanceD [] (AppT (ConT Main.Test) (AppT (AppT (TupleT 2) (ConT GHC.Base.Int)) (ConT GHC.Base.Int))) []] *Main> runQ [d| instance Test (a,b) |] >>= putStrLn . show *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive patterns in record update Jeremy Shaw. At Wed, 31 Dec 2003 08:11:47 -0000, Simon Peyton-Jones wrote:
In GHC 6.2, Template Haskell has various bugs. I think they are all fixed in the HEAD, so you can either build from source or grab a development snapshot from the GHC site.
The HEAD version of TH has a slightly different programming interface too -- see http://research.microsoft.com/~simonpj/tmp/notes2.ps
Simon
| -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Jeremy Shaw | Sent: 31 December 2003 02:19 | To: glasgow-haskell-users@haskell.org | Subject: classes and template haskell (bug?) | | 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@haskell.org, | or http://sourceforge.net/projects/ghc/. | | | Am I doing something wrong, or is this a bug? | | Thanks! | Jeremy Shaw. | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (3)
-
Jeremy Shaw
-
Simon Peyton-Jones
-
Sven Panne