ghc-7.10.0 type inference regression when faking injective type families

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

After quite a bit of thought, I agree that this is a regression and that the original program should be accepted. Make a bug report! Thanks, Richard

I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009
On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg
After quite a bit of thought, I agree that this is a regression and that the original program should be accepted.
Make a bug report!
Thanks, Richard

And I've closed it as worksforme. I couldn't reproduce the problem
with 7.11.20150103.
On Tue, Jan 20, 2015 at 11:42 AM, adam vogt
I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009
On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg
wrote: After quite a bit of thought, I agree that this is a regression and that the original program should be accepted.
Make a bug report!
Thanks, Richard
Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Wrongly, as it turned out. Sorry! The problem remains.
On Tue, Jan 20, 2015 at 2:37 PM, David Feuer
And I've closed it as worksforme. I couldn't reproduce the problem with 7.11.20150103.
On Tue, Jan 20, 2015 at 11:42 AM, adam vogt
wrote: I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009
On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg
wrote: After quite a bit of thought, I agree that this is a regression and that the original program should be accepted.
Make a bug report!
Thanks, Richard
Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Yes, I fixed it on the train. Most helpful. Busy tomorrow but I should have a fix committed by the end of the week Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Richard Eisenberg | Sent: 20 January 2015 16:24 | To: adam vogt | Cc: Glasgow-Haskell-Users | Subject: Re: ghc-7.10.0 type inference regression when faking injective | type families | | After quite a bit of thought, I agree that this is a regression and that | the original program should be accepted. | | Make a bug report! | | Thanks, | Richard | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (4)
-
adam vogt
-
David Feuer
-
Richard Eisenberg
-
Simon Peyton Jones