#3034: divInt# floated into a position which leads to low arity
-------------------------------------+--------------------------------------
Reporter:  batterseapower            |          Owner:                  
    Type:  run-time performance bug  |         Status:  new             
Priority:  normal                    |      Component:  Compiler        
 Version:  6.10.1                    |       Severity:  normal          
Keywords:                            |       Testcase:                  
      Os:  Unknown/Multiple          |   Architecture:  Unknown/Multiple
-------------------------------------+--------------------------------------
 Tyson Whitehead saw this in the Core output of one of his programs
 compiled using the MTL StateT:

 {{{
 $wdigit_s1GR [ALWAYS LoopBreaker Nothing] :: GHC.Prim.Int#
                                            -> GHC.Types.Int
                                            ->
 Control.Monad.State.Strict.StateT
                                                 GHC.Types.Int
 (Control.Monad.Error.ErrorT
                                                    GHC.Base.String
 Control.Monad.Identity.Identity)
                                                 (GHC.Types.Int,
 GHC.Types.Int)
 [Arity 1
 Str: DmdType L]
 $wdigit_s1GR =
 \ (ww_X1H6 :: GHC.Prim.Int#) ->
   let {
     lvl_s1H5 [ALWAYS Just D(T)] :: GHC.Types.Int
     [Str: DmdType]
     lvl_s1H5 =
       case GHC.Prim.-# 2147483647 ww_X1H6 of wild2_a1xs [ALWAYS Just L] {
         __DEFAULT ->
           case GHC.Base.divInt# wild2_a1xs 10
           of wild21_a1xt [ALWAYS Just L] { __DEFAULT ->
           GHC.Types.I# wild21_a1xt
           };
         (-2147483648) -> lvl_s1Ha
       } } in
   (\ (eta_X1nK :: GHC.Types.Int) (eta_s1Dl :: GHC.Types.Int) ->
      case eta_s1Dl
      of y_XrP [ALWAYS Just A] { GHC.Types.I# ipv_s19d [ALWAYS Just L] ->
      case GHC.Prim.<=# ipv_s19d 214748363
      of wild_a19h [ALWAYS Dead Just A] {
        GHC.Bool.False ->
          case lvl_s1H5
          of wild1_X1zB [ALWAYS Just A]
          { GHC.Types.I# y_X1zG [ALWAYS Just L] ->
          case GHC.Prim.<=# ipv_s19d y_X1zG
          of wild_X1z [ALWAYS Dead Just A] {
            GHC.Bool.False ->
              a_s1Hk
              `cast` (right
 }}}

 This REALLY SHOULD have arity 3 because that allows:
  * More worker/wrapper
  * Less sharing of trivial partial applications elsewhere in his program

 Here is my reply to him, explaining why it all happens:

 {{{
 Yes - GHC wants to share the work of (maxBound-x)`div`10 between
 several partial applications of "digit". This is usually a good idea,
 but in this case it sucks because it's resulted in a massively
 increased arity. IMHO GHC should fix this by:
 * Marking divInt# INLINE in the base library. This would result in
 your code would just containing uses of quotInt#
 * Making some operations cheap even if they may fail
 (PrimOp.primpOpIsCheap should change). Though this might mean that we
 turn non-terminating programs into terminating ones (such operations
 get pushed inside lambdas) but this is consistent with our treatment
 of lambdas generally.

 Actually, your divInt# call wouldn't even usually be floated out to
 between two lambdas, but at the time FloatOut runs there is something
 in between the \x lambda and the lambdas from the state monad - the
 monadic bind operator! So FloatOut feels free to move the computation
 for "x" up even though that >>= will go away as soon as we run the
 simplifier. What a disaster!
 }}}

 So one of FloatOut and primOpIsCheap probably needs to be fixed.

 I've attached a program that can reproduce this issue.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3034>
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