#4941: SpecConstr generates functions that do not use their arguments
---------------------------------+------------------------------------------
    Reporter:  simonpj           |        Owner:                         
        Type:  task              |       Status:  new                    
    Priority:  normal            |    Milestone:  _|_                    
   Component:  Compiler          |      Version:  7.0.1                  
    Keywords:                    |     Testcase:                         
   Blockedby:                    |   Difficulty:                         
          Os:  Unknown/Multiple  |     Blocking:                         
Architecture:  Unknown/Multiple  |      Failure:  Runtime performance bug
---------------------------------+------------------------------------------
Changes (by batterseapower):

  * failure:  None/Unknown => Runtime performance bug


Comment:

 I added this after SpecConstr:

 {{{
         -- Attempt to clean up dead bindings introduced by SpecConstr with
 another
         -- round of absence analysis and simplification
         runWhen strictness (CoreDoPasses [
                 simpl_phase 0 ["pre-final-strictness"] max_iter,
                 CoreDoStrictness,
                 CoreDoWorkerWrapper,
                 CoreDoGlomBinds
                 ]),
 }}}

 And it does indeed fix the rubbish left in STUArray-Rewrite2 after #4945
 is fixed. Even though the absent arguments in that example are invariant
 around the inner loop (so keeping them around doesn't cause allocation in
 the inner loop), the outer loop *can* usefully avoid allocating thunks for
 those arguments, because it calls the inner loop a few different ways.

 Another argument for doing strictness analysis after SpecConstr is that
 some of the specialisations might be strict in a way that the non-
 specialised version is not. A concrete example of this is the Tak program
 I sent you by email yesterday:

 {{{
 module Tak (tak) where

 tak' :: Int -> Int -> Int -> Bool -> Int
 tak' x y z b = if b
               then z
               else tak (let x' = x-1 in tak' x' y z (not (y < x')))
                        (let y' = y-1 in tak' y' z x (not (z < y')))
                        (let z' = z-1 in tak' z' x y (not (x < z')))

 tak :: Int -> Int -> Int -> Int
 tak x y z = tak' x y z (not (y < x))
 }}}

 If we do strictness analysis after SpecConstr (compile with @-O2 -fspec-
 constr-count=4@), we are able to totally unbox all Int to Int# in this
 program because the specialisations specialise tak' on whether the last
 (boolean) argument is True or False!

 Parenthetical remark: actually, even with this change the resulting Tak
 program contains some stupidity in the form of functions like this one:

 {{{
 $w$stak'1_rr8
   :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
 [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType LLL]
 $w$stak'1_rr8 =
   \ (w_sqz :: GHC.Prim.Int#)
     (w1_sqA :: GHC.Prim.Int#)
     (w2_sqB :: GHC.Prim.Int#) ->
     let {
       a_smv [Dmd=Just L] :: GHC.Prim.Int#
       [LclId, Str=DmdType]
       a_smv = GHC.Prim.-# w_sqz 1 } in
     let {
       a1_smt [Dmd=Just L] :: GHC.Prim.Int#
       [LclId, Str=DmdType]
       a1_smt = GHC.Prim.-# w1_sqA 1 } in
     let {
       y_smH [Dmd=Just U(L)] :: GHC.Types.Int
       [LclId, Str=DmdType m]
       y_smH =
         case GHC.Prim.<# w_sqz a1_smt of _ {
           GHC.Types.False -> GHC.Types.I# w2_sqB;
           GHC.Types.True ->
             case $w$stak'1_rr8 w2_sqB w_sqz a1_smt of ww_sqE { __DEFAULT
 ->
             GHC.Types.I# ww_sqE
             }
         } } in
     let {
       a2_smr [Dmd=Just L] :: GHC.Prim.Int#
       [LclId, Str=DmdType]
       a2_smr = GHC.Prim.-# w2_sqB 1 } in
     let {
       x_smF [Dmd=Just U(L)] :: GHC.Types.Int
       [LclId, Str=DmdType m]
       x_smF =
         case GHC.Prim.<# w1_sqA a2_smr of _ {
           GHC.Types.False -> GHC.Types.I# w_sqz;
           GHC.Types.True ->
             case $w$stak'1_rr8 w_sqz w1_sqA a2_smr of ww_sqE { __DEFAULT
 ->
             GHC.Types.I# ww_sqE
             }
         } } in
     case GHC.Prim.<# w2_sqB a_smv of _ {
       GHC.Types.False ->
         case y_smH of _ { GHC.Types.I# x1_Xmg ->
         case x_smF of _ { GHC.Types.I# y1_Xmo ->
         case GHC.Prim.<# x1_Xmg y1_Xmo of _ {
           GHC.Types.False -> w1_sqA;
           GHC.Types.True -> $w$stak'1_rr8 w1_sqA x1_Xmg y1_Xmo
         }
         }
         };
       GHC.Types.True ->
         case y_smH of _ { GHC.Types.I# x1_Xmg ->
         case x_smF of _ { GHC.Types.I# y1_Xmo ->
         case GHC.Prim.<# x1_Xmg y1_Xmo of _ {
           GHC.Types.False -> $w$stak'1_rr8 w1_sqA w2_sqB a_smv;
           GHC.Types.True ->
             case $w$stak'1_rr8 w1_sqA w2_sqB a_smv of ww_sqE { __DEFAULT
 ->
             Tak.$w$stak' ww_sqE x1_Xmg y1_Xmo
             }
         }
         }
         }
     }
 }}}

 You can see that e.g. y_smH allocates a I# box explicitly, which is then
 explicitly demanded in both branches of the case! What is going on?? This
 pattern occurs no less than 4 times in the tidied core output.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to