[GHC] #11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1

#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/Interna... 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

#11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: | ImpredicativeTypes, | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: ImpredicativeTypes => ImpredicativeTypes, TypeApplications * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11428#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: | ImpredicativeTypes, | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hopefully my work (Phab:D1777 is an unfinished checkpoint) toward #11397 will nab this as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11428#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11428: ImpredicativeTypes causes GHC panic with 8.0.1-rc1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: fixed | ImpredicativeTypes, | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Indeed this now fails with the error {{{ T11428.hs:12:13: error: • Couldn't match expected type ‘forall a. a -> a’ with actual type ‘Pipe o2 r0 -> Pipe o2 r0’ • When checking that: Pipe o2 r0 -> Pipe o2 r0 is more polymorphic than: forall a. a -> a The lambda expression ‘\ o' p' -> HaveOutput p' o'’ has two arguments, but its type ‘o2 -> forall a. a -> a’ has only one In the second argument of ‘maybe’, namely ‘(\ o' p' -> HaveOutput p' o')’ • Relevant bindings include f :: o1 -> Maybe o2 (bound at T11428.hs:11:16) mapOutputMaybe :: (o1 -> Maybe o2) -> Pipe o1 r -> Pipe o2 r (bound at T11428.hs:11:1) }}} When compiled with `ImpredicativeTypes`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11428#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC