GHC 8 superclass chain constraint regression

Good day! It seems that GHC 8 regresses with regard to GHC 7.10, when it tries to satisfy the constraints, implied by instance context. The following does not build on GHC 8.0.1 RC2, but does on 7.10.3:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} --{-# LANGUAGE UndecidableSuperClasses #-} -- this doesn't matter {-# LANGUAGE UnicodeSyntax #-}
module Foo where
class Super a class Super a ⇒ Left a class Super a ⇒ Right a instance (Left a) ⇒ Right a
the error being:
• Could not deduce (Super a) arising from the superclasses of an instance declaration from the context: Left a bound by the instance declaration at repro.hs:9:10-27 Possible fix: add (Super a) to the context of the instance declaration • In the instance declaration for ‘Right a’
A look through the GHC 8 status page, produced no bugs that seemed related to my uneducated guess. It also /roughly/ seems that https://phabricator.haskell.org/D1594 could possibly be related. Thanks to lyxia on #haskell for pointing that this actually works on 7.10.. -- с уважениeм / respectfully, Косырев Сергей

Ben Gamari
Kosyrev Serge <_deepfire@feelingofgreen.ru> writes:
Thanks for reporting this. Have you opened a Trac ticket for this issue? If not could you do so?
Just done so: https://ghc.haskell.org/trac/ghc/ticket/11762#ticket -- с уважениeм, Косырев Сергей
participants (2)
-
Ben Gamari
-
Kosyrev Serge