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

Antoine Latter aslatter at gmail.com
Fri May 22 18:55:17 EDT 2009


I suppose I should send my reply to the list ...


---------- Forwarded message ----------
From: Antoine Latter <aslatter at gmail.com>
Date: Fri, May 22, 2009 at 5:54 PM
Subject: Re: [Haskell-cafe] Data.Binary suboptimal instance
To: Khudyakov Alexey <alexey.skladnoy at gmail.com>


On Fri, May 22, 2009 at 4:36 PM, Khudyakov Alexey
<alexey.skladnoy at gmail.com> wrote:
>> 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


More information about the Haskell-Cafe mailing list