gadt changes in ghc 6.10
Daniel Gorín
dgorin at dc.uba.ar
Tue Oct 14 10:27:12 EDT 2008
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
More information about the Glasgow-haskell-users
mailing list