One more code sample which compiled with GHC 7.2.1 and does not with the new RC:

>>>>>
{-# LANGUAGE FlexibleContexts, FlexibleInstances,
FunctionalDependencies, MultiParamTypeClasses, RankNTypes,
UndecidableInstances, TypeFamilies  #-}

newtype MyMonadT m a = MyMonadT (m a)

class MyClass b m | m -> b where
    data StM m :: * -> *
    myFunc :: b a -> m a

instance MyClass b m => MyClass b (MyMonadT m) where
    newtype StM (MyMonadT m) b = StMMine [b]
    myFunc = undefined
<<<<<

In the instance, in GHC 7.2 the 'b' on the LHS of the newtype
introduces a fresh type binding. In the RC I get a kind error, because
the compiler seems to be trying to make all of the 'b' labeled types
the same type.

Since the 'b' isn't an indexing parameter, it doesn't make since for
it to not introduce a new binding.

This seems like an odd UI corner case, so I'm not sure what the
correct answer is. But it is a regression, so I thought I would ask
and make sure it was on purpose.

Antoine

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

Reply via email to