
#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