[Haskell-cafe] Project Euler Problem 357 in Haskell
Daniel Fischer
daniel.is.fischer at googlemail.com
Tue Nov 8 15:01:38 CET 2011
On Tuesday 08 November 2011, 12:21:14, mukesh tiwari wrote:
> Hello all
> Being a Haskell enthusiastic , first I tried to solve this problem in
> Haskell but it running for almost 10 minutes on my computer but not
> getting the answer.
Hmm, finishes in 13.36 seconds here, without any changes.
Of course, it has to be compiled with optimisations, ghc -O2.
> A similar C++ program outputs the answer almost instant
2.85 seconds. g++ -O3.
So, yes, much faster, but not orders of magnitude.
> so could some one please tell me how to improve this Haskell
> program.
>
> import Control.Monad.ST
> import Data.Array.ST
> import Data.Array.Unboxed
> import Control.Monad
>
> prime :: Int -> UArray Int Bool
> prime n = runSTUArray $ do
> arr <- newArray ( 2 , n ) True :: ST s ( STUArray s Int Bool )
> forM_ ( takeWhile ( \x -> x*x <= n ) [ 2 .. n ] ) $ \i -> do
> ai <- readArray arr i
> when ( ai ) $ forM_ [ i^2 , i^2 + i .. n ] $ \j -> do
> writeArray arr j False
>
> return arr
Hmm, would have to look at the core, if the optimiser isn't smart enough to
eliminate the lists, you get considerable overhead from that.
Anyway, readArray/writeArray perform bounds checks, you don't have that in
C++, so if you use unsafeRead and unsafeWrite instead, it'll be faster.
(You're doing the checks in *your* code, no point in repeating it.)
>
> pList :: UArray Int Bool
> pList = prime $ 10 ^ 8
>
> divPrime :: Int -> Bool
> divPrime n = all ( \d -> if mod n d == 0 then pList ! ( d + div n d )
> else True ) $ [ 1 .. truncate . sqrt . fromIntegral $ n ]
Use rem and quot instead of mod and div.
That doesn't make too much difference here, but it gains a bit.
That allocates a list, if you avoid that and check in a loop, like in C++,
it'll be a bit faster.
And instead of (!), use unsafeAt to omit a redundant bounds-check.
>
>
> main = putStrLn . show . sum $ [ if and [ pList ! i , divPrime . pred $
> i ] then pred i else 0 | i <- [ 2 .. 10 ^ 8 ] ]
Dont use
and [condition1, condition2]
that's more readable and faster if written as
condition1 && condition2
Don't use pred, use (i-1) instead.
And you're gratuitously adding a lot of 0s, filter the list
sum [i | i <- [1 .. 99999999], pList ! (i+1) && divPrime i]
However, you're allocating a lot of list cells here, it will be faster if
you calculate the sum in a loop, like you do in C++.
Eliminating the unnecessary bounds-checks and the intermediate lists, it
runs in 4.3 seconds here, not too bad compared to the C++.
However, use a better algorithm.
As is, for each prime p you do trial division on (p-1). For every (p-1)
satisfying the criterion, you do about sqrt(p-1) divisions, that costs a
lot of time. You can make the factorisation (and hence finding of divisors)
cheap if you slightly modify your sieve.
>
>
> C++ program which outputs the answer almost instant.
>
> #include<cstdio>
> #include<iostream>
> #include<vector>
> #define Lim 100000001
> using namespace std;
>
> bool prime [Lim];
> vector<int> v ;
>
> void isPrime ()
> {
> for( int i = 2 ; i * i <= Lim ; i++)
> if ( !prime [i]) for ( int j = i * i ; j <= Lim ; j += i ) prime
[j]
> = 1 ;
>
> for( int i = 2 ; i <= Lim ; i++) if ( ! prime[i] ) v.push_back( i )
;
> //cout<<v.size()<<endl;
> //for(int i=0;i<10;i++) cout<<v[i]<<" ";cout<<endl;
>
> }
>
> int main()
> {
> isPrime();
> int n = v.size();
> long long sum = 0;
> for(int i = 0 ; i < n ; i ++)
> {
> int k = v[i]-1;
> bool f = 0;
> for(int i = 1 ; i*i<= k ; i++)
> if ( k % i == 0 && prime[ i + ( k / i ) ] ) { f=1 ; break ; }
>
> if ( !f ) sum += k;
> }
> cout<<sum<<endl;
> }
>
>
> Regards
> Mukesh Tiwari
More information about the Haskell-Cafe
mailing list