[Haskell-cafe] Slow IO?

Eugene Kirpichov ekirpichov at gmail.com
Sun Aug 30 08:34:13 EDT 2009


Here's my version that works in 0.7s for me for a file with 10^7
"999999999"'s but for some reason gets a 'wrong answer' at SPOJ :)

{-# LANGUAGE BangPatterns #-}
module Main where

import qualified Data.ByteString.Lazy as B
import Data.Word

answer :: Int -> B.ByteString -> Int
answer k = fst . B.foldl' f (0, 0)
  where f :: (Int,Int) -> Word8 -> (Int,Int)
        f (!countSoFar, !x) 10
          | x`mod`k==0 = (countSoFar+1, 0)
          | otherwise  = (countSoFar,   0)
        f (!countSoFar, !x) c = (countSoFar, 10*x+(fromIntegral c)-48)

readInt :: B.ByteString -> Int
readInt = B.foldl' (\x c -> 10*x+fromIntegral c-48) 0

main = do
  (line, rest) <- B.break (==10) `fmap` B.getContents
  let [n, k] = map readInt . B.split 32 $ line
  putStrLn . show $ answer k rest - 1


2009/8/30 Steve <stevech1097 at yahoo.com.au>:
> On Sun, 2009-08-30 at 06:30 -0400, Gwern Branwen wrote:
>> On Sun, Aug 30, 2009 at 6:14 AM, Steve<stevech1097 at yahoo.com.au> wrote:
>> > 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
>>
>> Did you try readInt?
>> http://hackage.haskell.org/packages/archive/bytestring/0.9.1.4/doc/html/Data-ByteString-Char8.html#23
>>
>
> Thanks. I didn't see readInt. It allows me to use ByteString and produce
> results about 10 times faster than System.IO hGetContents. It makes me
> wonder why the System.IO functions have not been replaced by
> Data.ByteString.
>
> My program runs in 8.56 seconds (its over the 8 secs limit but it was
> accepted).
>
> I compared the top 10 C/C++ results against the top 10 Haskell results:
> C/C++   ~0.4 secs
> Haskell ~5.0 secs
> So it looks like Haskell is ~13 slower for IO than C/C++, even (I
> assume) when using Data.ByteString or other speed-up tricks.
>
> Steve
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru


More information about the Haskell-Cafe mailing list