
On Sun, 2009-08-30 at 14:40 +0400, Eugene Kirpichov wrote: Thanks, that works nicely too. However, I believe its not a standard package, so I don't think it can be used for Sphere Online problems. I timed a test run on a 10MB file and its a little slower than my solution with the ByteString readInt improvement. Steve
module Main where
import qualified Data.ByteString.Lazy as B import Data.ByteString.Nums.Careless -- from bytestring-nums package
bint :: B.ByteString -> Int bint = int
main = do line : rest <- B.split 10 `fmap` B.getContents let [n, k] = map int . B.split 32 $ line putStrLn . show . length . tail . filter ((==0).(`mod`k).bint) $ rest
This does a 100MB file in 2.7s (probably because the file is cached by the filesystem).
2009/8/30 Steve
: Hi, I'm tackling a Sphere Online Judge tutorial question where it tests how fast you can process input data. You need to achieve at least 2.5MB of input data per second at runtime (on an old machine running ghc 6.6.1). This is probably close to the limit of Haskell's ability.
https://www.spoj.pl/problems/INTEST/
I can see that 24 haskell programmers have solved it, but most are very close to the 8 secs limit (and 6/24 are even over the limit!).
Here's my code. It fails with a "time limit exceeded" error. (I think it would calculate the correct result, eventually).
module Main where
import qualified Data.List as DLi import qualified System.IO as SIO
main :: IO () main = do line1 <- SIO.hGetLine SIO.stdin let k = read $ words line1 !! 1 s <- SIO.hGetContents SIO.stdin print $ count s k
count :: String -> Int -> Int count s k = DLi.foldl' foldFunc 0 (map read $ words s) where foldFunc :: Int -> Int -> Int foldFunc a b | mod b k == 0 = a+1 | otherwise = a
I tried using Data.ByteString but then found that 'read' needs a String, not a ByteString. I tried using buffered IO, but it did not make any difference.
Any suggestions on how to speed it up?
Regards, Steve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe