
Hi After installing ghc 6.10-rc, I have a program that no longer compiles. I get the dreaded "GADT pattern match...." error, instead :) Here is a boiled-down example: {-# OPTIONS_GHC -XGADTs -XEmptyDataDecls #-} module T where data S data M data Wit t where S :: Wit S M :: Wit M data Impl t a where I1 :: Maybe a -> Impl S a I2 :: [a] -> Impl M a type W_ t a = Wit t -> Impl t a newtype W t a = Wrap (W_ t a) bind :: W t a -> (a -> W t b) -> W_ t b bind (Wrap w) f = \wit -> case wit of S -> case w S of I1 m -> I1 $ do a <- m case f a of Wrap w' -> case w' S of I1 m' -> m' M -> case w M of I2 m -> I2 $ do a <- m case f a of Wrap w' -> case w' M of I2 m' -> m' While in ghc 6.8.3 this compiles fine, with ghc 6.10 i get: $ ghc --make T.hs [1 of 1] Compiling T ( T.hs, T.o ) T.hs:26:57: GADT pattern match with non-rigid result type `Maybe a' Solution: add a type signature In a case alternative: I1 m' -> m' In the expression: case w' S of { I1 m' -> m' } In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' } I've tried adding some signatures (together with - XScopedTypeVariables), but with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :) Thanks! Daniel

dgorin:
I've tried adding some signatures (together with - XScopedTypeVariables), but with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :)
If you work out how to make it compile, can you document the soln. here, http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching Cheers, Don

On Oct 14, 2008, at 7:48 PM, Don Stewart wrote:
dgorin:
I've tried adding some signatures (together with - XScopedTypeVariables), but with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :)
If you work out how to make it compile, can you document the soln. here,
http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching
Cheers, Don
Sure, but I must say I'm still kind of lost, here....

On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín
Hi
After installing ghc 6.10-rc, I have a program that no longer compiles. I get the dreaded "GADT pattern match...." error, instead :)
Here is a boiled-down example:
{-# OPTIONS_GHC -XGADTs -XEmptyDataDecls #-} module T where
data S data M
data Wit t where S :: Wit S M :: Wit M
data Impl t a where I1 :: Maybe a -> Impl S a I2 :: [a] -> Impl M a
type W_ t a = Wit t -> Impl t a
newtype W t a = Wrap (W_ t a)
bind :: W t a -> (a -> W t b) -> W_ t b bind (Wrap w) f = \wit -> case wit of S -> case w S of I1 m -> I1 $ do a <- m case f a of Wrap w' -> case w' S of I1 m' -> m' M -> case w M of I2 m -> I2 $ do a <- m case f a of Wrap w' -> case w' M of I2 m' -> m'
While in ghc 6.8.3 this compiles fine, with ghc 6.10 i get:
$ ghc --make T.hs [1 of 1] Compiling T ( T.hs, T.o )
T.hs:26:57: GADT pattern match with non-rigid result type `Maybe a' Solution: add a type signature In a case alternative: I1 m' -> m' In the expression: case w' S of { I1 m' -> m' } In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' }
I don't have 6.10 handy to try out your program, but in 6.8 and older the type error message you're getting means that the compiler needs more "outside in" help with type checking this. Usually this means adding type more type signatures on the outside. For example, maybe you need to give the type signatures inside the case to make the types inside the pattern matches of the case more rigid. That probably didn't make a lot of sense :( So here is an example, case wit :: {- Try adding a signature here -} of ... Given that your code has such deep pattern nesting I would argue that it is in your best interest to add local functions (in a where clause) along with their explicit type signatures. Start with the inner most case expressions and convert those to local functions and work your way out. I've tried adding some signatures (together with -XScopedTypeVariables), but
with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :)
I think adding local functions is easier than randomly sprinkling in the type signatures. It has a nice side-effect that your new code is often easier to read as well. Good luck! Jason

On Oct 14, 2008, at 10:19 PM, Jason Dagit wrote:
On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín
wrote: Hi After installing ghc 6.10-rc, I have a program that no longer compiles. I get the dreaded "GADT pattern match...." error, instead :)
Here is a boiled-down example: [...]
I don't have 6.10 handy to try out your program, but in 6.8 and older the type error message you're getting means that the compiler needs more "outside in" help with type checking this.
Usually this means adding type more type signatures on the outside. For example, maybe you need to give the type signatures inside the case to make the types inside the pattern matches of the case more rigid. That probably didn't make a lot of sense :( So here is an example,
case wit :: {- Try adding a signature here -} of ...
Given that your code has such deep pattern nesting I would argue that it is in your best interest to add local functions (in a where clause) along with their explicit type signatures. Start with the inner most case expressions and convert those to local functions and work your way out.
I've tried adding some signatures (together with - XScopedTypeVariables), but with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :)
I think adding local functions is easier than randomly sprinkling in the type signatures. It has a nice side-effect that your new code is often easier to read as well.
Good luck! Jason
Thanks for the advice! By using some auxiliary functions I can now compile an alternative version of the program. And although the resulting program is more clear, I'd still like to know if this can be achieved be adding only annotations to the original program. The reason for this is that, for performance reasons, I depend on the case-of-case transformation removing every possible case construct. I already verified this is happening for the original program and I rather keep the code as is than browse through the generated core again :) I must say that I also found this thread to be very helpful: http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153 I'll make sure the wiki points to it. For the record the resulting code is this: {-# LANGUAGE GADTs, EmptyDataDecls #-} module T where data S data M data Wit t where S :: Wit S M :: Wit M data Impl t a where I1 :: Maybe a -> Impl S a I2 :: [a] -> Impl M a type W_ t a = Wit t -> Impl t a newtype W t a = Wrap (W_ t a) unWrap1 :: Impl S a -> Maybe a unWrap1 (I1 m) = m unWrap2 :: Impl M a -> [a] unWrap2 (I2 m) = m bind :: W t a -> (a -> W t b) -> W_ t b bind (Wrap w) f = \wit -> case wit of S -> I1 $ do a <- unWrap1 (w S) case (f a) of Wrap w' -> unWrap1 (w' S) M -> I2 $ do a <- unWrap2 (w M) case (f a) of Wrap w' -> unWrap2 (w' M) Bye Daniel

On Tue, Oct 14, 2008 at 6:37 PM, Daniel Gorín
On Oct 14, 2008, at 10:19 PM, Jason Dagit wrote:
On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín
wrote: Hi
After installing ghc 6.10-rc, I have a program that no longer compiles. I get the dreaded "GADT pattern match...." error, instead :)
Here is a boiled-down example:
[...]
I don't have 6.10 handy to try out your program, but in 6.8 and older the type error message you're getting means that the compiler needs more "outside in" help with type checking this.
Usually this means adding type more type signatures on the outside. For example, maybe you need to give the type signatures inside the case to make the types inside the pattern matches of the case more rigid. That probably didn't make a lot of sense :( So here is an example,
case wit :: {- Try adding a signature here -} of ...
Given that your code has such deep pattern nesting I would argue that it is in your best interest to add local functions (in a where clause) along with their explicit type signatures. Start with the inner most case expressions and convert those to local functions and work your way out.
I've tried adding some signatures (together with -XScopedTypeVariables),
but with no luck. Why is it that this no longer compiles? More importantly, how can I make it compile again? :)
I think adding local functions is easier than randomly sprinkling in the type signatures. It has a nice side-effect that your new code is often easier to read as well.
Good luck! Jason
Thanks for the advice!
By using some auxiliary functions I can now compile an alternative version of the program. And although the resulting program is more clear, I'd still like to know if this can be achieved be adding only annotations to the original program. The reason for this is that, for performance reasons, I depend on the case-of-case transformation removing every possible case construct. I already verified this is happening for the original program and I rather keep the code as is than browse through the generated core again :)
It's unfortunate that you have such a situation with the optimizer. How often do you check that the optimizer is still smart enough? It seems like the sort of thing that could easily break between compiler releases. If you are going to depend on, I wonder if you could write a test to ensure that it is happening every time.
I must say that I also found this thread to be very helpful:
http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153
That is a good thread and it helped me a lot in the past too. One of the most important bits is when Simon says this: GHC now enforces the rule that in a GADT pattern match - the type of the scrutinee must be rigid - the result type must be rigid - the type of any variable free in the case branch must be rigid I would hypothesize that most people who encounter the message you're getting fall into the last case, but I may be biased by my own experiences.
http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153
I'll make sure the wiki points to it.
Oh, good idea! Thanks!
For the record the resulting code is this:
{-# LANGUAGE GADTs, EmptyDataDecls #-} module T where
data S data M
data Wit t where S :: Wit S M :: Wit M
data Impl t a where I1 :: Maybe a -> Impl S a I2 :: [a] -> Impl M a
type W_ t a = Wit t -> Impl t a
newtype W t a = Wrap (W_ t a)
unWrap1 :: Impl S a -> Maybe a unWrap1 (I1 m) = m
unWrap2 :: Impl M a -> [a] unWrap2 (I2 m) = m
bind :: W t a -> (a -> W t b) -> W_ t b bind (Wrap w) f = \wit -> case wit of S -> I1 $ do a <- unWrap1 (w S) case (f a) of Wrap w' -> unWrap1 (w' S) M -> I2 $ do a <- unWrap2 (w M) case (f a) of Wrap w' -> unWrap2 (w' M)
My (untested) hunch is that, Wrap w', needs a type signature in your original version. I think this because of the 3rd case I mentioned above. It would seem that your unWrap1 and unWrap2 fix the witness type, either S or M. Without playing with it (and again I don't have 6.10 handy), I'm not sure which side of the arrow needs the type signature. It could be that you need something like: Wrap (w' :: A type signature fixing M or S) Or, you need it on the other side: Wrap w' -> (w' :: some type sig) M Either way, I think think the type t needs to be mentioned somewhere. Good luck and let me know what you figure out, I'm quite curious now. Jason

| After installing ghc 6.10-rc, I have a program that | no longer compiles. I get the dreaded "GADT pattern match...." | error, instead :) I'm sorry it's dreaded! Jason is right that the key point is this: GHC now enforces the rule that in a GADT pattern match - the type of the scrutinee must be rigid - the result type must be rigid - the type of any variable free in the case branch must be rigid In your case the error message was: GADT.hs:26:56: GADT pattern match with non-rigid result type `Maybe a' Solution: add a type signature In a case alternative: I1 m' -> m' In the expression: case w' S of { I1 m' -> m' } In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' } So it's the result type of the entire case match that isn't rigid. Where does that result type come from... ah .. from a do-expression, which itself is the argument of $, which is also applied to I1. That's too hard for GHC to figure out. You need to specify the result type yourself. I've done so in the program below. I've added -XScopedTypeVariables so that I can give the signature. The relevant signatures themselves are marked --- NB ---. I've wrapped them around the entire do-expression, but it'd also be fine to have put them further "in" around the case expression itself. In this program it's not an ideal place to put a type signature because it looks a bit lost at the bottom. I hope this helps. I'm still trying to find a really good way to explain the reasoning here. Do pls augment the wiki page with what you have learned! Simon {-# OPTIONS_GHC -XGADTs -XEmptyDataDecls -XScopedTypeVariables #-} module T where data S data M data Wit t where S :: Wit S M :: Wit M data Impl t a where I1 :: Maybe a -> Impl S a I2 :: [a] -> Impl M a type W_ t a = Wit t -> Impl t a newtype W t a = Wrap (W_ t a) bind :: forall a b t. W t a -> (a -> W t b) -> W_ t b ------- the forall brings a,b,t into scope inside bind bind (Wrap w) f = \wit -> case wit of S -> case w S of I1 m -> I1 (do a <- m case f a of Wrap w' -> case w' S of I1 m' -> m' :: Maybe b) --- NB -------- M -> case w M of I2 m -> I2 (do a <- m case f a of Wrap w' -> case w' M of I2 m' -> m' :: [b]) --- NB --------

Hi, Simon Thanks a lot for your mail. It turns out I could have resolved this by myself (with the help of this thread http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153 , to be honest). What I was missing was this key part:
bind :: forall a b t. W t a -> (a -> W t b) -> W_ t b ------- the forall brings a,b,t into scope inside bind
So, while I had turned on the ScopedTypeVariables extension, none of the type variables in question was actually in scope. How embarrassing! I can't blame anyone but me for this but, anyway, I feel that it may have helped me if the introduction of Section 8.7.6 of the user manual were a little more explicit about this. Although the example reads "f :: forall a. [a] -> [a]", and the text below says "The type signature for f brings the type variable into scope", the role of the "forall" is not mentioned until Section 8.7.6.2 (and since I already knew what the extension was about, and was only looking for the proper extension name, I didn't make it that far :)) Also, since you are always willing to get examples of confusing error messages, I wanted to bring this one into attention:
In your case the error message was:
GADT.hs:26:56: GADT pattern match with non-rigid result type `Maybe a' Solution: add a type signature In a case alternative: I1 m' -> m' In the expression: case w' S of { I1 m' -> m' } In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' }
This is when ScopedTypeVariables is off. Now, what I found very confusing at first is that I thought the "a" in 'Maybe a' was referring to the "a" in 'W t a -> (a -> W t b) -> W_ t b', and I couldn't see how that could be happening. Once ScopedTypeVariables is on, one gets 'GADT pattern match with non-rigid result type `Maybe a1'" and everything makes more sense :) And maybe the "add a type signature" can be more explicit? Like "add a type signature that makes the type of the result known at the matching point". Just a suggestion...
I hope this helps. I'm still trying to find a really good way to explain the reasoning here. Do pls augment the wiki page with what you have learned!
I've put some of this in the "Upgrading packages" wiki, and added a link to the previous thread which I found to be very clear. Thanks again! Daniel

| > In your case the error message was: | > | > GADT.hs:26:56: | > GADT pattern match with non-rigid result type `Maybe a' | > Solution: add a type signature | > In a case alternative: I1 m' -> m' | > In the expression: case w' S of { I1 m' -> m' } | > In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' } | > | ... | And maybe the "add a type signature" can be more explicit? Like "add a | type signature that makes the type of the result known at the matching | point". Just a suggestion... Good suggestion. I've done that. Simon
participants (4)
-
Daniel Gorín
-
Don Stewart
-
Jason Dagit
-
Simon Peyton-Jones