[GHC] #9420: Impredicative type instantiation without -XImpredicativeTypes
GHC
ghc-devs at haskell.org
Thu Aug 7 20:12:01 UTC 2014
#9420: Impredicative type instantiation without -XImpredicativeTypes
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Consider this module:
{{{
{-# LANGUAGE RankNTypes #-}
module Bug where
rank2 :: ((forall a. a -> a) -> b) -> ()
rank2 _ = ()
foo :: () -> ()
foo x = x
quux :: (forall a. a -> a) -> Int
quux _ = 5
bar = foo . rank2 $ quux
}}}
The `(.)` in the definition of `bar` requires an impredicative
instantiation -- that is, one of its type variables is instantiated to a
forall-type. Yet, the module compiles without `-XImpredicativeTypes`. To
confirm this behavior, the following is an excerpt from `-ddump-simpl`:
{{{
Bug.bar =
break<7>()
(break<6>()
GHC.Base..
@ ()
@ ()
@ ((forall a_a1Tj. a_a1Tj -> a_a1Tj) -> GHC.Types.Int)
Bug.foo
(Bug.rank2 @ GHC.Types.Int))
Bug.quux
}}}
Note the third type argument to `(.)`.
Fixing this would be a breaking change that could affect users.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9420>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list