{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Database.CQL.Protocol.Codec
( encodeByte
, decodeByte
, encodeSignedByte
, decodeSignedByte
, encodeShort
, decodeShort
, encodeSignedShort
, decodeSignedShort
, encodeInt
, decodeInt
, encodeString
, decodeString
, encodeLongString
, decodeLongString
, encodeBytes
, decodeBytes
, encodeShortBytes
, decodeShortBytes
, encodeUUID
, decodeUUID
, encodeList
, decodeList
, encodeMap
, decodeMap
, encodeMultiMap
, decodeMultiMap
, encodeSockAddr
, decodeSockAddr
, encodeConsistency
, decodeConsistency
, encodeOpCode
, decodeOpCode
, encodePagingState
, decodePagingState
, decodeKeyspace
, decodeTable
, decodeColumnType
, decodeQueryId
, putValue
, getValue
) where
import Control.Applicative
import Control.Monad
import Data.Bits
import Data.ByteString (ByteString)
import Data.Decimal
import Data.Int
import Data.IP
#ifdef INCOMPATIBLE_VARINT
import Data.List (unfoldr)
#else
import Data.List (foldl')
#endif
import Data.Text (Text)
import Data.UUID (UUID)
import Data.Word
import Data.Serialize hiding (decode, encode)
import Database.CQL.Protocol.Types
import Network.Socket (SockAddr (..), PortNumber)
import Prelude
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import qualified Data.UUID as UUID
encodeByte :: Putter Word8
encodeByte :: Putter Word8
encodeByte = Putter Word8
forall t. Serialize t => Putter t
put
decodeByte :: Get Word8
decodeByte :: Get Word8
decodeByte = Get Word8
forall t. Serialize t => Get t
get
encodeSignedByte :: Putter Int8
encodeSignedByte :: Putter Int8
encodeSignedByte = Putter Int8
forall t. Serialize t => Putter t
put
decodeSignedByte :: Get Int8
decodeSignedByte :: Get Int8
decodeSignedByte = Get Int8
forall t. Serialize t => Get t
get
encodeShort :: Putter Word16
encodeShort :: Putter Word16
encodeShort = Putter Word16
forall t. Serialize t => Putter t
put
decodeShort :: Get Word16
decodeShort :: Get Word16
decodeShort = Get Word16
forall t. Serialize t => Get t
get
encodeSignedShort :: Putter Int16
encodeSignedShort :: Putter Int16
encodeSignedShort = Putter Int16
forall t. Serialize t => Putter t
put
decodeSignedShort :: Get Int16
decodeSignedShort :: Get Int16
decodeSignedShort = Get Int16
forall t. Serialize t => Get t
get
encodeInt :: Putter Int32
encodeInt :: Putter Int32
encodeInt = Putter Int32
forall t. Serialize t => Putter t
put
decodeInt :: Get Int32
decodeInt :: Get Int32
decodeInt = Get Int32
forall t. Serialize t => Get t
get
encodeString :: Putter Text
encodeString :: Putter Text
encodeString = Putter ByteString
encodeShortBytes Putter ByteString -> (Text -> ByteString) -> Putter Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
decodeString :: Get Text
decodeString :: Get Text
decodeString = ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> Get ByteString -> Get Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
decodeShortBytes
encodeLongString :: Putter LT.Text
encodeLongString :: Putter Text
encodeLongString = Putter ByteString
encodeBytes Putter ByteString -> (Text -> ByteString) -> Putter Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LT.encodeUtf8
decodeLongString :: Get LT.Text
decodeLongString :: Get Text
decodeLongString = do
Int32
n <- Get Int32
forall t. Serialize t => Get t
get :: Get Int32
ByteString -> Text
LT.decodeUtf8 (ByteString -> Text) -> Get ByteString -> Get Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Get ByteString
getLazyByteString (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n)
encodeBytes :: Putter LB.ByteString
encodeBytes :: Putter ByteString
encodeBytes ByteString
bs = do
Putter Int32
forall t. Serialize t => Putter t
put (Int64 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
LB.length ByteString
bs) :: Int32)
Putter ByteString
putLazyByteString ByteString
bs
decodeBytes :: Get (Maybe LB.ByteString)
decodeBytes :: Get (Maybe ByteString)
decodeBytes = do
Int32
n <- Get Int32
forall t. Serialize t => Get t
get :: Get Int32
if Int32
n Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< Int32
0
then Maybe ByteString -> Get (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> Get ByteString -> Get (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Get ByteString
getLazyByteString (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n)
encodeShortBytes :: Putter ByteString
encodeShortBytes :: Putter ByteString
encodeShortBytes ByteString
bs = do
Putter Word16
forall t. Serialize t => Putter t
put (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
bs) :: Word16)
Putter ByteString
putByteString ByteString
bs
decodeShortBytes :: Get ByteString
decodeShortBytes :: Get ByteString
decodeShortBytes = do
Word16
n <- Get Word16
forall t. Serialize t => Get t
get :: Get Word16
Int -> Get ByteString
getByteString (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n)
encodeUUID :: Putter UUID
encodeUUID :: Putter UUID
encodeUUID = Putter ByteString
putLazyByteString Putter ByteString -> (UUID -> ByteString) -> Putter UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> ByteString
UUID.toByteString
decodeUUID :: Get UUID
decodeUUID :: Get UUID
decodeUUID = do
Maybe UUID
uuid <- ByteString -> Maybe UUID
UUID.fromByteString (ByteString -> Maybe UUID) -> Get ByteString -> Get (Maybe UUID)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Get ByteString
getLazyByteString Int64
16
Get UUID -> (UUID -> Get UUID) -> Maybe UUID -> Get UUID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Get UUID
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"decode-uuid: invalid") UUID -> Get UUID
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe UUID
uuid
encodeList :: Putter [Text]
encodeList :: Putter [Text]
encodeList [Text]
sl = do
Putter Word16
forall t. Serialize t => Putter t
put (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
sl) :: Word16)
Putter Text -> Putter [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Text
encodeString [Text]
sl
decodeList :: Get [Text]
decodeList :: Get [Text]
decodeList = do
Word16
n <- Get Word16
forall t. Serialize t => Get t
get :: Get Word16
Int -> Get Text -> Get [Text]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n) Get Text
decodeString
encodeMap :: Putter [(Text, Text)]
encodeMap :: Putter [(Text, Text)]
encodeMap [(Text, Text)]
m = do
Putter Word16
forall t. Serialize t => Putter t
put (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([(Text, Text)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, Text)]
m) :: Word16)
[(Text, Text)] -> ((Text, Text) -> Put) -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Text, Text)]
m (((Text, Text) -> Put) -> Put) -> ((Text, Text) -> Put) -> Put
forall a b. (a -> b) -> a -> b
$ \(Text
k, Text
v) -> Putter Text
encodeString Text
k Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Text
encodeString Text
v
decodeMap :: Get [(Text, Text)]
decodeMap :: Get [(Text, Text)]
decodeMap = do
Word16
n <- Get Word16
forall t. Serialize t => Get t
get :: Get Word16
Int -> Get (Text, Text) -> Get [(Text, Text)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n) ((,) (Text -> Text -> (Text, Text))
-> Get Text -> Get (Text -> (Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString Get (Text -> (Text, Text)) -> Get Text -> Get (Text, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Text
decodeString)
encodeMultiMap :: Putter [(Text, [Text])]
encodeMultiMap :: Putter [(Text, [Text])]
encodeMultiMap [(Text, [Text])]
mm = do
Putter Word16
forall t. Serialize t => Putter t
put (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([(Text, [Text])] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, [Text])]
mm) :: Word16)
[(Text, [Text])] -> ((Text, [Text]) -> Put) -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Text, [Text])]
mm (((Text, [Text]) -> Put) -> Put) -> ((Text, [Text]) -> Put) -> Put
forall a b. (a -> b) -> a -> b
$ \(Text
k, [Text]
v) -> Putter Text
encodeString Text
k Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter [Text]
encodeList [Text]
v
decodeMultiMap :: Get [(Text, [Text])]
decodeMultiMap :: Get [(Text, [Text])]
decodeMultiMap = do
Word16
n <- Get Word16
forall t. Serialize t => Get t
get :: Get Word16
Int -> Get (Text, [Text]) -> Get [(Text, [Text])]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n) ((,) (Text -> [Text] -> (Text, [Text]))
-> Get Text -> Get ([Text] -> (Text, [Text]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString Get ([Text] -> (Text, [Text])) -> Get [Text] -> Get (Text, [Text])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [Text]
decodeList)
encodeSockAddr :: Putter SockAddr
encodeSockAddr :: Putter SockAddr
encodeSockAddr (SockAddrInet PortNumber
p HostAddress
a) = do
Putter Word8
putWord8 Word8
4
Putter HostAddress
putWord32le HostAddress
a
Putter HostAddress
putWord32be (PortNumber -> HostAddress
forall a b. (Integral a, Num b) => a -> b
fromIntegral PortNumber
p)
encodeSockAddr (SockAddrInet6 PortNumber
p HostAddress
_ (HostAddress
a, HostAddress
b, HostAddress
c, HostAddress
d) HostAddress
_) = do
Putter Word8
putWord8 Word8
16
Putter HostAddress
putWord32host HostAddress
a
Putter HostAddress
putWord32host HostAddress
b
Putter HostAddress
putWord32host HostAddress
c
Putter HostAddress
putWord32host HostAddress
d
Putter HostAddress
putWord32be (PortNumber -> HostAddress
forall a b. (Integral a, Num b) => a -> b
fromIntegral PortNumber
p)
encodeSockAddr (SockAddrUnix String
_) = String -> Put
forall a. HasCallStack => String -> a
error String
"encode-socket: unix address not supported"
#if MIN_VERSION_network(2,6,1) && !MIN_VERSION_network(3,0,0)
encodeSockAddr (SockAddrCan _) = error "encode-socket: can address not supported"
#endif
decodeSockAddr :: Get SockAddr
decodeSockAddr :: Get SockAddr
decodeSockAddr = do
Word8
n <- Get Word8
getWord8
case Word8
n of
Word8
4 -> do
HostAddress
i <- Get HostAddress
getIPv4
PortNumber
p <- Get PortNumber
getPort
SockAddr -> Get SockAddr
forall (m :: * -> *) a. Monad m => a -> m a
return (SockAddr -> Get SockAddr) -> SockAddr -> Get SockAddr
forall a b. (a -> b) -> a -> b
$ PortNumber -> HostAddress -> SockAddr
SockAddrInet PortNumber
p HostAddress
i
Word8
16 -> do
(HostAddress, HostAddress, HostAddress, HostAddress)
i <- Get (HostAddress, HostAddress, HostAddress, HostAddress)
getIPv6
PortNumber
p <- Get PortNumber
getPort
SockAddr -> Get SockAddr
forall (m :: * -> *) a. Monad m => a -> m a
return (SockAddr -> Get SockAddr) -> SockAddr -> Get SockAddr
forall a b. (a -> b) -> a -> b
$ PortNumber
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress)
-> HostAddress
-> SockAddr
SockAddrInet6 PortNumber
p HostAddress
0 (HostAddress, HostAddress, HostAddress, HostAddress)
i HostAddress
0
Word8
_ -> String -> Get SockAddr
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get SockAddr) -> String -> Get SockAddr
forall a b. (a -> b) -> a -> b
$ String
"decode-socket: unknown: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
n
where
getPort :: Get PortNumber
getPort :: Get PortNumber
getPort = HostAddress -> PortNumber
forall a b. (Integral a, Num b) => a -> b
fromIntegral (HostAddress -> PortNumber) -> Get HostAddress -> Get PortNumber
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get HostAddress
getWord32be
getIPv4 :: Get Word32
getIPv4 :: Get HostAddress
getIPv4 = Get HostAddress
getWord32le
getIPv6 :: Get (Word32, Word32, Word32, Word32)
getIPv6 :: Get (HostAddress, HostAddress, HostAddress, HostAddress)
getIPv6 = (,,,) (HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get HostAddress
getWord32host Get
(HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host Get
(HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host Get
(HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get (HostAddress, HostAddress, HostAddress, HostAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host
encodeConsistency :: Putter Consistency
encodeConsistency :: Putter Consistency
encodeConsistency Consistency
Any = Putter Word16
encodeShort Word16
0x00
encodeConsistency Consistency
One = Putter Word16
encodeShort Word16
0x01
encodeConsistency Consistency
Two = Putter Word16
encodeShort Word16
0x02
encodeConsistency Consistency
Three = Putter Word16
encodeShort Word16
0x03
encodeConsistency Consistency
Quorum = Putter Word16
encodeShort Word16
0x04
encodeConsistency Consistency
All = Putter Word16
encodeShort Word16
0x05
encodeConsistency Consistency
LocalQuorum = Putter Word16
encodeShort Word16
0x06
encodeConsistency Consistency
EachQuorum = Putter Word16
encodeShort Word16
0x07
encodeConsistency Consistency
Serial = Putter Word16
encodeShort Word16
0x08
encodeConsistency Consistency
LocalSerial = Putter Word16
encodeShort Word16
0x09
encodeConsistency Consistency
LocalOne = Putter Word16
encodeShort Word16
0x0A
decodeConsistency :: Get Consistency
decodeConsistency :: Get Consistency
decodeConsistency = Get Word16
decodeShort Get Word16 -> (Word16 -> Get Consistency) -> Get Consistency
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get Consistency
forall a (m :: * -> *).
(Eq a, Num a, MonadFail m, Show a) =>
a -> m Consistency
mapCode
where
mapCode :: a -> m Consistency
mapCode a
0x00 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
Any
mapCode a
0x01 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
One
mapCode a
0x02 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
Two
mapCode a
0x03 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
Three
mapCode a
0x04 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
Quorum
mapCode a
0x05 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
All
mapCode a
0x06 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
LocalQuorum
mapCode a
0x07 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
EachQuorum
mapCode a
0x08 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
Serial
mapCode a
0x09 = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
LocalSerial
mapCode a
0x0A = Consistency -> m Consistency
forall (m :: * -> *) a. Monad m => a -> m a
return Consistency
LocalOne
mapCode a
code = String -> m Consistency
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m Consistency) -> String -> m Consistency
forall a b. (a -> b) -> a -> b
$ String
"decode-consistency: unknown: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
code
encodeOpCode :: Putter OpCode
encodeOpCode :: Putter OpCode
encodeOpCode OpCode
OcError = Putter Word8
encodeByte Word8
0x00
encodeOpCode OpCode
OcStartup = Putter Word8
encodeByte Word8
0x01
encodeOpCode OpCode
OcReady = Putter Word8
encodeByte Word8
0x02
encodeOpCode OpCode
OcAuthenticate = Putter Word8
encodeByte Word8
0x03
encodeOpCode OpCode
OcOptions = Putter Word8
encodeByte Word8
0x05
encodeOpCode OpCode
OcSupported = Putter Word8
encodeByte Word8
0x06
encodeOpCode OpCode
OcQuery = Putter Word8
encodeByte Word8
0x07
encodeOpCode OpCode
OcResult = Putter Word8
encodeByte Word8
0x08
encodeOpCode OpCode
OcPrepare = Putter Word8
encodeByte Word8
0x09
encodeOpCode OpCode
OcExecute = Putter Word8
encodeByte Word8
0x0A
encodeOpCode OpCode
OcRegister = Putter Word8
encodeByte Word8
0x0B
encodeOpCode OpCode
OcEvent = Putter Word8
encodeByte Word8
0x0C
encodeOpCode OpCode
OcBatch = Putter Word8
encodeByte Word8
0x0D
encodeOpCode OpCode
OcAuthChallenge = Putter Word8
encodeByte Word8
0x0E
encodeOpCode OpCode
OcAuthResponse = Putter Word8
encodeByte Word8
0x0F
encodeOpCode OpCode
OcAuthSuccess = Putter Word8
encodeByte Word8
0x10
decodeOpCode :: Get OpCode
decodeOpCode :: Get OpCode
decodeOpCode = Get Word8
decodeByte Get Word8 -> (Word8 -> Get OpCode) -> Get OpCode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> Get OpCode
forall a (m :: * -> *).
(Eq a, Num a, MonadFail m, Show a) =>
a -> m OpCode
mapCode
where
mapCode :: a -> m OpCode
mapCode a
0x00 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcError
mapCode a
0x01 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcStartup
mapCode a
0x02 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcReady
mapCode a
0x03 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcAuthenticate
mapCode a
0x05 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcOptions
mapCode a
0x06 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcSupported
mapCode a
0x07 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcQuery
mapCode a
0x08 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcResult
mapCode a
0x09 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcPrepare
mapCode a
0x0A = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcExecute
mapCode a
0x0B = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcRegister
mapCode a
0x0C = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcEvent
mapCode a
0x0D = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcBatch
mapCode a
0x0E = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcAuthChallenge
mapCode a
0x0F = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcAuthResponse
mapCode a
0x10 = OpCode -> m OpCode
forall (m :: * -> *) a. Monad m => a -> m a
return OpCode
OcAuthSuccess
mapCode a
word = String -> m OpCode
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m OpCode) -> String -> m OpCode
forall a b. (a -> b) -> a -> b
$ String
"decode-opcode: unknown: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
word
decodeColumnType :: Get ColumnType
decodeColumnType :: Get ColumnType
decodeColumnType = Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType
where
toType :: Word16 -> Get ColumnType
toType Word16
0x0000 = Text -> ColumnType
CustomColumn (Text -> ColumnType) -> Get Text -> Get ColumnType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString
toType Word16
0x0001 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
AsciiColumn
toType Word16
0x0002 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
BigIntColumn
toType Word16
0x0003 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
BlobColumn
toType Word16
0x0004 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
BooleanColumn
toType Word16
0x0005 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
CounterColumn
toType Word16
0x0006 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
DecimalColumn
toType Word16
0x0007 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
DoubleColumn
toType Word16
0x0008 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
FloatColumn
toType Word16
0x0009 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
IntColumn
toType Word16
0x000A = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
TextColumn
toType Word16
0x000B = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
TimestampColumn
toType Word16
0x000C = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
UuidColumn
toType Word16
0x000D = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
VarCharColumn
toType Word16
0x000E = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
VarIntColumn
toType Word16
0x000F = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
TimeUuidColumn
toType Word16
0x0010 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
InetColumn
toType Word16
0x0011 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
DateColumn
toType Word16
0x0012 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
TimeColumn
toType Word16
0x0013 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
SmallIntColumn
toType Word16
0x0014 = ColumnType -> Get ColumnType
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnType
TinyIntColumn
toType Word16
0x0020 = ColumnType -> ColumnType
ListColumn (ColumnType -> ColumnType) -> Get ColumnType -> Get ColumnType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType)
toType Word16
0x0021 = ColumnType -> ColumnType -> ColumnType
MapColumn (ColumnType -> ColumnType -> ColumnType)
-> Get ColumnType -> Get (ColumnType -> ColumnType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType) Get (ColumnType -> ColumnType) -> Get ColumnType -> Get ColumnType
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType)
toType Word16
0x0022 = ColumnType -> ColumnType
SetColumn (ColumnType -> ColumnType) -> Get ColumnType -> Get ColumnType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType)
toType Word16
0x0030 = do
Text
_ <- Get Text
decodeString
Text
t <- Get Text
decodeString
Text -> [(Text, ColumnType)] -> ColumnType
UdtColumn Text
t ([(Text, ColumnType)] -> ColumnType)
-> Get [(Text, ColumnType)] -> Get ColumnType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
decodeShort
Int -> Get (Text, ColumnType) -> Get [(Text, ColumnType)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n ((,) (Text -> ColumnType -> (Text, ColumnType))
-> Get Text -> Get (ColumnType -> (Text, ColumnType))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString Get (ColumnType -> (Text, ColumnType))
-> Get ColumnType -> Get (Text, ColumnType)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType))
toType Word16
0x0031 = [ColumnType] -> ColumnType
TupleColumn ([ColumnType] -> ColumnType) -> Get [ColumnType] -> Get ColumnType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
decodeShort
Int -> Get ColumnType -> Get [ColumnType]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n (Get Word16
decodeShort Get Word16 -> (Word16 -> Get ColumnType) -> Get ColumnType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16 -> Get ColumnType
toType)
toType Word16
other = String -> Get ColumnType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get ColumnType) -> String -> Get ColumnType
forall a b. (a -> b) -> a -> b
$ String
"decode-type: unknown: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word16 -> String
forall a. Show a => a -> String
show Word16
other
encodePagingState :: Putter PagingState
encodePagingState :: Putter PagingState
encodePagingState (PagingState ByteString
s) = Putter ByteString
encodeBytes ByteString
s
decodePagingState :: Get (Maybe PagingState)
decodePagingState :: Get (Maybe PagingState)
decodePagingState = (ByteString -> PagingState)
-> Maybe ByteString -> Maybe PagingState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> PagingState
PagingState (Maybe ByteString -> Maybe PagingState)
-> Get (Maybe ByteString) -> Get (Maybe PagingState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe ByteString)
decodeBytes
putValue :: Version -> Putter Value
putValue :: Version -> Putter Value
putValue Version
_ (CqlCustom ByteString
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter ByteString
putLazyByteString ByteString
x
putValue Version
_ (CqlBoolean Bool
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Word8
putWord8 Putter Word8 -> Putter Word8
forall a b. (a -> b) -> a -> b
$ if Bool
x then Word8
1 else Word8
0
putValue Version
_ (CqlInt Int32
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int32
forall t. Serialize t => Putter t
put Int32
x
putValue Version
_ (CqlBigInt Int64
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int64
forall t. Serialize t => Putter t
put Int64
x
putValue Version
_ (CqlFloat Float
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Float -> Put
putFloat32be Float
x
putValue Version
_ (CqlDouble Double
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Double -> Put
putFloat64be Double
x
putValue Version
_ (CqlText Text
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter ByteString
putByteString (Text -> ByteString
T.encodeUtf8 Text
x)
putValue Version
_ (CqlUuid UUID
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter UUID
encodeUUID UUID
x
putValue Version
_ (CqlTimeUuid UUID
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter UUID
encodeUUID UUID
x
putValue Version
_ (CqlTimestamp Int64
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int64
forall t. Serialize t => Putter t
put Int64
x
putValue Version
_ (CqlAscii Text
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter ByteString
putByteString (Text -> ByteString
T.encodeUtf8 Text
x)
putValue Version
_ (CqlBlob ByteString
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter ByteString
putLazyByteString ByteString
x
putValue Version
_ (CqlCounter Int64
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int64
forall t. Serialize t => Putter t
put Int64
x
putValue Version
_ (CqlInet IP
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ case IP
x of
IPv4 IPv4
i -> Putter HostAddress
putWord32le (IPv4 -> HostAddress
toHostAddress IPv4
i)
IPv6 IPv6
i -> do
let (HostAddress
a, HostAddress
b, HostAddress
c, HostAddress
d) = IPv6 -> (HostAddress, HostAddress, HostAddress, HostAddress)
toHostAddress6 IPv6
i
Putter HostAddress
putWord32host HostAddress
a
Putter HostAddress
putWord32host HostAddress
b
Putter HostAddress
putWord32host HostAddress
c
Putter HostAddress
putWord32host HostAddress
d
putValue Version
_ (CqlVarInt Integer
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Integer
integer2bytes Integer
x
putValue Version
_ (CqlDecimal Decimal
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ do
Putter Int32
forall t. Serialize t => Putter t
put (Word8 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Decimal -> Word8
forall i. DecimalRaw i -> Word8
decimalPlaces Decimal
x) :: Int32)
Putter Integer
integer2bytes (Decimal -> Integer
forall i. DecimalRaw i -> i
decimalMantissa Decimal
x)
putValue Version
V4 (CqlDate Int32
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int32
forall t. Serialize t => Putter t
put Int32
x
putValue Version
_ v :: Value
v@(CqlDate Int32
_) = String -> Put
forall a. HasCallStack => String -> a
error (String -> Put) -> String -> Put
forall a b. (a -> b) -> a -> b
$ String
"putValue: date: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
v
putValue Version
V4 (CqlTime Int64
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int64
forall t. Serialize t => Putter t
put Int64
x
putValue Version
_ v :: Value
v@(CqlTime Int64
_) = String -> Put
forall a. HasCallStack => String -> a
error (String -> Put) -> String -> Put
forall a b. (a -> b) -> a -> b
$ String
"putValue: time: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
v
putValue Version
V4 (CqlSmallInt Int16
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int16
forall t. Serialize t => Putter t
put Int16
x
putValue Version
_ v :: Value
v@(CqlSmallInt Int16
_) = String -> Put
forall a. HasCallStack => String -> a
error (String -> Put) -> String -> Put
forall a b. (a -> b) -> a -> b
$ String
"putValue: smallint: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
v
putValue Version
V4 (CqlTinyInt Int8
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Int8
forall t. Serialize t => Putter t
put Int8
x
putValue Version
_ v :: Value
v@(CqlTinyInt Int8
_) = String -> Put
forall a. HasCallStack => String -> a
error (String -> Put) -> String -> Put
forall a b. (a -> b) -> a -> b
$ String
"putValue: tinyint: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
v
putValue Version
v (CqlUdt [(Text, Value)]
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ ((Text, Value) -> Put) -> [(Text, Value)] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Version -> Putter Value
putValue Version
v Putter Value -> ((Text, Value) -> Value) -> (Text, Value) -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Value) -> Value
forall a b. (a, b) -> b
snd) [(Text, Value)]
x
putValue Version
v (CqlList [Value]
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ do
Putter Int32
encodeInt (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Value] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Value]
x))
Putter Value -> [Value] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Version -> Putter Value
putValue Version
v) [Value]
x
putValue Version
v (CqlSet [Value]
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ do
Putter Int32
encodeInt (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Value] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Value]
x))
Putter Value -> [Value] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Version -> Putter Value
putValue Version
v) [Value]
x
putValue Version
v (CqlMap [(Value, Value)]
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ do
Putter Int32
encodeInt (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([(Value, Value)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Value, Value)]
x))
[(Value, Value)] -> ((Value, Value) -> Put) -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Value, Value)]
x (((Value, Value) -> Put) -> Put) -> ((Value, Value) -> Put) -> Put
forall a b. (a -> b) -> a -> b
$ \(Value
k, Value
w) -> Version -> Putter Value
putValue Version
v Value
k Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Version -> Putter Value
putValue Version
v Value
w
putValue Version
v (CqlTuple [Value]
x) = Put -> Put
toBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Putter Value -> [Value] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Version -> Putter Value
putValue Version
v) [Value]
x
putValue Version
_ (CqlMaybe Maybe Value
Nothing) = Putter Int32
forall t. Serialize t => Putter t
put (-Int32
1 :: Int32)
putValue Version
v (CqlMaybe (Just Value
x)) = Version -> Putter Value
putValue Version
v Value
x
getValue :: Version -> ColumnType -> Get Value
getValue :: Version -> ColumnType -> Get Value
getValue Version
v (ListColumn ColumnType
t) = [Value] -> Value
CqlList ([Value] -> Value) -> Get [Value] -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Value] -> Get [Value]
forall a. Get [a] -> Get [a]
getList (do
Int32
len <- Get Int32
decodeInt
Int -> Get Value -> Get [Value]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
len) (Version -> ColumnType -> Get Value
getValue Version
v ColumnType
t))
getValue Version
v (SetColumn ColumnType
t) = [Value] -> Value
CqlSet ([Value] -> Value) -> Get [Value] -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Value] -> Get [Value]
forall a. Get [a] -> Get [a]
getList (do
Int32
len <- Get Int32
decodeInt
Int -> Get Value -> Get [Value]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
len) (Version -> ColumnType -> Get Value
getValue Version
v ColumnType
t))
getValue Version
v (MapColumn ColumnType
t ColumnType
u) = [(Value, Value)] -> Value
CqlMap ([(Value, Value)] -> Value) -> Get [(Value, Value)] -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [(Value, Value)] -> Get [(Value, Value)]
forall a. Get [a] -> Get [a]
getList (do
Int32
len <- Get Int32
decodeInt
Int -> Get (Value, Value) -> Get [(Value, Value)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
len) ((,) (Value -> Value -> (Value, Value))
-> Get Value -> Get (Value -> (Value, Value))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Version -> ColumnType -> Get Value
getValue Version
v ColumnType
t Get (Value -> (Value, Value)) -> Get Value -> Get (Value, Value)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Version -> ColumnType -> Get Value
getValue Version
v ColumnType
u))
getValue Version
v (TupleColumn [ColumnType]
t) = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
CqlTuple ([Value] -> Value) -> Get [Value] -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ColumnType -> Get Value) -> [ColumnType] -> Get [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Version -> ColumnType -> Get Value
getValue Version
v) [ColumnType]
t
getValue Version
v (MaybeColumn ColumnType
t) = do
Int32
n <- Get Int32 -> Get Int32
forall a. Get a -> Get a
lookAhead (Get Int32
forall t. Serialize t => Get t
get :: Get Int32)
if Int32
n Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< Int32
0
then Int -> Get ()
uncheckedSkip Int
4 Get () -> Get Value -> Get Value
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Value -> Get Value
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Value -> Value
CqlMaybe Maybe Value
forall a. Maybe a
Nothing)
else Maybe Value -> Value
CqlMaybe (Maybe Value -> Value) -> (Value -> Maybe Value) -> Value -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Value) -> Get Value -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Version -> ColumnType -> Get Value
getValue Version
v ColumnType
t
getValue Version
_ (CustomColumn Text
_) = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ ByteString -> Value
CqlCustom (ByteString -> Value) -> Get ByteString -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytesLazy
getValue Version
_ ColumnType
BooleanColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
CqlBoolean (Bool -> Value) -> (Word8 -> Bool) -> Word8 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
0) (Word8 -> Value) -> Get Word8 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
getValue Version
_ ColumnType
IntColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Value
CqlInt (Int32 -> Value) -> Get Int32 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int32
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
BigIntColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int64 -> Value
CqlBigInt (Int64 -> Value) -> Get Int64 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
FloatColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Float -> Value
CqlFloat (Float -> Value) -> Get Float -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Float
getFloat32be
getValue Version
_ ColumnType
DoubleColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Double -> Value
CqlDouble (Double -> Value) -> Get Double -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Double
getFloat64be
getValue Version
_ ColumnType
TextColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
CqlText (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8 (ByteString -> Value) -> Get ByteString -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytes
getValue Version
_ ColumnType
VarCharColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
CqlText (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8 (ByteString -> Value) -> Get ByteString -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytes
getValue Version
_ ColumnType
AsciiColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
CqlAscii (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8 (ByteString -> Value) -> Get ByteString -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytes
getValue Version
_ ColumnType
BlobColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ ByteString -> Value
CqlBlob (ByteString -> Value) -> Get ByteString -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytesLazy
getValue Version
_ ColumnType
UuidColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ UUID -> Value
CqlUuid (UUID -> Value) -> Get UUID -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get UUID
decodeUUID
getValue Version
_ ColumnType
TimeUuidColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ UUID -> Value
CqlTimeUuid (UUID -> Value) -> Get UUID -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get UUID
decodeUUID
getValue Version
_ ColumnType
TimestampColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int64 -> Value
CqlTimestamp (Int64 -> Value) -> Get Int64 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
CounterColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int64 -> Value
CqlCounter (Int64 -> Value) -> Get Int64 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
InetColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ IP -> Value
CqlInet (IP -> Value) -> Get IP -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
Int
len <- Get Int
remaining
case Int
len of
Int
4 -> IPv4 -> IP
IPv4 (IPv4 -> IP) -> (HostAddress -> IPv4) -> HostAddress -> IP
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostAddress -> IPv4
fromHostAddress (HostAddress -> IP) -> Get HostAddress -> Get IP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get HostAddress
getWord32le
Int
16 -> do
(HostAddress, HostAddress, HostAddress, HostAddress)
a <- (,,,) (HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get HostAddress
getWord32host Get
(HostAddress
-> HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host Get
(HostAddress
-> HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get
(HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host Get
(HostAddress
-> (HostAddress, HostAddress, HostAddress, HostAddress))
-> Get HostAddress
-> Get (HostAddress, HostAddress, HostAddress, HostAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get HostAddress
getWord32host
IP -> Get IP
forall (m :: * -> *) a. Monad m => a -> m a
return (IP -> Get IP) -> IP -> Get IP
forall a b. (a -> b) -> a -> b
$ IPv6 -> IP
IPv6 ((HostAddress, HostAddress, HostAddress, HostAddress) -> IPv6
fromHostAddress6 (HostAddress, HostAddress, HostAddress, HostAddress)
a)
Int
n -> String -> Get IP
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get IP) -> String -> Get IP
forall a b. (a -> b) -> a -> b
$ String
"getNative: invalid Inet length: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
getValue Version
V4 ColumnType
DateColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Value
CqlDate (Int32 -> Value) -> Get Int32 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int32
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
DateColumn = String -> Get Value
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getNative: date type"
getValue Version
V4 ColumnType
TimeColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int64 -> Value
CqlTime (Int64 -> Value) -> Get Int64 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
TimeColumn = String -> Get Value
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getNative: time type"
getValue Version
V4 ColumnType
SmallIntColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int16 -> Value
CqlSmallInt (Int16 -> Value) -> Get Int16 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int16
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
SmallIntColumn = String -> Get Value
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getNative: smallint type"
getValue Version
V4 ColumnType
TinyIntColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Int8 -> Value
CqlTinyInt (Int8 -> Value) -> Get Int8 -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int8
forall t. Serialize t => Get t
get
getValue Version
_ ColumnType
TinyIntColumn = String -> Get Value
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getNative: tinyint type"
getValue Version
_ ColumnType
VarIntColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ Integer -> Value
CqlVarInt (Integer -> Value) -> Get Integer -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Integer
bytes2integer
getValue Version
_ ColumnType
DecimalColumn = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ do
Int32
x <- Get Int32
forall t. Serialize t => Get t
get :: Get Int32
Integer
y <- Get Integer
bytes2integer
Value -> Get Value
forall (m :: * -> *) a. Monad m => a -> m a
return (Decimal -> Value
CqlDecimal (Word8 -> Integer -> Decimal
forall i. Word8 -> i -> DecimalRaw i
Decimal (Int32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
x) Integer
y))
getValue Version
v (UdtColumn Text
_ [(Text, ColumnType)]
x) = Get Value -> Get Value
forall a. Get a -> Get a
withBytes (Get Value -> Get Value) -> Get Value -> Get Value
forall a b. (a -> b) -> a -> b
$ [(Text, Value)] -> Value
CqlUdt ([(Text, Value)] -> Value) -> Get [(Text, Value)] -> Get Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
let ([Text]
n, [ColumnType]
t) = [(Text, ColumnType)] -> ([Text], [ColumnType])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Text, ColumnType)]
x
[Text] -> [Value] -> [(Text, Value)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
n ([Value] -> [(Text, Value)]) -> Get [Value] -> Get [(Text, Value)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ColumnType -> Get Value) -> [ColumnType] -> Get [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Version -> ColumnType -> Get Value
getValue Version
v) [ColumnType]
t
getList :: Get [a] -> Get [a]
getList :: Get [a] -> Get [a]
getList Get [a]
m = do
Int32
n <- Get Int32 -> Get Int32
forall a. Get a -> Get a
lookAhead (Get Int32
forall t. Serialize t => Get t
get :: Get Int32)
if Int32
n Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< Int32
0 then Int -> Get ()
uncheckedSkip Int
4 Get () -> Get [a] -> Get [a]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [a] -> Get [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
else Get [a] -> Get [a]
forall a. Get a -> Get a
withBytes Get [a]
m
withBytes :: Get a -> Get a
withBytes :: Get a -> Get a
withBytes Get a
p = do
Int
n <- Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Int) -> Get Int32 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Get Int32
forall t. Serialize t => Get t
get :: Get Int32)
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get ()) -> String -> Get ()
forall a b. (a -> b) -> a -> b
$ String
"withBytes: null (length = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
ByteString
b <- Int -> Get ByteString
getBytes Int
n
case Get a -> ByteString -> Either String a
forall a. Get a -> ByteString -> Either String a
runGet Get a
p ByteString
b of
Left String
e -> String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get a) -> String -> Get a
forall a b. (a -> b) -> a -> b
$ String
"withBytes: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
e
Right a
x -> a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
remainingBytes :: Get ByteString
remainingBytes :: Get ByteString
remainingBytes = Get Int
remaining Get Int -> (Int -> Get ByteString) -> Get ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Get ByteString
getByteString (Int -> Get ByteString) -> (Int -> Int) -> Int -> Get ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
remainingBytesLazy :: Get LB.ByteString
remainingBytesLazy :: Get ByteString
remainingBytesLazy = Get Int
remaining Get Int -> (Int -> Get ByteString) -> Get ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int64 -> Get ByteString
getLazyByteString (Int64 -> Get ByteString)
-> (Int -> Int64) -> Int -> Get ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
toBytes :: Put -> Put
toBytes :: Put -> Put
toBytes Put
p = do
let bytes :: ByteString
bytes = Put -> ByteString
runPut Put
p
Putter Int32
forall t. Serialize t => Putter t
put (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
bytes) :: Int32)
Putter ByteString
putByteString ByteString
bytes
#ifdef INCOMPATIBLE_VARINT
integer2bytes :: Putter Integer
integer2bytes n = do
put sign
put (unroll (abs n))
where
sign = fromIntegral (signum n) :: Word8
unroll :: Integer -> [Word8]
unroll = unfoldr step
where
step 0 = Nothing
step i = Just (fromIntegral i, i `shiftR` 8)
bytes2integer :: Get Integer
bytes2integer = do
sign <- get
bytes <- get
let v = roll bytes
return $! if sign == (1 :: Word8) then v else - v
where
roll :: [Word8] -> Integer
roll = foldr unstep 0
where
unstep b a = a `shiftL` 8 .|. fromIntegral b
#else
integer2bytes :: Putter Integer
integer2bytes :: Putter Integer
integer2bytes Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 = Putter Word8
putWord8 Word8
0x00
| Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== -Integer
1 = Putter Word8
putWord8 Word8
0xFF
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = do
let bytes :: [Word8]
bytes = Integer -> Integer -> [Word8]
explode (-Integer
1) Integer
n
Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Word8] -> Word8
forall a. [a] -> a
head [Word8]
bytes Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
0x80) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$
Putter Word8
putWord8 Word8
0xFF
Putter Word8 -> [Word8] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Word8
putWord8 [Word8]
bytes
| Bool
otherwise = do
let bytes :: [Word8]
bytes = Integer -> Integer -> [Word8]
explode Integer
0 Integer
n
Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Word8] -> Word8
forall a. [a] -> a
head [Word8]
bytes Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
0x80) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$
Putter Word8
putWord8 Word8
0x00
Putter Word8 -> [Word8] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Word8
putWord8 [Word8]
bytes
explode :: Integer -> Integer -> [Word8]
explode :: Integer -> Integer -> [Word8]
explode Integer
x Integer
n = Integer -> [Word8] -> [Word8]
forall a. Num a => Integer -> [a] -> [a]
loop Integer
n []
where
loop :: Integer -> [a] -> [a]
loop !Integer
i ![a]
acc
| Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
x = [a]
acc
| Bool
otherwise = Integer -> [a] -> [a]
loop (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
8) (Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc)
bytes2integer :: Get Integer
bytes2integer :: Get Integer
bytes2integer = do
Word8
msb <- Get Word8
getWord8
[Word8]
bytes <- ByteString -> [Word8]
B.unpack (ByteString -> [Word8]) -> Get ByteString -> Get [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
remainingBytes
if Word8
msb Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
0x80
then Integer -> Get Integer
forall (m :: * -> *) a. Monad m => a -> m a
return ([Word8] -> Integer
implode (Word8
msbWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
bytes))
else Integer -> Get Integer
forall (m :: * -> *) a. Monad m => a -> m a
return (- ([Word8] -> Integer
implode ((Word8 -> Word8) -> [Word8] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Word8
forall a. Bits a => a -> a
complement (Word8
msbWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
bytes)) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1))
implode :: [Word8] -> Integer
implode :: [Word8] -> Integer
implode = (Integer -> Word8 -> Integer) -> Integer -> [Word8] -> Integer
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Integer -> Word8 -> Integer
forall a a. (Bits a, Integral a, Num a) => a -> a -> a
fun Integer
0
where
fun :: a -> a -> a
fun a
i a
b = a
i a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
b
#endif
decodeKeyspace :: Get Keyspace
decodeKeyspace :: Get Keyspace
decodeKeyspace = Text -> Keyspace
Keyspace (Text -> Keyspace) -> Get Text -> Get Keyspace
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString
decodeTable :: Get Table
decodeTable :: Get Table
decodeTable = Text -> Table
Table (Text -> Table) -> Get Text -> Get Table
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
decodeString
decodeQueryId :: Get (QueryId k a b)
decodeQueryId :: Get (QueryId k a b)
decodeQueryId = ByteString -> QueryId k a b
forall k a b. ByteString -> QueryId k a b
QueryId (ByteString -> QueryId k a b)
-> Get ByteString -> Get (QueryId k a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
decodeShortBytes