Re: [GHC] #5767: Integer inefficiencies

2012-01-26 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  igloo   
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.4.1   
 Component:  Compiler |Version:  7.5 
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by PHO):

 * cc: pho@… (added)


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


Re: [GHC] #5767: Integer inefficiencies

2012-01-16 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  igloo   
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.4.1   
 Component:  Compiler |Version:  7.5 
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by simonpj):

 Note: the call to `smallInteger` arises from the `fromIntegral` method of
 `Integral Int` (in `base:GHC.Real`):
 {{{
 instance  Integral Int  where
 toInteger (I# i) = smallInteger i
 }}}
 So, yes we need a `integerToInt (smallInteger n)` RULE.

 Ditto `int64ToInteger` and `wordToInteger`.

 Also we'd like a RULE for `(smallInteger (I# n)`, which should generate an
 `Integer` literal.  This isn't easy right now for tiresome reasons.  !ToDo
 for 7.6.  The most plausible route for doing it is to take `mkIntegerLit`
 out of `Integer` literals, and keep it somewhere global instead.

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


Re: [GHC] #5767: Integer inefficiencies

2012-01-15 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  igloo   
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.4.1   
 Component:  Compiler |Version:  7.5 
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * owner:  = igloo
  * priority:  normal = highest
  * milestone:  = 7.4.1


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


Re: [GHC] #5767: Integer inefficiencies

2012-01-15 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  igloo   
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.4.1   
 Component:  Compiler |Version:  7.5 
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by rl):

 I finally found a small test case for the missing
 `integerToInt/smallInteger` rule:

 {{{
 foo :: (Integral a, Num a) = a - a
 {-# INLINE foo #-}
 foo x = fromIntegral x

 bar :: Int - Int
 bar x = foo x
 }}}

 The head generates this:

 {{{
 foo_$sfoo =
   \ (eta_B1 :: Int) -
 case eta_B1 of _ { I# i_ara -
 case integerToInt (smallInteger i_ara) of wild1_ard { __DEFAULT -
 I# wild1_ard
 }
 }

 bar = foo_$sfoo
 }}}

 Whereas 7.2.2 generates this:

 {{{
 bar_$sfoo = \ (eta_B1 :: Int) - eta_B1

 bar = bar_$sfoo
 }}}

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


Re: [GHC] #5767: Integer inefficiencies

2012-01-14 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.5 
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by rl):

  * status:  closed = new
  * resolution:  fixed =


Comment:

 I'm still seeing a regression compared to GHC 7.2.2 in this bit of Core:

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

 As I said, adding an `integerToInt/smallInteger` rule should help.

 Note also that without the `INLINE` pragma on `foo`, both 7.2.2 and now
 the HEAD generate this code for my original example:

 {{{
 bar1 :: Int
 bar1 =
   case GHC.Float.$w$cproperFraction @ Int GHC.Real.$fIntegralInt 51.0
   of _ { (# ww1_arU, _ #) - ww1_arU }

 bar :: Int - Int
 bar = \ (x_a9P :: Int) - plusInt bar1 x_a9P
 }}}

 This isn't a regression but doesn't seem right.

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


Re: [GHC] #5767: Integer inefficiencies

2012-01-13 Thread GHC
#5767: Integer inefficiencies
-+--
Reporter:  rl|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.5
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 I can see why this is.  Stay tuned

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


Re: [GHC] #5767: Integer inefficiencies

2012-01-13 Thread GHC
#5767: Integer inefficiencies
-+--
Reporter:  rl|   Owner: 
Type:  bug   |  Status:  merge  
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.5
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * status:  new = merge


Comment:

 Fixed by
 {{{
 commit 1074c2da93cc89cd183375ae414a18dc536a7b5d
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Fri Jan 13 15:46:56 2012 +

 Get the knownKeyNames for doubleFromInteger right

 There was a trivial typo which meant that important
 newly-added rules would never fire!

  compiler/prelude/PrelNames.lhs |8 
  1 files changed, 4 insertions(+), 4 deletions(-)
 }}}
 Ian, please merge; and perhaps add a test?

 Simon

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


Re: [GHC] #5767: Integer inefficiencies

2012-01-13 Thread GHC
#5767: Integer inefficiencies
--+-
  Reporter:  rl   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.5 
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Good spot; merged as 102df6a7bc5657eef85f26d88ab6c071ec9b0b24 and I've
 added more cases covering this to `integerConstantFolding`.

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


[GHC] #5767: Integer inefficiencies

2012-01-12 Thread GHC
#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