advice on GADT type witnesses needed

Hi all, Jason and I have been working on getting GADT type witnesses into darcs, and have run into a puzzling error. For the life of me, I can't see how this is an actual error, to the point that I'm wondering if it's actually a bug in ghc. You can check out the code and reproduce this with darcs get http://physics.oregonstate.edu/~roundyd/darcs-gadts cd darcs-gadts autoconf ./configure --with-type-witnesses make darcs At this point ghc will compile for a bit. It shouldn't get past Viewing, since we haven't converted over much of the code yet, but it fails inexplicably on Show. The error message we get is: ghc -DPACKAGE_NAME=\"darcs\" -DPACKAGE_TARNAME=\"darcs\" -DPACKAGE_VERSION=\"1.0.9\" -DPACKAGE_STRING=\"darcs\ 1.0.9\" -DPACKAGE_BUGREPORT=\"bugs@darcs.net\" -DSTDC_HEADERS=1 -DHAVE_SYS_TYPES_H=1 -DHAVE_SYS_STAT_H=1 -DHAVE_STDLIB_H=1 -DHAVE_STRING_H=1 -DHAVE_MEMORY_H=1 -DHAVE_STRINGS_H=1 -DHAVE_INTTYPES_H=1 -DHAVE_STDINT_H=1 -DHAVE_UNISTD_H=1 -DGADT_WITNESSES=1 -DHAVE_TERMIO_H=1 -cpp -package regex-compat -package QuickCheck -package mtl -package parsec -package html -package unix -O -funbox-strict-fields -Wall -Werror -I. -I./src -i./src -DHAVE_CURSES -DHAVE_CURL -c src/Darcs/Patch/Show.lhs src/Darcs/Patch/Show.lhs:50:0: Quantified type variable `y' is unified with another quantified type variable `x' When trying to generalise the type inferred for `showPatch' Signature type: forall x y. Patch x y -> Doc Type to generalise: Patch y y -> Doc In the type signature for `showPatch' When generalising the type(s) for showPatch, showComP, showSplit, showConflicted, showNamed make: *** [src/Darcs/Patch/Show.o] Error 1 The relevant code is showPatch :: Patch C(x,y) -> Doc showPatch (FP f AddFile) = showAddFile f ... showPatch (Conflicted p ps) = showConflicted p ps and the trouble comes about because of (in Core.lhs) data Patch C(x,y) where NamedP :: !PatchInfo -> ![PatchInfo] -> !(Patch C(x,y)) -> Patch C(x,y) ... Conflicted :: Patch C(a,b) -> FL Patch C(b,c) -> Patch C(c,c) Still, this makes no sense to me. If any type gurus could help clarify, that would be great. Thanks! -- David Roundy Department of Physics Oregon State University

