Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Sebastian,

Why would I write a slow, complicated algorithm in C#?

I'm not making these comparisons for some academic paper, I'm trying to get
a feel for how the languages run in practice.

And really in practice, I'm never going to write a prime algorithm using
merge and so on, I'd just use the original naive Haskell algorithm, that
runs 500 times slower (at least) than my naive C# algo.  I'm just allowing
you guys to optimize to see how close you can get.

Note that the C# algo is not something created by C# experts, it's just
something I hacked together in like 2 minutes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
Sebastian,
Why would I write a slow, complicated algorithm in C#?
I'm not making these comparisons for some academic paper,
I'm trying to get a feel for how the languages run in
practice.
And really in practice, I'm never going to write a prime
algorithm using merge and so on, I'd just use the original
naive Haskell algorithm, that runs 500 times slower (at
least) than my naive C# algo.  I'm just allowing you guys to
optimize to see how close you can get.
Note that the C# algo is not something created by C#
experts, it's just something I hacked together in like 2
minutes.

For fast, mutable prime sieves, see the shootout:


http://shootout.alioth.debian.org/gp4/benchmark.php?test=nsievebitslang=ghcid=4

(a bit sieve) is pretty fast, 1.8x highly optimised C, and also
readable, for what it does:

import Data.Array.IO
import Data.Array.Base
import System
import Text.Printf

main = do
n - getArgs = readIO . head :: IO Int
mapM_ (sieve . (1 *) . (2 ^)) [n, n-1, n-2]

sieve n = do
a - newArray (2,n) True :: IO (IOUArray Int Bool) -- an array of Bool
r - go a n 2 0
printf Primes up to %8d %8d\n (n::Int) (r::Int) :: IO ()

go !a !m !n !c
| n == m= return c
| otherwise = do
e - unsafeRead a n
if e
then let loop !j
| j = m= unsafeWrite a j False  loop 
(j+n)
| otherwise = go a m (n+1) (c+1)
 in loop (n+n)
else go a m (n+1) c

So perhaps just code up a mutable array version the same as for C# ?

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Hey, guys, I just realized this test is not really fair!

I've been using the Microsoft .Net compiler ,which is a proprietary
closed-source compiler.

To be fair to Haskell, we should probably compare it to other open source
products, such as g++ and mono?

Here are the timings ;-)

Haskell
==

J:\dev\haskellghc -O2 -o primechaddai.exe PrimeChaddai.hs

J:\dev\haskellprimechaddai
number of primes: 664579
Elapsed time: 26.234

g++
===

J:\dev\test\testperfg++ -O2 -o prime.exe prime.cpp

J:\dev\test\testperfprime
number of primes: 664579
elapsed time: 0.984

mono


J:\dev\test\testperferase primecs.exe

J:\dev\test\testperfgmcs primecs.cs

J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,719

Microsoft C#
=

J:\dev\test\testperfcsc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,6875

Not only does mono come close to the Microsoft .Net time, both mono and
Microsoft .Net are faster than g++ ;-) and whack Haskell.

Here's the C++ code for completeness:

#include iostream
#include ctime
using namespace std;

int CalculateNumberOfPrimes( int maxprime )
{
   bool *IsPrime = new bool[ maxprime ];

   for( int i = 0; i  maxprime; i++ )
   {
   IsPrime[i] = true;
   }

   int NumberOfPrimes = 0;

   for( int i = 2; i  maxprime; i++ )
   {
   if( IsPrime[i] )
   {
   NumberOfPrimes++;
   for( int j = ( i  1 ); j  maxprime; j+= i )
   {
   IsPrime[ j] = false;
   }
   }
   }

   return NumberOfPrimes;
}

int main( int argc, char *argv[] )
{
   clock_t start = clock();

   int NumberOfPrimes = CalculateNumberOfPrimes( 1000 );
   cout  number of primes:   NumberOfPrimes  endl;

   clock_t finish = clock();
   double time = (double(finish)-double(start))/CLOCKS_PER_SEC;
   cout  elapsed time:   time  endl;

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

Sebastian,

Why would I write a slow, complicated algorithm in C#?

I'm not making these comparisons for some academic paper, I'm trying to get
a feel for how the languages run in practice.

And really in practice, I'm never going to write a prime algorithm using
merge and so on, I'd just use the original naive Haskell algorithm, that
runs 500 times slower (at least) than my naive C# algo.  I'm just allowing
you guys to optimize to see how close you can get.

Note that the C# algo is not something created by C# experts, it's just
something I hacked together in like 2 minutes.



I take it you really are using the Sieve as a final program then? And
not just as a benchmark?
Because if you *are* trying to compare the two languages fairly, then
your reply just doesn't make sense. Just because you aren't using the
laziness of your data structure in the Haskell version for this
benchmark doesn't mean it's not there, and could be exploited in a
*real* program. Therefore if you want to compare it to C# you can't
just ignore the main properties of the Haskell version in order to
make it faster in C#! Heck, take that to its extreme (you don't seem
to care much about using the same algorithm in both languages anyway)
you could just hard code the answer for all 32 bit numbers in a large
table for the C# version and claim it's millions of times faster!

The C# algorithm is the same as the Haskell algorithm! You can't just
pick and choose two different algorithms and say that one of the
languages is better based on that!

It's like saying C is faster than Erlang on your computer, even though
Erlang scales to hundreds of threads (Why would I write something
using threads in C?). Stick with one algorithm, and implement it in
the same way in both languages, and then compare. If one of the
languages manages to handles this more gracefully and elegantly,
that's beside the point and doesn't give you the license to go off and
do something completely different in the other language and still
think you have anything useful on your hands.

The fact is that languages are different, with different strenghts and
weaknesses. Whatever comparison you come up with, chances are that one
of the languages will deal with it more gracefully. If you implement
something using lazy streams, Haskell will be more elegant, if you
want to use low level pointer arithmetic than C will do better etc. So
either you have to implement a Haskell version of your C# code, or
implement a C# version of your Haskell code (which I did). Just
because the benchmark is simple, doesn't mean you can tailor-fit the
algorithm to the specific properties of the benchmark in one of the
instances, while keeping it general and nice in the other.


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[me thinks he doth protest too much] ;-)

The rules of the competition are quite fair: both sides make an optimal
algorithm using their preferred language.  It's ok to hardcode the first 3
or 4 primes if you must,  hardcoding the entire resultset is out ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[me thinks he doth protest too much] ;-)

The rules of the competition are quite fair: both sides make an optimal
algorithm using their preferred language.  It's ok to hardcode the first 3
or 4 primes if you must,  hardcoding the entire resultset is out ;-)


Why? How may primes are there amont the first 2^32-1 numbers?
Shouldn't be unreasonable to just stick it in a table/map if all
you're interested in is getting the fastest result regardless of
algorithm... Seems quite arbitrary that you allow various tricks to
make C# look better (it might still be faster, but I haven't seen you
do a fair comparison yet!), but won't take it to its logical
conclusion!

If you *are* interested in a fair comparison I recommend you don't
cheat in either language, and try to write a more general algorithm
for both, that have the same properties (e.g. lazy streams of primes
in both, or a fixed up-front allocated array of primes in both).

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
Hey, guys, I just realized this test is not really fair!
I've been using the Microsoft .Net compiler ,which is a
proprietary closed-source compiler.
To be fair to Haskell, we should probably compare it to
other open source products, such as g++ and mono?
Here are the timings ;-)
Haskell
==
J:\dev\haskellghc -O2 -o primechaddai.exe PrimeChaddai.hs
J:\dev\haskellprimechaddai
number of primes: 664579
Elapsed time: 26.234

Oh, I think we can do a bit better than that
See below.


g++
===
J:\dev\test\testperfg++ -O2 -o prime.exe prime.cpp
J:\dev\test\testperfprime
number of primes: 664579
elapsed time: 0.984
mono

J:\dev\test\testperferase primecs.exe
J:\dev\test\testperfgmcs primecs.cs
J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,719
Microsoft C#
=
J:\dev\test\testperfcsc /nologo primecs.cs
J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,6875
Not only does mono come close to the Microsoft .Net time,
both mono and Microsoft .Net are faster than g++ ;-) and
whack Haskell.


I reimplemented your C++ program, could you time this please?


{-# OPTIONS -O2 -fbang-patterns #-}

import Data.Array.IO
import Data.Array.Base
import System
import Control.Monad
import Data.Bits
import Text.Printf

main = sieve 1000

sieve n = do
a - newArray (2,n) True :: IO (IOUArray Int Bool) -- an array of Bool
r - go a n 2 0
printf Primes up to %8d %8d\n (n::Int) (r::Int) :: IO ()

go !a !m !n !c
| n == m= return c
| otherwise = do
e - unsafeRead a n
if e then let loop !j
| j  m = do
x - unsafeRead a j
when x (unsafeWrite a j False)
loop (j+n)

| otherwise = go a m (n+1) (c+1)
  in loop (n `shiftL` 1)
 else go a m (n+1) c

On my machine:

$ ghc -o primes primes.hs

$ time ./primes
Primes up to 1000   664579
./primes  0.52s user 0.01s system 99% cpu 0.533 total

0.5s. So rather fast.

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

[snip] unsafeWrite[snip]
[snip]unsafeRead[snip]


Hi Donald, the idea is to use this for operational code, so avoiding unsafe
operations is preferable ;-)  You'll note that the C# version is not using
unsafe operations, although to be fair that's because they worked out slower
than the safe version ;-)

