[GHC] #12652: Type checker no longer accepting code using function composition and rank-n types
GHC
ghc-devs at haskell.org
Sun Oct 2 05:53:29 UTC 2016
#12652: Type checker no longer accepting code using function composition and rank-n
types
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following program (reduced from Cabal code that uses HasCallStack)
typechecks in GHC 8.0, but not on HEAD:
{{{
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ImplicitParams #-}
module Foo where
type T a = (?x :: Int) => a
type M a = T (IO a)
f :: T (T a -> a)
f x = x
g :: Int -> M ()
g = undefined
h :: Int -> M ()
-- h x = f (g x) -- works on HEAD
h = f . g -- fails on HEAD, works on GHC 8.0
}}}
It's possible that this is just fall out from the recent impredicativity
changes but I just wanted to make sure that this was on purpose.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12652>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list