On 6/14/07, David Roundy
src/Darcs/Patch/Show.lhs:50:0: Quantified type variable `y' is unified with another quantified type variable `x' When trying to generalise the type inferred for `showPatch' Signature type: forall x y. Patch x y -> Doc Type to generalise: Patch y y -> Doc In the type signature for `showPatch' When generalising the type(s) for showPatch, showComP, showSplit, showConflicted, showNamed make: *** [src/Darcs/Patch/Show.o] Error 1
The relevant code is
showPatch :: Patch C(x,y) -> Doc showPatch (FP f AddFile) = showAddFile f ... showPatch (Conflicted p ps) = showConflicted p ps
and the trouble comes about because of (in Core.lhs)
data Patch C(x,y) where NamedP :: !PatchInfo -> ![PatchInfo] -> !(Patch C(x,y)) -> Patch C(x,y) ... Conflicted :: Patch C(a,b) -> FL Patch C(b,c) -> Patch C(c,c)
I would like to add that I've tried (and failed) to construct a minimal example that demonstrates the type check failure by simulating the relevant code above. This makes me wonder if the problem is not in the obvious place(s). For anyone reading along and not understanding our use of C(x,y), that's a c pre-processor macro we've defined in gadts.h. The C stands for context. In the case of the patches above, we're annotating the type with the context for the patch; x for the context required by the patch and y for the context after applying the patch. The reason we use a macro is so that we can incrementally make this modification to the code and easily disable it at compile time since it doesn't work everywhere yet. Thanks, Jason

On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote:
On 6/14/07, David Roundy
wrote: src/Darcs/Patch/Show.lhs:50:0: Quantified type variable `y' is unified with another quantified type variable `x' When trying to generalise the type inferred for `showPatch' Signature type: forall x y. Patch x y -> Doc Type to generalise: Patch y y -> Doc In the type signature for `showPatch' When generalising the type(s) for showPatch, showComP, showSplit, showConflicted, showNamed make: *** [src/Darcs/Patch/Show.o] Error 1
The relevant code is
showPatch :: Patch C(x,y) -> Doc showPatch (FP f AddFile) = showAddFile f ... showPatch (Conflicted p ps) = showConflicted p ps
and the trouble comes about because of (in Core.lhs)
data Patch C(x,y) where NamedP :: !PatchInfo -> ![PatchInfo] -> !(Patch C(x,y)) -> Patch C(x,y) ... Conflicted :: Patch C(a,b) -> FL Patch C(b,c) -> Patch C(c,c)
I would like to add that I've tried (and failed) to construct a minimal example that demonstrates the type check failure by simulating the relevant code above. This makes me wonder if the problem is not in the obvious place(s).
Here's one: module Q where data Foo x y where Foo :: Foo a b -> Foo b c -> Foo c c ------ module W where import Q wibble :: Foo a b -> String wibble (Foo x y) = foo x y foo :: Foo a b -> Foo b c -> String foo x y = wibble x ++ wibble y 6.6 and 6.6.1 say: $ ghc -c Q.hs -fglasgow-exts $ ghc -c W.hs W.hs:7:0: Quantified type variable `b' is unified with another quantified type variable `a' When trying to generalise the type inferred for `wibble' Signature type: forall a b. Foo a b -> String Type to generalise: Foo b b -> String In the type signature for `wibble' When generalising the type(s) for wibble, foo $ ghc -c W.hs -fglasgow-exts $ i.e. you need to give the -fglasgow-exts flag when compiling W.hs. An {-# OPTIONS_GHC -fglasgow-exts #-} pragma in Show.lhs fixes the real thing too. The HEAD is the same, except the error is: W.hs:7:8: GADT pattern match in non-rigid context for `Foo' Tell GHC HQ if you'd like this to unify the context In the pattern: Foo x y In the definition of `wibble': wibble (Foo x y) = foo x y I suspect your problem in making a testcase was moving the GADT declaration into the same file as the function, and thus needing to compile it with -fglasgow-exts anyway. I'm not sure if GHC's behaviour is what is expected though; Simon? Thanks Ian

On 6/15/07, Ian Lynagh
On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote:
On 6/14/07, David Roundy
wrote: src/Darcs/Patch/Show.lhs:50:0: Quantified type variable `y' is unified with another quantified type variable `x' When trying to generalise the type inferred for `showPatch' Signature type: forall x y. Patch x y -> Doc Type to generalise: Patch y y -> Doc In the type signature for `showPatch' When generalising the type(s) for showPatch, showComP, showSplit, showConflicted, showNamed make: *** [src/Darcs/Patch/Show.o] Error 1
The relevant code is
showPatch :: Patch C(x,y) -> Doc showPatch (FP f AddFile) = showAddFile f ... showPatch (Conflicted p ps) = showConflicted p ps
and the trouble comes about because of (in Core.lhs)
data Patch C(x,y) where NamedP :: !PatchInfo -> ![PatchInfo] -> !(Patch C(x,y)) -> Patch C(x,y) ... Conflicted :: Patch C(a,b) -> FL Patch C(b,c) -> Patch C(c,c)
I would like to add that I've tried (and failed) to construct a minimal example that demonstrates the type check failure by simulating the relevant code above. This makes me wonder if the problem is not in the obvious place(s).
Here's one:
module Q where
data Foo x y where Foo :: Foo a b -> Foo b c -> Foo c c
------
module W where
import Q
wibble :: Foo a b -> String wibble (Foo x y) = foo x y
foo :: Foo a b -> Foo b c -> String foo x y = wibble x ++ wibble y
6.6 and 6.6.1 say:
$ ghc -c Q.hs -fglasgow-exts $ ghc -c W.hs
W.hs:7:0: Quantified type variable `b' is unified with another quantified type variable `a' When trying to generalise the type inferred for `wibble' Signature type: forall a b. Foo a b -> String Type to generalise: Foo b b -> String In the type signature for `wibble' When generalising the type(s) for wibble, foo $ ghc -c W.hs -fglasgow-exts $
i.e. you need to give the -fglasgow-exts flag when compiling W.hs. An {-# OPTIONS_GHC -fglasgow-exts #-} pragma in Show.lhs fixes the real thing too.
The HEAD is the same, except the error is:
W.hs:7:8: GADT pattern match in non-rigid context for `Foo' Tell GHC HQ if you'd like this to unify the context In the pattern: Foo x y In the definition of `wibble': wibble (Foo x y) = foo x y
I suspect your problem in making a testcase was moving the GADT declaration into the same file as the function, and thus needing to compile it with -fglasgow-exts anyway.
Yes, you're basically right about what I tried. I did suspect putting things into different modules was important, so I did that, but I was using ghci with -fglasgow-exts to load all the files. So that explains why I failed to trigger the problem. Sounds like this should be easy to fix on our end. thanks! Jason

On Fri, Jun 15, 2007 at 01:32:32PM -0700, Jason Dagit wrote:
I suspect your problem in making a testcase was moving the GADT declaration into the same file as the function, and thus needing to compile it with -fglasgow-exts anyway.
Yes, you're basically right about what I tried. I did suspect putting things into different modules was important, so I did that, but I was using ghci with -fglasgow-exts to load all the files. So that explains why I failed to trigger the problem. Sounds like this should be easy to fix on our end.
Indeed, I've already fixed this in my latest. Thanks Ian! :) -- David Roundy Department of Physics Oregon State University

I've improved the error message for this case. It was indeed bizarrely confusing.
Simon
| -----Original Message-----
| From: Ian Lynagh [mailto:igloo@earth.li]
| Sent: 15 June 2007 15:53
| To: Jason Dagit
| Cc: haskell-cafe@haskell.org; darcs-devel@darcs.net; Simon Peyton-Jones
| Subject: Re: [darcs-devel] advice on GADT type witnesses needed
|
| On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote:
| > On 6/14/07, David Roundy

On 6/20/07, Simon Peyton-Jones
I've improved the error message for this case. It was indeed bizarrely confusing.
While we're on the subject of bizarrely confusing error messages :) I had some code like this: ... where MergeResult (_:>p2') (_:>p1' ) (_cp1 :\./:_cp2) = fancy_merge $ p1 :\./: p2 and GHC gave me this error message: My brain just exploded. I can't handle pattern bindings for existentially-quantified constructors. Which is amusing, but it doesn't hint (enough) at the workaround, which appears to be using 'case' instead of let/where. Any chance this could be improved to suggest the user tries switching to a case? I'm now using this code: case fancy_merge $ p1 :\./: p2 of MergeResult (_:>p2') (_:>p1' ) (_cp1 :\./:_cp2) Which seems to make it further with the type checking (my code is wrong, but at least now I get a normal error from ghc). Thanks, Jason
Simon
| -----Original Message----- | From: Ian Lynagh [mailto:igloo@earth.li] | Sent: 15 June 2007 15:53 | To: Jason Dagit | Cc: haskell-cafe@haskell.org; darcs-devel@darcs.net; Simon Peyton-Jones | Subject: Re: [darcs-devel] advice on GADT type witnesses needed | | On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote: | > On 6/14/07, David Roundy
wrote: | > | > >src/Darcs/Patch/Show.lhs:50:0: | > > Quantified type variable `y' is unified with another quantified type | > > variable `x' | > > When trying to generalise the type inferred for `showPatch' | > > Signature type: forall x y. Patch x y -> Doc | > > Type to generalise: Patch y y -> Doc | > > In the type signature for `showPatch' | > > When generalising the type(s) for showPatch, showComP, showSplit, | > > showConflicted, showNamed | > >make: *** [src/Darcs/Patch/Show.o] Error 1 | > > | > >The relevant code is | > > | > >showPatch :: Patch C(x,y) -> Doc | > >showPatch (FP f AddFile) = showAddFile f | > >... | > >showPatch (Conflicted p ps) = showConflicted p ps | > > | > >and the trouble comes about because of (in Core.lhs) | > > | > >data Patch C(x,y) where | > > NamedP :: !PatchInfo -> ![PatchInfo] -> !(Patch C(x,y)) -> Patch C(x,y) | > >... | > > Conflicted :: Patch C(a,b) -> FL Patch C(b,c) -> Patch C(c,c) | > > | > | > I would like to add that I've tried (and failed) to construct a | > minimal example that demonstrates the type check failure by simulating | > the relevant code above. This makes me wonder if the problem is not | > in the obvious place(s). | | Here's one: | | module Q where | | data Foo x y where | Foo :: Foo a b -> Foo b c -> Foo c c | | ------ | | module W where | | import Q | | wibble :: Foo a b -> String | wibble (Foo x y) = foo x y | | foo :: Foo a b -> Foo b c -> String | foo x y = wibble x ++ wibble y | | 6.6 and 6.6.1 say: | | $ ghc -c Q.hs -fglasgow-exts | $ ghc -c W.hs | | W.hs:7:0: | Quantified type variable `b' is unified with another quantified type variable `a' | When trying to generalise the type inferred for `wibble' | Signature type: forall a b. Foo a b -> String | Type to generalise: Foo b b -> String | In the type signature for `wibble' | When generalising the type(s) for wibble, foo | $ ghc -c W.hs -fglasgow-exts | $ | | i.e. you need to give the -fglasgow-exts flag when compiling W.hs. | An {-# OPTIONS_GHC -fglasgow-exts #-} pragma in Show.lhs fixes the real | thing too. | | The HEAD is the same, except the error is: | | W.hs:7:8: | GADT pattern match in non-rigid context for `Foo' | Tell GHC HQ if you'd like this to unify the context | In the pattern: Foo x y | In the definition of `wibble': wibble (Foo x y) = foo x y | | I suspect your problem in making a testcase was moving the GADT | declaration into the same file as the function, and thus needing to | compile it with -fglasgow-exts anyway. | | I'm not sure if GHC's behaviour is what is expected though; Simon? | | | Thanks | Ian

Good idea. I'll improve the message by adding the suggestion to use a case expression instead.
Simon
| -----Original Message-----
| From: dagitj@gmail.com [mailto:dagitj@gmail.com] On Behalf Of Jason Dagit
| Sent: 21 June 2007 00:46
| To: Simon Peyton-Jones
| Cc: Ian Lynagh; haskell-cafe@haskell.org; darcs-devel@darcs.net
| Subject: Re: [darcs-devel] advice on GADT type witnesses needed
|
| On 6/20/07, Simon Peyton-Jones

On Thu, Jun 21, 2007 at 10:51:25AM +0100, Simon Peyton-Jones wrote:
Good idea. I'll improve the message by adding the suggestion to use a case expression instead.
Or do notation. I almost always prefer do notation, even if it means something like: fromJust $ do a' :< b' <- commute (b :< a) a'' :< c' <- commute (c :< a') return a' -- David Roundy http://www.darcs.net
participants (4)
-
David Roundy
-
Ian Lynagh
-
Jason Dagit
-
Simon Peyton-Jones