Also, the whole algorithm is bound to the IO Monad, which is something I'd
like to avoid if possible, since my entire interest in Haskell stems from
the possibilites of running programs easily on 1 megacore processors in the
future.

Initial compilation gives an error:

PrimeDonald.hs:18:3: Illegal bang-pattern (use -fbang-patterns)

Ok, I'm ok with compiler patches, that's half the point of such a
competition really, to encourage compiler optimization.

Anyway, congrats you got nearly as fast as C#!

J:\dev\haskellghc -fglasgow-exts -fbang-patterns -O2 -o PrimeDonald.exePrimeDo
nald.hs

J:\dev\haskellprimedonald
number of primes: 664579
Elapsed time: 0.797

J:\dev\test\testperferase primecs.exe

J:\dev\test\testperfgmcs primecs.cs

J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,719

J:\dev\test\testperferase primecs.exe

J:\dev\test\testperfcsc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,6875

Here is the Haskell code:

module Main
  where

import Data.Array.IO
import Data.Array.Base
import System
import System.Time
import System.Locale

calculateNumberOfPrimes n = do
  a - newArray (2,n) True :: IO (IOUArray Int Bool) -- an array of
Bool
  go a n 2 0

go !a !m !n !c
  | n == m= return c
  | otherwise = do
  e - unsafeRead a n
  if e
  then let loop !j
  | j = m= unsafeWrite a j False  loop
(j+n)
  | otherwise = go a m (n+1) (c+1)
   in loop (n+n)
  else go a m (n+1) c

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime - gettime
 numberOfPrimes - (calculateNumberOfPrimes 1000)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - gettime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( Elapsed time:  ++ show(secondsfloat) )
 return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED]
wrote:
 [snip] unsafeWrite[snip]
 [snip]unsafeRead[snip]
Hi Donald, the idea is to use this for operational code, so
avoiding unsafe operations is preferable ;-)  You'll note
that the C# version is not using unsafe operations, although
to be fair that's because they worked out slower than the
safe version ;-)

unsafe' here just means direct array indexing. Same as the other
languages. Haskell's 'unsafe' is a little more paranoid that other
languages.

Also, the whole algorithm is bound to the IO Monad, which is
something I'd like to avoid if possible, since my entire
interest in Haskell stems from the possibilites of running
programs easily on 1 megacore processors in the future.

You're deciding that on a cache-thrashing primes benchmark?

Since the goal is to flip bits very quickly in the cache, you could
localise this to the ST monad then, as its perfectly pure on the
outside.

Anyway, congrats you got nearly as fast as C#!

Try the other version I just sent. This one trashes cache lines
needlessly.

What C# version are you using, by the way? (So I can check if it does
any tricks).

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

hughperkins:

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED]
wrote:
 [snip] unsafeWrite[snip]
 [snip]unsafeRead[snip]
Hi Donald, the idea is to use this for operational code, so
avoiding unsafe operations is preferable ;-)  You'll note
that the C# version is not using unsafe operations, although
to be fair that's because they worked out slower than the
safe version ;-)

unsafe' here just means direct array indexing. Same as the other
languages. Haskell's 'unsafe' is a little more paranoid that other
languages.

Also, the whole algorithm is bound to the IO Monad, which is
something I'd like to avoid if possible, since my entire
interest in Haskell stems from the possibilites of running
programs easily on 1 megacore processors in the future.

You're deciding that on a cache-thrashing primes benchmark?

Since the goal is to flip bits very quickly in the cache, you could
localise this to the ST monad then, as its perfectly pure on the
outside.


Yep:

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits


main = print ( pureSieve 17984 )

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of 
Bool   
go a n 2 0

go !a !m !n !c
  | n == m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x (unsafeWrite a j False)
  loop (j+n)

  | otherwise = go a m (n+1) (c+1)
in loop (n `shiftL` 1)
   else go a m (n+1) c

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:


What C# version are you using, by the way? (So I can check if it does
any tricks).



- csc is in the Microsoft.Net Framework 2.0 runtime, which you can download
from microsoft.com (free download).
- gmcs/mono are from Mono 1.2.2.1 , which you can download from
http://www.mono-project.com/Main_Page
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


 unsafe' here just means direct array indexing. Same as the other
 languages. Haskell's 'unsafe' is a little more paranoid that other
 languages.



Yes, I was kindof hoping it was something like that.  Cool :-)



 Since the goal is to flip bits very quickly in the cache, you could
 localise this to the ST monad then, as its perfectly pure on the
 outside.



Ok, awesome!

J:\dev\haskellghc -fglasgow-exts -O2 -o PrimeDonald2.exe PrimeDonald2.hs

J:\dev\haskellprimedonald2
number of primes: 664579
Elapsed time: 0.7031

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits
import System.Time
import System.Locale

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
  a - newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of
Bool
  go a n 2 0

go !a !m !n !c
 | n == m= return c
 | otherwise = do
 e - unsafeRead a n
 if e then let loop !j
 | j  m = do
 x - unsafeRead a j
 when x (unsafeWrite a j False)
 loop (j+n)

 | otherwise = go a m (n+1) (c+1)
   in loop (n `shiftL` 1)
  else go a m (n+1) c

calculateNumberOfPrimes :: Int - Int
calculateNumberOfPrimes = pureSieve

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime - gettime
 let numberOfPrimes = (calculateNumberOfPrimes 1000)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - gettime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( Elapsed time:  ++ show(secondsfloat) )
 return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:


On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

  unsafe' here just means direct array indexing. Same as the other
  languages. Haskell's 'unsafe' is a little more paranoid that other
  languages.


Yes, I was kindof hoping it was something like that.  Cool :-)



Errr ... wait... when you say direct array indexing, you mean that this
does or doesnt continue to do bounds checking on the array access?

I could imagine that it is unsafe simply because direct array indexing
prevents mathematically proving that the program wont crash (?), or it could
be unsafe in the C++ way, where going off the end of the array corrupts your
stack/heap?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:
 On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED]  wrote:

   unsafe' here just means direct array indexing. Same as the other
   languages. Haskell's 'unsafe' is a little more paranoid that other
   languages.


 Yes, I was kindof hoping it was something like that.  Cool :-)


Errr ... wait... when you say direct array indexing, you mean that this
does or doesnt continue to do bounds checking on the array access?

I could imagine that it is unsafe simply because direct array indexing
prevents mathematically proving that the program wont crash (?), or it could
be unsafe in the C++ way, where going off the end of the array corrupts your
stack/heap?



Well, *I* didn't say it but yes. Unsafe disables bounds checking
(which in this case is safe). I think you can just stick an unsafe{}
in the C# version to disable them.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


Well, *I* didn't say it but yes. Unsafe disables bounds checking
(which in this case is safe). I think you can just stick an unsafe{}
in the C# version to disable them.



Oh well that's not good.  Yes, you can use unsafe in C# too, but you know
there are reason why we use C# instead of C++, and one of those reasons is
precisely to avoid stack/heap corruption.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Hey, I just realized I can shave off another 30% in C# ;-)

So now the timings become:

Safe Haskell
=

J:\dev\haskellghc -O2 -o primechaddai.exe PrimeChaddai.hs

J:\dev\haskellprimechaddai
number of primes: 664579
Elapsed time: 26.234

Unsafe Haskell
===

J:\dev\haskellghc -fglasgow-exts -O2 -o PrimeDonald2.exe PrimeDonald2.hs

J:\dev\haskellprimedonald2
number of primes: 664579
Elapsed time: 0.7031

mono


J:\dev\test\testperferase primecs.exe  gmcs primecs.cs

J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,453

Microsoft.Net
==

J:\dev\test\testperferase primecs.exe  csc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,421875

Here's the fabulously complicated ;-) new C# algorithm:

   public int  CalculateNumberOfPrimes( int maxprime )
   {
   bool[]IsNotPrime = new bool[ maxprime ];
   int NumberOfPrimes = 1;

   int squarecutoff = (Int32)Math.Sqrt( maxprime ) + 1;
   for( int i = 3; i  maxprime; i+= 2 )
   {
   if( !IsNotPrime [i] )
   {
   NumberOfPrimes++;
   if( i  squarecutoff )
   {
   for( int j = ( i  1 ); j  maxprime; j+= i )
   {
   if( !IsNotPrime [j] )
   IsNotPrime [ j] = true;
   }
   }

   }
   }
   return NumberOfPrimes;
   }

(basically, we only cross off primes up to the square root of the size of
the grid.  I think this is a standard part of the standard Arostophenes grid
algorithm, so like I say the C# version is seriously unoptimized ;-) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

Hey, I just realized I can shave off another 30% in C# ;-)

So now the timings become:

Safe Haskell
=

J:\dev\haskellghc -O2 -o primechaddai.exe PrimeChaddai.hs

J:\dev\haskellprimechaddai
number of primes: 664579
Elapsed time: 26.234

Unsafe Haskell
===

J:\dev\haskellghc -fglasgow-exts -O2 -o PrimeDonald2.exe PrimeDonald2.hs

J:\dev\haskellprimedonald2
number of primes: 664579
Elapsed time: 0.7031

mono


J:\dev\test\testperferase primecs.exe  gmcs primecs.cs

J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,453

Microsoft.Net
==

J:\dev\test\testperferase primecs.exe  csc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,421875

Here's the fabulously complicated ;-) new C# algorithm:

public int  CalculateNumberOfPrimes( int maxprime )
{
bool[]IsNotPrime = new bool[ maxprime ];
int NumberOfPrimes = 1;

int squarecutoff = (Int32)Math.Sqrt( maxprime ) + 1;
for( int i = 3; i  maxprime; i+= 2 )
{
if( !IsNotPrime [i] )
{
NumberOfPrimes++;
if( i  squarecutoff )
{
for( int j = ( i  1 ); j  maxprime; j+= i )
{
if( !IsNotPrime [j] )
IsNotPrime [ j] = true;
}
}

}
}
return NumberOfPrimes;
}

(basically, we only cross off primes up to the square root of the size of
the grid.  I think this is a standard part of the standard Arostophenes grid
algorithm, so like I say the C# version is seriously unoptimized ;-) )



I don't see what the point of this is? Why do timings of different
algorithms? Of course you could do the same optimization in any
language, so why do you think it's relevant to change the algorithm in
*one* of the languages and then make comparisons?

BTW, I think a better optimization is to start the inner loop at the
square of the current prime, since any numbers smaller than that
would've already been crossed off by the other prime factors (which
must be smaller than the current prime). Nevertheless, there's no
point doing optimizations to this unless you do them to all
implementations!

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


I don't see what the point of this is? Why do timings of different
algorithms? Of course you could do the same optimization in any
language, so why do you think it's relevant to change the algorithm in
*one* of the languages and then make comparisons?



Sebastien,

Well, as you yourself said, different languages work differently, so there's
no point in trying to directly implement the C# algorithm in Haskell: it
just wont work, or it will be slow.  The same works from Haskell to C#.

So, you guys are Haskell experts, show the world what Haskell is capable
of.  Come up with algorithms to calculate prime numbers in Haskell that are:
- safe
- easy to understand/read/maintain
- fast

I'll ditch the sieve of arastophenes rule if you like.  Use any algorithm
you like.  Now that is fair I think?

I in turn will do my part to keep the C# version a step ahead of the Haskell
version.  It seems this is pretty easy :-D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 I don't see what the point of this is? Why do timings of different
 algorithms? Of course you could do the same optimization in any
 language, so why do you think it's relevant to change the algorithm in
 *one* of the languages and then make comparisons?


Sebastien,

Well, as you yourself said, different languages work differently, so there's
no point in trying to directly implement the C# algorithm in Haskell: it
just wont work, or it will be slow.  The same works from Haskell to C#.

So, you guys are Haskell experts, show the world what Haskell is capable of.
 Come up with algorithms to calculate prime numbers in Haskell that are:
- safe
- easy to understand/read/maintain
- fast

 I'll ditch the sieve of arastophenes rule if you like.  Use any algorithm
you like.  Now that is fair I think?

I in turn will do my part to keep the C# version a step ahead of the Haskell
version.  It seems this is pretty easy :-D


Try this one then. I removed the unsafe reads...
Still, I think youre methodology sucks. If you want to compare
languages you should implement the same algorithm. Dons implemented a
Haskell version of your C++ algorithm, even though it wasn't optimal.
He didn't go off an implement some state-of-the-art primes algorithm
that was completey different now did he?
If this is about comparing languages, you should compare them fairly.

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad

import System.Time
import System.Locale


main = do starttime - getClockTime
 let numberOfPrimes = (pureSieve 17984)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - getClockTime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( Elapsed time:  ++ show(secondsfloat) )
 return ()

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of 
Bool   
go a n 2 0

go !a !m !n !c
  | n == m= return c
  | otherwise = do
  e - readArray a n
  if e then let loop !j
  | j  m = do
  writeArray a j False
  loop (j+n)

  | otherwise = go a m (n+1) (c+1)
in loop (n * n)
   else go a m (n+1) c


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED]
wrote:
 
  I don't see what the point of this is? Why do timings of
  different
  algorithms? Of course you could do the same optimization
  in any
  language, so why do you think it's relevant to change the
  algorithm in
  *one* of the languages and then make comparisons?
 
Sebastien,
Well, as you yourself said, different languages work
differently, so there's no point in trying to directly
implement the C# algorithm in Haskell: it just wont work, or

In this case it is fine. You're setting bits in the cache. Please use the
same algorithm, or any conclusions are meaningless. 

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:
 On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  I don't see what the point of this is? Why do timings of different
  algorithms? Of course you could do the same optimization in any
  language, so why do you think it's relevant to change the algorithm in
  *one* of the languages and then make comparisons?
 

 Sebastien,

 Well, as you yourself said, different languages work differently, so there's
 no point in trying to directly implement the C# algorithm in Haskell: it
 just wont work, or it will be slow.  The same works from Haskell to C#.

 So, you guys are Haskell experts, show the world what Haskell is capable of.
  Come up with algorithms to calculate prime numbers in Haskell that are:
 - safe
 - easy to understand/read/maintain
 - fast

  I'll ditch the sieve of arastophenes rule if you like.  Use any algorithm
 you like.  Now that is fair I think?

 I in turn will do my part to keep the C# version a step ahead of the Haskell
 version.  It seems this is pretty easy :-D

Try this one then. I removed the unsafe reads...
Still, I think youre methodology sucks. If you want to compare
languages you should implement the same algorithm. Dons implemented a
Haskell version of your C++ algorithm, even though it wasn't optimal.
He didn't go off an implement some state-of-the-art primes algorithm
that was completey different now did he?
If this is about comparing languages, you should compare them fairly.

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad

import System.Time
import System.Locale


main = do starttime - getClockTime
  let numberOfPrimes = (pureSieve 17984)
  putStrLn( number of primes:  ++ show( numberOfPrimes ) )
  endtime - getClockTime
  let timediff = diffClockTimes endtime starttime
  let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
  putStrLn( Elapsed time:  ++ show(secondsfloat) )
  return ()

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of 
Bool
go a n 2 0

go !a !m !n !c
   | n == m= return c
   | otherwise = do
   e - readArray a n
   if e then let loop !j
   | j  m = do
   writeArray a j False
   loop (j+n)

   | otherwise = go a m (n+1) (c+1)
 in loop (n * n)
else go a m (n+1) c


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862



This will fail for large inputs btw, since there are only 32 bits in
an int.. This version makes sure it doesn't try to square something
which would go cause an int overflow:

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import System
import Control.Monad
import Data.Bits
import System.Time
import System.Locale


main = do starttime - getClockTime
 let numberOfPrimes = (pureSieve 17984)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - getClockTime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( Elapsed time:  ++ show(secondsfloat) )
 return ()

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of 
Bool   
go a n 2 0

go !a !m !n !c
  | n == m= return c
  | otherwise = do
  e - readArray a n
  if e then let loop !j
  | j  m = do
  writeArray a j False
  loop (j+n)

  | otherwise = go a m (n+1) (c+1)
in loop ( if n  46340 then n * n else n `shiftL` 1)
   else go a m (n+1) c


My GHC compiler is broken, I only have GHCi, but this is about twice
for me as fast as the previous version you benchmarked, btw.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:


In this case it is fine. You're setting bits in the cache. Please use the
same algorithm, or any conclusions are meaningless.



No, I'm counting prime numbers.  Somewhat faster it seems ;-)

Let's put this into the real world a moment.  You get a job, or you're at
your job, you spend several weeks writing some super-dooper program, telling
everyone how awesome it is because it's Haskell and it's l33t!

You run it, and it takes 24 hours to run.  It's ok, it's Haskell.

Some guy with long hair and no degree comes along, and rewrites your code in
C#.  Takes him like 30 minutes because he doesnt have to optimize it, it's
done automatically.

His program runs in 25 minutes (60 times faster, see the benchmarks above to
note that this is realistic).

Guess who gets fired?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


My GHC compiler is broken, I only have GHCi, but this is about twice
for me as fast as the previous version you benchmarked, btw.



Hi Sebastian,

Here are the results:

Haskell (Safe Haskell right?)
==

J:\dev\haskellghc -fglasgow-exts -O2 -o PrimeSebastian.exe
PrimeSebastian.hs

J:\dev\haskellprimesebastian
number of primes: 664579
Elapsed time: 1.375

mono


J:\dev\test\testperferase primecs.exe  gmcs primecs.cs

J:\dev\test\testperfmono primecs.exe
number of primes: 664579
elapsed time: 0,438

Microsoft .Net
==

J:\dev\test\testperferase primecs.exe  csc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,390625

