#if __GLASGOW_HASKELL__ >= 701 && __GLASGOW_HASKELL__ != 702
#endif
#ifdef GENERICS
#endif
#if MIN_VERSION_base(4,8,0)
#define HAS_NATURAL
#define HAS_VOID
#endif
#if MIN_VERSION_base(4,7,0)
#define HAS_FIXED_CONSTRUCTOR
#endif
#if __GLASGOW_HASKELL__ >= 704
#define HAS_GHC_FINGERPRINT
#endif
#ifndef HAS_FIXED_CONSTRUCTOR
#endif
module Data.Binary.Class (
Binary(..)
#ifdef GENERICS
, GBinaryGet(..)
, GBinaryPut(..)
#endif
) where
import Data.Word
import Data.Bits
import Data.Int
import Data.Complex (Complex(..))
#ifdef HAS_VOID
import Data.Void
#endif
import Data.Binary.Put
import Data.Binary.Get
#if ! MIN_VERSION_base(4,8,0)
import Control.Applicative
import Data.Monoid (mempty)
#endif
import Data.Monoid ((<>))
import Control.Monad
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Builder.Prim as Prim
import Data.List (unfoldr, foldl')
import qualified Data.ByteString as B
#if MIN_VERSION_bytestring(0,10,4)
import qualified Data.ByteString.Short as BS
#endif
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Ratio as R
import qualified Data.Tree as T
import Data.Array.Unboxed
#ifdef GENERICS
import GHC.Generics
#endif
#ifdef HAS_NATURAL
import Numeric.Natural
#endif
import qualified Data.Fixed as Fixed
#if __GLASGOW_HASKELL__ >= 606
import qualified Data.Sequence as Seq
import qualified Data.Foldable as Fold
#endif
#ifdef HAS_GHC_FINGERPRINT
import GHC.Fingerprint
#endif
import Data.Version (Version(..))
#ifdef GENERICS
class GBinaryPut f where
gput :: f t -> Put
class GBinaryGet f where
gget :: Get (f t)
#endif
class Binary t where
put :: t -> Put
get :: Get t
putList :: [t] -> Put
putList = defaultPutList
#ifdef GENERICS
default put :: (Generic t, GBinaryPut (Rep t)) => t -> Put
put = gput . from
default get :: (Generic t, GBinaryGet (Rep t)) => Get t
get = to `fmap` gget
#endif
defaultPutList :: Binary a => [a] -> Put
defaultPutList xs = put (length xs) <> mapM_ put xs
#ifdef HAS_VOID
instance Binary Void where
put = absurd
get = mzero
#endif
instance Binary () where
put () = mempty
get = return ()
instance Binary Bool where
put = putWord8 . fromIntegral . fromEnum
get = getWord8 >>= toBool
where
toBool 0 = return False
toBool 1 = return True
toBool c = fail ("Could not map value " ++ show c ++ " to Bool")
instance Binary Ordering where
put = putWord8 . fromIntegral . fromEnum
get = getWord8 >>= toOrd
where
toOrd 0 = return LT
toOrd 1 = return EQ
toOrd 2 = return GT
toOrd c = fail ("Could not map value " ++ show c ++ " to Ordering")
instance Binary Word8 where
put = putWord8
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.word8 xs)
get = getWord8
instance Binary Word16 where
put = putWord16be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.word16BE xs)
get = getWord16be
instance Binary Word32 where
put = putWord32be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.word32BE xs)
get = getWord32be
instance Binary Word64 where
put = putWord64be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.word64BE xs)
get = getWord64be
instance Binary Int8 where
put = putInt8
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.int8 xs)
get = getInt8
instance Binary Int16 where
put = putInt16be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.int16BE xs)
get = getInt16be
instance Binary Int32 where
put = putInt32be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.int32BE xs)
get = getInt32be
instance Binary Int64 where
put = putInt64be
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.int64BE xs)
get = getInt64be
instance Binary Word where
put = putWord64be . fromIntegral
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.word64BE (map fromIntegral xs))
get = liftM fromIntegral getWord64be
instance Binary Int where
put = putInt64be . fromIntegral
putList xs =
put (length xs)
<> putBuilder (Prim.primMapListFixed Prim.int64BE (map fromIntegral xs))
get = liftM fromIntegral getInt64be
type SmallInt = Int32
instance Binary Integer where
put n | n >= lo && n <= hi =
putBuilder (Prim.primFixed (Prim.word8 Prim.>*< Prim.int32BE) (0, fromIntegral n))
where
lo = fromIntegral (minBound :: SmallInt) :: Integer
hi = fromIntegral (maxBound :: SmallInt) :: Integer
put n =
putWord8 1
<> put sign
<> put (unroll (abs n))
where
sign = fromIntegral (signum n) :: Word8
get = do
tag <- get :: Get Word8
case tag of
0 -> liftM fromIntegral (get :: Get SmallInt)
_ -> do sign <- get
bytes <- get
let v = roll bytes
return $! if sign == (1 :: Word8) then v else v
#ifdef HAS_FIXED_CONSTRUCTOR
instance Binary (Fixed.Fixed a) where
put (Fixed.MkFixed a) = put a
get = Fixed.MkFixed `liftM` get
#else
instance forall a. Fixed.HasResolution a => Binary (Fixed.Fixed a) where
put x = put (truncate (x * fromInteger (Fixed.resolution (undefined :: Maybe a))) :: Integer)
get = (\x -> fromInteger x / fromInteger (Fixed.resolution (undefined :: Maybe a))) `liftM` get
#endif
unroll :: (Integral a, Bits a) => a -> [Word8]
unroll = unfoldr step
where
step 0 = Nothing
step i = Just (fromIntegral i, i `shiftR` 8)
roll :: (Integral a, Bits a) => [Word8] -> a
roll = foldl' unstep 0 . reverse
where
unstep a b = a `shiftL` 8 .|. fromIntegral b
#ifdef HAS_NATURAL
type NaturalWord = Word64
instance Binary Natural where
put n | n <= hi =
putWord8 0
<> put (fromIntegral n :: NaturalWord)
where
hi = fromIntegral (maxBound :: NaturalWord) :: Natural
put n =
putWord8 1
<> put (unroll (abs n))
get = do
tag <- get :: Get Word8
case tag of
0 -> liftM fromIntegral (get :: Get NaturalWord)
_ -> do bytes <- get
return $! roll bytes
#endif
instance (Binary a,Integral a) => Binary (R.Ratio a) where
put r = put (R.numerator r) <> put (R.denominator r)
get = liftM2 (R.%) get get
instance Binary a => Binary (Complex a) where
put (r :+ i) = put (r, i)
get = (\(r,i) -> r :+ i) <$> get
instance Binary Char where
put = putCharUtf8
putList str = put (length str) <> putStringUtf8 str
get = do
let getByte = liftM (fromIntegral :: Word8 -> Int) get
shiftL6 = flip shiftL 6 :: Int -> Int
w <- getByte
r <- case () of
_ | w < 0x80 -> return w
| w < 0xe0 -> do
x <- liftM (xor 0x80) getByte
return (x .|. shiftL6 (xor 0xc0 w))
| w < 0xf0 -> do
x <- liftM (xor 0x80) getByte
y <- liftM (xor 0x80) getByte
return (y .|. shiftL6 (x .|. shiftL6
(xor 0xe0 w)))
| otherwise -> do
x <- liftM (xor 0x80) getByte
y <- liftM (xor 0x80) getByte
z <- liftM (xor 0x80) getByte
return (z .|. shiftL6 (y .|. shiftL6
(x .|. shiftL6 (xor 0xf0 w))))
getChr r
where
getChr w
| w <= 0x10ffff = return $! toEnum $ fromEnum w
| otherwise = fail "Not a valid Unicode code point!"
instance (Binary a, Binary b) => Binary (a,b) where
put (a,b) = put a <> put b
get = liftM2 (,) get get
instance (Binary a, Binary b, Binary c) => Binary (a,b,c) where
put (a,b,c) = put a <> put b <> put c
get = liftM3 (,,) get get get
instance (Binary a, Binary b, Binary c, Binary d) => Binary (a,b,c,d) where
put (a,b,c,d) = put a <> put b <> put c <> put d
get = liftM4 (,,,) get get get get
instance (Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a,b,c,d,e) where
put (a,b,c,d,e) = put a <> put b <> put c <> put d <> put e
get = liftM5 (,,,,) get get get get get
instance (Binary a, Binary b, Binary c, Binary d, Binary e, Binary f)
=> Binary (a,b,c,d,e,f) where
put (a,b,c,d,e,f) = put (a,(b,c,d,e,f))
get = do (a,(b,c,d,e,f)) <- get ; return (a,b,c,d,e,f)
instance (Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g)
=> Binary (a,b,c,d,e,f,g) where
put (a,b,c,d,e,f,g) = put (a,(b,c,d,e,f,g))
get = do (a,(b,c,d,e,f,g)) <- get ; return (a,b,c,d,e,f,g)
instance (Binary a, Binary b, Binary c, Binary d, Binary e,
Binary f, Binary g, Binary h)
=> Binary (a,b,c,d,e,f,g,h) where
put (a,b,c,d,e,f,g,h) = put (a,(b,c,d,e,f,g,h))
get = do (a,(b,c,d,e,f,g,h)) <- get ; return (a,b,c,d,e,f,g,h)
instance (Binary a, Binary b, Binary c, Binary d, Binary e,
Binary f, Binary g, Binary h, Binary i)
=> Binary (a,b,c,d,e,f,g,h,i) where
put (a,b,c,d,e,f,g,h,i) = put (a,(b,c,d,e,f,g,h,i))
get = do (a,(b,c,d,e,f,g,h,i)) <- get ; return (a,b,c,d,e,f,g,h,i)
instance (Binary a, Binary b, Binary c, Binary d, Binary e,
Binary f, Binary g, Binary h, Binary i, Binary j)
=> Binary (a,b,c,d,e,f,g,h,i,j) where
put (a,b,c,d,e,f,g,h,i,j) = put (a,(b,c,d,e,f,g,h,i,j))
get = do (a,(b,c,d,e,f,g,h,i,j)) <- get ; return (a,b,c,d,e,f,g,h,i,j)
instance Binary a => Binary [a] where
put = putList
get = do n <- get :: Get Int
getMany n
getMany :: Binary a => Int -> Get [a]
getMany n = go [] n
where
go xs 0 = return $! reverse xs
go xs i = do x <- get
x `seq` go (x:xs) (i1)
instance (Binary a) => Binary (Maybe a) where
put Nothing = putWord8 0
put (Just x) = putWord8 1 <> put x
get = do
w <- getWord8
case w of
0 -> return Nothing
_ -> liftM Just get
instance (Binary a, Binary b) => Binary (Either a b) where
put (Left a) = putWord8 0 <> put a
put (Right b) = putWord8 1 <> put b
get = do
w <- getWord8
case w of
0 -> liftM Left get
_ -> liftM Right get
instance Binary B.ByteString where
put bs = put (B.length bs)
<> putByteString bs
get = get >>= getByteString
instance Binary ByteString where
put bs = put (fromIntegral (L.length bs) :: Int)
<> putLazyByteString bs
get = get >>= getLazyByteString
#if MIN_VERSION_bytestring(0,10,4)
instance Binary BS.ShortByteString where
put bs = put (BS.length bs)
<> putShortByteString bs
get = get >>= fmap BS.toShort . getByteString
#endif
instance (Binary a) => Binary (Set.Set a) where
put s = put (Set.size s) <> mapM_ put (Set.toAscList s)
get = liftM Set.fromDistinctAscList get
instance (Binary k, Binary e) => Binary (Map.Map k e) where
put m = put (Map.size m) <> mapM_ put (Map.toAscList m)
get = liftM Map.fromDistinctAscList get
instance Binary IntSet.IntSet where
put s = put (IntSet.size s) <> mapM_ put (IntSet.toAscList s)
get = liftM IntSet.fromDistinctAscList get
instance (Binary e) => Binary (IntMap.IntMap e) where
put m = put (IntMap.size m) <> mapM_ put (IntMap.toAscList m)
get = liftM IntMap.fromDistinctAscList get
#if __GLASGOW_HASKELL__ >= 606
instance (Binary e) => Binary (Seq.Seq e) where
put s = put (Seq.length s) <> Fold.mapM_ put s
get = do n <- get :: Get Int
rep Seq.empty n get
where rep xs 0 _ = return $! xs
rep xs n g = xs `seq` n `seq` do
x <- g
rep (xs Seq.|> x) (n1) g
#endif
instance Binary Double where
put d = put (decodeFloat d)
get = do
x <- get
y <- get
return $! encodeFloat x y
instance Binary Float where
put f = put (decodeFloat f)
get = do
x <- get
y <- get
return $! encodeFloat x y
instance (Binary e) => Binary (T.Tree e) where
put (T.Node r s) = put r <> put s
get = liftM2 T.Node get get
instance (Binary i, Ix i, Binary e) => Binary (Array i e) where
put a =
put (bounds a)
<> put (rangeSize $ bounds a)
<> mapM_ put (elems a)
get = do
bs <- get
n <- get
xs <- getMany n
return (listArray bs xs)
instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) where
put a =
put (bounds a)
<> put (rangeSize $ bounds a)
<> mapM_ put (elems a)
get = do
bs <- get
n <- get
xs <- getMany n
return (listArray bs xs)
#ifdef HAS_GHC_FINGERPRINT
instance Binary Fingerprint where
put (Fingerprint x1 x2) = put x1 <> put x2
get = do
x1 <- get
x2 <- get
return $! Fingerprint x1 x2
#endif
instance Binary Version where
put (Version br tags) = put br <> put tags
get = Version <$> get <*> get