[Haskell-cafe]Prime Generator time limit exceeded

Hi I'm new to Haskell. I found this site on the Haskell wiki https://www.spoj.pl. But I got some trouble on trying to solve the problem titled "Prime Generator" https://www.spoj.pl/problems/PRIME1. The online-judge system tells me "time limit excedded" Would you be so kind to tell me how to make it more faster? And any other suggestion is welcome. Thanks in advance. --------------------------------------Code begin------------------------------------------------------------ module Main where import IO import List main = do input_size<-getLine content<-get_contents (read input_size) mapM_ (\r-> do mapM_ (print) (primeGenerator (parse r)); putStrLn "") content get_contents n | n == 0 = return [] | otherwise = do content<-getLine rests<-get_contents (n-1) return ([content]++rests) primeGenerator [start,end] = [x | x<-[start..end], all (== 1) (map (gcd x) [2..(x-1)]), x/=1] parse s = unfoldr (\x-> case x of [] -> Nothing _ -> Just (head (reads x))) s -------------------------------Code ends-------------------------------------------------------------------------------- (BTW: I'm new to this mailling list also, forgive my rudeness if I am, and forgive my poor English)

I didn't see any other replies and didn't want to leave you hanging, so... Three hints: 1) you are testing every integer >= 2 as a divisor when you only need to test prime numbers <= floor(sqrt(n)) 2) Since for all n > 2, floor(sqrt(n)) < n, you can use the very primes you are generating in the test part of the function itself, confident that you won't overtake your own function. 3) The function primeGenerator [start,end] seems more efficient that primeGenerator [2,end], but the latter is (almost) always faster, because you need those primes to test for primality. A dropWhile (< start) can trim off the unneeded junk when you're done. 4) It won't make your code any faster, but it maybe more elegant to lazily calculate an infinite list of primes, then truncate with takeWhile (<= end), if only for symmetry with dropWhile (< start) SPOILER ALERT: I have appended two of my own solutions at the end of this e-mail for fun (one with list comprehensions, one in point-free notation). Whether you scroll down to look at them is up to you of course... :) alaiyeshi wrote:
Hi
I'm new to Haskell.
I found this site on the Haskell wiki https://www.spoj.pl. But I got some trouble on trying to solve the problem titled "Prime Generator" https://www.spoj.pl/problems/PRIME1.
The online-judge system tells me "time limit excedded" Would you be so kind to tell me how to make it more faster? And any other suggestion is welcome. Thanks in advance.
--------------------------------------Code begin------------------------------------------------------------ module Main where
import IO import List
main = do input_size<-getLine content<-get_contents (read input_size) mapM_ (\r-> do mapM_ (print) (primeGenerator (parse r)); putStrLn "") content
get_contents n | n == 0 = return [] | otherwise = do content<-getLine rests<-get_contents (n-1) return ([content]++rests)
primeGenerator [start,end] = [x | x<-[start..end], all (== 1) (map (gcd x) [2..(x-1)]), x/=1]
parse s = unfoldr (\x-> case x of [] -> Nothing _ -> Just (head (reads x))) s
-------------------------------Code ends--------------------------------------------------------------------------------
(BTW: I'm new to this mailling list also, forgive my rudeness if I am, and forgive my poor English)
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Just calculate the infinite list of primes (lazily), -- then trip the range to fit primeGenerator [start,end] = takeWhile (<= end) . dropWhile (< start) $ primes -- Pointed notation with list comprehensions primes = (2 : [x | x <- [3,5..], isPrime x]) -- Efficient test presupposes the existence of primes -- This works because to determine whether p is prime you only need -- to know the primes strictly less than p (except for 2 of course!) isPrime x = null divisors where divisors = [y | y <- onlyUpToSqrtX primes, x `mod` y == 0] onlyUpToSqrtX = fst . span (<= sqrtX) sqrtX = floor (sqrt (fromIntegral x)) -- A point-free notation, as an alternative primes' = (2 : filter isPrime [3,5..]) -- indivisible n > 1 where isPrime = and -- i.e. all are . map (/= 0) -- not equal to 0, applied to . remOf -- remainders of odd ints -- where remOf n is when you remOf n = map (mod n) -- divide into n a list of . flip take primes' -- primes, but only . length -- as many as . takeWhile (<= n) -- are less than n, that is . map (^ 2) -- the square of each of the $ primes' -- primes

Two more hints I used in my code: 5) Except for 2, all primes are odd. Don't bother testing the evens. 6) sqrt(n) is (a little) costly, but I used it in my first solution for clarity. You can also create an infinite list of squares of primes, then trim the list of primes to the length of (takeWhile (<= n) squarePrimes). I haven't tested whether this is actually faster or slower than using sqrt, though! Math functions take only time, but lists require memory allocation. Dan Weston wrote:
I didn't see any other replies and didn't want to leave you hanging, so...
Three hints:
1) you are testing every integer >= 2 as a divisor when you only need to test prime numbers <= floor(sqrt(n))
2) Since for all n > 2, floor(sqrt(n)) < n, you can use the very primes you are generating in the test part of the function itself, confident that you won't overtake your own function.
3) The function primeGenerator [start,end] seems more efficient that primeGenerator [2,end], but the latter is (almost) always faster, because you need those primes to test for primality. A dropWhile (< start) can trim off the unneeded junk when you're done.
4) It won't make your code any faster, but it maybe more elegant to lazily calculate an infinite list of primes, then truncate with takeWhile (<= end), if only for symmetry with dropWhile (< start)
SPOILER ALERT: I have appended two of my own solutions at the end of this e-mail for fun (one with list comprehensions, one in point-free notation). Whether you scroll down to look at them is up to you of course... :)
alaiyeshi wrote:
Hi
I'm new to Haskell.
I found this site on the Haskell wiki https://www.spoj.pl. But I got some trouble on trying to solve the problem titled "Prime Generator" https://www.spoj.pl/problems/PRIME1.
The online-judge system tells me "time limit excedded" Would you be so kind to tell me how to make it more faster? And any other suggestion is welcome. Thanks in advance.
--------------------------------------Code begin------------------------------------------------------------ module Main where
import IO import List
main = do input_size<-getLine content<-get_contents (read input_size) mapM_ (\r-> do mapM_ (print) (primeGenerator (parse r)); putStrLn "") content
get_contents n | n == 0 = return [] | otherwise = do content<-getLine rests<-get_contents (n-1) return ([content]++rests)
primeGenerator [start,end] = [x | x<-[start..end], all (== 1) (map (gcd x) [2..(x-1)]), x/=1]
parse s = unfoldr (\x-> case x of [] -> Nothing _ -> Just (head (reads x))) s
-------------------------------Code ends--------------------------------------------------------------------------------
(BTW: I'm new to this mailling list also, forgive my rudeness if I am, and forgive my poor English)
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Just calculate the infinite list of primes (lazily), -- then trip the range to fit primeGenerator [start,end] = takeWhile (<= end) . dropWhile (< start) $ primes
-- Pointed notation with list comprehensions primes = (2 : [x | x <- [3,5..], isPrime x])
-- Efficient test presupposes the existence of primes -- This works because to determine whether p is prime you only need -- to know the primes strictly less than p (except for 2 of course!) isPrime x = null divisors where divisors = [y | y <- onlyUpToSqrtX primes, x `mod` y == 0] onlyUpToSqrtX = fst . span (<= sqrtX) sqrtX = floor (sqrt (fromIntegral x))
-- A point-free notation, as an alternative primes' = (2 : filter isPrime [3,5..]) -- indivisible n > 1 where isPrime = and -- i.e. all are . map (/= 0) -- not equal to 0, applied to . remOf -- remainders of odd ints -- where remOf n is when you remOf n = map (mod n) -- divide into n a list of . flip take primes' -- primes, but only . length -- as many as . takeWhile (<= n) -- are less than n, that is . map (^ 2) -- the square of each of the $ primes' -- primes

Thanks a lot. (you really spoil me;-)) What a stupid mistake I've made!(flush) I'll rewrite my code later.

The problem with your approach is the gratuitous use of division, which tends to be very slow. In my solution, I first generate a list of "seed primes", all primes less than sqrt 1000000000. Then, for each input m and n, I generate all multiples of the seed primes between m and n. I then output each number that isn't a multiple of a seed prime. Tips: - Haskell will infer the Integer type by default, an unbounded type. Operations on Integer are often considerably slower than Int, the corresponding bounded type. - The accumArray function is a handy way to collect all the generated multiples. For maximum speed, use a UArray Int Bool. - gcd is a particularly expensive function to use here, perhaps you can use the mod function instead? - here is a handy function to generate your seed primes: sieve [] = [] sieve (x:xs) = x : [y | y <- xs, y `mod` x /= 0] Spencer Janssen On Nov 1, 2006, at 10:49 AM, alaiyeshi wrote:
Hi
I'm new to Haskell.
I found this site on the Haskell wiki https://www.spoj.pl. But I got some trouble on trying to solve the problem titled "Prime Generator" https://www.spoj.pl/problems/PRIME1.
The online-judge system tells me "time limit excedded" Would you be so kind to tell me how to make it more faster? And any other suggestion is welcome. Thanks in advance.
--------------------------------------Code begin------------------------------------------------------------ module Main where
import IO import List
main = do input_size<-getLine content<-get_contents (read input_size) mapM_ (\r-> do mapM_ (print) (primeGenerator (parse r)); putStrLn "") content
get_contents n | n == 0 = return [] | otherwise = do content<-getLine rests<-get_contents (n-1) return ([content]++rests)
primeGenerator [start,end] = [x | x<-[start..end], all (== 1) (map (gcd x) [2.. (x-1)]), x/=1]
parse s = unfoldr (\x-> case x of [] -> Nothing _ -> Just (head (reads x))) s
-------------------------------Code ends------------------------------------------------------------------ --------------
(BTW: I'm new to this mailling list also, forgive my rudeness if I am, and forgive my poor English) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you for replying. Smart method! I've learned much;-) I'll have a try using UArray. Also, I guess my code still waste too much time "parsing" input (I compiled my code with -prof flag on)... Maybe ByteString may save me (or a smarter brain), What is your opinion about doing faster IO, would you please tell me?