(I incorporated your suggestion for the innerloop, which shaved off another
20% or so in the C# classes)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[Argh, no way can a Microsoft language be better than Haskell]

Well, if you scan higher in the thread, there are two benchmarks.  The prime
numbers benchmark was a simple 10 minute benchmark to compare the
computational speed (something which Haskell ought to do well in?)

The other benchmark is OpenGl.  I'll try that one soon.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[Argh, no way can a Microsoft language be better than Haskell]

Well, if you scan higher in the thread, there are two benchmarks.  The prime
numbers benchmark was a simple 10 minute benchmark to compare the
computational speed (something which Haskell ought to do well in?)

The other benchmark is OpenGl.  I'll try that one soon.


Nice, so because I think your methodology is undiciplined and tells
you nothing useful, I must be biased against microsoft products right?

Btw, guess what company name is on my paycheck every month? That's
right, microsoft. I'm not biased in any way against microsoft products
(since I make them myself!).

Nobody is claiming that Haskell is the best language for writing tight
inner assembly like loops. So what's the point in making those
comparisons? How about you write some programs that do algebraic
manipulations of data structures? Something a bit more representative
of real world code, and a bit more high level? Or how about you just
take a look at the shootout I linked you to? They have far more
benchmarks than you'll have time to implement, I'm sure.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
Hey, I just realized I can shave off another 30% in C# ;-)
So now the timings become:

Ok. So do the same thing to the Haskell program. The compilers should
produce pretty much identical assembly.


{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

main = print (pureSieve 1000)

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (0,n-1) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 2 0

go !a !m cutoff !n !c
  | n == m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False
  loop (j+n)

  | otherwise = go a m cutoff (n+1) (c+1)

in loop ( if n  46340 then n * n else n `shiftL` 1)
else go a m cutoff (n+1) (c+1)

   else go a m cutoff (n+1) c

$ ghc -o primes primes.hs
$ time ./primes
664579
./primes  0.38s user 0.00s system 95% cpu 0.392 total

And indeed, it runs nearly 50% faster.

All this benchmark does is thrash the cache, so every write that avoids 
dirtying the cache is worth avoiding, hence you should always check if
you need to set a bit. Given the same algorithm, any native code
compiler should produce roughly the same result, since its really a
hardware benchmark.
 
-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

hughperkins:

Hey, I just realized I can shave off another 30% in C# ;-)
So now the timings become:

Ok. So do the same thing to the Haskell program. The compilers should
produce pretty much identical assembly.


{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

main = print (pureSieve 1000)

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (0,n-1) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 2 0

go !a !m cutoff !n !c
  | n == m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False


Surely you can remove the read here, and just always do the write?

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


Surely you can remove the read here, and just always do the write?



Ah you'd think so, but if it's anything like the C# version, strangely that
would be slower.  In his last message Don explains that this is because the
write dirties the cache, which is a Bad Move (tm).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 Surely you can remove the read here, and just always do the write?



Ah you'd think so, but if it's anything like the C# version, strangely that
would be slower.  In his last message Don explains that this is because the
write dirties the cache, which is a Bad Move (tm).




Ah, it was faster in GHCi, and I couldn't test it compiled because my
GHC install is a bit messed up at the moment...

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
dons:
 hughperkins:
  
 Hey, I just realized I can shave off another 30% in C# ;-)
 So now the timings become:
 
 Ok. So do the same thing to the Haskell program. The compilers should
 produce pretty much identical assembly.
 

Oh, and I forgot you count up by two now. Here's the Haskell
transliteration (again).


{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

main = print (pureSieve 1000)

pureSieve :: Int - Int
pureSieve n = runST( sieve n )

sieve n = do
a - newArray (3,n) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 3 1

go !a !m cutoff !n !c
  | n = m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False
  loop (j+n)

  | otherwise = go a m cutoff (n+2) (c+1)

in loop ( if n  46340 then n * n else n `shiftL` 1)
else go a m cutoff (n+2) (c+1)

   else go a m cutoff (n+2) c


Marginally faster:

$ time ./primes
664579
./primes  0.34s user 0.00s system 89% cpu 0.385 total

Very cache-dependent though, so widely varying runtimes could be
expected.

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
dons:
 dons:
  hughperkins:
   
  Hey, I just realized I can shave off another 30% in C# ;-)
  So now the timings become:
  
  Ok. So do the same thing to the Haskell program. The compilers should
  produce pretty much identical assembly.
  
 
 Oh, and I forgot you count up by two now. Here's the Haskell
 transliteration (again).

Oh, also, I was using the wrong brackets in the last program!
Stick with me, because this makes the program go at least 100x faster.

First, we'll move the pureSieve into a library module:

{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

module Primes (pureSieve) where

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

pureSieve :: Int - Int
pureSieve n = runST ( sieve n )

sieve n = do
a - newArray (3,n) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 3 1

go !a !m cutoff !n !c
  | n = m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False
  loop (j+n)

  | otherwise = go a m cutoff (n+2) (c+1)

in loop ( if n  46340 then n * n else n `shiftL` 1)
else go a m cutoff (n+2) (c+1)

   else go a m cutoff (n+2) c

And now just a module to call it:

{-# OPTIONS -fth #-}

import Primes

main = print $( let x = pureSieve 1000 in [| x |] )

Pretty simple to compile and run this now:

$ ghc --make -o primes Main.hs
$ time ./primes
664579
./primes  0.00s user 0.01s system 228% cpu 0.003 total

Oh! Much faster. Looks like Haskell is 100x faster than C#.
Who gets fired? :)

-- Don
{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

module Primes (pureSieve) where

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

pureSieve :: Int - Int
pureSieve n = runST ( sieve n )

sieve n = do
a - newArray (3,n) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 3 1

go !a !m cutoff !n !c
  | n = m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False
  loop (j+n)

  | otherwise = go a m cutoff (n+2) (c+1)

in loop ( if n  46340 then n * n else n `shiftL` 1)
else go a m cutoff (n+2) (c+1)

   else go a m cutoff (n+2) c

{-# OPTIONS -fth -O2 -optc-O -fbang-patterns #-}

import Primes

main = print $( let x = pureSieve 1000 in [| x |] )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

dons:
 dons:
  hughperkins:
  
  Hey, I just realized I can shave off another 30% in C# ;-)
  So now the timings become:
 
  Ok. So do the same thing to the Haskell program. The compilers should
  produce pretty much identical assembly.
 

 Oh, and I forgot you count up by two now. Here's the Haskell
 transliteration (again).

Oh, also, I was using the wrong brackets in the last program!
Stick with me, because this makes the program go at least 100x faster.

First, we'll move the pureSieve into a library module:

{-# OPTIONS -O2 -optc-O -fbang-patterns #-}

module Primes (pureSieve) where

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad
import Data.Bits

pureSieve :: Int - Int
pureSieve n = runST ( sieve n )

sieve n = do
a - newArray (3,n) True :: ST s (STUArray s Int Bool)
let cutoff = truncate (sqrt (fromIntegral n)) + 1
go a n cutoff 3 1

go !a !m cutoff !n !c
  | n = m= return c
  | otherwise = do
  e - unsafeRead a n
  if e then
if n  cutoff
then let loop !j
  | j  m = do
  x - unsafeRead a j
  when x $ unsafeWrite a j False
  loop (j+n)

  | otherwise = go a m cutoff (n+2) (c+1)

in loop ( if n  46340 then n * n else n `shiftL` 1)
else go a m cutoff (n+2) (c+1)

   else go a m cutoff (n+2) c

And now just a module to call it:

{-# OPTIONS -fth #-}

import Primes

main = print $( let x = pureSieve 1000 in [| x |] )

Pretty simple to compile and run this now:

$ ghc --make -o primes Main.hs
$ time ./primes
664579
./primes  0.00s user 0.01s system 228% cpu 0.003 total

Oh! Much faster. Looks like Haskell is 100x faster than C#.
Who gets fired? :)



Oooh, I love it!


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 15/07/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:


 Oh! Much faster. Looks like Haskell is 100x faster than C#.
 Who gets fired? :)



Well, you've switched back to using unsafe operations there, Donald ;-)

Anyway, before you guys get too narked at me ;-) I'd just like to say that
I'm very impressed by the work that is going on in Haskell.  I wouldnt be
here otherwise.  Haskell stands a very good chance of solving one of the
great unsolved issues at this time, which is: managing threading.

Just dont want you guys to get too complacent ;-) Running benchmarks against
Java and so on is much more motivational than running against g++, because
you can no longer say oh well Java is faster because it doesnt have a GC!,
because clearly it does; and bounds-checking, and many other useful goodies
besides.

So keep up the good work.  I'm quite happy for my tax dollars to be being
spent on Haskell research :-) and I'm really looking forward to seeing what
comes out of it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Brandon S. Allbery KF8NH


On Jul 15, 2007, at 7:53 , Sebastian Sylvan wrote:


Still, I think youre methodology sucks. If you want to compare
languages you should implement the same algorithm. (...)
If this is about comparing languages, you should compare them fairly.


But is it comparing them fairly if you use an algorithm which favors  
direct naive procedural implementation (i.e. favors C#), or one which  
favors a lazy mathematical formalism (i.e. Haskell)?


Seems to me you get the best picture by picking two algorithms, one  
which favors C# and one which favors Haskell, and implementing both  
in both languages.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Brandon S. Allbery KF8NH


On Jul 15, 2007, at 8:45 , Donald Bruce Stewart wrote:


main = print $( let x = pureSieve 1000 in [| x |] )


I'm reminded of the C++ expert in CMU SCS who used to amuse himself  
by making template expansion do all the real work at compile time.   
(Yes, including a prime sieve.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Steve Schafer
On Sun, 15 Jul 2007 14:15:03 +0200, you wrote:

...a simple 10 minute benchmark to compare the computational speed...

We should forget about small efficiencies, say about 97% of the time:
premature optimization is the root of all evil. 
  - Donald Knuth (paraphrasing Tony Hoare)

Haskell is about improving software quality. A meaningful benchmark
would be one that compares end-to-end software development lifecycles,
including not only runtime performance, but also development costs,
debugging and maintenance time, reliability, etc.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Brandon wrote:


Seems to me you get the best picture by picking two algorithms, one

which favors C# and one which favors Haskell, and implementing both
in both languages.

Sounds good to me.  What is a good problem that favors Haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Donald Bruce Stewart
hughperkins:
 
Brandon wrote:
 Seems to me you get the best picture by picking two
algorithms, one
which favors C# and one which favors Haskell, and
implementing both
in both languages.
Sounds good to me.  What is a good problem that favors
Haskell?

NO. We just *did* this.

Firstly, to compare GHC Haskell and C#, look at the shootout:


http://shootout.alioth.debian.org/gp4/benchmark.php?test=alllang=ghclang2=csharp

C# does better than I expected! 2.6x faster than one Haskell program,
usually 2-4x slower.  Really poor at lightweight concurrency.
Don't do toy benchmarks here, fix the C# ones on the shootout!

Secondly, we just did this for prime sieves:

  * imperative bit sieves on this list, in C# and Haskell, roughly
identical runtimes, though Hugh didn't benchmark the fastest Haskell ones.

This is to be expected, every compiled languages runs into the cache
on this benchmark anyway, see here:

   http://shootout.alioth.debian.org/gp4/benchmark.php?test=nsievelang=all

  * lazy sieves, C# was 100x slower than the naive Haskell implementation.
That's the real story here, laziness is just hard and painful in C#.

However, if you're keen, and agreeing to implement the same algorithm on
both systems, I'd have a go in C# at 'chameneos', a concurrency
benchmark,

http://shootout.alioth.debian.org/gp4/benchmark.php?test=chameneoslang=all

or maybe 'pidigits', a lazy pi generator,


http://shootout.alioth.debian.org/gp4/benchmark.php?test=pidigitslang=ghcid=0

Should be a challenge in C#.

-- Don

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:


However, if you're keen, and agreeing to implement the same algorithm on
both systems,



Sorry, the rule is you use what's available in your chosen language,
otherwise I have to restrict myself only to use things available in Haskell,
which is kindof silly dont you think?

The issue with the shootout is there's no room for creativity, it's like
working for a manager who micro-manages.

My ideal testing environment is something like http://topcoder.com , but
topcoder doesnt support Haskell at this time (probably because it would lose
all the time, so noone would use it)

I'd quite like to see a version of topcoder for Haskell, but shootout is not
it.

I'd have a go in C# at 'chameneos', a concurrency

benchmark,


http://shootout.alioth.debian.org/gp4/benchmark.php?test=chameneoslang=all



I'll have a look.  The GHC solution seems to be safe I think?  so it seems
fair.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:


I'd have a go in C# at 'chameneos', a concurrency
 benchmark,


 http://shootout.alioth.debian.org/gp4/benchmark.php?test=chameneoslang=all




Errr this is kindof a strange problem, the answer is always N * 2?

And there we see why I dislike shootout ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:
 However, if you're keen, and agreeing to implement the same algorithm on
 both systems,

Sorry, the rule is you use what's available in your chosen language,
otherwise I have to restrict myself only to use things available in Haskell,
which is kindof silly dont you think?


Nobody is saying anything different. We're just saying that you have
to implement the same thing in both languages. Don't compare insertion
sort with merge sort, for example, compare insertion sort with
insertion sort and merge sort with merge sort. If you don't, any
differences you detect have nothing to do with the language itself,
and is as such completely useless!

If you have a neat way of doing something due to some language
feature, then do use it (see lazy lists in Haskell, compared to the
awkward lazy streams in C#, or imperative array updates in C# compared
to the somewhat awkward readArray/writeArray etc.)! But use the same
algorithm if you want to draw any valid conclusions!

As we've demonstrated there's nothing stopping you from writing
imperative C-like algorithms in Haskell (just like C#), and there
certainly wasn't any major performance difference (did you even
benchmark Dons latest entry? Not the template haskell one, but the one
before that? If you want you can replace the unsafeRead/unsafeWrite in
the same way I did in mine -- I'd still like to see how it fares with
the better cache performance and the other optimizations that you had
in the C# version).

If you want to compare two languages, then implement the same
algorithm in each. Don't implement a naive and elegant, or a flexible
and general algorithm in one of the languages, and then compare it
with a completely different algorithm in the other language (written
specifically for the benchmark itself, rather than as a
general/flexible algorithm). It just doesn't give you any useful data,
and you'd be wasting your time, and we wouldn't want that would we?

I think dons summed it up nicely. We tried both approaches,
lazy/general, and imperative/fast. In the former verion C# was
horrible compared to Haskell, in the latter the performance was about
the same (again, please benchmark Dons latest entry if you haven't).
Hardly a resounding victory for C#!



The issue with the shootout is there's no room for creativity, it's like
working for a manager who micro-manages.


I thought the point wasn't to compare programmer's creativity, but to
compare languages?

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Just for laughs, here's my solution to Chameneos.

J:\dev\haskellcsc /nologo Chameneos2.cs

J:\dev\haskellchameneos2
200
elapsed time: 0

Compares quite favorably to the Haskell solution:

J:\dev\haskellghc -fglasgow-exts -O2 -o Chameneos.exe Chameneos.hs

J:\dev\haskellchameneos
200
number of primes: ()
Elapsed time: 1.2811

Think outside the box people ;-)

using System;

class Chameneos
{
  public void Go(int N)
  {
 Console.WriteLine( N * 2 );
  }
}


class EntryPoint
{
   public static void Main()
   {
   System.DateTime start = System.DateTime.Now;

  new Chameneos().Go(100);

  System.DateTime finish = System.DateTime.Now;
  double time = finish.Subtract( start ).TotalMilliseconds;;

  Console.WriteLine( elapsed time:  + ( time / 1000 ) );
   }
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

Oh wait, hmmm, might have misread the question :-D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:


On 7/15/07, Hugh Perkins [EMAIL PROTECTED] wrote:

 I'd have a go in C# at 'chameneos', a concurrency
  benchmark,
 
   
http://shootout.alioth.debian.org/gp4/benchmark.php?test=chameneoslang=all
 
 


Errr this is kindof a strange problem, the answer is always N * 2?

And there we see why I dislike shootout ;-)



By the way, sortof felt guilty for not really creating imaginary Chameneos,
and there's also the race condition to think about.

Race condition
===

(or: why is it N * 2)

There is an insane race condition in the question, which really renders the
question rather uncool, but let's accept for now that it's ok to have insane
race conditions in our programs.  There are two possibilities:

1. The insane race condition means that each test condition produces a
different output, and the question is entirely invalid
2. The race condition has no affect on the output

If 1 is true, the question is entirely invalid.  We're going to assume that
the question is valid, which means the race condition has no affect on the
result.

That means that we can imagine the chaemeneos meeting in any order we like.

So we send c1 then c2.  That's one meeting, and each chameneos has met other
other chameneos.

We iterate N times, so C1 and c2 both met another chameneos N times, giving
a total of N * 2.

The colors are entirely irrelevant, and do not have any affect on the
meetings, because they do not affect whether meetings take place or not.

Imaginary Chameneos


The question asks us to imagine N chameneos of different colors meeting.
Chameneos do not really exist, they're an imaginary creation.  So we have to
imagine N imaginary chameneos meeting imaginarily.

Rest assured, as I pressed the Enter key I did duly imagine the 100
chameneos in many colors all meeting and changing colors and becoming faded.

Oh, you want the computer to imagine the imaginary chameneos meeting and
changing colors?  Well now, a computer doesnt really imagine anything, we
ascribe meaning to arbitrary symbols in our code.

So, just to put your mind at rest,  the function Chameneos.Go( int N ) in
my code represents N chameneos in many colors meeting and changing colors,
so to the extent that a computer can imagine things, the computer really did
imagine imaginary chameneos imaginarily meeting :-D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


I thought the point wasn't to compare programmer's creativity, but to
compare languages?



Sebastian, you cant directly compare languages, you can only compare the
results of a pairing between developers and those languages.  There's no
absolute way to make the comparison, you just have to average out, over
scenarios that are relevant to whatever you're doing.

If we assume that Haskell programmers are at least as creative as C#
programmers - and most Haskell programmers seem to take this as written ;-)
- then this should balance out ok.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 I thought the point wasn't to compare programmer's creativity, but to
 compare languages?


Sebastian, you cant directly compare languages, you can only compare the
results of a pairing between developers and those languages.


Sure you can. Keep the programmer and the algorithm constant, and swap
out the languages. Or have multiple programmers
collaborating/competing on implementing the same algorithm on both
side, converging on an optimum for each language, and compare the
results (this is what the shootout does).

Kudos on managing to completely sidestep the two suggested benchmarks
by complaining that one of them isimaginary. Because, you know, your
primes program was such a great example of a real-world application.
You don't think that multiple agents interacting in a concurrent
setting is representative for real programs? It is, and by simplifying
it down to the core problem, you can test the difficult bit far more
easily than if you were to require everyone to write a full-on telecom
operatings sytem, or any other application that's concurrent in the
same style, for each language you want to compare.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

Hi Sebastian,

There are literally thousands of problems at http://topcoder.com.  I'm
totally fine with using any of these as a benchmark.

Can you find one that shows off the strengths of Haskell?


You don't think that multiple agents interacting in a concurrent

setting is representative for real programs? It is, and by simplifying
it down to the core problem, you can test the difficult bit far more
easily than if you were to require everyone to write a full-on telecom
operatings sytem, or any other application that's concurrent in the
same style, for each language you want to compare.

Yes, actually that's exactly the problem I have at work that I'm looking for
a solution for.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:


or maybe 'pidigits', a lazy pi generator,


http://shootout.alioth.debian.org/gp4/benchmark.php?test=pidigitslang=ghcid=0



This is I/O bound, which isnt interesting, unless you really want to
benchmark I/O to console?

We can improve it by instead of printing the digits to I/O, returning the
number of occurrences of a specific digit, let's say 3.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

Hi Sebastian,

There are literally thousands of problems at http://topcoder.com.  I'm
totally fine with using any of these as a benchmark.

Can you find one that shows off the strengths of Haskell?


Can you find me a list of the contests? I find that site impossible to
navigate efficiently.

Roughly speaking the strenths of Haskell are mainly increased
productivity, safety, and realiability. Not something you can test for
by meassuring performance of finished solutions (who knows how long
the C version took to create?). However, in terms of performance
Haskell is pretty good at laziness, algebraic manipulations of
(possibly infinite) data structures, and concurrency (especially if
you require atomic operations on shared data - since you can use STM
rather than locks, which also gives you exception safety for free).

Also, I believe you already have two suggested benchmarks that you
could try, so why not start with those since they already have
implementations in lots of languages, including Haskell and C#?



 You don't think that multiple agents interacting in a concurrent
setting is representative for real programs? It is, and by simplifying
it down to the core problem, you can test the difficult bit far more
easily than if you were to require everyone to write a full-on telecom
operatings sytem, or any other application that's concurrent in the
same style, for each language you want to compare.

Yes, actually that's exactly the problem I have at work that I'm looking for
a solution for.


Okay, so what's the problem then?
Why not implement this one very simple application that tests just
this thing and see what happens? In fact, there already is a C#
implementation for it, if you can't find anything wrong with it, then
don't you have the information you need? If you can find something
wrong with it, fix it (and submit the fix!), and see how the improved
version fares (remember, you can't change the algorithm as it would
void the comparison!).

Point is, you have at least two suggested problems that you could try
out, and you now say that one of them is even a great fit for your
specific problem domain, so get cracking and you'll have your answer
shortly!

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Hugh Perkins

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[Lots of stuff]

Ok, Sebastian, there's such a thing as analysing products along multiple
orthogonal axes.

At no point have I claimed that C# is better at threading than Haskell, in
fact I'm pretty sure I've mostly suggested that Haskell might have answers
for this?

Nevertheless, threading is not the only point of interest when one analyses
a language.  One is also interested in things like:
- how easy is it to check function parameters for type (ok in Haskell) and
name (not ok)
- how fast does a pure computational function actually run.  It's fine
saying threading will multiple execution times by the number of cores, but
on a 256-core machine, if the underlying code runs 500 times slower, you're
actually going to run 50% slower overall ;-) and use up every processor on
that machine just for that one task
- how easy it to do things that are necessary for one's job. For me this
means things like:
  - is it easy to serialize arbitrary objects to/from xml (answer: didnt
used to be, but I managed to implement a good-enough solution)
  - create forms/web pages (answer: havent checked yet)
  - carry out network rpc (answer: doesnt exist yet, would need to write it
myself)
  - use opengl (not for my job, but I enjoy doing things outside of work
too ;-) )
- how easy is it for typical developers to use.  (answer: not easy; that
means developers will cost lots more money)

So... benchmarking comes into play to find out how fast a pure computational
function actually runs (point 2), and how well opengl runs (point 3.4).  I
didnt try opengl yet, I'm not holding my breath, but I'll give it a shot and
see what happens.

For the pure computation, FWIW my personal conclusions at the moment:
- Haskell can get up to C# speeds, by using imperative algorithms
- what does this say about lazy algorithms???
- intuitively written, maintainable Haskell algorithms run at far from C#
speeds

It's ok, I'm not planning on using Haskell today, I'm sure you guys will
sort this stuff out by the time Haskell becomes useful.

Or: the concepts from Haskell that work well will be imported into other
languages.  If you can run haskell in imperative-mode, I dont see why C#
cant run in pure mode.  In that case, knowing how haskell works will
probably make it easier to understand how C#-puremode works.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Sebastian Sylvan

On 15/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
[Lots of stuff]

Ok, Sebastian, there's such a thing as analysing products along multiple
orthogonal axes.


And yet you don't seem willing to do so? Why is that? You asked for
problems where Haskell does well, performance-wise, and then you make
up ridiculous excuses to avoid accepting the problems presented!


So... benchmarking comes into play to find out how fast a pure computational
function actually runs (point 2), and how well opengl runs (point 3.4).  I
didnt try opengl yet, I'm not holding my breath, but I'll give it a shot and
see what happens.


OpenGL is mostly written in C, so most of the code will likely run the
exact same bits. It's just an interface to a C library.


For the pure computation, FWIW my personal conclusions at the moment:
- Haskell can get up to C# speeds, by using imperative algorithms
- what does this say about lazy algorithms???


It says that lazy algorithms are often slower than low-level
imperative algorithms. This is true in both Haskell and C#, as shown.
But what do we also know about lazy algorithms? That they are far more
modular and flexible! An interesting point is that lazy algorithms
were (in this benchmark) two orders of magnitude faster in Haskell
than in C#! So maybe if you want to focus on high-level, maintainable,
and /correct/ code, you can do so at far less performance cost using
Haskell?


- intuitively written, maintainable Haskell algorithms run at far from C#
speeds


Actually no, it was about 100x faster! Again, you make the error of
comparing a lazy stream based version with an imperative low-level
version.
If you want to make claims, then use either of the two
apples-to-apples comparisons that we've done here. Either compare the
high-level lazy versions, or the low-level imperative versions.

You're comparing a low-level inflexible highly specialized algorithm
to a completely different high-level and flexible (and a bit naive!)
algorithm. That's not a fair comparison. It may be that Haskell is
very good at writing this flexible and high level code, but that
doesn't mean you get to compare it to inflexible and low level code
and then claim Haskell is slow!
C# was faster originally because you had to do far more work to to
implement the algorithm, and the end result is hardly reusable at all,
and in larger application the cost of debugging and maintenance also
goes way up. But guess what? As shown in this thread, you can pay this
cost in Haskell too /where needed/ and get similar speeds as C#!

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-15 Thread Andreas Marth
If you are so sure that C# will be better than haskell why not prove it at the 
ICFP (http://www.icfpcontest.org/).
That should be as fair as possible with your requests for comparison.
It is running next weekend (20th-23rd of July), so you can prove how superior 
your C# is.
If you win, peobably everyone here will recognize it.
So go and register.

  - Original Message - 
  From: Hugh Perkins 
  To: Sebastian Sylvan 
  Cc: haskell-cafe@haskell.org 
  Sent: Sunday, July 15, 2007 10:39 PM
  Subject: Re: Re[4]: [Haskell-cafe] In-place modification


  On 7/15/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  [Lots of stuff]

  Ok, Sebastian, there's such a thing as analysing products along multiple 
orthogonal axes. 

  At no point have I claimed that C# is better at threading than Haskell, in 
fact I'm pretty sure I've mostly suggested that Haskell might have answers for 
this?

  Nevertheless, threading is not the only point of interest when one analyses a 
language.  One is also interested in things like: 
  - how easy is it to check function parameters for type (ok in Haskell) and 
name (not ok)
  - how fast does a pure computational function actually run.  It's fine saying 
threading will multiple execution times by the number of cores, but on a 
256-core machine, if the underlying code runs 500 times slower, you're actually 
going to run 50% slower overall ;-) and use up every processor on that machine 
just for that one task 
  - how easy it to do things that are necessary for one's job. For me this 
means things like:
 - is it easy to serialize arbitrary objects to/from xml (answer: didnt 
used to be, but I managed to implement a good-enough solution) 
 - create forms/web pages (answer: havent checked yet)
 - carry out network rpc (answer: doesnt exist yet, would need to write it 
myself)
 - use opengl (not for my job, but I enjoy doing things outside of work too 
;-) ) 
  - how easy is it for typical developers to use.  (answer: not easy; that 
means developers will cost lots more money)

  So... benchmarking comes into play to find out how fast a pure computational 
function actually runs (point 2), and how well opengl runs (point 3.4).  I 
didnt try opengl yet, I'm not holding my breath, but I'll give it a shot and 
see what happens.

  For the pure computation, FWIW my personal conclusions at the moment:
  - Haskell can get up to C# speeds, by using imperative algorithms 
  - what does this say about lazy algorithms???
  - intuitively written, maintainable Haskell algorithms run at far from C# 
speeds

  It's ok, I'm not planning on using Haskell today, I'm sure you guys will sort 
this stuff out by the time Haskell becomes useful. 

  Or: the concepts from Haskell that work well will be imported into other 
languages.  If you can run haskell in imperative-mode, I dont see why C# cant 
run in pure mode.  In that case, knowing how haskell works will probably make 
it easier to understand how C#-puremode works. 




--


  ___
  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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

So no, using the form of my argument, it is NOT possible to prove

anything about Haskell -vs- C.  It is ONLY possible to make claims
about Haskell *libraries* -vs- C *libraries*.

You can claim anything you like, but if you want people to believe it you'd
be best providing the code used so that others can reproduce the tests,
comment, optimize ;-)

I've done some simple benchmarks between C#/Java/C++ before.  Here are two,
one for a prime number algorithm, one for OpenGl, which is more of a real
world situation, and entirely relevant to the original thread, which was
talking about performance for games programming.

I havent run the same benchmarks in Haskell, because I'm not experienced
enough to be able to write an optimized Haskell solution to either problem,
but I'm sure I've come to the right place to find someone who can do this
;-)

Algorithms


For algorithms, the results are so close that simple compiler switch changes
can make the difference between C++ or Java or C# being the fastest.

Here's a prime-number benchmark between C++ and C# (along with code):

http://spring.clan-sy.com/phpbb/viewtopic.php?t=7634postdays=0postorder=ascstart=60
post Thu Nov 02, 2006 3:18 am

 C++ version:
H:\dev\test\CSharpAIH:\dev\test\testperf\prime.exe
number of primes: 664579
elapsed time: 2.265

C# version:
H:\dev\test\CSharpAIH:\dev\test\testperf\primecs.exe
number of primes: 664579
elapsed time: 2.03125

Admittedly, optimizations are turned off by default in cl, and turned on by
default in C#. Nevertheless, these execution times are clearly not miles
apart.

OpenGl
==

Here's an OpenGl benchmark between C# vertex3f and C# drawArrays, and
between C# and Java.

http://spring.clan-sy.com/phpbb/viewtopic.php?t=7634postdays=0postorder=ascstart=100

OpenGl C#: post of Sun Dec 03, 2006 5:54 am
OpenGl Java: post of Mon Dec 18, 2006 12:35 pm

I used a simple OpenGl application to benchmark Java and C#, because my
target was to write an OpenGl application.  You have to benchmark the things
that you will be doing with your final application ;-)

