[Haskell-cafe]Prime Generator time limit exceeded

alaiyeshi alaiyeshi025 at 163.com
Wed Nov 1 11:49:21 EST 2006


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)


More information about the Haskell-Cafe mailing list