ghc-7.10.0 type inference regression when faking injective type families

adam vogt vogt.adam at gmail.com
Tue Jan 20 05:29:34 UTC 2015


Hello List,

With ghc - 7.8 and 7.6 the following program is accepted:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

class (UnF (F a) ~ a, Show a) => C a where
    type F a
    f :: F a -> a

type family UnF a

g :: forall a. C a => a -> String
g _ = show a
  where a = f (undefined :: F a) -- :: a


ghc-7.10.0.20141222 does not accept the program unless I uncomment the
type signature (a :: a).


I believe this is the main difference that prevents HList from
compiling with 7.10, but I could have made a mistake in coming up with
this minimal example.

Regards,
Adam


More information about the Glasgow-haskell-users mailing list