Pickling a finite map (Binary + zlib) [was: [Haskell-cafe] Data.Binary poor read performance]

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Tue Feb 24 11:50:07 EST 2009


Don Stewart wrote:
> dons:
[...]
> Just serialising straight lists of pairs,
[...]
> And reading them back in,
> 
>     main = do
>         [f] <- getArgs
>         m <- decode `fmap` L.readFile f
>         print (length (m :: [(B.ByteString,Int)]))
>         print "done"

Well, you don't actually read the whole list here, just its length:

    instance Binary a => Binary [a] where
        put l  = put (length l) >> mapM_ put l
        get    = do n <- get :: Get Int
                    replicateM n get

To demonstrate, this works:

    main = do
        L.writeFile "v" (encode (42 :: Int))
        m <- decode `fmap` L.readFile "v"
        print (length (m :: [Int]))

So instead, we should try something like this:

    import Control.Parallel.Strategies

    instance NFData B.ByteString where
        rnf bs = bs `seq` ()

    main = do
        [f] <- getArgs
        m <- decode `fmap` L.readFile f
        print (rnf m `seq` length (m :: [(B.ByteString,Int)]))

My timings:

reading list, without rnf:
    0.04s
with rnf:
    0.16s
reading a Data.Map:
    0.52s
with rnf:
    0.62s

Bertram


More information about the Haskell-Cafe mailing list