
#8913: either bug or confusing error message mixing PolyKinds and TypeFamilies -------------------------------------------+------------------------------- Reporter: ghorn | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.8.1-rc2 Keywords: PolyKinds, TypeFamilies | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- I found this when using GHC.Generics, but it has to do with TypeFamilies so here is a stand-alone example: {{{ {-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} module Test where class GCat f where gcat :: f p -> Int cat :: (GCat (MyRep a), MyGeneric a) => a -> Int cat x = gcat (from x) class MyGeneric a where type MyRep a :: * -> * from :: a -> (MyRep a) p }}} This code gives the error message {{{ src/Dyno/Test.hs:12:9: Could not deduce (GCat (MyRep a)) arising from a use of ‘gcat’ from the context (GCat (MyRep a), MyGeneric a) bound by the type signature for cat :: (GCat (MyRep a), MyGeneric a) => a -> Int at src/Dyno/Test.hs:11:8-48 In the expression: gcat (from x) In an equation for ‘cat’: cat x = gcat (from x) Failed, modules loaded: none. }}} If this is not a bug then error message is pretty confusing because it's saying "Can't deduce (C a) from (C a)", where the message I'm used to is "Can't derive (C a) from (C a0)" or something that indicates the mismatch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8913 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler