[GHC] #8346: Rank 1 type signature still requires RankNTypes
GHC
ghc-devs at haskell.org
Mon Sep 23 16:49:24 CEST 2013
#8346: Rank 1 type signature still requires RankNTypes
----------------------------------------------+----------------------------
Reporter: tinctorius | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects valid program | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets: #2605
----------------------------------------------+----------------------------
Comment (by tinctorius):
Now, about a fix for this. It can be done quickly, and it can be done
elegantly.
* The quick fix: when you see `A -> (forall B. C)`, think `forall B. (A ->
C)`.
This specific bug should vanish. However, the problem is bigger:
{{{
{-# LANGUAGE ExplicitForAll #-}
newtype Wrap a r = Wrap (a -> r)
tuple :: forall a. Wrap a (forall b. b -> (a, b))
tuple = Wrap $ \x y -> (x, y)
}}}
* The elegant fix: when you see `C T1 T2 .. (forall X. TK .. TN)`, and `C`
is covariant in its `K`-th parameter, think `forall X. C T1 T2 .. TK ..
TN`.
This is of course a lot harder. Perhaps the new roles feature can be
leveraged to carry this information around.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8346#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list