{-# LANGUAGE DeriveGeneric #-}
module Data.MessagePack where
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad
import GHC.Generics (Generic)
import Data.Bits
import Data.Int
import Data.MessagePack.Spec
import Data.Serialize
import Data.Word
import qualified Data.ByteString as BS
import qualified Data.Map as M
data Object = ObjectNil
| ObjectUInt Word64
| ObjectInt Int64
| ObjectBool Bool
| ObjectFloat Float
| ObjectDouble Double
| ObjectString BS.ByteString
| ObjectBinary BS.ByteString
| ObjectArray [Object]
| ObjectMap (M.Map Object Object )
| ObjectExt !Int8 BS.ByteString
deriving (Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq, Eq Object
Eq Object
-> (Object -> Object -> Ordering)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Object)
-> (Object -> Object -> Object)
-> Ord Object
Object -> Object -> Bool
Object -> Object -> Ordering
Object -> Object -> Object
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Object -> Object -> Object
$cmin :: Object -> Object -> Object
max :: Object -> Object -> Object
$cmax :: Object -> Object -> Object
>= :: Object -> Object -> Bool
$c>= :: Object -> Object -> Bool
> :: Object -> Object -> Bool
$c> :: Object -> Object -> Bool
<= :: Object -> Object -> Bool
$c<= :: Object -> Object -> Bool
< :: Object -> Object -> Bool
$c< :: Object -> Object -> Bool
compare :: Object -> Object -> Ordering
$ccompare :: Object -> Object -> Ordering
$cp1Ord :: Eq Object
Ord, Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show, (forall x. Object -> Rep Object x)
-> (forall x. Rep Object x -> Object) -> Generic Object
forall x. Rep Object x -> Object
forall x. Object -> Rep Object x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Object x -> Object
$cfrom :: forall x. Object -> Rep Object x
Generic)
instance NFData Object
instance Serialize Object where
put :: Putter Object
put (ObjectUInt Word64
i)
| Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word64
0 Bool -> Bool -> Bool
&& Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
0x100 = Putter Word8
putWord8 Word8
uint8 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
i)
| Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word64
0 Bool -> Bool -> Bool
&& Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
0x10000 = Putter Word8
putWord8 Word8
uint16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
i)
| Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word64
0 Bool -> Bool -> Bool
&& Word64
i Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
0x100000000 = Putter Word8
putWord8 Word8
uint32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
i)
| Bool
otherwise = Putter Word8
putWord8 Word8
uint64 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word64
putWord64be (Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
i)
put (ObjectInt Int64
i)
| Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
0 Bool -> Bool -> Bool
&& Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
127 = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ Int64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i
| Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= -Int64
32 Bool -> Bool -> Bool
&& Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= -Int64
1 = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ Int64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i
| Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= -Int64
0x80 Bool -> Bool -> Bool
&& Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0x80 = Putter Word8
putWord8 Word8
int8 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Int64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i)
| Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= -Int64
0x8000 Bool -> Bool -> Bool
&& Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0x8000 = Putter Word8
putWord8 Word8
int16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i)
| Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= -Int64
0x80000000 Bool -> Bool -> Bool
&& Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0x80000000 = Putter Word8
putWord8 Word8
int32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i)
| Bool
otherwise = Putter Word8
putWord8 Word8
int64 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word64
putWord64be (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i)
put Object
ObjectNil = Putter Word8
putWord8 Word8
nil
put (ObjectBool Bool
b) = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ if Bool
b then Word8
true else Word8
false
put (ObjectFloat Float
f) = Putter Word8
putWord8 Word8
float32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Float -> PutM ()
putFloat32be Float
f
put (ObjectDouble Double
d) = Putter Word8
putWord8 Word8
float64 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Double -> PutM ()
putFloat64be Double
d
put (ObjectString ByteString
t) =
PutM ()
header PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter ByteString
putByteString ByteString
t
where
size :: Int
size = ByteString -> Int
BS.length ByteString
t
header :: PutM ()
header
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
31 = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ Word8
fixstr Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x100 = Putter Word8
putWord8 Word8
str8 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000 = Putter Word8
putWord8 Word8
str16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Bool
otherwise = Putter Word8
putWord8 Word8
str32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
put (ObjectBinary ByteString
bytes) =
PutM ()
header PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter ByteString
putByteString ByteString
bytes
where
size :: Int
size = ByteString -> Int
BS.length ByteString
bytes
header :: PutM ()
header
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x100 = Putter Word8
putWord8 Word8
bin8 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000 = Putter Word8
putWord8 Word8
bin16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Bool
otherwise = Putter Word8
putWord8 Word8
bin32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
put (ObjectArray [Object]
a) =
PutM ()
buildArray PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Object -> [Object] -> PutM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Object
forall t. Serialize t => Putter t
put [Object]
a
where
size :: Int
size = [Object] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Object]
a
buildArray :: PutM ()
buildArray
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
15 = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ Word8
fixarray Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000 = Putter Word8
putWord8 Word8
array16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Bool
otherwise = Putter Word8
putWord8 Word8
array32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
put (ObjectMap Map Object Object
m) =
PutM ()
buildMap PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ((Object, Object) -> PutM ()) -> [(Object, Object)] -> PutM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Object, Object) -> PutM ()
forall t. Serialize t => Putter t
put (Map Object Object -> [(Object, Object)]
forall k a. Map k a -> [(k, a)]
M.toList Map Object Object
m)
where
size :: Int
size = Map Object Object -> Int
forall k a. Map k a -> Int
M.size Map Object Object
m
buildMap :: PutM ()
buildMap
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
15 = Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ Word8
fixmap Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000 = Putter Word8
putWord8 Word8
map16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Bool
otherwise = Putter Word8
putWord8 Word8
map32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
put (ObjectExt Int8
t ByteString
bytes) = PutM ()
header PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
t) PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter ByteString
putByteString ByteString
bytes
where
size :: Int
size = ByteString -> Int
BS.length ByteString
bytes
header :: PutM ()
header
| Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Putter Word8
putWord8 Word8
fixext1
| Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 = Putter Word8
putWord8 Word8
fixext2
| Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 = Putter Word8
putWord8 Word8
fixext4
| Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
8 = Putter Word8
putWord8 Word8
fixext8
| Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
16 = Putter Word8
putWord8 Word8
fixext16
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x100 = Putter Word8
putWord8 Word8
ext8 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word8
putWord8 (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000 = Putter Word8
putWord8 Word8
ext16 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word16
putWord16be (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
| Bool
otherwise = Putter Word8
putWord8 Word8
ext32 PutM () -> PutM () -> PutM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Word32
putWord32be (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size)
get :: Get Object
get =
Get Word8
getWord8 Get Word8 -> (Word8 -> Get Object) -> Get Object
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> Get Object
getObject
where
getObject :: Word8 -> Get Object
getObject Word8
k
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
nil = Object -> Get Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
ObjectNil
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
false = Object -> Get Object
forall (m :: * -> *) a. Monad m => a -> m a
return (Object -> Get Object) -> Object -> Get Object
forall a b. (a -> b) -> a -> b
$ Bool -> Object
ObjectBool Bool
False
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
true = Object -> Get Object
forall (m :: * -> *) a. Monad m => a -> m a
return (Object -> Get Object) -> Object -> Get Object
forall a b. (a -> b) -> a -> b
$ Bool -> Object
ObjectBool Bool
True
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
bin8 = do Int
n <- Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Get Word8 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
ByteString -> Object
ObjectBinary (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
bin16 = do Int
n <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
ByteString -> Object
ObjectBinary (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
bin32 = do Int
n <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Get Word32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
ByteString -> Object
ObjectBinary (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
float32 = Float -> Object
ObjectFloat (Float -> Object) -> Get Float -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Float
getFloat32be
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
float64 = Double -> Object
ObjectDouble (Double -> Object) -> Get Double -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Double
getFloat64be
| Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
posFixintMask Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
posFixint = Object -> Get Object
forall (m :: * -> *) a. Monad m => a -> m a
return (Object -> Get Object) -> Object -> Get Object
forall a b. (a -> b) -> a -> b
$ Int64 -> Object
ObjectInt (Int64 -> Object) -> Int64 -> Object
forall a b. (a -> b) -> a -> b
$ Word8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
k
| Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
negFixintMask Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
negFixint = Object -> Get Object
forall (m :: * -> *) a. Monad m => a -> m a
return (Object -> Get Object) -> Object -> Get Object
forall a b. (a -> b) -> a -> b
$ Int64 -> Object
ObjectInt (Int64 -> Object) -> Int64 -> Object
forall a b. (a -> b) -> a -> b
$ Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
k :: Int8)
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
uint8 = Word64 -> Object
ObjectUInt (Word64 -> Object) -> (Word8 -> Word64) -> Word8 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Object) -> Get Word8 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
uint16 = Word64 -> Object
ObjectUInt (Word64 -> Object) -> (Word16 -> Word64) -> Word16 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Object) -> Get Word16 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
uint32 = Word64 -> Object
ObjectUInt (Word64 -> Object) -> (Word32 -> Word64) -> Word32 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Object) -> Get Word32 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
uint64 = Word64 -> Object
ObjectUInt (Word64 -> Object) -> Get Word64 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getWord64be
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
int8 = Int64 -> Object
ObjectInt (Int64 -> Object) -> (Int8 -> Int64) -> Int8 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int8 -> Object) -> Get Int8 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Int8
forall t. Serialize t => Get t
get :: Get Int8)
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
int16 = Int64 -> Object
ObjectInt (Int64 -> Object) -> (Int16 -> Int64) -> Int16 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int16 -> Object) -> Get Int16 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Int16
forall t. Serialize t => Get t
get :: Get Int16)
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
int32 = Int64 -> Object
ObjectInt (Int64 -> Object) -> (Int32 -> Int64) -> Int32 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Object) -> Get Int32 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Int32
forall t. Serialize t => Get t
get :: Get Int32)
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
int64 = Int64 -> Object
ObjectInt (Int64 -> Object) -> (Int64 -> Int64) -> Int64 -> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Object) -> Get Int64 -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Int64
forall t. Serialize t => Get t
get :: Get Int64)
| Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
fixstrMask Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixstr = let n :: Int
n = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Word8 -> Int
forall a b. (a -> b) -> a -> b
$ Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8 -> Word8
forall a. Bits a => a -> a
complement Word8
fixstrMask
in ByteString -> Object
ObjectString (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
str8 = do Int
n <- Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Get Word8 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
ByteString -> Object
ObjectString (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
str16 = do Int
n <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
ByteString -> Object
ObjectString (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
str32 = do Int
n <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Get Word32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
ByteString -> Object
ObjectString (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
fixarrayMask Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixarray = let n :: Int
n = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Word8 -> Int
forall a b. (a -> b) -> a -> b
$ Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8 -> Word8
forall a. Bits a => a -> a
complement Word8
fixarrayMask
in [Object] -> Object
ObjectArray ([Object] -> Object) -> Get [Object] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get Object -> Get [Object]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get Object
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
array16 = do Int
n <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
[Object] -> Object
ObjectArray ([Object] -> Object) -> Get [Object] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get Object -> Get [Object]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get Object
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
array32 = do Int
n <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Get Word32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
[Object] -> Object
ObjectArray ([Object] -> Object) -> Get [Object] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get Object -> Get [Object]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get Object
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
fixmapMask Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixmap = let n :: Int
n = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Word8 -> Int
forall a b. (a -> b) -> a -> b
$ Word8
k Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8 -> Word8
forall a. Bits a => a -> a
complement Word8
fixmapMask
in Map Object Object -> Object
ObjectMap (Map Object Object -> Object)
-> ([(Object, Object)] -> Map Object Object)
-> [(Object, Object)]
-> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Object, Object)] -> Map Object Object
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Object, Object)] -> Object)
-> Get [(Object, Object)] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get (Object, Object) -> Get [(Object, Object)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get (Object, Object)
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
map16 = do Int
n <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
Map Object Object -> Object
ObjectMap (Map Object Object -> Object)
-> ([(Object, Object)] -> Map Object Object)
-> [(Object, Object)]
-> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Object, Object)] -> Map Object Object
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Object, Object)] -> Object)
-> Get [(Object, Object)] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get (Object, Object) -> Get [(Object, Object)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get (Object, Object)
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
map32 = do Int
n <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Get Word32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
Map Object Object -> Object
ObjectMap (Map Object Object -> Object)
-> ([(Object, Object)] -> Map Object Object)
-> [(Object, Object)]
-> Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Object, Object)] -> Map Object Object
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Object, Object)] -> Object)
-> Get [(Object, Object)] -> Get Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get (Object, Object) -> Get [(Object, Object)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get (Object, Object)
forall t. Serialize t => Get t
get
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
ext8 = do Int
n <- Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> Get Word8 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
ext16 = do Int
n <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
ext32 = do Int
n <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Get Word32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be
Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
n
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixext1 = Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
1
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixext2 = Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
2
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixext4 = Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
4
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixext8 = Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
8
| Word8
k Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
fixext16 = Int8 -> ByteString -> Object
ObjectExt (Int8 -> ByteString -> Object)
-> Get Int8 -> Get (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8)
Get (ByteString -> Object) -> Get ByteString -> Get Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
16
| Bool
otherwise = String -> Get Object
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get Object) -> String -> Get Object
forall a b. (a -> b) -> a -> b
$ String
"mark byte not supported: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
k