[GHC] #9195: ImpredicativeTypes and ConstraintKinds don't interact as expected
GHC
ghc-devs at haskell.org
Wed Jun 11 19:43:48 UTC 2014
#9195: ImpredicativeTypes and ConstraintKinds don't interact as expected
----------------------------+----------------------------------------------
Reporter: | Owner:
MikeIzbicki | Status: new
Type: bug | Milestone:
Priority: normal | Version: 7.8.2
Component: Compiler | Operating System: Unknown/Multiple
Keywords: | Type of failure: GHC rejects valid program
Architecture: | Test Case:
Unknown/Multiple | Blocking:
Difficulty: Unknown |
Blocked By: |
Related Tickets: |
----------------------------+----------------------------------------------
Given this code:
{{{
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ImpredicativeTypes,
ConstraintKinds #-}
class P a b
instance P a b
type Test a = forall b. P a b
}}}
I would expect to be able to actually use the Test Constraint in a
function, like so:
{{{
foo :: Test a => a -> a
foo = id
}}}
But GHC complains that:
{{{
Illegal polymorphic or qualified type: Test a
In the type signature for ‘foo’: foo :: Test a => a -> a
}}}
I get the exact same error message if I replace ImpredicativeTypes with
RankNTypes. If this is intended behavior under ImpredicativeTypes, how
difficult would it be to add another extension that allows this type of
polymorphism?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9195>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list