OpenGl is very stressful for anything other than C/C++, because it involves
a lot of calls across the C / other-language interface, along with
associated marshalling costs and so on.

By comparing the time to run with using a brute-force Vertex3f call per
vertex, with the time to call DrawArrays, after pushing everything to a
vertex array, you can get a measure of the inter-language boundary overhead
involved.  (DrawArrays runs either in the graphics card, or in the graphics
card driver, or both, but either way it's happening on the native side of
the native/other-language boundary)

I was going to run the same benchmark on Haskell, but I gave up on seeing
Haskell opengl doesnt support alpha-blending yet, so I'm guessing Haskell
opengl has not been used very much just yet ;-)



If someone can provide an optimized version of the prime number algorithm in
Haskell, I'll run it in both Haskell and C# and print the results.  The
algorithm is a simple sieve of Eratosthenes (I think).  This is basically
the kind of algorithm Haskell is built for ;-) so if it doesn't win this
it's go-home time ;-)

Well, until automatic threading arrives of course.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Henk-Jan van Tuyl


There was some discussion about prime number generators earlier this year:
  http://www.haskell.org/pipermail/haskell-cafe/2007-February/022347.html
  http://www.haskell.org/pipermail/haskell-cafe/2007-February/022699.html

You can find several sources there.

Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--



