[GHC] #10665: INLINE breaks rewrite rules when '-g' is used

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The bug is found when building conduit-1.2.4.2 package with '-O2 -g' options. The distilled sample looks like that: {{{#!hs {-# LANGUAGE BangPatterns #-} module RewriteBug (bug) where bug :: () -> () bug () = bug () {-# NOINLINE bug #-} a2 :: () a2 = () {-# INLINE[1] a2 #-} {-# RULES "bug a2" [0] bug a2 = () #-} {- Crashes as: $ inplace/bin/ghc-stage2 -c -O1 -fforce-recomp RewriteBug.hs -g ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150721 for x86_64-unknown-linux): Tick in rule () -} }}} My theory of sequence of actions is the following: - rewrite rule gets read as-is by GHC (gentle phase) - a2 INLINE changes LHS of rewrite rule (phase 1) - when time comes to apply 'bug a2' rule GHC detects INLINE problem (phase 0) In real code it happened across multiple files. The bug is reproducible in both ghc-7.10.2-rc2 and today's HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Your diagnosis sounds dead right to me. It is very unreliable to have a rule where functions on the LHS can be inlined when the rule is active. Better to make sure that the rule is active only up to phase 2 (say), and the inlining of `a2` happens only after phase 2. Maybe this is really a bug in (the RULES of) conduit? Can you describe the actual RULE and inlining? Getting a panic is bad. Probably we should simply not inline in the LHS of a rule, regardless of INLINE pragmas. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): (side note: I'm not an author of those packages, just a mere distribution packager :)) conduit is a big package, i'll try to prepare self-contained bundle to ease analysis of existing RULES in there. Meanwhile I've found smaller package that fails in similar way: unification-fd-0.10.0.1. The plus is that everything happens in a single module '''Data.Functor.Fixedpoint'''. The failure is: {{{ $ ghc -hide-all-packages -package=base -O2 -c -g Fixedpoint.hs ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): Tick in rule eps_aPv @ (Fix f_aPy) (unFix @ f_aPy x_a2gY) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug (Or with -dsuppress-uniques:) Tick in rule eps @ (Fix f) (unFix @ f x) }}} Would it be easy to add actual rule name to that crash to ease analysis of what exactly went wrong? (Or maybe there already is a trace knob for it?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * Attachment "Fixedpoint.hs" added. taken as-is from unification-fd-0.10.0.1/src/Data/Functor/Fixedpoint.hs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): And here goes conduit sample: http://code.haskell.org/~slyfox/when-rules- tick-in-conduit-T10665.tar.gz (3MB of haskell code). Tarball contains original hackage packages with 2-3 language pragmas added. It does not require external depends and can be built with inplace/bin /ghc-stage2. Fails thusly on 7.10.2: {{{ $ ./trigger-a-bug.bash [97 of 99] Compiling Data.Conduit.Extra.ZipConduitSpec ( conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.hs, conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): Tick in rule unstream @ a21_a4C66 @ Void @ m_a4C64 @ b_a4C65 (ConduitWithStream @ a21_a4C66 @ Void @ m_a4C64 @ b_a4C65 (let { $dApplicative_a4BDD :: Applicative (ConduitM a21_a4C66 Void m_a4C64) [LclId, Str=DmdType] $dApplicative_a4BDD = $fApplicativeConduitM @ a21_a4C66 @ Void @ m_a4C64 ($fFunctorConduitM @ a21_a4C66 @ Void @ m_a4C64) } in ... }}} To follow by source code: {{{#!hs --| rewrite rule is triggered by '$$' operator at conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.hs: res <- src $$ conduit =$ sink --| '''conduit-1.2.4.3/Data/Conduit/List.hs''' refines rewrite rule as: {-# RULES "conduit: $$ fold" forall src f b. src $$ fold f b = connectFold src f b #-} --| '''fold''' is defined at conduit-1.2.4.3/Data/Conduit/List.hs: fold, foldC :: Monad m => (b -> a -> b) -> b -> Consumer a m b foldC f = loop where loop !accum = await >>= maybe (return accum) (loop . f accum) {-# INLINE foldC #-} STREAMING(fold, foldC, foldS, f accum) --| STREAMING is a macro in conduit-1.2.4.3/fusion-macros.h that inlines 'fold' lately: #define STREAMING(name, nameC, nameS, vars) ;\ name = nameC ;\ {-# INLINE [0] name #-} ;\ {-# RULES "unstream name" forall vars. \ name vars = unstream (streamConduit (nameC vars) (nameS vars)) \ #-} }}} Here delaying inline does not help as rewrite rule becomes broken when compliling one module (where it's defined) and used in another. That's the reson why original reproducer so carefully setups phases. To be able to compile it under windows you might need to change {{{ -D'UNIX=1' \ }}} to {{{ -D'WINDOWS=1' \ }}} in '''trigger-a-bug.bash''' script. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 7.10.3
Component: Compiler | Version: 7.10.2-rc2
(CodeGen) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: new => merge
* milestone: => 7.10.3
Comment:
I believe this is fixed by
{{{
commit bc4b64ca5b99bff6b3d5051b57cb2bc52bd4c841
Author: Simon Peyton Jones

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): Replying to [comment:4 simonpj]:
Meanwhile, can you confirm fixed in HEAD?
HEAD works. Thank you! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This was merged to `ghc-7.10` as mentioned in #10528. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10665#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC