GADT problems
Simon Peyton-Jones
simonpj at microsoft.com
Mon Sep 15 08:48:19 EDT 2008
| > | (case undefined of Foo GadtValue -> ()) :: () -- is rigid
...
|
| But the first compiles fine, so it seems that the scrutinee doesn't have
| to always be rigid?
Not for me! Either with 6.8.3 or HEAD. What compiler are you using?
Simon
$ ghc-6.8.3 -c Neil.hs
Neil.hs:17:12:
GADT pattern match in non-rigid context for `GadtValue'
Solution: add a type signature
In the pattern: GadtValue
In the pattern: Foo GadtValue
In a case alternative: Foo GadtValue -> ()
bash-3.2$ ~/builds-04/validate-HEAD/ghc/stage1-inplace/ghc -c Neil.hs
Neil.hs:17:12:
GADT pattern match in non-rigid context for `GadtValue'
Solution: add a type signature
In the pattern: GadtValue
In the pattern: Foo GadtValue
In a case alternative: Foo GadtValue -> ()
bash-3.2$
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
module Test where
data E x = E x
data Foo a where
Foo :: Gadt a -> Foo a
data Gadt a where
GadtValue :: a -> Gadt (E a)
g :: Int -> ()
g x = case undefined of
Foo GadtValue -> ()
More information about the Glasgow-haskell-users
mailing list