[GHC] #9196: Higher-rank constraint treated as type instead
GHC
ghc-devs at haskell.org
Wed Jun 11 20:50:07 UTC 2014
#9196: Higher-rank constraint treated as type instead
------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
When I say
{{{
{-# LANGUAGE RankNTypes #-}
module Bug where
class P z
foo :: (forall b. P (a, b)) => a -> a
foo x = x
}}}
I get
{{{
Bug.hs:7:9:
Couldn't match expected type ‘a -> a’ with actual type ‘P (a, b0)’
Relevant bindings include
x :: forall b. P (a, b) (bound at Bug.hs:7:5)
foo :: (forall b. P (a, b)) -> a -> a (bound at Bug.hs:7:1)
In the expression: x
In an equation for ‘foo’: foo x = x
}}}
I expected my code to be rejected, but not with that error message. It
seems that GHC thinks `forall b. P (a, b))` has kind `*`, not kind
`Constraint`.
Encountered while experimenting with #9195.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9196>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list