Re: [GHC] #2289: Needless reboxing of values when returning from a tight loop

2012-10-23 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|   Owner:   
  
Type:  bug |  Status:  new  
  
Priority:  lowest  |   Milestone:  7.6.2
  
   Component:  Compiler| Version:  6.8.2
  
Keywords:  boxing, loops, performance  |  Os:  Unknown/Multiple 
  
Architecture:  Unknown/Multiple| Failure:  Runtime performance 
bug
  Difficulty:  Unknown |Testcase:   
  
   Blockedby:  |Blocking:   
  
 Related:  |  
---+
Changes (by alpmestan):

 * cc: alpmestan@… (added)


-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2012-09-20 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|   Owner:   
  
Type:  bug |  Status:  new  
  
Priority:  lowest  |   Milestone:  7.6.2
  
   Component:  Compiler| Version:  6.8.2
  
Keywords:  boxing, loops, performance  |  Os:  Unknown/Multiple 
  
Architecture:  Unknown/Multiple| Failure:  Runtime performance 
bug
  Difficulty:  Unknown |Testcase:   
  
   Blockedby:  |Blocking:   
  
 Related:  |  
---+
Changes (by jwlato):

 * cc: jwlato@… (added)


-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2012-07-05 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|   Owner:   
  
Type:  bug |  Status:  new  
  
Priority:  lowest  |   Milestone:  7.6.1
  
   Component:  Compiler| Version:  6.8.2
  
Keywords:  boxing, loops, performance  |  Os:  Unknown/Multiple 
  
Architecture:  Unknown/Multiple| Failure:  Runtime performance 
bug
  Difficulty:  Unknown |Testcase:   
  
   Blockedby:  |Blocking:   
  
 Related:  |  
---+
Changes (by akio):

 * cc: tkn.akio@… (added)


-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2012-05-28 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|   Owner:   
  
Type:  bug |  Status:  new  
  
Priority:  lowest  |   Milestone:  7.6.1
  
   Component:  Compiler| Version:  6.8.2
  
Keywords:  boxing, loops, performance  |  Os:  Unknown/Multiple 
  
Architecture:  Unknown/Multiple| Failure:  Runtime performance 
bug
  Difficulty:  Unknown |Testcase:   
  
   Blockedby:  |Blocking:   
  
---+

