gadt changes in ghc 6.10

Jason Dagit dagit at codersbase.com
Tue Oct 14 20:19:10 EDT 2008


On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín <dgorin at dc.uba.ar> 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:
>
> {-# 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081014/ec6e2086/attachment.htm


More information about the Glasgow-haskell-users mailing list