On Sat, 14 Jul 2007 08:07:34 +0200, Hugh Perkins [EMAIL PROTECTED]  
wrote:





If someone can provide an optimized version of the prime number  
algorithm in

Haskell, I'll run it in both Haskell and C# and print the results.  The
algorithm is a simple sieve of Eratosthenes (I think).  This is basically
the kind of algorithm Haskell is built for ;-) so if it doesn't win this
it's go-home time ;-)

Well, until automatic threading arrives of course.




--

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

On 7/14/07, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:



There was some discussion about prime number generators earlier this year:
   http://www.haskell.org/pipermail/haskell-cafe/2007-February/022347.html
   http://www.haskell.org/pipermail/haskell-cafe/2007-February/022699.html

Ok, so using the following code:


module Main
  where


import IO
import Char
import GHC.Float
import List
import Control.Monad
import System.Time
import System.Locale

sieve :: [Int] - [Int]
sieve [] = []
sieve (p : xs) = p : sieve [x | x - xs, x `mod` p  0]

calculateNumberOfPrimes :: Int - Int
calculateNumberOfPrimes max = 1 + length( sieve [ 3,5.. (max -1) ] )

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime - gettime
 let numberOfPrimes = (calculateNumberOfPrimes 20)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - gettime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( show(secondsfloat) )
 return ()

