gadt changes in ghc 6.10

Simon Peyton-Jones simonpj at microsoft.com
Wed Oct 15 04:22:01 EDT 2008


| 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 --------




More information about the Glasgow-haskell-users mailing list