Re: [Haskell-cafe] Re: Profiling nested case

2008-07-24 Thread Ryan Ingram
Done.  http://hackage.haskell.org/trac/ghc/ticket/2465

  -- ryan

On 7/23/08, Simon Peyton-Jones [EMAIL PROTECTED] wrote:
 | I had similar experiences as you when attempting to write high
 | performance Haskell; the language makes you want to use high-level
 | abstracted functions but the optimizer (while amazing, to be honest)
 | seems to miss a few cases that it seems like it should hit.

 Ryan, if you find any of these, do please submit them to GHC's Trac 
 bug-tracker. There's a special category for performance bugs.  Small programs 
 of the form GHC should hit this, but doesn't are incredibly useful.

 Thanks

 Simon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Profiling nested case

2008-07-23 Thread Simon Peyton-Jones
| I had similar experiences as you when attempting to write high
| performance Haskell; the language makes you want to use high-level
| abstracted functions but the optimizer (while amazing, to be honest)
| seems to miss a few cases that it seems like it should hit.

Ryan, if you find any of these, do please submit them to GHC's Trac 
bug-tracker. There's a special category for performance bugs.  Small programs 
of the form GHC should hit this, but doesn't are incredibly useful.

Thanks

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Profiling nested case

2008-07-21 Thread Ryan Ingram
I had similar experiences as you when attempting to write high
performance Haskell; the language makes you want to use high-level
abstracted functions but the optimizer (while amazing, to be honest)
seems to miss a few cases that it seems like it should hit.

The problem seems to be that the compiler is extremely good at
optimizing systems-level code, but that any control-structure
function needs to be extremely inlined to be successful.  You might
try re-writing sequence or foldM a few different ways using the
same test function and see what you can get.

One thing that I notice about this code is that if you switch Right
and Left you will get the default behavior for the Either monad:

worldSceneSwitch point = case redSphere (0,50,0) 50 point of
   v@(Left _) - v
   Right d1 - case greenSphere (25,-250,0) 50 point of
 v@(Left _) - v
 Right d2 - Right $ d1 `min` d2

is the same as

worldSceneSwitch point = do
d1 - redSphere (0, 50, 0) 50 point
d2 - greenSphere (25, -250, 0) 50 point
Right (d1 `min` d2)

Here is the same concept using foldM:

minimumM (x : xs) = do
v0 - x
foldM (return . min) v0 xs

worldSceneSwitch point = minimumM [
redSphere (0, 50, 0) 50 point,
greenSphere (25, -250, 0) 50 point
  ]

However, the performance here will be terrible if minimumM and foldM
do not get sufficiently inlined; you do not want to be allocating list
thunks just to execute them shortly thereafter.

  -- ryan

On Sat, Jul 19, 2008 at 6:48 AM, Mitar [EMAIL PROTECTED] wrote:
 Hi!

 I had to change code somewhat. Now I have a function like:

 worldScene point = case redSphere (0,50,0) 50 point of
  v@(Right _) - v
  Left d1 - case greenSphere (25,-250,0) 50 point of
v@(Right _) - v
Left d2 - Left $ d1 `min` d2

 (Of course there could be more objects.)

 Any suggestion how could I make this less hard-coded? Something which
 would take a list of objects (object functions) and then return a
 Right if any object function return Right or a minimum value of all
 Lefts. But that it would have similar performance? If not on my GHC
 version (6.8.3) on something newer (which uses fusion or something).
 Is there some standard function for this or should I write my own
 recursive function to run over a list of object functions? But I am
 afraid that this will be hard to optimize for compiler.

 (It is important to notice that the order of executing object
 functions is not important so it could be a good candidate for
 parallelism.)


 Mitar
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Profiling nested case

2008-07-19 Thread Mitar
Hi!

I had to change code somewhat. Now I have a function like:

worldScene point = case redSphere (0,50,0) 50 point of
  v@(Right _) - v
  Left d1 - case greenSphere (25,-250,0) 50 point of
v@(Right _) - v
Left d2 - Left $ d1 `min` d2

(Of course there could be more objects.)

Any suggestion how could I make this less hard-coded? Something which
would take a list of objects (object functions) and then return a
Right if any object function return Right or a minimum value of all
Lefts. But that it would have similar performance? If not on my GHC
version (6.8.3) on something newer (which uses fusion or something).
Is there some standard function for this or should I write my own
recursive function to run over a list of object functions? But I am
afraid that this will be hard to optimize for compiler.

(It is important to notice that the order of executing object
functions is not important so it could be a good candidate for
parallelism.)


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Profiling nested case

2008-07-18 Thread Ben Franksen
Mitar wrote:
 On Fri, Jul 18, 2008 at 3:54 PM, Chaddaï Fouché
 [EMAIL PROTECTED] wrote:
 So that I can easily change the type everywhere. But it would be much
 nicer to write:

 data Quaternion a = Q !a !a !a !a deriving (Eq,Show)

 Only the performance of Num instance functions of Quaternion is then
 quite worse.

 You can probably use a specialization pragma to get around that.
 
 But why is this not automatic? If I use Quaternions of only one type
 in the whole program then why it does not make specialized version for
 it? At least with -O2 switch.

You could try jhc: it does whole program optimization. Ghc compiles each
module separately.

Cheers
Ben

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Profiling nested case

2008-07-18 Thread Don Stewart
ben.franksen:
 Mitar wrote:
  On Fri, Jul 18, 2008 at 3:54 PM, Chaddaï Fouché
  [EMAIL PROTECTED] wrote:
  So that I can easily change the type everywhere. But it would be much
  nicer to write:
 
  data Quaternion a = Q !a !a !a !a deriving (Eq,Show)
 
  Only the performance of Num instance functions of Quaternion is then
  quite worse.
 
  You can probably use a specialization pragma to get around that.
  
  But why is this not automatic? If I use Quaternions of only one type
  in the whole program then why it does not make specialized version for
  it? At least with -O2 switch.
 
 You could try jhc: it does whole program optimization. Ghc compiles each
 module separately.

No need to switch compilers. GHC is able to do a pretty good job.
Consider,


data Q a = Q !a !a !a !a deriving (Eq,Show)

-- yeah, polymorphic
go :: Num a = Q a - Q a
go (Q 0 0 0 0) = Q 1 2 3 4
go (Q a b c d) = go $! Q (a * a) (b * b) (c * c) (d * d)

-- ah, but we fix it.
type QI = Q Int

-- and try that:
main = print (go (Q 2 3 7 13 :: QI))



GHC specialises and gives us,

$wgo :: Int# - Int# - Int# - Int# - Q Int
 
So just use ghc-core to check what you're getting.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe