module containing GADTs no longer compiles in ghc 6.8.0
Daniel Gorín
dgorin at dc.uba.ar
Thu Sep 27 18:45:58 EDT 2007
Hi Simon,
Thanks for your prompt response. Actually, the problem was with lambda
patterns containing GADT constructors in let bindings and I guess GHC doesn't
like that anymore.
After replacing them with case statements everything compiles fine.... as long
as I don't turn on -O2 optimizations :(
This boiled-down example illustrates my problem:
> {-# OPTIONS_GHC -fglasgow-exts #-}
> module T where
>
> data T a where T :: T a -> T [a]
>
> class C a where
> f :: a -> ()
>
> instance C (T [a]) where
> f (T x@(T _)) = f x
$ ghc --make -c -Wall -O2 T
[1 of 1] Compiling T ( T.hs, t/T.o )
ghc-6.8.0.20070917: panic! (the 'impossible' happened)
(GHC version 6.8.0.20070917 for i386-unknown-linux):
Template variable unbound in rewrite rule
co_X6j{tv} [tv]
[a{tv a5u} [sk], co_a5X{tv} [tv], a{tv a5Y} [sk], co_a60{tv} [tv],
ds_d67{v} [lid]]
[a{tv X5P} [sk], co_X6j{tv} [tv], a{tv X6l} [sk], co_X6o{tv} [tv],
ds_X6w{v} [lid]]
[TYPE a{tv a5Y} [sk],
(main:T.T{v r5Q} [gid]
@ a{tv a5u} [sk]
@ a{tv a5Y} [sk]
@ co_a60{tv} [tv]
ds_d67{v} [lid])
`cast` (base:GHC.Prim.trans{(w) tc 34y}
(main:T.T{tc r1} (base:GHC.Prim.right{(w) tc 34E} co_a5X{tv}
[tv]))
(base:GHC.Prim.trans{(w) tc 34y}
(main:T.T{tc r1}
(base:GHC.Prim.right{(w) tc 34E}
(base:GHC.Prim.sym{(w) tc 34v} co_a5X{tv} [tv])))
(main:T.T{tc r1} co_a60{tv} [tv]))
:: <pred>main:T.T{tc r1} a{tv a5u} [sk]
~
main:T.T{tc r1} [a{tv a5Y} [sk]])]
[TYPE a{tv a5Y} [sk],
wild_Xc{v} [lid]
`cast` (base:GHC.Prim.trans{(w) tc 34y}
(main:T.T{tc r1} (base:GHC.Prim.right{(w) tc 34E} co_a5X{tv}
[tv]))
(base:GHC.Prim.trans{(w) tc 34y}
(main:T.T{tc r1}
(base:GHC.Prim.right{(w) tc 34E}
(base:GHC.Prim.sym{(w) tc 34v} co_a5X{tv} [tv])))
(main:T.T{tc r1} co_a60{tv} [tv]))
:: <pred>main:T.T{tc r1} a{tv a5u} [sk]
~
main:T.T{tc r1} [a{tv a5Y} [sk]])]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Thanks
Daniel
On Wednesday 26 September 2007 13:55:10 Simon Peyton-Jones wrote:
> | PS: On a side note, I found this error message to be kind of funny. It
> | seems to indicate no real error but some sort of error-message-driven
> | poll!
>
> That's exactly what it is, and you are the pollee.
>
> Nevertheless it's probably needlessly obscure. The point is this: you are
> doing case x of { ... }
> where the "..." has GADT patterns. But GHC doesn't know what type 'x' is.
> Usually type inference will suffice, but not for GADTs.
>
> Solution: use a type signature to tell GHC just what type x has. Example:
>
> f x = case x of ...
>
> give f a type signature
>
> f :: forall a. T a -> Int
>
> There ought to be a "contributed documentation" wiki page about GADTs here
> http://haskell.org/haskellwiki/GHC
> but there isn't yet. Would someone like to start one?
>
> sorry brevity, rushing to get to icfp
>
> Simon
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org
> | [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Daniel
> | Gorín
> | Sent: 26 September 2007 17:34
> | To: glasgow-haskell-users at haskell.org
> | Subject: module containing GADTs no longer compiles in ghc 6.8.0
> |
> | Hi
> |
> | I just tried to compile a project of mine that builds fine using ghc
> | 6.6.1 and got many errors like this:
> |
> | src/HyLo/Formula/NNF.hs:247:48:
> | GADT pattern match in non-rigid context for `Opaque'
> | Tell GHC HQ if you'd like this to unify the context
> | In the pattern: Opaque f'
> | In the expression: \ (Opaque f') -> Opaque (Box r f')
> | In the definition of `box':
> | box = \ (Opaque f') -> Opaque (Box r f')
> |
> | I don't know what a "non-rigid context" is, nor if "I like this to unify
> | the context" or not, but I would certainly be happy if I could get this
> | module to compile again! :)
> |
> | For the record, I was using ghc-6.8.0.20070917. Please let me know if you
> | need further information....
> |
> | Thanks
> | Daniel
> |
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list