With 20 as the upper limit on the sieve, this gives:

O:\dev\haskellghc -fglasgow-exts -O2 -o prime.exe Prime.hs

O:\dev\haskellprime
number of primes: 17984
8.734

For comparison, on the same machine, in C# this gives:

O:\dev\test\testperfcsc /nologo primecs.cs

O:\dev\test\testperfprimecs
number of primes: 17984
elapsed time: 0,015625

That's over 500 times faster ;-)

Here's the code in C#

using System;

class Primes
{

   public int  CalculateNumberOfPrimes( int maxprime )
   {
   bool[]IsNotPrime = new bool[ maxprime ];
   int NumberOfPrimes = 1;

   for( int i = 3; i  maxprime; i+= 2 )
   {
   if( !IsNotPrime [i] )
   {
   NumberOfPrimes++;
   for( int j = ( i  1 ); j  maxprime; j+= i )
   {
   if( !IsNotPrime [j] )
   IsNotPrime [ j] = true;
   }

   }
   }

   return NumberOfPrimes;
   }
}

class EntryPoint
{
   public static void Main()
   {
   System.DateTime start = System.DateTime.Now;

  int NumberOfPrimes = new Primes().CalculateNumberOfPrimes( 20 );

  System.DateTime finish = System.DateTime.Now;
  double time = finish.Subtract( start ).TotalMilliseconds;;

  Console.WriteLine( number of primes:  + NumberOfPrimes );
  Console.WriteLine( elapsed time:  + ( time / 1000 ) );
   }
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Chaddaï Fouché

That's over 500 times faster ;-)


... Did you really read the Haskell code ?
You're comparing two completely unrelated algorithms, talk about a
fair comparison !

Maybe a reading of
http://en.literateprograms.org/Sieve_of_Eratosthenes_(Haskell) would
help you ?
Note that you C# code algorithm could be written in Haskell quite
compactly, it would already be a better match !

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

As I say, I'm not a Haskell expert, so feel free to provide a better
implementation.

On 7/15/07, Chaddaï Fouché [EMAIL PROTECTED] wrote:


... Did you really read the Haskell code ?
You're comparing two completely unrelated algorithms, talk about a
fair comparison !

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Derek Elkins
Read http://www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf

On Sun, 2007-07-15 at 00:38 +0200, Hugh Perkins wrote:
 As I say, I'm not a Haskell expert, so feel free to provide a better
 implementation.
 
 On 7/15/07, Chaddaï Fouché [EMAIL PROTECTED] wrote:
 ... Did you really read the Haskell code ?
 You're comparing two completely unrelated algorithms, talk
 about a
 fair comparison !
 
 ___
 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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

There's really a tendency in this newsgroup to point people to huge
documents, when a small copy and paste would make the answer so much more
accessible ;-)

Anyway... so reading through the paper, it looks like its using a priority
queue?  Which basically is changing the algorithm somewhat compared to the
C# version.

Anyway, if you can provide a working Haskell version, I'll be happy to run
it.  I sortof suspect that if it gave results within 30% of the C# version
someone would already have done so ;-)

On 7/15/07, Derek Elkins [EMAIL PROTECTED] wrote:


Read http://www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Chaddaï Fouché

2007/7/15, Hugh Perkins [EMAIL PROTECTED]:

There's really a tendency in this newsgroup to point people to huge
documents, when a small copy and paste would make the answer so much more
accessible ;-)


I was pointing you on a document of quite honest size in my opinion,
and not really hard to read...
But well if you want a piece of code, here it is :
--

merge xs@(x:xt) ys@(y:yt) = case compare x y of
   LT - x : (merge xt ys)
   EQ - x : (merge xt yt)
   GT - y : (merge xs yt)

diff  xs@(x:xt) ys@(y:yt) = case compare x y of
   LT - x : (diff xt ys)
   EQ - diff xt yt
   GT - diff xs yt

primes, nonprimes :: [Int]
primes= [2,3,5] ++ (diff [7,9..] nonprimes)
nonprimes = foldr1 f . map g $ tail primes
   where f (x:xt) ys = x : (merge xt ys)
 g p = [ n*p | n - [p,p+2..]]

--
The HaskellWiki repertory it under primes and it's at least 170
times faster than the extra-naive sieve you used in your comparison on
my computer... (I have some doubts on the accuracy of the benchmark
and System.Time at this level of precision, especially on Windows)

An implementation with DiffArray (not even DiffUArray since there's no
instance for Bool ? Is there a bitvector implementation somewhere to
make up for this ?) and exactly your algorithm is already more than 20
times faster than the naive sieve.

Note that this kind of benchmark is pretty pointless anyway since
you're not really using C# in your program : you're using a subset of
C# that's almost immediately translatable in the corresponding C code,
and indeed the JIT compiler must compile to the same code as the
equivalent C code, so it's no surprise at all that the performances
are similar !
Due to the nature of Haskell, it's not so easy to do the same thing
(write a C program in Haskell as you wrote a C program in C#), so the
conclusion is obviously to Haskell disadvantage.

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Derek Elkins
On Sun, 2007-07-15 at 00:53 +0200, Hugh Perkins wrote:
 There's really a tendency in this newsgroup to point people to huge
 documents, when a small copy and paste would make the answer so much
 more accessible ;-)
 
 Anyway... so reading through the paper, it looks like its using a
 priority queue?  Which basically is changing the algorithm somewhat
 compared to the C# version. 
 
 Anyway, if you can provide a working Haskell version, I'll be happy to
 run it.  I sortof suspect that if it gave results within 30% of the C#
 version someone would already have done so ;-)

It's a six page document, and the point was in the first paragraph.

Here's part of a giant thread about this that occurred in February:
http://www.haskell.org/pipermail/haskell-cafe/2007-February/022854.html

There is a zip file with 15 Haskell implementations and timing
comparisons to a C version.  The author of that email is, incidentally,
the author of the paper I referred to.

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Donald Bruce Stewart
derek.a.elkins:
 On Sun, 2007-07-15 at 00:53 +0200, Hugh Perkins wrote:
  There's really a tendency in this newsgroup to point people to huge
  documents, when a small copy and paste would make the answer so much
  more accessible ;-)
  
  Anyway... so reading through the paper, it looks like its using a
  priority queue?  Which basically is changing the algorithm somewhat
  compared to the C# version. 
  
  Anyway, if you can provide a working Haskell version, I'll be happy to
  run it.  I sortof suspect that if it gave results within 30% of the C#
  version someone would already have done so ;-)
 
 It's a six page document, and the point was in the first paragraph.
 
 Here's part of a giant thread about this that occurred in February:
 http://www.haskell.org/pipermail/haskell-cafe/2007-February/022854.html
 
 There is a zip file with 15 Haskell implementations and timing
 comparisons to a C version.  The author of that email is, incidentally,
 the author of the paper I referred to.

And those implementations are also in darcs now,

http://www.cse.unsw.edu.au/~dons/code/nobench/spectral/primes/

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

Chaddai,

Unfortunately, your program doesnt work ;-)

The function needs to take a parameter, which is the upper limit on our
sieve, and return a single value, which is the number of primes in that
interval.  Complex requirements I know ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Chaddaï Fouché

Well, I see, it is indeed very complex requirement...
Maybe you could do the very complex following operation to at least
test the speed of this implementation : let lastPrime = primes !!
17983

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

On 7/15/07, Derek Elkins [EMAIL PROTECTED] wrote:


Read http://www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf




Ok, so switched to using the Data.Map version from this paper, which looks
like a lazy, but real, version of the sieve of Arostothenes.

This does run quite a lot faster, so we're going to run on a sieve of
100 to increase the timings a bit (timings on 20 in C# are a bit
inaccurate...).

Here are the results:

J:\dev\haskellghc -O2 -fglasgow-exts -o Prime2.exe Prime2.hs

J:\dev\haskellprime2
number of primes: 78493
19.547

J:\dev\test\testperfcsc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 78498
elapsed time: 0,0625

So, only 300 times faster this time ;-)

Here's the Haskell code:

module Main
  where


import IO
import Char
import GHC.Float
import List
import qualified Data.Map as Map
import Control.Monad
import System.Time
import System.Locale

sieve xs = sieve' xs Map.empty
  where
 sieve' [] table = []
 sieve' (x:xs) table =
case Map.lookup x table of
   Nothing - ( x : sieve' xs (Map.insert (x*x) [x] table) )
   Just facts - (sieve' xs (foldl reinsert (Map.delete x table)
facts))
  where
reinsert table prime = Map.insertWith (++) (x+prime) [prime]
table

calculateNumberOfPrimes :: Int - Int
calculateNumberOfPrimes max = length (sieve [ 2.. max ])

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime - gettime
 let numberOfPrimes = (calculateNumberOfPrimes 100)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - gettime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( show(secondsfloat) )
 return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Chaddaï Fouché

2007/7/15, Chaddaï Fouché [EMAIL PROTECTED]:

Well, I see, it is indeed very complex requirement...
Maybe you could do the very complex following operation to at least
test the speed of this implementation : let lastPrime = primes !!
17983



Or if you really want a function with your requirement, maybe you
could take the painful steps needed to write :
let numberOfPrimes = length $ takeWhile ( 20) primes
?
--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Hugh Perkins

(Random observation: Hmmm, strange, in the Data.Map version of primes above,
we are missing 5 primes?)

Hi Chaddai,

Your algorithm does work significantly better than the others I've posted
here :-)

So much so, that we're going for a grid of 1000 to get the timings in an
easy-to-measure range.  Here are the results:

J:\dev\haskellghc -O2 -fglasgow-exts -o PrimeChaddai.exe PrimeChaddai.hs

J:\dev\haskellprimechaddai
number of primes: 664579
30.984

J:\dev\test\testperfcsc /nologo primecs.cs

J:\dev\test\testperfprimecs
number of primes: 664579
elapsed time: 0,859375

So, only 30 times faster now, which is quite a lot better :-D

Here's the full .hs code:

module Main
   where

import IO
import Char
import GHC.Float
import List
import qualified Data.Map as Map
import Control.Monad
import System.Time
import System.Locale

merge xs@(x:xt) ys@(y:yt) = case compare x y of
  LT - x : (merge xt ys)
  EQ - x : (merge xt yt)
  GT - y : (merge xs yt)

diff  xs@(x:xt) ys@(y:yt) = case compare x y of
  LT - x : (diff xt ys)
  EQ - diff xt yt
  GT - diff xs yt

primes, nonprimes :: [Int]
primes= [2,3,5] ++ (diff [7,9..] (nonprimes))
nonprimes = foldr1 f . map g $ tail (primes)
  where f (x:xt) ys = x : (merge xt ys)
g p = [ n*p | n - [p,p+2..]]

calculateNumberOfPrimes max = length $ takeWhile (  max ) primes

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime - gettime
 let numberOfPrimes = (calculateNumberOfPrimes 1000)
 putStrLn( number of primes:  ++ show( numberOfPrimes ) )
 endtime - gettime
 let timediff = diffClockTimes endtime starttime
 let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1
 putStrLn( show(secondsfloat) )
 return ()


On 7/15/07, Chaddaï Fouché [EMAIL PROTECTED] wrote:


Or if you really want a function with your requirement, maybe you
could take the painful steps needed to write :
let numberOfPrimes = length $ takeWhile ( 20) primes
?

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


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-14 Thread Sebastian Sylvan

On 14/07/07, Hugh Perkins [EMAIL PROTECTED] wrote:

As I say, I'm not a Haskell expert, so feel free to provide a better
implementation.



It's not really about providing a better implementation as that
would imply that the algorithms are the same, which they are not.
You're comparing two quite different algorithms (see the paper to
which you've already been pointed).

You need to specify what you actually want to compare. Maybe you need
to write a C# version of the Haskell version?

using System;
using System.Collections.Generic;

namespace ConsoleApplication1
{

   class Program
   {

   static IEnumerableint FromTo(int from, int to)
   {
   for (int i = from; i = to; ++i)
   {
   yield return i;
   }
   }

   static IEnumerableint Drop( int x, IEnumerableint list )
   {
   IEnumeratorint it = list.GetEnumerator();

   for (int i = 0; i  x; ++i)
   {
   if (!it.MoveNext())
   {
   yield break;
   }
   }

   while ( it.MoveNext() )
   {
   yield return it.Current;
   }

   }

   static IEnumerableint FilterDivisible(int x, IEnumerableint list)
   {
   foreach (int i in list)
   {
   if (i % x != 0)
   {
   yield return i;
   }
   }
   }

   static IEnumerableint Sieve(IEnumerableint list)
   {
   IEnumeratorint it = list.GetEnumerator();

   if (!it.MoveNext())
   {
   yield break;
   }

   int p = it.Current;
   yield return p;

   foreach (int i in Sieve( FilterDivisible( p, Drop( 1, list ) ) ) )
   {
   yield return i;
   }
   }

   static IEnumerableint Primes( int max )
   {
   return Sieve( FromTo(2, max) );
   }

   static int MaxPrime( int max )
   {
   int count = 0;

   foreach (int i in Primes(max))
   {
   ++count;
   }

   return count;
   }

   static void Main(string[] args)
   {
   Console.WriteLine(Count {0}, MaxPrime(17984));

   Console.ReadLine();
   }
   }
}


And yes, this one uses lazy streams just like the Haskell version, and
it also uses the same algorithm so it should be a much more fair
comparison. I gave up waiting for this one to terminate on large
inputs, btw. :-)


So yeah, apples to apples, the difference is hardly ordes of
magnitude. But when you construct a micro-benchmark where you write
one of the version in a way which essentially maps directly to
hardware, you're going to see that version be a lot faster. If you
actually *use* the languages a bit more fairly (e.g. use lazy streams
in C#, since you used them in Haskell -- or by all means, write a
Haskell version using unboxed ST arrays) you'll see something a bit
more useful. And that's if you manage to use the same algorithm for
both languages, of course.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] In-place modification

2007-07-12 Thread ok
I wrote [student code in Java twice the size of C code, 150 times  
slower].


On 12 Jul 2007, at 7:04 pm, Bulat Ziganshin wrote:

using student's work, it's easy to proof that Basic is faster than
assembler (and haskell is as fast and memory-efficient as C,
citing haskell-cafe)


This completely ignores everything else I wrote.  The first point is
that IT WAS NOT THE STUDENT'S FAULT.  The performance bottleneck was
ENTIRELY in code provided by Sun.

And the second point of my message, which has also been ignored, is
that languages are NOT the sole determiner of productivity c, but
libraries also.  My post was not about Java-the-language, but about
java.io the library, and about the fact that libraries can have far
more effect than anything the compiler does.

So no, using the form of my argument, it is NOT possible to prove
anything about Haskell -vs- C.  It is ONLY possible to make claims
about Haskell *libraries* -vs- C *libraries*.


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