GADT problems

Mitchell, Neil neil.mitchell.2 at credit-suisse.com
Fri Sep 12 08:50:32 EDT 2008


Hi

The following code works in GHC 6.8.3, works in GHC 6.9.20071111, but
doesn't work in GHC HEAD.

{-# LANGUAGE GADTs, ScopedTypeVariables #-}

module Test where

data E x = E x

data Foo where
  Foo :: Gadt a -> Foo

data Gadt a where
  GadtValue :: Gadt (E a)

f (Foo GadtValue) = True
f _ = False

Under GHC HEAD I get the error: 

GADT pattern match with non-rigid result type `t'
  Solution: add a type signature
In the definition of `f': f (Foo GadtValue) = True

Adding a type signature to f fixes this problem:

f :: Foo -> Bool

But I haven't found anywhere other than the top level f to add a type
signature. When the match is in a list comprehension, it becomes much
harder. While playing further I discovered this example:

foos = undefined
g = [() | Foo GadtValue <- foos]

This code doesn't compile under GHC HEAD, but does under 6.8.3. However,
adding the type signature:

g :: [()]

Makes the code compile. This is surprising, as [()] isn't a GADT type,
so shouldn't need stating explicitly.

Any help on what these errors mean, or how they can be fixed with local
type annotations?

Thanks

Neil

==============================================================================
Please access the attached hyperlink for an important electronic communications disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==============================================================================



More information about the Glasgow-haskell-users mailing list