Skip to content

Instantly share code, notes, and snippets.

@Mozk0
Created November 23, 2011 06:52
Show Gist options
  • Save Mozk0/1388049 to your computer and use it in GitHub Desktop.
Save Mozk0/1388049 to your computer and use it in GitHub Desktop.
Lazy encoding / decoding of [a] using Data.Binary in Haskell
{-# LANGUAGE FlexibleInstances #-}
--
-- head $ decode $ encode [1..] -- : infinite loop
-- head $ runLazily $ decode $ encode $ Lazily [1..] -- : 1
--
module Data.Binary.Lazy (
Lazily(..),
) where
import Data.Binary
import Data.Binary.Get
import Data.Functor ((<$>))
import Data.List (unfoldr)
import qualified Data.ByteString.Lazy as L
newtype Lazily a = Lazily { runLazily :: a }
chunkSize = 65535
instance Binary a => Binary (Lazily [a]) where
get = Lazily . concat . unfoldr get1 <$> getRemainingLazyByteString
where get1 s | L.null s = Nothing
get1 s | otherwise = Just $ drop3rd $ runGetState get s 0
put = mapM_ put . group chunkSize . runLazily
group :: Int -> [a] -> [[a]]
group n = unfoldr group1
where group1 [] = Nothing
group1 xs = Just $ splitAt n xs
drop3rd :: (a, b, c) -> (a, b)
drop3rd (x, y, _) = (x, y)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment