[GHC] #12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- ghc version: 41ec722d71 with assertion that fails in https://ghc.haskell.org/trac/ghc/ticket/12926 commented out {{{#!hs {-# LANGUAGE TypeFamilies #-} module Numeric.Polynomial.Log () where class AdditiveGroup v where (^+^) :: v -> v -> v negateV :: v -> v (^-^) :: v -> v -> v v ^-^ v' = v ^+^ negateV v' class AdditiveGroup v => VectorSpace v where type Scalar v :: * (*^) :: Scalar v -> v -> v data Poly1 a = Poly1 a a data IntOfLog poly a = IntOfLog !a !(poly a) instance Num a => AdditiveGroup (Poly1 a) where {-# INLINE (^+^) #-} {-# INLINE negateV #-} Poly1 a b ^+^ Poly1 a' b' = Poly1 (a + a') (b + b') negateV (Poly1 a b) = Poly1 (negate a) (negate b) instance (AdditiveGroup (poly a), Num a) => AdditiveGroup (IntOfLog poly a) where {-# INLINE (^+^) #-} {-# INLINE negateV #-} IntOfLog k p ^+^ IntOfLog k' p' = IntOfLog (k + k') (p ^+^ p') negateV (IntOfLog k p) = IntOfLog (negate k) (negateV p) {-# SPECIALISE instance Num a => AdditiveGroup (IntOfLog Poly1 a) #-} instance (VectorSpace (poly a), Scalar (poly a) ~ a, Num a) => VectorSpace (IntOfLog poly a) where type Scalar (IntOfLog poly a) = a s *^ IntOfLog k p = IntOfLog (s * k) (s *^ p) }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161206 for x86_64-unknown-linux): ASSERT failed! $dAdditiveGroup_aIU Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1114:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1163:22 in ghc:Outputable assertPprPanic, called at compiler/stgSyn/CoreToStg.hs:967:78 in ghc:CoreToStg Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1114:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1118:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1161:5 in ghc:Outputable assertPprPanic, called at compiler/stgSyn/CoreToStg.hs:967:78 in ghc:CoreToStg Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest * component: Compiler => Compiler (CodeGen) * milestone: => 8.2.1 Comment: I can also reproduce this with 9bcc4e335b34c00191e8897aa7393c3856e8996f, {{{ $ ghc -O ~/hi.hs [1 of 1] Compiling Numeric.Polynomial.Log ( /home/ben/hi.hs, /home/ben/hi.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161207 for x86_64-unknown-linux): StgCmmEnv: variable not found $dAdditiveGroup_aIP local binds for: *^ ^+^ negateV ^-^ $p1VectorSpace $fAdditiveGroupPoly1 $WIntOfLog $fAdditiveGroupIntOfLog_$cnegateV $fAdditiveGroupIntOfLog_$c^+^ $fAdditiveGroupPoly1_$c^-^ $fAdditiveGroupPoly1_$cnegateV $fAdditiveGroupPoly1_$c^+^ w_s12P ww_s12Q ww1_s12R ww2_s12S ww3_s12T dt_s12U Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1116:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1120:37 in ghc:Outputable pprPanic, called at compiler/codeGen/StgCmmEnv.hs:137:9 in ghc:StgCmmEnv Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It looks like the failing assertion is this, {{{#!hs lookupBinding :: IdEnv HowBound -> Id -> HowBound lookupBinding env v = case lookupVarEnv env v of Just xx -> xx Nothing -> ASSERT2( isGlobalId v, ppr v ) ImportBound }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): If I comment out this assertion there are other failures on the same code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It sounds very much like uniques are overflowing. We are working on confirming this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2844 Comment: Here is a patch fixing some of the fragility of the current unique setup. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): https://ghc.haskell.org/trac/ghc/ticket/12899 - related -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor
and -O
-------------------------------------+-------------------------------------
Reporter: pacak | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
(CodeGen) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2844
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: According to pacak the fix in comment:7 has fixed the issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): This ticket is _NOT_ related to unique identifier and it still fails with fix in place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh dear, yes, you are quite right. My apologies! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I know exactly what is going on here, thanks to the nice example in the Description. It's a long-standing bug in the implementation of `{-# SPECIALISE instance ... #-}`. Core Lint nails it instantly. I'll look at this early next week. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor
and -O
-------------------------------------+-------------------------------------
Reporter: pacak | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
(CodeGen) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2844
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor
and -O
-------------------------------------+-------------------------------------
Reporter: pacak | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
(CodeGen) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2844
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Also relevant (the commit message should say #12944 not #12444): {{{ revision="c48595eef2bca6d91ec0a649839f8066f269e6a4" Never apply worker/wrapper to DFuns While fixing Trac #12444 I found an occasion on which we applied worker/wrapper to a DFunId. This is bad: it destroys the magic DFunUnfolding. This patch is a minor refactoring that stops this corner case happening, and tidies up the code a bit too. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deSugar/should_compile/T12944 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => deSugar/should_compile/T12944 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.3 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deSugar/should_compile/T12944 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => merge * milestone: 8.2.1 => 8.0.3 Comment: The main patch here, in comment:13, is a candidate for 8.0.3 since it fixes an outright bug. So I'll switch to merge status. But it may depend (in a trivial and easily-avoidable way) on an earlier commit {{{ 05d233e8e18284cb98dc320bf58191ba4d86c754 Move InId/OutId to CoreSyn }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deSugar/should_compile/T12944 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2844 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC