[Haskell-cafe] Project Euler Problem 357 in Haskell
Ivan Lazar Miljenovic
ivan.miljenovic at gmail.com
Tue Nov 8 12:59:06 CET 2011
May I suggest you try a non-ST solution first (e.g. using Data.IntMap)
first (assuming an auxiliary data-structure is required)?
Also, I'm not sure if the logic in the two versions is the same: I'm
not sure about how you handle the boolean aspect in C++, but you have
a third for-loop there that doesn't seem to correspond to anything in
the Haskell version.
On 8 November 2011 22:50, mukesh tiwari <mukeshtiwari.iiitm at gmail.com> wrote:
> I am not sure about Int overflow. There is no case of Int overflow in prime
> , pList and divPrime function however lets assuming Int overflow in main but
> then still answer should be outputted.
>
> Regards
> Mukesh Tiwari
>
> On Tue, Nov 8, 2011 at 5:08 PM, Lyndon Maydwell <maydwell at gmail.com> wrote:
>>
>> Could Int be overflowing?
>>
>> On Tue, Nov 8, 2011 at 7:21 PM, mukesh tiwari
>> <mukeshtiwari.iiitm at gmail.com> 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. A similar C++ program outputs the answer almost instant 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
>> >
>> > 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 ]
>> >
>> >
>> > main = putStrLn . show . sum $ [ if and [ pList ! i , divPrime . pred $
>> > i ]
>> > then pred i else 0 | i <- [ 2 .. 10 ^ 8 ] ]
>> >
>> >
>> > 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
>> >
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe at haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>> >
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
--
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
IvanMiljenovic.wordpress.com
More information about the Haskell-Cafe
mailing list