#5767: Integer inefficiencies
-------------------------------------+--------------------------------------
 Reporter:  rl                       |          Owner:                  
     Type:  bug                      |         Status:  new             
 Priority:  normal                   |      Component:  Compiler        
  Version:  7.5                      |       Keywords:                  
       Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |       Testcase:                  
Blockedby:                           |       Blocking:                  
  Related:                           |  
-------------------------------------+--------------------------------------
 Here is a small program:

 {{{
 module T where
 foo :: RealFrac a => a -> a -> Int
 {-# INLINE [0] foo #-}
 foo x y = truncate $ (y-x)+2

 module U where
 import T
 bar :: Int -> Int
 bar x = foo 1 50 + x
 }}}

 GHC 7.2.2 generates this optimal code:

 {{{
 bar = \ (x_abs :: Int) -> case x_abs of _ { I# y_auX -> I# (+# 51 y_auX) }
 }}}

 Whereas the current HEAD generates this:

 {{{
 bar2 :: Integer
 bar2 = __integer 2

 bar1 :: Int
 bar1 =
   case doubleFromInteger bar2
   of wild_arl { __DEFAULT -> I# (double2Int# (+## 49.0 wild_arl)) }

 bar :: Int -> Int
 bar = \ (x_a9S :: Int) -> plusInt bar1 x_a9S
 }}}

 If I remove the INLINE pragma from `foo`, the HEAD generates this:

 {{{
 bar1 :: Int
 bar1 =
   case doubleFromInteger foo1
   of wild_asr { __DEFAULT ->
   case GHC.Float.$w$cproperFraction
          @ Int GHC.Real.$fIntegralInt (+## 49.0 wild_asr)
   of _ { (# ww1_as1, _ #) ->
   ww1_as1
   }
   }

 bar :: Int -> Int
 bar = \ (x_a9W :: Int) -> plusInt bar1 x_a9W
 }}}

 Interestingly, without the INLINE pragma 7.2.2 doesn't fare much better.

 I've also seen this bit in the generated code with the HEAD but not with
 7.2.2:

 {{{
 case integerToInt (smallInteger a_s2jL) of wild_a1dA { __DEFAULT -> f
 wild_a1dA }
 }}}

 I couldn't boil it down to a small test case yet but it leads to a
 significant performance regression in at least one `vector` benchmark. I
 suppose fixing this is only a matter of adding an
 `integerToInt/smallInteger` rule.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to