Hi Sebastian,

Is this perhaps another instance of #3851? http://hackage.haskell.org/trac/ghc/ticket/3851


Cheers,
Pedro

On Thu, Apr 15, 2010 at 14:10, Sebastian Fischer <sebf@informatik.uni-kiel.de> wrote:
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.)



_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users