[GHC] #12589: GHC panic with defer-typed-holes

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- Does this still happen in HEAD? {{{#!hs import qualified GHC.Generics as GHC import Generics.SOP import Generics.SOP.TH import Data.Proxy gminbound' :: (Generic a, Code a ~ (xs:xss), All2 Bounded (Code a)) => a gminbound' = minBound & I & hcpure (Proxy @Bounded) & apInjs_POP & head & to }}} Fails but doesn't crash with {{{ $ ghci -ignore-dot-ghci -XTypeApplications -XTypeOperators -XDataKinds -XGADTs -XFlexibleContexts /tmp/tX96.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tX96.hs, interpreted ) /tmp/tX96.hs:8:3: error: Variable not in scope: (&) :: t4 -> (a0 -> I a0) -> t3 /tmp/tX96.hs:9:3: error: Variable not in scope: (&) :: t3 -> t5 -> t2 /tmp/tX96.hs:10:3: error: Variable not in scope: (&) :: t2 -> (POP f1 xss0 -> [SOP f1 xss0]) -> t1 /tmp/tX96.hs:11:3: error: Variable not in scope: (&) :: t1 -> ([a1] -> a1) -> t0 /tmp/tX96.hs:12:3: error: Variable not in scope: (&) :: t0 -> (Rep a2 -> a2) -> a Failed, modules loaded: none. Prelude> }}} but crashes with `-fdefer-typed-holes` {{{ $ ghci -ignore-dot-ghci -fdefer-typed-holes -XTypeApplications -XTypeOperators -XDataKinds -XGADTs -XFlexibleContexts /tmp/tX96.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tX96.hs, interpreted ) /tmp/tX96.hs:8:3: warning: [-Wtyped-holes] Variable not in scope: (&) :: t4 -> (a0 -> I a0) -> t3 /tmp/tX96.hs:9:3: warning: [-Wtyped-holes] Variable not in scope: (&) :: t3 -> t5 -> t2 /tmp/tX96.hs:10:3: warning: [-Wtyped-holes] Variable not in scope: (&) :: t2 -> (POP f1 xss0 -> [SOP f1 xss0]) -> t1 /tmp/tX96.hs:11:3: warning: [-Wtyped-holes] Variable not in scope: (&) :: t1 -> ([a1] -> a1) -> t0 /tmp/tX96.hs:12:3: warning: [-Wtyped-holes] Variable not in scope: (&) :: t0 -> (Rep a2 -> a2) -> a ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): opt_univ fell into a hole {aabX} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}} ---- More minimal example, still requires [https://hackage.haskell.org/package /generics-sop-0.2.2.0 generics-sop]: {{{#!hs import Generics.SOP a = minBound & hcpure (Proxy @Bounded) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Simplified version without any dependencies (''generics-sop''): {{{#!hs import Data.Proxy hcpure :: proxy c -> (forall a. c a => f a) -> h f xs hcpure _ _ = undefined a = minBound & hcpure (Proxy @Bounded) }}} This is a good use case for #393, because of the rank-2 type we need to supply two wildcard arguments. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. In HEAD (and therefore I think 8.0 but I'm not certain) an out-of- scope variable is an error, so we get {{{ T12589.hs:11:14: error: Variable not in scope: (&) :: t0 -> t1 -> t }}} regardless of `-fefer-typed-holes`. If I change it to be {{{ a = _foo minBound (hcpure (Proxy @Bounded)) }}} using a named wildcard, with `-defer-typed-holes` in HEAD I get {{{ s:12:5: warning: [-Wtyped-holes] * Found hole: _foo :: t0 -> t1 -> t Where: `t0' is an ambiguous type variable `t1' is an ambiguous type variable `t' is a rigid type variable bound by the inferred type of a :: t at T12589.hs:12:1-43 Or perhaps `_foo' is mis-spelled, or not in scope * In the expression: _foo In the expression: _foo minBound (hcpure (Proxy @Bounded)) In an equation for `a': a = _foo minBound (hcpure (Proxy @Bounded)) * Relevant bindings include a :: t (bound at T12589.hs:12:1) T12589.hs:12:20: warning: [-Wdeferred-type-errors] * Cannot instantiate unification variable `t1' with a type involving foralls: (forall a. Bounded a => f0 a) -> h0 f0 xs0 GHC doesn't yet support impredicative polymorphism * In the second argument of `_foo', namely `(hcpure (Proxy @Bounded))' In the expression: _foo minBound (hcpure (Proxy @Bounded)) In an equation for `a': a = _foo minBound (hcpure (Proxy @Bounded)) }}} which is what I'd expect. I have not investigated the "falling ito a hole" error becuase it just doesn't happen in HEAD. So could someone test with 8.0.1? If it's ok there then let's just add a regression test and declare it fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This program: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} import Data.Proxy hcpure :: proxy c -> (forall a. c a => f a) -> h f xs hcpure _ _ = undefined a = minBound & hcpure (Proxy @Bounded) }}} produces that GHC panic with GHC 8.0.1, but not with GHC 8.0.2 or HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It appears that af21e38855f7d517774542b360178b05045ecb08 was the commit that fixed this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T12589 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => merge * testcase: => typecheck/should_fail/T12589 Comment: Since this test will also work in GHC 8.0.2, the above commit can be safely merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12589: GHC panic with defer-typed-holes -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T12589 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Test merged to `ghc-8.0` as 9467dfa8cc63de5742a27caf0cdab997156c7409. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12589#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC