[GHC] #11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1
GHC
ghc-devs at haskell.org
Thu Jan 14 20:03:47 UTC 2016
#11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.0.1-rc1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
ImpredicativeTypes |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I noticed this issue when attempting to compile `conduit` with GHC
8.0.1-rc1 (specifically, the
[https://github.com/snoyberg/conduit/blob/master/conduit/Data/Conduit/Internal/Pipe.hs
Data.Conduit.Internal.Pipe] module). This (greatly simplified) code, which
compiles without issue on GHC 7.10.3:
{{{#!hs
{-# LANGUAGE ImpredicativeTypes #-}
module Data.Conduit.Internal.Pipe where
data Pipe o r =
HaveOutput (Pipe o r) o
mapOutputMaybe :: (o1 -> Maybe o2) -> Pipe o1 r -> Pipe o2 r
mapOutputMaybe f (HaveOutput p o) =
maybe id (\o' p' -> HaveOutput p' o') (f o) (mapOutputMaybe f p)
}}}
emits a GHC panic with GHC 8.0.1-rc1:
{{{
[1 of 1] Compiling Data.Conduit.Internal.Pipe ( Wat.hs, interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 8.0.0.20160111 for x86_64-unknown-linux):
matchExpectedFunTys
<>
a_a15Z[tau:5] -> b_a15Y[tau:5]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Note that this code does not require `-XImpredicativeTypes`, and removing
the pragma makes the code compile again.
Marking as high since it's a regression, but not highest because
`-XImpredicativeTypes` has long been broken (see also #11319). Still, this
currently happens on code in the wild, and perhaps it would be worth
turning this into a more sensible error.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11428>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list