[GHC] #14844: SpecConstr also non-recursive function

GHC ghc-devs at haskell.org
Mon Mar 19 19:45:20 UTC 2018


#14844: SpecConstr also non-recursive function
-------------------------------------+-------------------------------------
        Reporter:  nomeata           |                Owner:  (none)
            Type:  task              |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.5
      Resolution:                    |             Keywords:  SpecConstr
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 nomeata):

 And here some details on the second point. After the first run of
 SpecConstr, we have somthing like this
 {{{
 $w$lf_s6DU [InlPrag=NOUSERINLINE[0]]
   :: Double -> Double -> GHC.Prim.Int# -> (# Double, Double #)
 [LclId, Arity=3, Str=<L,U(U)><L,U(U)><S,U>m]
 $w$lf_s6DU
   = \ (ww_s6AD :: Double)
       (ww_s6AE :: Double)
       (ww_s6AI :: GHC.Prim.Int#) ->
       joinrec {
         $s$l$w$lf_s6Hv :: GHC.Prim.Int# -> GHC.Prim.Double# ->
 GHC.Prim.Double# -> (# Double, Double #)
         [LclId[JoinId(3)], Arity=3, Str=<L,U><L,U><L,U>]
         $s$l$w$lf_s6Hv (sc_s6Hu :: GHC.Prim.Int#)
                        (sc_s6Ht :: GHC.Prim.Double#)
                        (sc_s6Hs :: GHC.Prim.Double#)
 …

         $l$w$lf_X6Ep [Occ=LoopBreaker] :: Double -> Double ->
 GHC.Prim.Int# -> (# Double, Double #)
         [LclId[JoinId(3)],
          Arity=3,
          RULES: "SC:$l$w$lf0"
                     forall (sc_s6Hu :: GHC.Prim.Int#)
                            (sc_s6Ht :: GHC.Prim.Double#)
                            (sc_s6Hs :: GHC.Prim.Double#).
                       $l$w$lf_X6Ep (GHC.Types.D# sc_s6Hs) (GHC.Types.D#
 sc_s6Ht) sc_s6Hu
                       = jump $s$l$w$lf_s6Hv sc_s6Hu sc_s6Ht sc_s6Hs]
         $l$w$lf_X6Ep (ww_X6B9 [Dmd=<L,U(U)>] :: Double)
                      (ww_X6Bb [Dmd=<L,U(U)>] :: Double)
                      (ww_X6Bg [Dmd=<S,U>] :: GHC.Prim.Int#)
 …
             }; } in
       jump $l$w$lf_X6Ep ww_s6AD ww_s6AE ww_s6AI
 …
 …
 …
                                              case $w$lf_s6DU
                                                     (GHC.Types.D#
 (GHC.Prim.cosDouble# wild2_a5jY))
                                                     (GHC.Types.D#
 (GHC.Prim.sinDouble# wild2_a5jY))
                                                     wild_XM
                                              of

 }}}

 We can clearly see that `$w$lf_s6DU` has been loopified, with a local
 joinrec `$l$w$lf_X6Ep`, and that this local join rec `$l$w$lf_X6Ep` has
 been !SpecConstr’ed to `$s$l$w$lf_s6Hv`.

 But why does `$w$lf_s6DU` not get `SpecConstr’ed? Because of
 {{{
 specialise entry {
   $w$lf_s6DU [$w$lf_s6DU (D# (cosDouble# wild2_a5jY))
                          (D# (sinDouble# wild2_a5jY)) wild_XM]
 callToPats
   [D# (cosDouble# wild2_a5jY), D# (sinDouble# wild2_a5jY), wild_XM]
   [unk-occ, unk-occ, unk-occ]
 }}}
 which means that it sees the calls passing constructors, but it does not
 know that the arguments (e.g. `ww_s6AD`) get scrutinizes, so it does not
 act on this.

 After simplification, however, we have
 {{{
 $w$lf_s6DU [InlPrag=NOUSERINLINE[0]]
   :: Double -> Double -> GHC.Prim.Int# -> (# Double, Double #)
 [LclId,
  Arity=3,
  Str=<L,U(U)><L,U(U)><S,U>m,
  RULES: "SC:$w$lf0" [0]
             forall (sc_s6KF :: GHC.Prim.Int#)
                    (sc_s6KE :: GHC.Prim.Double#)
                    (sc_s6KD :: GHC.Prim.Double#).
               $w$lf_s6DU (GHC.Types.D# sc_s6KD) (GHC.Types.D# sc_s6KE)
 sc_s6KF
               = $s$w$lf_s6KG sc_s6KF sc_s6KE sc_s6KD]
 $w$lf_s6DU
   = \ (ww_s6AD :: Double)
       (ww_s6AE :: Double)
       (ww_s6AI :: GHC.Prim.Int#) ->
       joinrec {
         $s$l$w$lf_s6Hv [Occ=LoopBreaker]
           :: GHC.Prim.Int#
              -> GHC.Prim.Double# -> GHC.Prim.Double# -> (# Double, Double
 #)
 …
             }; } in
       case ww_s6AD of ww3_s6DY { GHC.Types.D# ww4_s6DZ ->
       case ww_s6AE of ww5_s6E1 { GHC.Types.D# ww6_s6E2 ->
       case GHC.Prim.remInt# ww_s6AI 2# of {
         __DEFAULT ->
           case ww_s6AI of wild_X11 {
 …
 }}}
 i.e. `$l$w$lf_X6Ep` has been inlined and thus exposed a case analysis of
 ww_s6AD, and now `$w$lf_s6DU` gets specialized as expected.

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


More information about the ghc-tickets mailing list