Fundep/Existential Types in 5.03

Ashley Yakeley ashley@semantic.org
Fri, 5 Apr 2002 16:59:45 -0800


Consider this:

  module Test3 where

  class C a b | a -> b where
     	m :: a -> b

  data D a = forall b. (C a b) => MkD a

  f :: (C a b) => D a -> b
  f (MkD a) = m a

This compiles fine under GHC 5.02.2. But under 5.03, it gives an error:

Model/Test3.hs:9:
    Inferred type is less polymorphic than expected
        Quantified type variable `b' escapes
    When checking an existential match that binds
    and whose type is D a -> b1
    In the definition of `f': f (MkD a) = m a

I consider that the 5.02.2 behaviour is preferable, and that this is a 
perfectly good program. 'b' does not escape because it is fundep on 'a', 
which is specified in the type-signature. There can be only one.

What was changed in 5.03 and why?

-- 
Ashley Yakeley, Seattle WA