[GHC] #9072: RankNTypes composition now requires ImpredicativeTypes
GHC
ghc-devs at haskell.org
Sat May 3 19:07:48 UTC 2014
#9072: RankNTypes composition now requires ImpredicativeTypes
-------------------------------------+-------------------------------------
Reporter: gelisam | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.8.2
checker) | Operating System: Unknown/Multiple
Keywords: | Type of failure: GHC rejects
Architecture: Unknown/Multiple | valid program
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
-------------------------------------+-------------------------------------
{{{
{-# LANGUAGE RankNTypes #-}
instantiateId :: (forall a. a -> a) -> Int -> Int
instantiateId f = f
passes :: [Int] -> [Int]
passes = map (instantiateId id)
-- Couldn't match type ‘a0 -> a0’ with ‘forall a. a -> a’
fails :: [Int] -> [Int]
fails = (map . instantiateId) id
}}}
works with ghc 7.6,
fails with ghc 7.8,
works with ghc 7.8 + `ImpredicativeTypes`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9072>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list