[GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family.
GHC
ghc-devs at haskell.org
Mon Jun 12 23:48:16 UTC 2017
#13814: Unable to resolve instance for polykinded superclass constraint on
associated-type-family.
-------------------------------------+-------------------------------------
Reporter: isovector | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: polykinds,
| type families
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Replying to [comment:3 simonpj]:
> The real problem is that `Back` is too polymorphic. If it had kind `k
-> k` we'd probably be fine.
Ah, you're right. This program //does// typecheck, as expected:
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Test where
class Back t
class Back (FrontBack t) => Front t where
type FrontBack (t :: k) :: k
instance Back Bool
instance Front Int where
type FrontBack Int = Bool
}}}
> Maybe we should complain about the unresolved kind variables in the
class decl?
That sounds like a good approach, yes. The error message might be
confusing since it mentions an inferred kind variable, but I'd argue that
that error would be far clearer than the current one, which is rather
enigmatic.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13814#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list