#5535: Performance regression vs. 7.2.1
---------------------------------+------------------------------------------
    Reporter:  simonmar          |       Owner:  igloo           
        Type:  bug               |      Status:  new             
    Priority:  highest           |   Milestone:  7.4.1           
   Component:  Compiler          |     Version:  7.2.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------
Changes (by igloo):

  * difficulty:  => Unknown


Comment:

 OK, I think the essence of the problem is here:
 {{{
 {-# LANGUAGE MagicHash, UnboxedTuples #-}

 module Q (whenDiverge) where

 import GHC.Base
 import GHC.Integer

 whenDiverge :: Int -> Int -> Double -> Bool
 whenDiverge limit radius d
   = walkIt (replicate limit d)
   where
      walkIt []              = True
      walkIt (x : _)
         | diverge x radius  = True
         | otherwise         = False

 diverge :: Double -> Int -> Bool
 diverge d radius = exponentDouble d > radius

 exponentDouble :: Double -> Int
 exponentDouble x = case decodeDouble x of
                    (m,n) -> if m == (0 :: Integer)
                             then (0 :: Int)
                             else n + floatDigits x

 decodeDouble :: Double -> (Integer, Int)
 decodeDouble (D# x#) = case decodeDoubleInteger x# of
                        (# i, j #) -> (i, I# j)
 }}}

 When compiled with 7.2.1 `-O2`, the two top-level functions (`whenDiverge`
 and its wrapper) have `Caf=NoCafRefs`. When compiled with HEAD, they
 don't. It looks like the problem is the `(0 :: Integer)` literal, which
 under the hood uses `GHC.Integer.Type.mkInteger`, which calls
 `negateInteger`, which has a CAF for the (minBound :: Int) case.

 So I changed it not to use a CAF:
 {{{
 -negateInteger (S# INT_MINBOUND) = NEG_INT_MINBOUND
 +negateInteger i@(S# INT_MINBOUND) = negateInteger (toBig i)
 }}}
 and now `negateInteger` and `mkInteger` have `HasNoCafRefs` in the
 `GHC.Integer.Type` interface file, but `whenDiverge` still doesn't have
 it.

 Simon, any idea what's going wrong please?

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