On Nov 2, 2006, at 8:48 AM, alaiyeshi wrote:
Also, I guess my code still waste too much time "parsing" input (I compiled my code with -prof flag on)... Maybe ByteString may save me (or a smarter brain), What is your opinion about doing faster IO, would you please tell me?
ByteString will likely make this problem go faster, but sadly SPOJ doesn't have the FPS library or GHC 6.6. My submission doesn't use any fancy IO tricks and manages to complete in 2.28 seconds. There is one major problem with your IO code. get_contents will read every line of input before doing any other processing or output. This could potentially eat up a ton of memory, and thereby make your program slow. A better approach is to interleave reading input and printing output. Here is the input code from my submission: \begin{code} main = do cases <- readLn replicateM_ cases $ do s <- getLine let [m, n] = map read $ words s {- fill in the blank! -} \end{code} Cheers, Spencer Janssen

Thank you so much! I've met replicateM_ for the first time;-) This could be a "template" for doing online-judge exercises I guess. And it's very useful for newbies like me. Again many Thanks:-)

Hello alaiyeshi, Thursday, November 2, 2006, 9:26:37 PM, you wrote:
I've met replicateM_ for the first time;-) This could be a "template" for doing online-judge exercises I guess. And it's very useful for newbies like me.
make an date for 'interact' :))) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Wow! Thank you for your suggestion. But I guess in this problem the first input line and the other are different in their meaning. Thus if I use interact I should "parse" the input(again), I guess.

Hello alaiyeshi, Friday, November 3, 2006, 4:23:40 PM, you wrote:
But I guess in this problem the first input line and the other are different in their meaning. Thus if I use interact I should "parse" the input(again), I guess.
it seems that you don't understand that functional programming has just the same power as imperative one: process (header:rest) = process2 header rest -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 11/2/06, Spencer Janssen
On Nov 2, 2006, at 8:48 AM, alaiyeshi wrote:
Also, I guess my code still waste too much time "parsing" input (I compiled my code with -prof flag on)... Maybe ByteString may save me (or a smarter brain), What is your opinion about doing faster IO, would you please tell me?
ByteString will likely make this problem go faster, but sadly SPOJ doesn't have the FPS library or GHC 6.6. My submission doesn't use any fancy IO tricks and manages to complete in 2.28 seconds.
There is one major problem with your IO code. get_contents will read every line of input before doing any other processing or output. This could potentially eat up a ton of memory, and thereby make your program slow. A better approach is to interleave reading input and printing output. Here is the input code from my submission:
\begin{code} main = do cases <- readLn replicateM_ cases $ do s <- getLine let [m, n] = map read $ words s {- fill in the blank! -} \end{code}
Wouldn't this be the same as: \begin{code} main = do cases <- readLn -- probably don't need this anymore c <- getContents -- this should be lazy let ls = lines c -- lazy too flip mapM_ ls $ \s -> do let [m, n] = map read $ words s {- fill in the blank! -} \end{code} Initially I was thinking this version might be preferable, but now I see it's actually more lines (although could be condensed). Jason
participants (5)
-
alaiyeshi
-
Bulat Ziganshin
-
Dan Weston
-
Jason Dagit
-
Spencer Janssen