[Haskell-cafe] Fast number parsing with strict bytestrings [Was: Re: Seemingly subtle change causes large performance variation]

Donald Bruce Stewart dons at cse.unsw.edu.au
Thu Jun 7 21:42:41 EDT 2007


mdanish:
> Hello,
> 
> I've been playing with the INTEST problem on SPOJ which demonstrates
> the ability to write a program which processes large quantities of
> input data.  http://www.spoj.pl/problems/INTEST/
  
> But when I make a slight modification, the program chews up a ton more memory
> and takes more time:
> 
> import Control.Monad
> import Data.Maybe
> import qualified Data.ByteString.Char8 as B
> 
> divisibleBy :: Int -> Int -> Bool
> a `divisibleBy` n = a `rem` n == 0
> 
> main :: IO ()
> main = do
>     [n,k] <- (map int . B.split ' ') `fmap` B.getLine :: IO [Int]
> 
>     let
>         doLine :: Int -> Int -> IO Int
>         doLine r _ = B.getLine >>= return . testDiv r
>         -- 'return' moved here      ^^


What follows is a solution to the original question, and then a dramatic
rewrite, showing the fastest way (that I know of) to parse \n separated
lists of numbers in Haskell.  The results should outperform C fairly
well.


*** Solution 1: don't be so lazy in the fold.

First, look at that lazy fold. A simple fix, try being explict about forcing
your accumulator:

        doLine :: Int -> Int -> IO Int
        doLine r _ = B.getLine >>= \s -> return $! testDiv r s


And some timing data:

Original:
    $ time ./A < in
    29359
    ./A < in  1.52s user 0.06s system 93% cpu 1.679 total

Too lazy:
    $ time ./B < in
    29359
    ./B < in  3.84s user 0.26s system 82% cpu 4.957 total

Hand back some strictness hints:
    $ time ./D < in
    29359
    ./D < in  1.52s user 0.03s system 94% cpu 1.637 total


*** Solution 2: use lazy bytestrings to avoid gunky IO


Now, however, I'd give up on that explict getLine stuff, and use a lazy
bytestring. Something like this:

    import Data.Maybe
    import Data.List
    import qualified Data.ByteString.Lazy.Char8 as L

    main :: IO ()
    main = do
        (l:ls) <- L.lines `fmap` L.getContents -- done with IO now.
        let [n,k] = map int (L.split ' ' l)
        print . foldl' (test k) 0 . map int . take n $ ls

    test :: Int -> Int -> Int -> Int
    test k acc n | n `divisibleBy` k = acc+1
                 | otherwise         = acc

    int :: L.ByteString -> Int
    int = fst . fromJust . L.readInt

    divisibleBy :: Int -> Int -> Bool
    a `divisibleBy` n = a `rem` n == 0


The general rule for bytestring loops is to avoid IO, and to use lazy
bytestrings if you need 'lines'. Also, program in a high level, using
combinators, rather than your own loops, so that fusion will kick in (we
get some list fusion here).

And running it:

    $ time ./C < in
    29359
    ./C < in  1.22s user 0.04s system 94% cpu 1.335 total

Ok, faster, and cleaner. Avoid mixing IO into your code!


*** Solution 3: 4x faster by processing strict cache chunks


Now the fun part.

The following code is the fastest way I know to process lists of numbers
(in any language). Its' based on similar code I wrote for the language
shootout.  The key trick is to use lazy bytestrings *only* as a method
for filling the cache with newline-aligned chunks of numbers. Once
you've got that perfectly-sized chunk, walk its lines, and process them.
This is all done in Haskell, and relies on an understanding of the low
level details of bytestring optimisations.

The general framework could be reused for any code that needs to process
a list of numbers in a file, where you care about speed.

It performs as follows:

    $ time ./F < in
    29359
    ./F < in  0.24s user 0.01s system 76% cpu 0.327 total

Pretty fast..

Previous experience[1] indicates it is pretty hard to write a C line
parsing program[2] that that run this fast.  And the code, with comments:

1. http://shootout.alioth.debian.org/gp4/benchmark.php?test=sumcol&lang=ghc&id=0
2. http://shootout.alioth.debian.org/gp4/benchmark.php?test=sumcol&lang=gcc&id=2


    {-# OPTIONS -fbang-patterns #-}

    import Data.Char
    import Data.Maybe
    import Data.ByteString.Base
    import qualified Data.ByteString.Char8      as S
    import qualified Data.ByteString.Lazy.Char8 as L

    main = do
        ss <- L.getContents -- done with IO now.

        let (l,ls) = L.break (=='\n') ss

            -- don't need count, we're allocating lazily
            k      = fst . fromJust . L.readInt . last . L.split ' ' $ l

            file   = L.toChunks (L.tail ls) -- a lazy list of strict cache chunks

        print $ process k 0 file

    divisibleBy :: Int -> Int -> Bool
    a `divisibleBy` n = a `rem` n == 0

    -- ---------------------------------------------------------------------
    --
    -- Optimised parsing of strict bytestrings representing \n separated numbers
    --

    --
    -- we have the file as a list of cache chunks
    -- align them on \n boundaries, and process each chunk separately
    -- when the next chunk is demanded, it will be read in.
    --
    process :: Int -> Int -> [S.ByteString] -> Int
    process k i []      = i
    process k !i (s:t:ts) | S.last s /= '\n' = process k (add k i s') ts'
      where
        (s',r) = S.breakEnd (=='\n') s
        ts'    = (S.append r t) : ts        -- join chunks on line boundaries

    process k i (s: ss) = process k (add k i s) ss

    --
    -- process a single cache-sized chunk of numbers, \n aligned
    --
    add :: Int -> Int -> S.ByteString -> Int
    add k i s | S.null s  = i
              | otherwise = test k i (parse x) xs
      where (x,xs) = uncons s

    --
    -- process a single line, until \n
    --
    test :: Int -> Int -> Int -> ByteString -> Int
    test k i !n t
        | y == '\n' = -- done reading the line, process it:
            if n `divisibleBy` k then add k (i+1) ys
                                 else add k i     ys
       | otherwise = test k i n' ys
      where (y,ys) = uncons t
            n'     = parse y + 10 * n

    parse c  = ord c - ord '0'

    -- fastest way to take the head of a strict bytestring
    uncons s = (w2c (unsafeHead s), unsafeTail s)


Cheers,
  Don


More information about the Haskell-Cafe mailing list