interaction of GADTs and data families: a bug?
Sebastian Fischer
sebf at informatik.uni-kiel.de
Thu Apr 15 08:10:42 EDT 2010
Dear GHC experts,
Certain behaviour when using
{-# LANGUAGE GADTs, TypeFamilies #-}
surprises me. The following is accepted by GHC 6.12.1:
data GADT a where
BoolGADT :: GADT Bool
foo :: GADT a -> a -> Int
foo BoolGADT True = 42
But the following is not:
data family DataFam a
data instance DataFam Bool where
BoolDataFam :: DataFam Bool
fffuuuu :: DataFam a -> a -> Int
fffuuuu BoolDataFam True = 42
GHC 6.12.1 throws the following error (GHC 6.10.4 panics):
Couldn't match expected type `a' against inferred type `Bool'
`a' is a rigid type variable bound by
the type signature for `fffuuuu' at gadtDataFam.hs:13:19
In the pattern: BoolDataFam
In the definition of `fffuuuu': fffuuuu BoolDataFam True = 42
I expect that `fffuuuu` should be accepted just like `foo`. Do I
expect too much?
Cheers,
Sebastian
--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)
More information about the Glasgow-haskell-users
mailing list