[GHC] #6087: Join points need strictness analysis

GHC ghc-devs at haskell.org
Fri Feb 9 07:31:47 UTC 2018


#6087: Join points need strictness analysis
-------------------------------------+-------------------------------------
        Reporter:  simonpj           |                Owner:  (none)
            Type:  bug               |               Status:  infoneeded
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  7.4.1
      Resolution:                    |             Keywords:  JoinPoints
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by osa1):

 I looked at `cse` and `circsim` which are smaller programs with increased
 allocation.

 Really the only difference I could find after a few hours of investigation
 is with `-flate-dmd-anal` we get new worker functions that return head and
 tail of a list in an unboxed tuple instead of returning a list. As far as
 I can see, the result is almost always packed back to a list at some point
 (somehwere in upper levels in the call stack). Overall the allocation
 should stay the same (because we allocate same number of cons cells, but
 allocate them in different places than we would without `-flate-dmd-
 anal`), so maybe this doesn't explain the allocation increase. Here's an
 example from `cse`, this is without late demand analysis:

 {{{
 $wgo1_r6PF :: [GHC.Types.Char] -> GHC.Prim.Int# -> [GHC.Types.Char]
 [GblId, Arity=2, Str=<S,1*U><S,1*U>m2, Unf=OtherCon []] =
     sat-only [] \r [w_s6Uz ww_s6UA]
         case w_s6Uz of {
           [] -> $wxs1_r6PE ww_s6UA;
           : y_s6UC [Occ=Once*] ys_s6UD [Occ=Once] ->
               case ww_s6UA of ds11_s6UE {
                 __DEFAULT ->
                     let {
                       sat_s6UG [Occ=Once] :: [GHC.Types.Char]
                       [LclId] =
                           [ys_s6UD ds11_s6UE] \u []
                               case -# [ds11_s6UE 1#] of sat_s6UF {
                                 __DEFAULT -> $wgo1_r6PF ys_s6UD sat_s6UF;
                               };
                     } in  : [y_s6UC sat_s6UG];
                 1# -> : [y_s6UC n_r6Py];
               };
         };
 }}}

 We generate this version with `-flate-dmd-anal`:

 {{{
 $w$wgo_r6Yf :: [GHC.Types.Char] -> GHC.Prim.Int# -> (# GHC.Types.Char,
 [GHC.Types.Char] #)
 [GblId, Arity=2, Str=<S,1*U><S,1*U>, Unf=OtherCon []] =
     sat-only [] \r [w_s73c w1_s73d]
         case w_s73c of {
           [] -> $w$wxs_r6Ye w1_s73d;
           : y_s73f [Occ=Once*] ys_s73g [Occ=Once] ->
               case w1_s73d of ds11_s73h {
                 __DEFAULT ->
                     let {
                       sat_s73m [Occ=Once] :: [GHC.Types.Char]
                       [LclId] =
                           [ys_s73g ds11_s73h] \u []
                               case -# [ds11_s73h 1#] of sat_s73i {
                                 __DEFAULT ->
                                     case $w$wgo_r6Yf ys_s73g sat_s73i of {
                                       (#,#) ww1_s73k [Occ=Once] ww2_s73l
 [Occ=Once] ->
                                           : [ww1_s73k ww2_s73l];
                                     };
                               };
                     } in  (#,#) [y_s73f sat_s73m];
                 1# -> (#,#) [y_s73f n_r6Y9];
               };
         };
 }}}

 Notice that in the recursive case we do the same thing in both cases, but
 with `-flate-dmd-anal` we pack the result in call site rather than
 returning packed result in the recursive call. The call sites look like
 this: (large code, pasting only the relevant parts)

 {{{
 let {
   sat_s757 [Occ=Once, Dmd=<L,1*U>] :: [GHC.Types.Char]
   [LclId] =
       [ww_s751] \s []
           case $w$wgo_r6Yf ww_s751 4# of {
             (#,#) ww3_s755 [Occ=Once] ww4_s756 [Occ=Once] ->
                 : [ww3_s755 ww4_s756];
           };
 } in  GHC.Base.++ ds10_r6Y7 sat_s757;
 }}}

 So we directly pack it again. Same transformation happens in `circsim`
 too. New worker:

 {{{
 $w$wxs_rb9n :: GHC.Prim.Int# -> (# Main.Boolean, [Main.Boolean] #)
 [GblId, Arity=1, Caf=NoCafRefs, Str=<S,1*U>, Unf=OtherCon []] =
     sat-only \r [w_sbe6]
         case w_sbe6 of ds1_sbe7 {
           __DEFAULT ->
               let {
                 sat_sbec [Occ=Once] :: [Main.Boolean]
                 [LclId] =
                     \u []
                         case -# [ds1_sbe7 1#] of sat_sbe8 {
                           __DEFAULT ->
                               case $w$wxs_rb9n sat_sbe8 of {
                                 (#,#) ww1_sbea [Occ=Once] ww2_sbeb
 [Occ=Once] ->
                                     : [ww1_sbea ww2_sbeb];
                               };
                         };
               } in  (#,#) [Main.T sat_sbec];
           1# -> (#,#) [Main.T GHC.Types.[]];
         };
 }}}

 exactly the same thing, recursive case directly packs the result. Call
 site:

 {{{
 case
     $w$wxs_rb9n y1_sbA8
 of
 { (#,#) ww1_sbAc [Occ=Once] ww2_sbAd [Occ=Once] ->
       : [ww1_sbAc ww2_sbAd];
 };
 }}}

 again result is directly packed.

 This happens in several places in both programs.

 I compared outputs both by mapping STG functions in outputs to each other
 manually and comparing the definitions, and also by using a diff tool to
 see if there are any extra code blocks etc. other than the ones I've
 already checked manually. These changes seem to be all unless I'm missing
 anything.

 I wonder what happens if I disable CPR in post-late-ww pass and only do
 worker-wrapper (not sure if it's currently possible but in theory it
 should be?). This should avoid the transformations described above,
 maybele  still winning in the other cases?

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


More information about the ghc-tickets mailing list