[GHC] #12630: Assertion failed with BuildFlavour = devel2

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tried to reproduce random ghc panic we have in our codebase with ghc8 so I decided to compile ghc with debug enabled. Source file: ghc-8.0.1-src.tar.xz build.mk changes: {{{ BuildFlavour = devel2 GhcStage1HcOpts = -DDEBUG GhcStage2HcOpts = -DDEBUG }}} source: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} module A where import GHC.Generics class B f where b :: [f a] toEnumDefault :: (B (Rep a)) => Int -> a toEnumDefault i = let l = b in to }}} result: {{{ [1 of 1] Compiling A ( a.hs, a.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): ASSERT failed! CallStack (from HasCallStack): assertPprPanic, called at compiler/types/TyCoRep.hs:1974:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2010:17 in ghc:TyCoRep substTy, called at compiler/types/TyCoRep.hs:1952:3 in ghc:TyCoRep in_scope InScope [a1BD :-> a_a1BD[sk], a1BI :-> k_a1BI[tau:3], a1BJ :-> f_a1BJ[tau:3], a1BL :-> a_a1BL[sk]] tenv [a1BD :-> a_a1BL[sk]] tenvFVs [a1Bz :-> k_a1Bz[tau:5], a1BL :-> a_a1BL[sk]] cenv [] cenvFVs [] tys [[f_a1BJ[tau:3] a_a1BD[sk]]] cos [] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): It looks like this has been fixed in HEAD, but not on the ghc-8.0 branch. I'm going to do a bisect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Bisection points to 15fc52819c as the commit that fixed the issue in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): This code still triggers the issue in ghc-8.0 branch as of 24 Oct 2016, code above - no longer does that. {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} module A where import GHC.Generics class Enum' f where enum' :: [f a] toEnumDefault :: (Generic a, Enum' (Rep a)) => Int -> a toEnumDefault i = let l = enum' in if (length l > i) then to (l !! i) else error "toEnum: invalid index" class GEnum a }}} {{{ [1 of 1] Compiling A ( Generics/Deriving/Enum.hs, Generics/Deriving/Enum.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1.20161022 for x86_64-unknown-linux): ASSERT failed! CallStack (from HasCallStack): assertPprPanic, called at compiler/types/TyCoRep.hs:2008:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2044:17 in ghc:TyCoRep substTy, called at compiler/types/TyCoRep.hs:1986:3 in ghc:TyCoRep in_scope InScope [a2Um :-> a_a2Um[sk], a2Ur :-> k_a2Ur[tau:3], a2Us :-> f_a2Us[tau:3], a2Uu :-> a_a2Uu[sk]] tenv [a2Um :-> a_a2Uu[sk]] tenvFVs [a2Ui :-> k_a2Ui[tau:5], a2Uu :-> a_a2Uu[sk]] cenv [] cenvFVs [] tys [[f_a2Us[tau:3] a_a2Um[sk]]] cos [] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): 15fc52819c helps but it's not included into release candidate -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thank you! The commit 15fc52819c is short and definitely good. Let's merge it into 8.0. In comment:5 you say that "helps"; does it fix the 8.0 branch? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): Right, picking 15fc52819c to 8.0 branch fixes the issue. Btw, right now I'm debugging one more issue that causes assertion failure with devel2 and it's still the case in 8.0 branch. At the moment smallest sample is down to 8 files with no external dependencies other than bytestring. I can try reducing it further but it's going hard. it's a sample for that new panic: {{{ (GHC version 8.0.1.20161022 for x86_64-unknown-linux): ASSERT failed! CallStack (from HasCallStack): assertPprPanic, called at compiler/types/TyCoRep.hs:2012:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2048:17 in ghc:TyCoRep substTy, called at compiler/simplCore/SimplEnv.hs:696:18 in ghc:SimplEnv in_scope InScope [00 :-> wild_00, Xw :-> wild_Xw, XD :-> wild_XD, XH :-> wild1_XH, XaWP :-> msg0_XaWP, a4vA :-> s'_a4vA, a4Db :-> ds2_a4Db, a4Dd :-> ipv_a4Dd, a4De :-> ipv1_a4De, a6eU :-> t'_a6eU, a6eV :-> pos'_a6eV, a6eW :-> more'_a6eW, a6eX :-> a1_a6eX, d4gB :-> dt_d4gB, d4gC :-> dt1_d4gC, d4gD :-> dt2_d4gD, d4gE :-> dt3_d4gE, d4gF :-> dt4_d4gF, d4gG :-> dt5_d4gG, rdYv :-> decodeOTCLine, reHX :-> $trModule, s6ZQ :-> nt1_s6ZQ, s6ZS :-> ipv1_s6ZS, seJM :-> $trModule_seJM, seJN :-> $trModule_seJN, seJU :-> lvl_seJU, seJY :-> lvl_seJY, seOl :-> $wsucc_seOl, seOu :-> $wdecodeOTCLine_seOu, sePd :-> lvl_sePd, sePe :-> lvl_sePe, sePf :-> lvl_sePf, sePg :-> lvl_sePg, sePh :-> lvl_sePh, sePi :-> lvl_sePi, sePk :-> lvl_sePk, sePl :-> lvl_sePl, sePm :-> lvl_sePm, sePn :-> lvl_sePn, sePp :-> fail_sePp, sePq :-> lvl_sePq, sePr :-> lvl_sePr, sePs :-> lvl_sePs, sePt :-> lvl_sePt, sePu :-> lvl_sePu, sePv :-> lvl_sePv, sePw :-> lvl_sePw, seQ0 :-> sc_seQ0, seQ1 :-> sc_seQ1, seQ2 :-> sc_seQ2, seQ3 :-> sc_seQ3, seQ7 :-> sc_seQ7, seQa :-> $s$wsucc_seQa] tenv [] tenvFVs [] cenv [seQ6 :-> sg_seQ6] cenvFVs [seQ6 :-> sg_seQ6] tys [ByteString] cos [] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): If it's OK in HEAD (is it?) I'd be inclined to leave it. The ASSERT is very conservative, so it's very unlikely to reveal a real bug Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak):
If it's OK in HEAD (is it?) I'd be inclined to leave it. The ASSERT is very conservative, so it's very unlikely to reveal a real bug
I'll check if HEAD fixes it. It might reveal a bug - it's from our codebase and there is a random compilation failure that goes away when compilation is restarted. If it's not this one - there might be something else - I decided to isolate it anyway. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): Simon: That other failure is not fixed in HEAD, but panic looks a bit different: {{{ (GHC version 8.1.20161024 for x86_64-unknown-linux): ASSERT failed! in_scope InScope {wild_00 wild_Xw wild1_XH t'_a2XC pos'_a2XD more'_a2XE a1_a2XF dt_d2iY dt1_d2iZ dt2_d2j0 dt3_d2j1 dt4_d2j2 dt5_d2j3 decodeOTCLine $trModule nt1_s3K7 ipv1_s3K9 $trModule_sc1H $trModule_sc1I lvl_sc1T $wsucc_sc5K $wdecodeOTCLine_sc5T lvl_sc6y lvl_sc6z lvl_sc6A lvl_sc6B lvl_sc6C lvl_sc6D lvl_sc6F lvl_sc6G lvl_sc6H lvl_sc6I fail_sc6K lvl_sc6L lvl_sc6M lvl_sc6N lvl_sc6O lvl_sc6P sc_sc7y sc_sc7z sc_sc7A sc_sc7B sc_sc7F $s$wsucc_sc7I} tenv [] tenvFVs [] cenv [sc7E :-> sg_sc7E] cenvFVs [sc7E :-> sg_sc7E] tys [ByteString] cos [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1076:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1125:22 in ghc:Outputable assertPprPanic, called at compiler/types/TyCoRep.hs:2070:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2103:17 in ghc:TyCoRep substTy, called at compiler/simplCore/SimplEnv.hs:701:18 in ghc:SimplEnv Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1076:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1080:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1123:5 in ghc:Outputable assertPprPanic, called at compiler/types/TyCoRep.hs:2070:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2103:17 in ghc:TyCoRep substTy, called at compiler/simplCore/SimplEnv.hs:701:18 in ghc:SimplEnv Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK this is `substTy` called from `SimplEnv` i.e. in the simplifier. Again it's unlikely to be causing a problem but I'd like to nail what's going on. Do you have time to make a reproducible case? It doesn't have to be terribly small, but having few dependencies is helpful. You 8-file blob might do. Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): It's 5 files blob now. I'll put it somewhere once I get to my computer.1 hour or so. There are similar failures all over our codebase, the biggest one is over 3k lines long -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by pacak): * Attachment "blob.zip" added. file sample -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): Simon: Attached a file sample. It produces panic if you use `ghc -O2 A.hs` for both 8.0.2 rc and latest HEAD branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12630: Assertion failed with BuildFlavour = devel2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: comment:5 merged to `ghc-8.0` as cc3a9504f638fe14fd6532c3b616343a2ee947dd. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12630#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC