[GHC] #12776: Panic Simplifier ticks exhausted since ghc 8

GHC ghc-devs at haskell.org
Tue Nov 8 12:41:37 UTC 2016


#12776: Panic Simplifier ticks exhausted since ghc 8
-------------------------------------+-------------------------------------
        Reporter:  sjcjoosten        |                Owner:
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      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 simonpj):

 Thank you for the small test case.  I can see what is happening here.
 After `SpecConstr`, and occurrence analysis we get
 {{{
 Rec {
 $slast_s_s1J5
   :: forall a_a1BZ. a_a1BZ -> Slist a_a1BZ -> Eq a_a1BZ => a_a1BZ
 $slast_s_s1J5 =
   \ (@ a_a1BZ)
     (sc_s1J0 :: a_a1BZ)
     (sc_s1J1 :: Slist a_a1BZ)
     (sc_s1IZ :: Eq a_a1BZ) ->
     case sc_s1J1 of wild_Xp [Dmd=<L,A>] {
       Nil_s -> sc_s1J0;
       Cons_s _ [Occ=Dead] _ [Occ=Dead] ->
         let {
           sc_s1J1 [Occ=Once] :: Slist a_a1BZ
           [LclId]
           sc_s1J1 = wild_Xp } in
         last_s @ a_a1BZ sc_s1IZ sc_s1J1
     }

 last_s [Occ=LoopBreaker]
   :: forall a_a1kp. Eq a_a1kp => Slist a_a1kp -> a_a1kp
 [RULES: "SC:last_s0" [ALWAYS]
             forall (@ a_a1BZ)
                    (sc_s1J0 :: a_a1BZ)
                    (sc_s1J1 :: Slist a_a1BZ)
                    (sc_s1IZ :: Eq a_a1BZ).
               last_s @ a_a1BZ
                             sc_s1IZ
                             (Cons_s @ a_a1BZ sc_s1J0 sc_s1J1)
               = $slast_s_s1J5 @ a_a1BZ sc_s1J0 sc_s1J1 sc_s1IZ]
 last_s =
   \ (@ a_a1BC)
     ($dEq_a1BE :: Eq a_a1BC)
     (ds_d1Do [Occ=Once!] :: Slist a_a1BC) ->
     case ds_d1Do of {
       Nil_s -> lvl_s1Fa @ a_a1BC;
       Cons_s x_a1kB [Occ=Once] xs_a1kC [Occ=Once!, Dmd=<S,U>] ->
         case xs_a1kC of {
           Nil_s -> x_a1kB;
           Cons_s a1_a1zd [Occ=Once] a2_a1ze [Occ=Once] ->
             $slast_s_s1J5 @ a_a1BC a1_a1zd a2_a1ze $dEq_a1BE
         }
     }
 end Rec }
 }}}
 Then in `last_s`:

 * `$s_last_s_s1J5` is inlined
 * The RULE fires, yielding a new cal to `$s_last_s_s1J5`
 * `$s_last_s_s1J5` is inlined again
 * and so on.

 The problem is that `$s_last_s_s1J5` should be a loop breaker.  See the
 extensive notes under `Note [Choosing loop breakers]`.

 But alas in `occAnalRec` we see this
 {{{
     pairs :: [(Id,CoreExpr)]
     pairs | isEmptyVarSet weak_fvs = reOrderNodes   0 bndr_set weak_fvs
 tagged_nodes       []
           | otherwise              = loopBreakNodes 0 bndr_set weak_fvs
 loop_breaker_edges []
 }}}
 We want to go via the `loopBreakNodes` call, but actually `weak_fvs` is
 empty so we go via the former call.

 I'm not yet sure exactly why... just recording breadcrumbs for now.

 How urgent is this for you, Stef?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12776#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list