Comment(by simonpj@…):

 commit 4fa3f16ddb9fa8e5d59bde5354918a39e0430a74
 {{{
 Author: Simon Peyton Jones 
 Date:   Mon May 28 17:33:42 2012 +0100

 Be less aggressive about the result discount

 This patch fixes Trac #6099 by reducing the result discount in
 CoreUnfold.conSize.
 See Note [Constructor size and result discount] in CoreUnfold.

 The existing version is definitely too aggressive. Simon M found it an
 "unambiguous win" but it is definitely what led to the bloat. In a
 function
 with a lot of case branches, all returning a constructor, the discount
 could
 grow arbitrarily large.

 I also had to increase the -funfolding-creation-threshold from 450 to
 750,
 otherwise some functions that should inline simply never get an
 unfolding.
 (The massive result discount was allow the unfolding to appear
 before.)

 The nofib results are these, picking a handful of outliers to show.

 Program   SizeAllocs   Runtime   Elapsed  TotalMem
 

  fulsom  -0.5% -1.6% -2.8% -2.6%+31.1%
maillist  -0.2% -0.0%  0.09  0.09 -3.7%
  mandel  -0.4% +6.6%  0.12  0.12 +0.0%
nucleic2  -0.2%+18.5%  0.11  0.11 +0.0%
 parstof  -0.4% +4.0%  0.00  0.00 +0.0%
 

 Min  -0.9% -1.6%-19.7%-19.7% -3.7%
 Max  +0.3%+18.5% +2.7% +2.7%+31.1%
  Geometric Mean  -0.3% +0.4% -3.0% -3.0% +0.2%

 Turns out that nucleic2 has a function
   Main.$wabsolute_pos =
 \ (ww_s4oj :: Types.Tfo) (ww1_s4oo :: Types.FloatT)
   (ww2_s4op :: Types.FloatT) (ww3_s4oq :: Types.FloatT) ->
   case ww_s4oj
   of _
   { Types.Tfo a_a1sS b_a1sT c_a1sU d_a1sV e_a1sW f_a1sX g_a1sY
 h_a1sZ i_a1t0 tx_a1t1 ty_a1t2 tz_a1t3 ->
   (# case ww1_s4oo of _ { GHC.Types.F# x_a2sO ->
  case a_a1sS of _ { GHC.Types.F# y_a2sS ->
  case ww2_s4op of _ { GHC.Types.F# x1_X2y9 ->
  case d_a1sV of _ { GHC.Types.F# y1_X2yh ->
  case ww3_s4oq of _ { GHC.Types.F# x2_X2yj ->
  case g_a1sY of _ { GHC.Types.F# y2_X2yr ->
  case tx_a1t1 of _ { GHC.Types.F# y3_X2yn ->
  GHC.Types.F#
(GHC.Prim.plusFloat#
   (GHC.Prim.plusFloat#
  (GHC.Prim.plusFloat#
 (GHC.Prim.timesFloat# x_a2sO y_a2sS)
 (GHC.Prim.timesFloat# x1_X2y9 y1_X2yh))
  (GHC.Prim.timesFloat# x2_X2yj y2_X2yr))
   y3_X2yn)
  } } },

 ,
  )

 This is pretty big, but inlining it does get rid of that F#
 allocation.
 But we'll also get rid of it with deep CPR: Trac #2289. For now we
 just
 accept the change.

  compiler/coreSyn/CoreUnfold.lhs |   73
 ++-
  compiler/main/StaticFlags.hs|7 +++-
  2 files changed, 47 insertions(+), 33 deletions(-)
 }}}

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2011-03-16 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
   
Type:  bug |   Status:  new 
   
Priority:  low |Milestone:  7.2.1   
   
   Component:  Compiler|  Version:  6.8.2   
   
Keywords:  boxing, loops, performance  | Testcase:  
   
   Blockedby:  |   Difficulty:  Unknown 
   
  Os:  Unknown/Multiple| Blocking:  
   
Architecture:  Unknown/Multiple|  Failure:  Runtime performance 
bug
---+
Changes (by michalt):

 * cc: michal.terepeta@… (added)


-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2011-01-31 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
   
Type:  bug |   Status:  new 
   
Priority:  low |Milestone:  7.0.2   
   
   Component:  Compiler|  Version:  6.8.2   
   
Keywords:  boxing, loops, performance  | Testcase:  
   
   Blockedby:  |   Difficulty:  Unknown 
   
  Os:  Unknown/Multiple| Blocking:  
   
Architecture:  Unknown/Multiple|  Failure:  Runtime performance 
bug
---+
Changes (by tibbe):

 * cc: johan.tibell@… (added)


-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2009-11-11 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
Type:  run-time performance bug|   Status:  new 
Priority:  normal  |Milestone:  6.12 branch 
   Component:  Compiler|  Version:  6.8.2   
Severity:  normal  |   Resolution:  
Keywords:  boxing, loops, performance  |   Difficulty:  Unknown 
Testcase:  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Comment (by simonmar):

 I believe this example fits into the same category.  We have a recursive
 tree traversal in the `ST` monad that returns an `Int`, and we want the
 `Int` unboxed.  Here's the complete code, both the version that doesn't
 optimise as well as we'd like, and the hand-optimised version:

 {{{
 {-# LANGUAGE BangPatterns, UnboxedTuples, MagicHash #-}
 module Test where

 import Data.Array.ST
 import Control.Monad.ST
 import Data.Array.Base
 import GHC.ST
 import GHC.Exts

 data Tree
   = Nil
   | Node {-#UNPACK#-} !Int
   !Tree
   !Tree
  {-#UNPACK#-} !Int

 #if 0
 -- The code we want to write
 traverse :: Tree -> STUArray s Int Int -> ST s Int
 traverse Nil !arr = return 0
 traverse (Node item child alt w) !arr = do
   childw <- traverse child arr
   altw   <- traverse alt arr
   itemw <- unsafeRead arr item
   unsafeWrite arr item (itemw + childw + w)
   return $! childw + w + altw
 #else
 -- The code we have to write
 traverse :: Tree -> STUArray s Int Int -> ST s Int
 traverse tree arr = ST $ \s ->
   case traverse' tree arr s of { (# s', i #) -> (# s', I# i #) }
   where
   traverse' Nil !arr s  = (# s, 0# #)
   traverse' (Node item child alt w@(I# w#)) !arr s0 =
  case traverse' child arr s0 of { (# s1, childw #) ->
  case traverse' alt arr   s1 of { (# s2, altw   #) ->
  case unsafeRead arr item of { ST f -> case f s2 of { (# s3, I# itemw
 #) ->
  case unsafeWrite arr item (I# itemw + I# childw + w) of { ST f ->
 case f s2 of { (# s4, _ #) ->
  (# s4, childw +# w# +# altw #)
  }}
 #endif
 }}}

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2009-04-14 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
Type:  run-time performance bug|   Status:  new 
Priority:  normal  |Milestone:  6.12 branch 
   Component:  Compiler|  Version:  6.8.2   
Severity:  normal  |   Resolution:  
Keywords:  boxing, loops, performance  |   Difficulty:  Unknown 
Testcase:  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Comment (by simonpj):

 See also #2387, and #1600

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2009-04-12 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
Type:  run-time performance bug|   Status:  new 
Priority:  normal  |Milestone:  6.12 branch 
   Component:  Compiler|  Version:  6.8.2   
Severity:  normal  |   Resolution:  
Keywords:  boxing, loops, performance  |   Difficulty:  Unknown 
Testcase:  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Changes (by igloo):

  * milestone:  6.10 branch => 6.12 branch

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-08-28 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by guest):

 * cc: [EMAIL PROTECTED] (added)

Comment:

 New code generator may help:
 [http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/NewCodeGen]

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-07-17 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by simonpj):

 Don't hold your breath for unboxed sum types.  For example, if the `Bool`
 is `True`, the other two fields may be uninitialised, and should not be
 followed by the GC. I suppose if you were prepared to stubs initialised to
 `(error "Bad")`, then you could do this worker/wrapper split for `go`:
 {{{
 readInt :: String -> Maybe (Int, String)
 readInt s = case readInt_w s of
(# True,  n, s #) -> Nothing
(# False, n, s #) -> Just (n,s)

 readInt_w :: String -> (# Bool, Int, String #)
 readInt_w s = case  of
 Just (n,s) -> (# False, n, s #)
 Nothing-> (# True, error "BAD", error "BAD" #)
 }}}
 Things get harder if there are more constructors in the sum type, or the
 constructors have more arguments.

 Simon

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-07-16 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by dons):

 Another case we'd like genralised CPR to work is for sum types.

 Consider the task of summing integers from a file, one per line. We need
 to parse
 each line, returning possibly success, in a tight loop:

 {{{
 import qualified Data.ByteString.Char8 as S

 main = print . go 0 =<< S.getContents
   where
 go !n s = case S.readInt s of
   S.Nothing-> n
   S.Just (k,t) -> go (n+k) (S.tail t)
 }}}

 Where

 {{{
 readInt :: ByteString -> Maybe (Int, ByteString)
 }}}

 We'd like the Just/Nothing tag returned in a register, in an ideal world.
 And the components
 of the pair as well. Currently we have to monomorphise the type, and
 flatten it , to get register returns here.

 Note that Clean uses a triple of (Bool, Int, String) for this kind of
 thing.

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-06-30 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by igloo):

  * milestone:  => 6.10 branch

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-06-26 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by simonpj):

 See also #2387, which shows another example of the same phenomenon.  (I'm
 closing #2387 to leave just this one open.)

 Simon

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-19 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by simonpj):

 (Retrying, having messed up typesetting.)

 Rats. I'd forgotten about the strictness question:
 {{{
 f :: Int -> (Int,Int)
 f x = (g x, h x)
 }}}
 Suppose `g` and `h` have the CPR property -- that is, they explicitly
 return a boxed value.  Then it's a mistake to transform to
 {{{
 f x = case (g x, h x) of { (I# r1, I# r2) ->
   (I# r1 ,I# r2) }
 }}}
 because that'd make f too strict.  But in your example, `g` and `h` are
 themselves constructors.

 My conclusion: for the ''nested'' part of CPR analysis we do not want to
 "look through" function calls, but rather look only for literal
 constructor applications.  I have not thought about how much this'd affect
 the analysis.

 Provided the analysis was modified in this way, it shouldn't be too hard
 to modify the worker/wrapper part to take account of it.

 But NB that `CprAnalyse` is dead code; the current analysis is done as
 part of strictness analysis in `DmdAnal`.  And the strictness analyser
 itself needs love and attention. So much to do, so little time.

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-19 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by simonpj):

 Rats.  I'd forgotten about the strictness question:
 {{{
 f :: Int -> (Int,Int)
 f x = (g x, h x)
 }}
 Suppose `g` and `h` have the CPR property -- that is, they explicitly
 return a boxed value.  Then it's a mistake to transform to
 {{{
 f x = case (g x, h x) of { (I# r1, I# r2) ->
   (I# r1 ,I# r2) }
 }}}
 because that'd make f too strict.  But in your example, `g` and `h` are
 themselves constructors.

 My conclusion: for the ''nested'' part of CPR analysis we do not want to
 "look through" function calls, but rather look only for literal
 constructor applications.  I have not thought about how much this'd affect
 the analysis.

 Provided the analysis was modified in this way, it shouldn't be too hard
 to modify the worker/wrapper part to take account of it.

 But NB that CprAnalyse is dead code; the current analysis is done as part
 of strictness analysis in DmdAnal.  And the strictness analyser itself
 needs love and attention. So much to do, so little time.


 Simon

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-19 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by dons):

 Looking in the CPR analyser, I see the following comment:

   The analysis here detects nested CPR information.  For example, if a
   function returns a constructed pair, the first element of which is a
   constructed int, then the analysis will detect nested CPR information
   for the int as well.  Unfortunately, the current transformations can't
   take advantage of the nested CPR information.  They have (broken now,
   I think) code which will flatten out nested CPR components and rebuild
   them in the wrapper, but enabling this would lose laziness.  It is
   possible to make use of the nested info: if we knew that a caller was
   strict in that position then we could create a specialized version of
   the function which flattened/reconstructed that position.

   It is not known whether this optimisation would be worthwhile.

 So, there's some skeleton code in their for the nested CPR stuff. And the
 CPR analyser seems pretty small too. Would working on this be worthwhile
 now?

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-19 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
+---
 Reporter:  dons|  Owner: 
 Type:  run-time performance bug| Status:  new
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  boxing, loops, performance  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by simonpj):

  * difficulty:  => Unknown

Comment:

 Nice example.  I took a little look at it.  Two things

 First, yes GHC never does a heap-check at the start of an alternative of a
 primop case; that is, one whose scrutinee is just a primop application.
 In this example that's bad, because there is no allocation before the
 conditional, and the hot path does no allocation at all.

 The fix is to put the heap check at the start of the alternatives, if no
 allocation precedes the case itself.  This would require a significant
 (but not drastic) change to the code generator.  Happily, it'll be a much
 easier change when John Dias's new back end comes on stream, we'll hold it
 till then.


 Second, and orthogonally, this loop has a nested CPR property. There is no
 reason that the CPR analyser can't deal with nested stuff, but it doesn't.
 There's a nice little project there too.

 Either of these would fix this particular example, but both are valuable
 in their own right.

 Simon

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-17 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner: 
Type:  run-time performance bug|   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  boxing, loops, performance  | Testcase: 
Architecture:  Unknown |   Os:  Unknown
---+
Comment (by dons):

 Note that if we specialise the constructor manually, we can get the
 correct unboxing:
 That is, just using strict pairs isn't enough:

 {{{
 data P a b = P {-# UNPACK #-} !a {-# UNPACK #-} !b
 }}}

 won't work.

 where we use P only for P Double Int, I'm unable to get the return value
 unboxed.

 If we specialise P, data P = P !Double !Int, then we do get the unpacking,
 as expected.

 This makes strict pairs a little less useful for accumulating state -- we
 have to specialise them
 directly ourselves to avoid the reboxing penalty.

-- 
Ticket URL: 
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] #2289: Needless reboxing of values when returning from a tight loop

2008-05-16 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner: 
Type:  run-time performance bug|   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  boxing, loops, performance  | Testcase: 
Architecture:  Unknown |   Os:  Unknown
---+
Comment (by dons):

 Here's a simple test case:

 {{{

 {-# LANGUAGE TypeOperators #-}
 {-# OPTIONS -funbox-strict-fields #-}

 import System.Environment
 import Text.Printf

 data P a b = P !a !b

 mean :: Double -> Double -> P Double Int
 mean n m = go n 0 0
 where
 go :: Double -> Int -> Double -> P Double Int
 go x l s | x > m  = P s l
  | otherwise  = go (x+1) (l+1) (s+x)

 main = do
 [d] <- map read `fmap` getArgs
 printf "%f\n" (case mean 1 d of
 (P x y) -> x / fromIntegral y)

 }}}

 Yields:

 {{{

 $wgo_s1az :: Double# -> Int# -> Double# -> (# Double, Int #)
 $wgo_s1az =
 \ (ww_X1au :: Double#)
 (ww1_X1az :: Int#)
 (ww2_X1aE :: Double#) ->
 case >## ww_X1au y_a178 of wild4_X1g {
 False ->
 $wgo_s1az
 (+## ww_X1au 1.0)
 (+# ww1_X1az 1)
 (+## ww2_X1aE ww_X1au);
 True -> (# D# ww2_X1aE, I# ww1_X1az #)
 };

 } in
 case $wgo_s1az 2.0 1 1.0 of ww_s1a2 { (# ww1_s1a4, ww2_s1a5 #) ->
 case ww1_s1a4 of wild4_a17r { D# x_a17t ->
 case ww2_s1a5 of wild5_aEV { I# x1_aEX ->
 case /## x_a17t (int2Double# x1_aEX)
 of wild21_a17z { __DEFAULT ->
 D# wild21_a17z

 }}}

 Exhibiting the reboxing.

 Running this:

 {{{
 $ time ./G 1e9
 5.067109
 ./G 1e9  2.21s user 0.00s system 99% cpu 2.225 total
 }}}

 While if we prevent the reboxing, by moving the division inside the loop:

 {{{

 $wgo_s1a0 :: Double# -> Int# -> Double# -> Double#
 $wgo_s1a0 =
  \ (ww_X19X :: Double#)
(ww1_X1a2 :: Int#)
(ww2_X1a7 :: Double#) ->
case >## ww_X19X y_a16C of wild4_X1g {
  False ->
$wgo_s1a0
  (+## ww_X19X 1.0)
  (+# ww1_X1a2 1)
  (+## ww2_X1a7 ww_X19X);
  True -> /## ww2_X1a7 (int2Double# ww1_X1a2
 }}}

 We get faster code:

 {{{

 $ time ./G 1e9
 5.067109
 ./G 1e9  1.84s user 0.01s system 99% cpu 1.861 total

 }}}

 So I suspect the boxing causes a heap check to end up inside the loop (run
 on every iteration?),
 and thus a performance loss.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs