Fwd: [Haskell-cafe] Data.Binary suboptimal instance

I suppose I should send my reply to the list ...
---------- Forwarded message ----------
From: Antoine Latter
You can! - It's again time to point out that Put shouldn't be a monad, but a monoid. But as it is, Put is a Writer monad on top of the Builder monoid. Better use that Builder monoid directly.
Could you elaborate? I didn't quite understand.
Anyway I had similar problem and simply wrote few functions. They encode/decode values of same type element by element. It's lazy enough so code could be written in following style:
Or you could go for the compromise position, where the list can be part of a complex data structure so you're not relying on EOF to find the end. (warning, I don't have my compiler handy so this may not even typecheck) import Control.Monad import Data.Monoid import Data.Binary.Builder import Data.Binary.Get data ChunkedList a = Cons [a] (ChunkedList a) -- Non-null list | Nil chunkSize = 50 fromList :: [a] -> ChunkedList a fromList [] = Nil fromList xs = let (front,back) = splitAt chunkSize xs in Cons front (fromList back) toList :: ChunkedList a -> [a] toList Nil = [] toList (Cons front back) = front ++ toList back putList :: (a -> Builder) -> [a] -> Builder putList f xs = putChunkedList (fromList xs) where putChunkedList Nil = singleton 0 putChunkedList (Cons front back) = mconcat [ singleton (genericLength front) , mconcat $ map f front , putChunkedList back ] getList :: Get a -> Get [a] getList m = toList `liftM` getChunkedList where getChunkedList = do cLen <- getWord8 case cLen of 0 -> return Nil _ -> Cons `liftM` replicateM (fromIntegral cLen) m `ap` getChunkedList

On Saturday 23 May 2009 02:55:17 Antoine Latter wrote:
Or you could go for the compromise position, where the list can be part of a complex data structure so you're not relying on EOF to find the end.
Interesting solution however it does not perform very nice. I wrote microbenchmark
xs :: [Word32] xs = [1..(10^6)]
Writing chunked list of Word32
B.writeFile "chunked" . toLazyByteString . putList putWord32be $ xs real 0m4.311s user 0m3.272s sys 0m0.096s
Reading chunked list of Word32
print . last . runGet (getList getWord32be) =<< B.readFile "chunked" real 0m0.634s user 0m0.496s sys 0m0.012s
Writing stream of Word32
B.writeFile "stream" . encodeStream $ xs real 0m0.391s user 0m0.252s sys 0m0.020s
Reading stream of Word32
print . (last :: [Word32] -> Word32) . decodeStream =<< B.readFile "stream" real 0m0.376s user 0m0.248s sys 0m0.020s
I didn'd do any profiling so I have no idea why writing is so slow. -- Best regard Khudyakov Alexey
participants (2)
-
Antoine Latter
-
Khudyakov Alexey