[GHC] #6087: Join points need strictness analysis

GHC ghc-devs at haskell.org
Wed Feb 14 14:47:01 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):

 > cse and circsim really do allocate (a little) more. But in your
 investigation you didn't find any allocation differences. Doesn't -ticky
 nail it for you?

 Just compared original vs. late demand analysis version of the same
 function in mate with help from ticky profiler and found the source of
 allocation.

 (the function is huge, copying the important bits. Both functions have
 same number of entries)

 Original function, important bit is how the second argument (Int) used:

 {{{
 $warg_sciK [InlPrag=NOUSERINLINE[0],
             Occ=OnceL*!,
             Dmd=<L,C(C1(C1(C1(U))))>]
   :: Board.Kind
      -> GHC.Types.Int
      -> GHC.Types.Int
      -> GHC.Types.Bool
      -> GHC.Types.Bool
 [LclId,
  Arity=4,
  Str=<S,1*U><S(S),U(U)><L,U(U)><L,1*U>,
  Unf=OtherCon []] =
     sat-only [w_scin
               ww_scio
               ww1_scip
               ds_sciq
               lvl17_scis
               lvl18_sciB] \r [ww2_sciL ww3_sciM ww4_sciN w1_sciO]
         let {
           lvl19_sciP [Occ=Once*!, Dmd=<L,1*U>] :: GHC.Types.Bool
           [LclId] =
               [ww_scio ww1_scip ds_sciq ww3_sciM] \s []
                   let {
                     lvl20_sciQ [Occ=OnceL*!, Dmd=<L,U(U)>] ::
 GHC.Types.Int
                     [LclId] =
                         [ds_sciq ww3_sciM] \u []
                             case ww3_sciM of wild_sciR {
                               GHC.Types.I# x1_sciS [Occ=Once] ->
                                   case ds_sciq of {
                                     (,) xk_sciU [Occ=Once!] _ [Occ=Dead]
 ->
                                         case xk_sciU of wild2_sciW {
                                           GHC.Types.I# y1_sciX [Occ=Once]
 ->
                                               case <=# [x1_sciS y1_sciX]
 of {
                                                 __DEFAULT -> wild_sciR;
                                                 1# -> wild2_sciW;
                                               };
                                         };
                                   };
                             }; } in
                   let {
                     lvl21_sciZ [Occ=OnceL*!, Dmd=<L,U(U)>] ::
 GHC.Types.Int
                     [LclId] =
                         [ds_sciq ww3_sciM] \u []
                             case ww3_sciM of wild_scj0 {
                               GHC.Types.I# x1_scj1 [Occ=Once] ->
                                   case ds_sciq of {
                                     (,) xk_scj3 [Occ=Once!] _ [Occ=Dead]
 ->
                                         case xk_scj3 of wild2_scj5 {
                                           GHC.Types.I# y1_scj6 [Occ=Once]
 ->
                                               case <=# [x1_scj1 y1_scj6]
 of {
                                                 __DEFAULT -> wild2_scj5;
                                                 1# -> wild_scj0;
                                               };
                                         };
                                   };
                             }; } in ...
 }}}

 It's used strictly, but also returned in boxed form in `__DEFAULT` case of
 first case expression and `1#` case of the second.

 Now with late demand analysis:

 {{{
 $w$warg_sd96 [InlPrag=NOUSERINLINE[0],
               Occ=OnceL*!,
               Dmd=<L,C(C1(C1(C1(U))))>]
   :: Board.Kind
      -> GHC.Prim.Int#
      -> GHC.Types.Int
      -> GHC.Types.Bool
      -> GHC.Types.Bool
 [LclId,
  Arity=4,
  Str=<S,1*U><S,U><L,U(U)><L,1*U>,
  Unf=OtherCon []] =
     sat-only [w_sd8J
               ww_sd8K
               ww1_sd8L
               ds_sd8M
               lvl17_sd8O
               lvl18_sd8X] \r [w1_sd97 ww2_sd98 w2_sd99 w3_sd9a]
         let {
           ww3_sd9b [Dmd=<L,U(U)>] :: GHC.Types.Int
           [LclId, Unf=OtherCon []] =
               CCCS GHC.Types.I#! [ww2_sd98]; } in
         let {
           lvl19_sd9c [Occ=Once*!, Dmd=<L,1*U>] :: GHC.Types.Bool
           [LclId] =
               [ww_sd8K ww1_sd8L ds_sd8M ww2_sd98 ww3_sd9b] \s []
                   let {
                     lvl20_sd9d [Occ=OnceL*!, Dmd=<L,U(U)>] ::
 GHC.Types.Int
                     [LclId] =
                         [ds_sd8M ww2_sd98 ww3_sd9b] \u []
                             case ds_sd8M of {
                               (,) xk_sd9f [Occ=Once!] _ [Occ=Dead] ->
                                   case xk_sd9f of wild1_sd9h {
                                     GHC.Types.I# y1_sd9i [Occ=Once] ->
                                         case <=# [ww2_sd98 y1_sd9i] of {
                                           __DEFAULT -> ww3_sd9b;
                                           1# -> wild1_sd9h;
                                         };
                                   };
                             }; } in
                   let {
                     lvl21_sd9k [Occ=OnceL*!, Dmd=<L,U(U)>] ::
 GHC.Types.Int
                     [LclId] =
                         [ds_sd8M ww2_sd98 ww3_sd9b] \u []
                             case ds_sd8M of {
                               (,) xk_sd9m [Occ=Once!] _ [Occ=Dead] ->
                                   case xk_sd9m of wild1_sd9o {
                                     GHC.Types.I# y1_sd9p [Occ=Once] ->
                                         case <=# [ww2_sd98 y1_sd9p] of {
                                           __DEFAULT -> wild1_sd9o;
                                           1# -> ww3_sd9b;
                                         };
                                   };
                             }; } in ...
 }}}

 now the second argument is `Int#` instead of `Int` as before, but we pack
 it in the first `let` because we need to return it boxed (`_DEFAULT` case
 of first case expression and `1#` case of the second case).

 This is the only extra source of allocation in mate as far as I can see
 from the ticky output so this should be responsible for 5% increase in
 `mate`.

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


More information about the ghc-tickets mailing list