[GHC] #10626: Missed opportunity for SpecConstr

GHC ghc-devs at haskell.org
Fri Jul 10 11:41:28 UTC 2015


#10626: Missed opportunity for SpecConstr
-------------------------------------+-------------------------------------
              Reporter:  simonpj     |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.10.1
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 Look at `perf/should_run/T4830`.  After `SpecConstr` and optimisation we
 finally get
 {{{
 Rec {
 Main.foo_$s$wfoo1 [Occ=LoopBreaker]
   :: Int# -> Double -> Double -> Double#
 [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType <L,1*U><L,U><L,U>]
 Main.foo_$s$wfoo1 =
   \ (sc_s4eN :: Int#) (sc1_s4eO :: Double) (sc2_s4eP :: Double) ->
     case sc_s4eN of ds_X1SR {
       __DEFAULT ->
         case sc1_s4eO of wild_a1Tf { D# x_a1Th ->
         case sc2_s4eP of wild1_a1Tj { D# y_a1Tl ->
         case tagToEnum# @ Bool (<=## x_a1Th y_a1Tl) of _ [Occ=Dead] {
           False -> Main.foo_$s$wfoo1 (-# ds_X1SR 1#) wild1_a1Tj wild_a1Tf;
           True -> Main.foo_$s$wfoo1 (-# ds_X1SR 1#) wild_a1Tf wild1_a1Tj
         }
         }
         };
       0# ->
         case sc1_s4eO of _ [Occ=Dead] { D# x_a1UL ->
         case sc2_s4eP of _ [Occ=Dead] { D# y_a1UP -> +## x_a1UL y_a1UP }
         }
     }
 end Rec }
 }}}
 If we ran `SpecConstr` again we'd specialise this function, because the
 recursive calls both have boxed arguments.

 I looked into why `SpecConstr` didn't catch it, and it's because
 `SpecConstr`'s input looks like this
 {{{
             case case tagToEnum# @ Bool (<=## x_a1Th y_a1Tl) of _
 [Occ=Dead] {
                    False -> (wild1_a1Tj, wild_a1Tf);
                    True -> wild_X8
                  }
             of r_s4e0 { (ipv_s4e1, ipv_s4e2) ->
             $wfoo_s4db (I# (-# ds_X1SR 1#)) (Just @ (Double, Double)
 r_s4e0)
 }}}
 Notice the case-of-case which doesn't expose the `Double` boxes of
 arguments to `$wfoo`.

 Why is that case-of-case still there?  Because of `Note [Single-
 alternative cases]` in Simplify.  Which is clearly a delicate spot so I
 don't want to meddle with it today. But it's intriguing. Maybe Sequent
 Core will do better.

 Note that late demand analysis also catches this case, yielding the
 (rather good)
 {{{
 Rec {
 Main.$w$s$wfoo [InlPrag=[0], Occ=LoopBreaker]
   :: Int# -> Double# -> Double# -> Double#
 [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType <S,1*U><L,U><L,U>]
 Main.$w$s$wfoo =
   \ (w_s4gW :: Int#) (ww_s4h1 :: Double#) (ww1_s4h5 :: Double#) ->
     case w_s4gW of ds_X1SW {
       __DEFAULT ->
         case tagToEnum# @ Bool (<=## ww_s4h1 ww1_s4h5) of _ [Occ=Dead] {
           False -> Main.$w$s$wfoo (-# ds_X1SW 1#) ww1_s4h5 ww_s4h1;
           True -> Main.$w$s$wfoo (-# ds_X1SW 1#) ww_s4h1 ww1_s4h5
         };
       0# -> +## ww_s4h1 ww1_s4h5
     }
 end Rec }
 }}}
 I'm pretty sure that late-demand-analysis should be on with `-O2` but
 someone should do a nofib run to check.

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


More information about the ghc-tickets mailing list