[GHC] #16139: GHC confused about type synonym kind with QuantifiedConstraints
GHC
ghc-devs at haskell.org
Mon Jan 7 00:56:26 UTC 2019
#16139: GHC confused about type synonym kind with QuantifiedConstraints
-------------------------------------+-------------------------------------
Reporter: Ashley | Owner: (none)
Yakeley |
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Keywords: | 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:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE KindSignatures, RankNTypes, ConstraintKinds,
QuantifiedConstraints #-}
module Bug where
import Data.Constraint
type E (c :: * -> Constraint) = forall (a :: *). Eq a => c a
}}}
{{{
Bug.hs:5:58: error:
• Expected a type, but ‘c a’ has kind ‘Constraint’
• In the type ‘forall (a :: *). Eq a => c a’
In the type declaration for ‘E’
|
5 | type E (c :: * -> Constraint) = forall (a :: *). Eq a => c a
| ^^^
}}}
Note that GHC accepts the program when the `Eq a` constraint is removed.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16139>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list