[GHC] #16038: Simplifier incorrectly breaks recursive groups

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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: -------------------------------------+------------------------------------- I found this while looking at compile time panic in my code for #9718. The test that triggers the panic is `T4003`, but here's a simpler version of the test: {{{ -- T4003B.hs module T4003B where import {-# SOURCE #-} T4003A (HsExpr) data HsOverLit id = OverLit (HsExpr id) deriving Eq ----------------------------------- -- T4003A.hs-boot module T4003A where data HsExpr i instance Eq i => Eq (HsExpr i) ----------------------------------- -- T4003A.hs module T4003A where import T4003B data HsExpr id = HsOverLit (HsOverLit id) | HsBracketOut (HsExpr id) deriving Eq }}} Compile in this order: T4003A.hs-boot, T4003B.hs, T4003A.hs {{{ $ ghc-stage1 -O -c T4003A.hs-boot $ ghc-stage1 -O -c T4003B.hs $ ghc-stage1 -O -c T4003A.hs }}} The last step fails with a panic because in the new STG pass I implemented for #9718 I assume that all recursive groups are already in a `Rec`, but this program has a set of bindings that are actually recursive but not in a `Rec`. If I dump ds and simpl outputs of the last step I see that this recursive group: (in the ds output) {{{ Rec { -- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} $fEqHsExpr $fEqHsExpr = \ @ id_a27U $dEq_a27V -> C:Eq ($c==_a27X $dEq_a27V) ($c/=_a287 $dEq_a27V) -- RHS size: {terms: 9, types: 11, coercions: 0, joins: 0/0} $c/=_a287 $c/=_a287 = \ @ id_a27U $dEq_a27V eta_B2 eta_B1 -> $dm/= ($fEqHsExpr $dEq_a27V) eta_B2 eta_B1 -- RHS size: {terms: 37, types: 37, coercions: 0, joins: 1/3} $c==_a27X $c==_a27X = \ @ id_a27U $dEq_a27V -> let { $dEq_a283 $dEq_a283 = $fEqHsExpr $dEq_a27V } in let { $dEq_a281 $dEq_a281 = $fEqHsOverLit $dEq_a27V } in \ ds_d2jB ds_d2jC -> join { fail_d2jD fail_d2jD _ = False } in case ds_d2jB of { HsOverLit a1_a27Q -> case ds_d2jC of { __DEFAULT -> jump fail_d2jD void#; HsOverLit b1_a27R -> == $dEq_a281 a1_a27Q b1_a27R }; HsBracketOut a1_a27S -> case ds_d2jC of { __DEFAULT -> jump fail_d2jD void#; HsBracketOut b1_a27T -> == $dEq_a283 a1_a27S b1_a27T } } end Rec } -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} $fxEqHsExpr $fxEqHsExpr = $fEqHsExpr }}} Becomes non-recursive in simplifier output: {{{ Rec { -- RHS size: {terms: 34, types: 45, coercions: 0, joins: 0/0} $fEqHsExpr_$c== $fEqHsExpr_$c== = \ @ id_a27U $dEq_a27V ds_d2jB ds1_d2jC -> case ds_d2jB of { HsOverLit a1_a27Q -> case ds1_d2jC of { HsOverLit b1_a27R -> case a1_a27Q of { OverLit a2_a2k8 -> case b1_a27R of { OverLit b2_a2kc -> == (noinline $fxEqHsExpr $dEq_a27V) a2_a2k8 b2_a2kc } }; HsBracketOut ipv_s2kg -> False }; HsBracketOut a1_a27S -> case ds1_d2jC of { HsOverLit ipv_s2kj -> False; HsBracketOut b1_a27T -> $fEqHsExpr_$c== $dEq_a27V a1_a27S b1_a27T } } end Rec } -- RHS size: {terms: 13, types: 10, coercions: 0, joins: 0/0} $fEqHsExpr_$c/= $fEqHsExpr_$c/= = \ @ id_a27U $dEq_a27V eta_B2 eta1_B1 -> case $fEqHsExpr_$c== $dEq_a27V eta_B2 eta1_B1 of { False -> True; True -> False } -- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} $fEqHsExpr $fEqHsExpr = \ @ id_a27U $dEq_a27V -> C:Eq ($fEqHsExpr_$c== $dEq_a27V) ($fEqHsExpr_$c/= $dEq_a27V) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} $fxEqHsExpr $fxEqHsExpr = $fEqHsExpr }}} Notice that `c==` refers to `fxEqHsExpr`, which refers to `fEqHsExpr`, which refers to `c==`, forming a recursive group. (Confirmed with GHC 8.6.3 and GHC HEAD) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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: | -------------------------------------+------------------------------------- Changes (by osa1): * priority: normal => highest * owner: (none) => osa1 Comment: Bumping priority as this may cause segfaults in GHC today. I'll be looking into this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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 osa1): I think what's happening is this: in the boot file we're declaring a dictionary for `Eq i => Eq (HsExpr i)` without saying anything about the implementation. In `B.hs` we then refer to this dictionary in `Eq i => Eq (HsOverLit i)` because `HsOverLit` refers to `HsExpr`. At this point there isn't a loop yet because we don't know that `HsExpr` will be referring to `HsOverLit`. Then in A.hs we define `HsExpr` with a reference to `HsOverLit`. The dictionary definitions are now recursive but in the current module there's no way to see that. At this point if we don't do any inlining we'll still have a recursive group, but functions in the group will be living in different object files. I don't know if this is something we support. Maybe this is also a problem. If we inline `Eq (HsExpr i) => Eq (HsOverLit i)` and its methods then we get a recursive group in `A.hs`, but I guess we don't do "glomming" in the right places and don't realize this. So I think we may have two problems here: - Without any inlining we get a recursive group where functions live in different object files. Is this something we support? - With inlining we don't realize that after inlining we make new recursive groups (previously non-recursive definitions become recursive). This seems to be a problem with "glomming", and the same thing should be happening with RULEs too. I'll read the relevant code for RULEs to see how this is handled for RULEs. One hacky thing I tried was to do glomming always in `occurAnalyzePgm`, but that didn't fix it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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 osa1): If I add print statements to print input and output of `occurAnalysePgm`, and also force it to do glomming always, I see that at one point this is the input: {{{ Rec { $fEqHsExpr $fEqHsExpr = \ @ id_a27U $dEq_a27V -> C:Eq ($c==_a27X $dEq_a27V) ($c/=_a287 $dEq_a27V) $c/=_a287 $c/=_a287 = \ @ id_a27U $dEq_a27V eta_B2 eta_B1 -> case $c==_a27X $dEq_a27V eta_B2 eta_B1 of { False -> True; True -> False } $c==_a27X $c==_a27X = \ @ id_a27U $dEq_a27V -> let { $dEq_a283 $dEq_a283 = $fEqHsExpr $dEq_a27V } in let { $dEq_a281 $dEq_a281 = $fEqHsOverLit $dEq_a27V } in \ ds_d2jB ds_d2jC -> join { fail_d2jD fail_d2jD _ = False } in case ds_d2jB of { HsOverLit a1_a27Q -> case ds_d2jC of { HsOverLit b1_a27R -> let { $dEq1_a2k1 $dEq1_a2k1 = noinline $fxEqHsExpr $dEq_a27V } in case a1_a27Q of { OverLit a1_a2k8 -> case b1_a27R of { OverLit b1_a2kc -> == $dEq1_a2k1 a1_a2k8 b1_a2kc } }; HsBracketOut ipv_s2kg -> False }; HsBracketOut a1_a27S -> case ds_d2jC of { HsOverLit ipv_s2kj -> False; HsBracketOut b1_a27T -> $c==_a27X $dEq_a27V a1_a27S b1_a27T } } end Rec } $fxEqHsExpr $fxEqHsExpr = $fEqHsExpr ... }}} This is already incorrect (`$fxEqHsExpr` should be in the recursive group), but what I don't understand is even after flattening the whole program and doing occurance analysis we end up with incorrect recursive group: {{{ Rec { $c==_a27X $c==_a27X = \ @ id_a27U $dEq_a27V ds_d2jB ds_d2jC -> case ds_d2jB of { HsOverLit a1_a27Q -> case ds_d2jC of { HsOverLit b1_a27R -> let { $dEq1_a2k1 $dEq1_a2k1 = noinline $fxEqHsExpr $dEq_a27V } in case a1_a27Q of { OverLit a1_a2k8 -> case b1_a27R of { OverLit b1_a2kc -> == $dEq1_a2k1 a1_a2k8 b1_a2kc } }; HsBracketOut _ -> False }; HsBracketOut a1_a27S -> case ds_d2jC of { HsOverLit _ -> False; HsBracketOut b1_a27T -> $c==_a27X $dEq_a27V a1_a27S b1_a27T } } end Rec } $c/=_a287 $c/=_a287 = \ @ id_a27U $dEq_a27V eta_B2 eta_B1 -> case $c==_a27X $dEq_a27V eta_B2 eta_B1 of { False -> True; True -> False } $fEqHsExpr $fEqHsExpr = \ @ id_a27U $dEq_a27V -> C:Eq ($c==_a27X $dEq_a27V) ($c/=_a287 $dEq_a27V) $fxEqHsExpr $fxEqHsExpr = $fEqHsExpr }}} Perhaps this is a bug in the occurance analysis? I wonder if the `noinline` is relevant somehow ... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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): Gah. I know what is happening. Patch coming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner: osa1
Type: bug | Status: new
Priority: highest | Milestone:
Component: Compiler | Version: 8.6.3
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 Simon Peyton Jones

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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): Well that was harder than I expected! Done now, thought. Omer: could you add a test? I'll leave it open for that reason. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner: osa1
Type: bug | Status: new
Priority: highest | Milestone:
Component: Compiler | Version: 8.6.3
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 Ömer Sinan Ağacan

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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 osa1): Done. Do we want to milestone this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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): Well, it's in the tree before 8.8 forks, so I suppose it'll automatically be in 8.8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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 osa1): I thought we're going to have another 8.6 release to fix #16057, if that happens maybe we should include this too? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 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):
I thought we're going to have another 8.6 release to fix #16057, if that happens maybe we should include this too?
Maybe. I don't think it'd destablise anything. But nor does it fix any bugs that anyone has reported. Do you think we could generate bogus code if this is not fixed? If so, is a test case easy to construct? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16038: Simplifier incorrectly breaks recursive groups -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: bug | Status: closed Priority: highest | Milestone: Component: Compiler | Version: 8.6.3 Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => closed * resolution: => fixed Comment: Fair enough, let's close this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16038#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC