[commit: packages/binary] master: Extend the Binary class with 'putList :: [a] -> Put' (dd1f895)
git at git.haskell.org
git at git.haskell.org
Mon Apr 4 11:05:33 UTC 2016
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/dd1f895317db3c5bc17d04a87daaae24480985f5
>---------------------------------------------------------------
commit dd1f895317db3c5bc17d04a87daaae24480985f5
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date: Sun Apr 3 20:09:36 2016 +0200
Extend the Binary class with 'putList :: [a] -> Put'
The default implementation of the new class function is the same as
'instance Binary a => Binary [a]' used to be.
'putList' will enable users to define their own serialization for lists of
types. We'll use this to give new list serialization implementations for types
already defined in binary.
>---------------------------------------------------------------
dd1f895317db3c5bc17d04a87daaae24480985f5
src/Data/Binary/Class.hs | 13 ++++++++++---
1 file changed, 10 insertions(+), 3 deletions(-)
diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index d0cf71a..071b2f0 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -146,6 +146,9 @@ class Binary t where
-- | Decode a value in the Get monad
get :: Get t
+ putList :: [t] -> Put
+ putList = defaultPutList
+
#ifdef GENERICS
default put :: (Generic t, GBinaryPut (Rep t)) => t -> Put
put = gput . from
@@ -154,6 +157,10 @@ class Binary t where
get = to `fmap` gget
#endif
+{-# INLINE defaultPutList #-}
+defaultPutList :: Binary a => [a] -> Put
+defaultPutList xs = put (length xs) >> mapM_ put xs
+
------------------------------------------------------------------------
-- Simple instances
@@ -495,9 +502,9 @@ instance (Binary a, Binary b, Binary c, Binary d, Binary e,
-- Container types
instance Binary a => Binary [a] where
- put l = put (length l) >> mapM_ put l
- get = do n <- get :: Get Int
- getMany n
+ put = putList
+ get = do n <- get :: Get Int
+ getMany n
-- | 'getMany n' get 'n' elements in order, without blowing the stack.
getMany :: Binary a => Int -> Get [a]
More information about the ghc-commits
mailing list