
#14010: UndecidableSuperClasses - Could not deduce (Category d) -------------------------------------+------------------------------------- Reporter: int-index | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple UndecidableSuperClasses | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this well-typed code: {{{#!hs {-# LANGUAGE NoImplicitPrelude, TypeInType, TypeFamilies, UndecidableSuperClasses, RankNTypes, TypeOperators, FlexibleContexts, TypeSynonymInstances, FlexibleInstances, UndecidableInstances #-} module Monolith where import Data.Kind (Type) import GHC.Exts (Constraint) type family (~>) :: c -> c -> Type type instance (~>) = (->) type instance (~>) = ArrPair type family Fst (p :: (a, b)) :: a where Fst '(x, _) = x type family Snd (p :: (a, b)) :: b where Snd '(_, y) = y data ArrPair a b = ArrPair (Fst a ~> Fst b) (Snd a ~> Snd b) type family Super c :: Constraint where Super Type = () Super (c, d) = (Category c, Category d) class Super cat => Category cat where id :: forall (a :: cat). a ~> a instance Category Type where id = \x -> x instance (Category c, Category d) => Category (c, d) where id = ArrPair id id class Category (c, d) => Functor (f :: c -> d) where --class (Category c, Category d) => Functor (f :: c -> d) where map :: (a ~> b) -> (f a ~> f b) data OnSnd f a b = OnSnd (f '(a, b)) instance Functor (f :: (c, d) -> Type) => Functor (OnSnd f a) where map f (OnSnd x) = OnSnd (map (ArrPair id f) x) }}} The compiler accepts it. But if I change the definition of 'Functor' for the commented one, I get an error: {{{ super.hs:39:10: error: • Could not deduce (Category d) arising from the superclasses of an instance declaration from the context: Functor f bound by the instance declaration at super.hs:39:10-61 Possible fix: add (Category d) to the context of the instance declaration • In the instance declaration for ‘Functor (OnSnd f a)’ | 39 | instance Functor (f :: (c, d) -> Type) => Functor (OnSnd f a) where | }}} I can reproduce this on 8.0.1, 8.2.0.20170704 and HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14010 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler