[Haskell-cafe] Re: FASTER primes

Daniel Fischer daniel.is.fischer at web.de
Tue Dec 29 21:16:48 EST 2009


Am Mittwoch 30 Dezember 2009 01:04:34 schrieb Will Ness:
>
> > While I haven't detected that with the primes code, I find that in my
> > ghci your code is approximately 2.5 times faster than ONeill or Bayer
> > when interpreted (no difference in scaling observed), while when compiled
> > with -O2, ONeill is approximately three times as fast as your code
>
> that was what I was getting at first too, before I've put into my code the
> _type_signatures_ and the "specialize" _pragmas_ as per her file. Then it
> was only 1.3x slower, when compiled (with about same asymptotics and memory
> usage).
>

Specialising your code to Int makes it half as fast as ONeill here (as an executable).
That is largely due to the fact that your code uses much more memory here (54MB vs. 2MB 
for the millionth prime), though, the MUT times have a ratio of about 1.5.

Now an interesting question is, why does it use so much memory here?
Can you send me your exact code so I can see how that behaves here?

> >and twice as fast as Bayer as an executable, about twice as fast as your
> > code and slightly slower than Bayer in ghci.
>
> see, this kind of inconsistencies is exactly why I was concentrating only
> on one platform in measuring the speed - the interp'/GHCi combination.

The problem with that is that one is primarily interested in speed for library functions, 
which are mostly used as compiled code.

> Especially when developing and trying out several approaches, to test with
> compiler just takes too long. :) And why should it give (sometimes) wildly
> different readings when running inside GHCi or standalone ??

Good question.

>
> > And I have huge memory problems in ghci with your code.
> > That may be due to my implementation of merge and minus, though. You
> > wrote 'standard' and I coded the straightforward methods.
>
> Here's what I'm using (BTW I've put it on the primes haskellwiki page too).
> The memory reported for interpreted is about half of PQ's (IIRC), and
> compiled - the same:
>
>  minus a@(x:xs) b@(y:ys) = case compare x y of
>         LT -> x: xs `minus` b
>         GT ->    a  `minus` ys
>         EQ ->    xs `minus` ys
>  minus a b  = a
>
>  merge a@(x:xs) b@(y:ys) = case compare x y of
>         LT -> x: merge xs b
>         EQ -> x: merge xs ys
>         GT -> y: merge a  ys
>  merge a b  = if null b then a else b

More or less the same that I wrote.

> > What's wrong with mutable arrays? There are a lot of algorithms which can
> > be easily and efficiently implemented using mutable unboxed arrays while
> > a comparably efficient implementation without mutable arrays is hard. For
> > those, I consider STUArrays the natural choice. Sieving primes falls into
> > that category.
>
> It's just that the mutating code tends to be convoluted, like in the
> example I mentioned of quicksort. One has to read the C code with good
> attention to understand it.

Convoluted is (often) an exaggeration. But I agree that the specification of 'what' is 
usually easier to understand than that of 'how'.

> "Normal" Haskell is much more visually apparent, like
>
>   primes = 2: 3: sieve (tail primes) [5,7..]
>    where
>     sieve (p:ps) xs = h ++ sieve ps (t `minus` tail [q,q+2*p..])
>                       where (h,~(_:t)) = span (< q) xs
>                             q          = p*p
>

Yes.

> or
>
>   primes = 2: 3: sieve [] (tail primes) 5
>    where
>     sieve fs (p:ps) x = [i | i<- [x,x+2..q-2], a!i]
>                           ++ sieve ((2*p,q):fs') ps (q+2)
>      where
>       q           = p*p
>       mults       = [ [y+s,y+2*s..q] | (s,y)<- fs]
>       fs'         = [ (s,last ms)    | ((s,_),ms)<- zip fs mults]
>       a           = accumArray (\a b->False) True (x,q-2)
>                              [(i,()) | ms<- mults, i<- ms]
>

Umm, really?
I'd think if you see what that does, you won't have difficulties with a mutable array 
sieve.



-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091229/00a51a37/attachment-0001.html


More information about the Haskell-Cafe mailing list