[GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family.
GHC
ghc-devs at haskell.org
Sun Jun 11 07:30:38 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
Keywords: polykinds, | Operating System: Unknown/Multiple
type families |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following program doesn't compile:
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Test where
class Back k
class Back (FrontBack k) => Front k where
type FrontBack k :: k'
instance Back Bool
instance Front Int where
type FrontBack Int = Bool
}}}
with the error message:
{{{
• No instance for (Back (FrontBack Int))
arising from the superclasses of an instance declaration
• In the instance declaration for ‘Front Int’
}}}
The example successfully compiles if the kind annotation on FrontBack is
removed.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13814>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list