[Haskell-cafe] Slow IO?

Steve stevech1097 at yahoo.com.au
Sun Aug 30 07:54:53 EDT 2009


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







More information about the Haskell-Cafe mailing list