{-# OPTIONS_GHC -funbox-strict-fields #-}
module Database.MySQL.BinLogProtocol.BinLogEvent where
import Control.Applicative
import Control.Monad
import Control.Monad.Loops (untilM)
import Data.Binary
import Data.Binary.Parser
import Data.Bits
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Unsafe as B
import Database.MySQL.BinLogProtocol.BinLogMeta
import Database.MySQL.BinLogProtocol.BinLogValue
import Database.MySQL.Protocol.Packet
import Database.MySQL.Protocol.MySQLValue
import Database.MySQL.Protocol.ColumnDef
import Control.Exception (throwIO)
import Database.MySQL.Query
import GHC.Generics (Generic)
data BinLogEventType
= BINLOG_UNKNOWN_EVENT
| BINLOG_START_EVENT_V3
| BINLOG_QUERY_EVENT
| BINLOG_STOP_EVENT
| BINLOG_ROTATE_EVENT
| BINLOG_INTVAR_EVENT
| BINLOG_LOAD_EVENT
| BINLOG_SLAVE_EVENT
| BINLOG_CREATE_FILE_EVENT
| BINLOG_APPEND_BLOCK_EVENT
| BINLOG_EXEC_LOAD_EVENT
| BINLOG_DELETE_FILE_EVENT
| BINLOG_NEW_LOAD_EVENT
| BINLOG_RAND_EVENT
| BINLOG_USER_VAR_EVENT
| BINLOG_FORMAT_DESCRIPTION_EVENT
| BINLOG_XID_EVENT
| BINLOG_BEGIN_LOAD_QUERY_EVENT
| BINLOG_EXECUTE_LOAD_QUERY_EVENT
| BINLOG_TABLE_MAP_EVENT
| BINLOG_WRITE_ROWS_EVENTv0
| BINLOG_UPDATE_ROWS_EVENTv0
| BINLOG_DELETE_ROWS_EVENTv0
| BINLOG_WRITE_ROWS_EVENTv1
| BINLOG_UPDATE_ROWS_EVENTv1
| BINLOG_DELETE_ROWS_EVENTv1
| BINLOG_INCIDENT_EVENT
| BINLOG_HEARTBEAT_EVENT
| BINLOG_IGNORABLE_EVENT
| BINLOG_ROWS_QUERY_EVENT
| BINLOG_WRITE_ROWS_EVENTv2
| BINLOG_UPDATE_ROWS_EVENTv2
| BINLOG_DELETE_ROWS_EVENTv2
| BINLOG_GTID_EVENT
| BINLOG_ANONYMOUS_GTID_EVENT
| BINLOG_PREVIOUS_GTIDS_EVENT
deriving (Int -> BinLogEventType -> ShowS
[BinLogEventType] -> ShowS
BinLogEventType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinLogEventType] -> ShowS
$cshowList :: [BinLogEventType] -> ShowS
show :: BinLogEventType -> String
$cshow :: BinLogEventType -> String
showsPrec :: Int -> BinLogEventType -> ShowS
$cshowsPrec :: Int -> BinLogEventType -> ShowS
Show, BinLogEventType -> BinLogEventType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinLogEventType -> BinLogEventType -> Bool
$c/= :: BinLogEventType -> BinLogEventType -> Bool
== :: BinLogEventType -> BinLogEventType -> Bool
$c== :: BinLogEventType -> BinLogEventType -> Bool
Eq, Int -> BinLogEventType
BinLogEventType -> Int
BinLogEventType -> [BinLogEventType]
BinLogEventType -> BinLogEventType
BinLogEventType -> BinLogEventType -> [BinLogEventType]
BinLogEventType
-> BinLogEventType -> BinLogEventType -> [BinLogEventType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BinLogEventType
-> BinLogEventType -> BinLogEventType -> [BinLogEventType]
$cenumFromThenTo :: BinLogEventType
-> BinLogEventType -> BinLogEventType -> [BinLogEventType]
enumFromTo :: BinLogEventType -> BinLogEventType -> [BinLogEventType]
$cenumFromTo :: BinLogEventType -> BinLogEventType -> [BinLogEventType]
enumFromThen :: BinLogEventType -> BinLogEventType -> [BinLogEventType]
$cenumFromThen :: BinLogEventType -> BinLogEventType -> [BinLogEventType]
enumFrom :: BinLogEventType -> [BinLogEventType]
$cenumFrom :: BinLogEventType -> [BinLogEventType]
fromEnum :: BinLogEventType -> Int
$cfromEnum :: BinLogEventType -> Int
toEnum :: Int -> BinLogEventType
$ctoEnum :: Int -> BinLogEventType
pred :: BinLogEventType -> BinLogEventType
$cpred :: BinLogEventType -> BinLogEventType
succ :: BinLogEventType -> BinLogEventType
$csucc :: BinLogEventType -> BinLogEventType
Enum)
data BinLogPacket = BinLogPacket
{ BinLogPacket -> Word32
blTimestamp :: !Word32
, BinLogPacket -> BinLogEventType
blEventType :: !BinLogEventType
, BinLogPacket -> Word32
blServerId :: !Word32
, BinLogPacket -> Word32
blEventSize :: !Word32
, BinLogPacket -> Word64
blLogPos :: !Word64
, BinLogPacket -> Word16
blFlags :: !Word16
, BinLogPacket -> ByteString
blBody :: !L.ByteString
, BinLogPacket -> Bool
blSemiAck :: !Bool
} deriving (Int -> BinLogPacket -> ShowS
[BinLogPacket] -> ShowS
BinLogPacket -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinLogPacket] -> ShowS
$cshowList :: [BinLogPacket] -> ShowS
show :: BinLogPacket -> String
$cshow :: BinLogPacket -> String
showsPrec :: Int -> BinLogPacket -> ShowS
$cshowsPrec :: Int -> BinLogPacket -> ShowS
Show, BinLogPacket -> BinLogPacket -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinLogPacket -> BinLogPacket -> Bool
$c/= :: BinLogPacket -> BinLogPacket -> Bool
== :: BinLogPacket -> BinLogPacket -> Bool
$c== :: BinLogPacket -> BinLogPacket -> Bool
Eq)
putSemiAckResp :: Word32 -> ByteString -> Put
putSemiAckResp :: Word32 -> ByteString -> Put
putSemiAckResp Word32
pos ByteString
fn = forall t. Binary t => t -> Put
put Word32
pos forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put ByteString
fn
getBinLogPacket :: Bool -> Bool -> Get BinLogPacket
getBinLogPacket :: Bool -> Bool -> Get BinLogPacket
getBinLogPacket Bool
checksum Bool
semi = do
Word8
_ <- Get Word8
getWord8
Bool
ack <- if Bool
semi
then Get Word8
getWord8 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (forall a. Eq a => a -> a -> Bool
== Word8
0x01) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Word32
ts <- Get Word32
getWord32le
BinLogEventType
typ <- forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
Word32
sid <- Get Word32
getWord32le
Word32
size <- Get Word32
getWord32le
Word32
pos <- Get Word32
getWord32le
Word16
flgs <- Get Word16
getWord16le
ByteString
body <- Int64 -> Get ByteString
getLazyByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
size forall a. Num a => a -> a -> a
- if Bool
checksum then Int64
23 else Int64
19)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
-> BinLogEventType
-> Word32
-> Word32
-> Word64
-> Word16
-> ByteString
-> Bool
-> BinLogPacket
BinLogPacket Word32
ts BinLogEventType
typ Word32
sid Word32
size (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
pos) Word16
flgs ByteString
body Bool
ack)
getFromBinLogPacket :: Get a -> BinLogPacket -> IO a
getFromBinLogPacket :: forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket Get a
g (BinLogPacket Word32
_ BinLogEventType
_ Word32
_ Word32
_ Word64
_ Word16
_ ByteString
body Bool
_ ) =
case forall a.
Get a
-> ByteString
-> Either (ByteString, Int64, String) (ByteString, Int64, a)
parseDetailLazy Get a
g ByteString
body of
Left (ByteString
buf, Int64
offset, String
errmsg) -> forall e a. Exception e => e -> IO a
throwIO (ByteString -> Int64 -> String -> DecodePacketException
DecodePacketFailed ByteString
buf Int64
offset String
errmsg)
Right (ByteString
_, Int64
_, a
r ) -> forall (m :: * -> *) a. Monad m => a -> m a
return a
r
getFromBinLogPacket' :: (BinLogEventType -> Get a) -> BinLogPacket -> IO a
getFromBinLogPacket' :: forall a. (BinLogEventType -> Get a) -> BinLogPacket -> IO a
getFromBinLogPacket' BinLogEventType -> Get a
g (BinLogPacket Word32
_ BinLogEventType
typ Word32
_ Word32
_ Word64
_ Word16
_ ByteString
body Bool
_ ) =
case forall a.
Get a
-> ByteString
-> Either (ByteString, Int64, String) (ByteString, Int64, a)
parseDetailLazy (BinLogEventType -> Get a
g BinLogEventType
typ) ByteString
body of
Left (ByteString
buf, Int64
offset, String
errmsg) -> forall e a. Exception e => e -> IO a
throwIO (ByteString -> Int64 -> String -> DecodePacketException
DecodePacketFailed ByteString
buf Int64
offset String
errmsg)
Right (ByteString
_, Int64
_, a
r ) -> forall (m :: * -> *) a. Monad m => a -> m a
return a
r
data FormatDescription = FormatDescription
{ FormatDescription -> Word16
fdVersion :: !Word16
, FormatDescription -> ByteString
fdMySQLVersion :: !ByteString
, FormatDescription -> Word32
fdCreateTime :: !Word32
, :: !ByteString
} deriving (Int -> FormatDescription -> ShowS
[FormatDescription] -> ShowS
FormatDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatDescription] -> ShowS
$cshowList :: [FormatDescription] -> ShowS
show :: FormatDescription -> String
$cshow :: FormatDescription -> String
showsPrec :: Int -> FormatDescription -> ShowS
$cshowsPrec :: Int -> FormatDescription -> ShowS
Show, FormatDescription -> FormatDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatDescription -> FormatDescription -> Bool
$c/= :: FormatDescription -> FormatDescription -> Bool
== :: FormatDescription -> FormatDescription -> Bool
$c== :: FormatDescription -> FormatDescription -> Bool
Eq, forall x. Rep FormatDescription x -> FormatDescription
forall x. FormatDescription -> Rep FormatDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormatDescription x -> FormatDescription
$cfrom :: forall x. FormatDescription -> Rep FormatDescription x
Generic)
getFormatDescription :: Get FormatDescription
getFormatDescription :: Get FormatDescription
getFormatDescription = Word16 -> ByteString -> Word32 -> ByteString -> FormatDescription
FormatDescription forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString Int
50
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32le
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get Word8
getWord8
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ByteString -> ByteString
L.toStrict forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
getRemainingLazyByteString)
eventHeaderLen :: FormatDescription -> BinLogEventType -> Word8
FormatDescription
fd BinLogEventType
typ = ByteString -> Int -> Word8
B.unsafeIndex (FormatDescription -> ByteString
fdEventHeaderLenVector FormatDescription
fd) (forall a. Enum a => a -> Int
fromEnum BinLogEventType
typ forall a. Num a => a -> a -> a
- Int
1)
data RotateEvent = RotateEvent
{ RotateEvent -> Word64
rPos :: !Word64, RotateEvent -> ByteString
rFileName :: !ByteString } deriving (Int -> RotateEvent -> ShowS
[RotateEvent] -> ShowS
RotateEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RotateEvent] -> ShowS
$cshowList :: [RotateEvent] -> ShowS
show :: RotateEvent -> String
$cshow :: RotateEvent -> String
showsPrec :: Int -> RotateEvent -> ShowS
$cshowsPrec :: Int -> RotateEvent -> ShowS
Show, RotateEvent -> RotateEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RotateEvent -> RotateEvent -> Bool
$c/= :: RotateEvent -> RotateEvent -> Bool
== :: RotateEvent -> RotateEvent -> Bool
$c== :: RotateEvent -> RotateEvent -> Bool
Eq)
getRotateEvent :: Get RotateEvent
getRotateEvent :: Get RotateEvent
getRotateEvent = Word64 -> ByteString -> RotateEvent
RotateEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getWord64le forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get ByteString
getRemainingByteString
data QueryEvent = QueryEvent
{ QueryEvent -> Word32
qSlaveProxyId :: !Word32
, QueryEvent -> Word32
qExecTime :: !Word32
, QueryEvent -> Word16
qErrCode :: !Word16
, QueryEvent -> ByteString
qStatusVars :: !ByteString
, QueryEvent -> ByteString
qSchemaName :: !ByteString
, QueryEvent -> Query
qQuery :: !Query
} deriving (Int -> QueryEvent -> ShowS
[QueryEvent] -> ShowS
QueryEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryEvent] -> ShowS
$cshowList :: [QueryEvent] -> ShowS
show :: QueryEvent -> String
$cshow :: QueryEvent -> String
showsPrec :: Int -> QueryEvent -> ShowS
$cshowsPrec :: Int -> QueryEvent -> ShowS
Show, QueryEvent -> QueryEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryEvent -> QueryEvent -> Bool
$c/= :: QueryEvent -> QueryEvent -> Bool
== :: QueryEvent -> QueryEvent -> Bool
$c== :: QueryEvent -> QueryEvent -> Bool
Eq, forall x. Rep QueryEvent x -> QueryEvent
forall x. QueryEvent -> Rep QueryEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryEvent x -> QueryEvent
$cfrom :: forall x. QueryEvent -> Rep QueryEvent x
Generic)
getQueryEvent :: Get QueryEvent
getQueryEvent :: Get QueryEvent
getQueryEvent = do
Word32
pid <- Get Word32
getWord32le
Word32
tim <- Get Word32
getWord32le
Word8
slen <- Get Word8
getWord8
Word16
ecode <- Get Word16
getWord16le
Word16
vlen <- Get Word16
getWord16le
ByteString
svar <- Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
vlen)
ByteString
schema <- Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
slen)
Word8
_ <- Get Word8
getWord8
ByteString
qry <- Get ByteString
getRemainingLazyByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
-> Word32
-> Word16
-> ByteString
-> ByteString
-> Query
-> QueryEvent
QueryEvent Word32
pid Word32
tim Word16
ecode ByteString
svar ByteString
schema (ByteString -> Query
Query ByteString
qry))
data QueryEvent' = QueryEvent' { QueryEvent' -> Query
qQuery' :: !Query } deriving (Int -> QueryEvent' -> ShowS
[QueryEvent'] -> ShowS
QueryEvent' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryEvent'] -> ShowS
$cshowList :: [QueryEvent'] -> ShowS
show :: QueryEvent' -> String
$cshow :: QueryEvent' -> String
showsPrec :: Int -> QueryEvent' -> ShowS
$cshowsPrec :: Int -> QueryEvent' -> ShowS
Show, QueryEvent' -> QueryEvent' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryEvent' -> QueryEvent' -> Bool
$c/= :: QueryEvent' -> QueryEvent' -> Bool
== :: QueryEvent' -> QueryEvent' -> Bool
$c== :: QueryEvent' -> QueryEvent' -> Bool
Eq)
getQueryEvent' :: Get QueryEvent'
getQueryEvent' :: Get QueryEvent'
getQueryEvent' = do
Word8
_ <- Get Word8
getWord8
Query -> QueryEvent'
QueryEvent' forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Query
Query forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
getRemainingLazyByteString
data TableMapEvent = TableMapEvent
{ TableMapEvent -> Word64
tmTableId :: !Word64
, TableMapEvent -> Word16
tmFlags :: !Word16
, TableMapEvent -> ByteString
tmSchemaName :: !ByteString
, TableMapEvent -> ByteString
tmTableName :: !ByteString
, TableMapEvent -> Int
tmColumnCnt :: !Int
, TableMapEvent -> [FieldType]
tmColumnType :: ![FieldType]
, TableMapEvent -> [BinLogMeta]
tmColumnMeta :: ![BinLogMeta]
, TableMapEvent -> ByteString
tmNullMap :: !ByteString
} deriving (Int -> TableMapEvent -> ShowS
[TableMapEvent] -> ShowS
TableMapEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableMapEvent] -> ShowS
$cshowList :: [TableMapEvent] -> ShowS
show :: TableMapEvent -> String
$cshow :: TableMapEvent -> String
showsPrec :: Int -> TableMapEvent -> ShowS
$cshowsPrec :: Int -> TableMapEvent -> ShowS
Show, TableMapEvent -> TableMapEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableMapEvent -> TableMapEvent -> Bool
$c/= :: TableMapEvent -> TableMapEvent -> Bool
== :: TableMapEvent -> TableMapEvent -> Bool
$c== :: TableMapEvent -> TableMapEvent -> Bool
Eq, forall x. Rep TableMapEvent x -> TableMapEvent
forall x. TableMapEvent -> Rep TableMapEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableMapEvent x -> TableMapEvent
$cfrom :: forall x. TableMapEvent -> Rep TableMapEvent x
Generic)
getTableMapEvent :: FormatDescription -> Get TableMapEvent
getTableMapEvent :: FormatDescription -> Get TableMapEvent
getTableMapEvent FormatDescription
fd = do
let hlen :: Word8
hlen = FormatDescription -> BinLogEventType -> Word8
eventHeaderLen FormatDescription
fd BinLogEventType
BINLOG_TABLE_MAP_EVENT
Word64
tid <- if Word8
hlen forall a. Eq a => a -> a -> Bool
== Word8
6 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le else Get Word64
getWord48le
Word16
flgs <- Get Word16
getWord16le
Word8
slen <- Get Word8
getWord8
ByteString
schema <- Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
slen)
Word8
_ <- Get Word8
getWord8
Word8
tlen <- Get Word8
getWord8
ByteString
table <- Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
tlen)
Word8
_ <- Get Word8
getWord8
Int
cc <- Get Int
getLenEncInt
ByteString
colTypBS <- Int -> Get ByteString
getByteString Int
cc
let typs :: [FieldType]
typs = forall a b. (a -> b) -> [a] -> [b]
map Word8 -> FieldType
FieldType (ByteString -> [Word8]
B.unpack ByteString
colTypBS)
ByteString
colMetaBS <- Get ByteString
getLenEncBytes
[BinLogMeta]
metas <- case forall a.
Get a
-> ByteString
-> Either (ByteString, Int64, String) (ByteString, Int64, a)
runGetOrFail (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FieldType]
typs FieldType -> Get BinLogMeta
getBinLogMeta) (ByteString -> ByteString
L.fromStrict ByteString
colMetaBS) of
Left (ByteString
_, Int64
_, String
errmsg) -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
errmsg
Right (ByteString
_, Int64
_, [BinLogMeta]
r) -> forall (m :: * -> *) a. Monad m => a -> m a
return [BinLogMeta]
r
ByteString
nullmap <- Int -> Get ByteString
getByteString ((Int
cc forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> a
`div` Int
8)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64
-> Word16
-> ByteString
-> ByteString
-> Int
-> [FieldType]
-> [BinLogMeta]
-> ByteString
-> TableMapEvent
TableMapEvent Word64
tid Word16
flgs ByteString
schema ByteString
table Int
cc [FieldType]
typs [BinLogMeta]
metas ByteString
nullmap)
data DeleteRowsEvent = DeleteRowsEvent
{ DeleteRowsEvent -> Word64
deleteTableId :: !Word64
, DeleteRowsEvent -> Word16
deleteFlags :: !Word16
, DeleteRowsEvent -> Int
deleteColumnCnt :: !Int
, DeleteRowsEvent -> BitMap
deletePresentMap :: !BitMap
, DeleteRowsEvent -> [[BinLogValue]]
deleteRowData :: ![[BinLogValue]]
} deriving (Int -> DeleteRowsEvent -> ShowS
[DeleteRowsEvent] -> ShowS
DeleteRowsEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRowsEvent] -> ShowS
$cshowList :: [DeleteRowsEvent] -> ShowS
show :: DeleteRowsEvent -> String
$cshow :: DeleteRowsEvent -> String
showsPrec :: Int -> DeleteRowsEvent -> ShowS
$cshowsPrec :: Int -> DeleteRowsEvent -> ShowS
Show, DeleteRowsEvent -> DeleteRowsEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRowsEvent -> DeleteRowsEvent -> Bool
$c/= :: DeleteRowsEvent -> DeleteRowsEvent -> Bool
== :: DeleteRowsEvent -> DeleteRowsEvent -> Bool
$c== :: DeleteRowsEvent -> DeleteRowsEvent -> Bool
Eq, forall x. Rep DeleteRowsEvent x -> DeleteRowsEvent
forall x. DeleteRowsEvent -> Rep DeleteRowsEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRowsEvent x -> DeleteRowsEvent
$cfrom :: forall x. DeleteRowsEvent -> Rep DeleteRowsEvent x
Generic)
getDeleteRowEvent :: FormatDescription -> TableMapEvent -> BinLogEventType -> Get DeleteRowsEvent
getDeleteRowEvent :: FormatDescription
-> TableMapEvent -> BinLogEventType -> Get DeleteRowsEvent
getDeleteRowEvent FormatDescription
fd TableMapEvent
tme BinLogEventType
typ = do
let hlen :: Word8
hlen = FormatDescription -> BinLogEventType -> Word8
eventHeaderLen FormatDescription
fd BinLogEventType
typ
Word64
tid <- if Word8
hlen forall a. Eq a => a -> a -> Bool
== Word8
6 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le else Get Word64
getWord48le
Word16
flgs <- Get Word16
getWord16le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BinLogEventType
typ forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_DELETE_ROWS_EVENTv2) forall a b. (a -> b) -> a -> b
$ do
Word16
extraLen <- Get Word16
getWord16le
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
extraLen forall a. Num a => a -> a -> a
- Int
2)
Int
colCnt <- Get Int
getLenEncInt
let (Int
plen, Int
poffset) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
colCnt forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
8
BitMap
pmap <- Int -> Int -> Get BitMap
getPresentMap Int
plen Int
poffset
Word64
-> Word16 -> Int -> BitMap -> [[BinLogValue]] -> DeleteRowsEvent
DeleteRowsEvent Word64
tid Word16
flgs Int
colCnt BitMap
pmap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Monad m => m a -> m Bool -> m [a]
untilM ([BinLogMeta] -> BitMap -> Get [BinLogValue]
getBinLogRow (TableMapEvent -> [BinLogMeta]
tmColumnMeta TableMapEvent
tme) BitMap
pmap) Get Bool
isEmpty
data WriteRowsEvent = WriteRowsEvent
{ WriteRowsEvent -> Word64
writeTableId :: !Word64
, WriteRowsEvent -> Word16
writeFlags :: !Word16
, WriteRowsEvent -> Int
writeColumnCnt :: !Int
, WriteRowsEvent -> BitMap
writePresentMap :: !BitMap
, WriteRowsEvent -> [[BinLogValue]]
writeRowData :: ![[BinLogValue]]
} deriving (Int -> WriteRowsEvent -> ShowS
[WriteRowsEvent] -> ShowS
WriteRowsEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WriteRowsEvent] -> ShowS
$cshowList :: [WriteRowsEvent] -> ShowS
show :: WriteRowsEvent -> String
$cshow :: WriteRowsEvent -> String
showsPrec :: Int -> WriteRowsEvent -> ShowS
$cshowsPrec :: Int -> WriteRowsEvent -> ShowS
Show, WriteRowsEvent -> WriteRowsEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WriteRowsEvent -> WriteRowsEvent -> Bool
$c/= :: WriteRowsEvent -> WriteRowsEvent -> Bool
== :: WriteRowsEvent -> WriteRowsEvent -> Bool
$c== :: WriteRowsEvent -> WriteRowsEvent -> Bool
Eq, forall x. Rep WriteRowsEvent x -> WriteRowsEvent
forall x. WriteRowsEvent -> Rep WriteRowsEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WriteRowsEvent x -> WriteRowsEvent
$cfrom :: forall x. WriteRowsEvent -> Rep WriteRowsEvent x
Generic)
getWriteRowEvent :: FormatDescription -> TableMapEvent -> BinLogEventType -> Get WriteRowsEvent
getWriteRowEvent :: FormatDescription
-> TableMapEvent -> BinLogEventType -> Get WriteRowsEvent
getWriteRowEvent FormatDescription
fd TableMapEvent
tme BinLogEventType
typ = do
let hlen :: Word8
hlen = FormatDescription -> BinLogEventType -> Word8
eventHeaderLen FormatDescription
fd BinLogEventType
typ
Word64
tid <- if Word8
hlen forall a. Eq a => a -> a -> Bool
== Word8
6 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le else Get Word64
getWord48le
Word16
flgs <- Get Word16
getWord16le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BinLogEventType
typ forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_WRITE_ROWS_EVENTv2) forall a b. (a -> b) -> a -> b
$ do
Word16
extraLen <- Get Word16
getWord16le
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
extraLen forall a. Num a => a -> a -> a
- Int
2)
Int
colCnt <- Get Int
getLenEncInt
let (Int
plen, Int
poffset) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
colCnt forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
8
BitMap
pmap <- Int -> Int -> Get BitMap
getPresentMap Int
plen Int
poffset
Word64
-> Word16 -> Int -> BitMap -> [[BinLogValue]] -> WriteRowsEvent
WriteRowsEvent Word64
tid Word16
flgs Int
colCnt BitMap
pmap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Monad m => m a -> m Bool -> m [a]
untilM ([BinLogMeta] -> BitMap -> Get [BinLogValue]
getBinLogRow (TableMapEvent -> [BinLogMeta]
tmColumnMeta TableMapEvent
tme) BitMap
pmap) Get Bool
isEmpty
data UpdateRowsEvent = UpdateRowsEvent
{ UpdateRowsEvent -> Word64
updateTableId :: !Word64
, UpdateRowsEvent -> Word16
updateFlags :: !Word16
, UpdateRowsEvent -> Int
updateColumnCnt :: !Int
, UpdateRowsEvent -> (BitMap, BitMap)
updatePresentMap :: !(BitMap, BitMap)
, UpdateRowsEvent -> [([BinLogValue], [BinLogValue])]
updateRowData :: ![ ([BinLogValue], [BinLogValue]) ]
} deriving (Int -> UpdateRowsEvent -> ShowS
[UpdateRowsEvent] -> ShowS
UpdateRowsEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRowsEvent] -> ShowS
$cshowList :: [UpdateRowsEvent] -> ShowS
show :: UpdateRowsEvent -> String
$cshow :: UpdateRowsEvent -> String
showsPrec :: Int -> UpdateRowsEvent -> ShowS
$cshowsPrec :: Int -> UpdateRowsEvent -> ShowS
Show, UpdateRowsEvent -> UpdateRowsEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRowsEvent -> UpdateRowsEvent -> Bool
$c/= :: UpdateRowsEvent -> UpdateRowsEvent -> Bool
== :: UpdateRowsEvent -> UpdateRowsEvent -> Bool
$c== :: UpdateRowsEvent -> UpdateRowsEvent -> Bool
Eq, forall x. Rep UpdateRowsEvent x -> UpdateRowsEvent
forall x. UpdateRowsEvent -> Rep UpdateRowsEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRowsEvent x -> UpdateRowsEvent
$cfrom :: forall x. UpdateRowsEvent -> Rep UpdateRowsEvent x
Generic)
getUpdateRowEvent :: FormatDescription -> TableMapEvent -> BinLogEventType -> Get UpdateRowsEvent
getUpdateRowEvent :: FormatDescription
-> TableMapEvent -> BinLogEventType -> Get UpdateRowsEvent
getUpdateRowEvent FormatDescription
fd TableMapEvent
tme BinLogEventType
typ = do
let hlen :: Word8
hlen = FormatDescription -> BinLogEventType -> Word8
eventHeaderLen FormatDescription
fd BinLogEventType
typ
Word64
tid <- if Word8
hlen forall a. Eq a => a -> a -> Bool
== Word8
6 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le else Get Word64
getWord48le
Word16
flgs <- Get Word16
getWord16le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BinLogEventType
typ forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_UPDATE_ROWS_EVENTv2) forall a b. (a -> b) -> a -> b
$ do
Word16
extraLen <- Get Word16
getWord16le
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Int -> Get ByteString
getByteString (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
extraLen forall a. Num a => a -> a -> a
- Int
2)
Int
colCnt <- Get Int
getLenEncInt
let (Int
plen, Int
poffset) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
colCnt forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
8
BitMap
pmap <- Int -> Int -> Get BitMap
getPresentMap Int
plen Int
poffset
BitMap
pmap' <- Int -> Int -> Get BitMap
getPresentMap Int
plen Int
poffset
Word64
-> Word16
-> Int
-> (BitMap, BitMap)
-> [([BinLogValue], [BinLogValue])]
-> UpdateRowsEvent
UpdateRowsEvent Word64
tid Word16
flgs Int
colCnt (BitMap
pmap, BitMap
pmap') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (m :: * -> *) a. Monad m => m a -> m Bool -> m [a]
untilM ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BinLogMeta] -> BitMap -> Get [BinLogValue]
getBinLogRow (TableMapEvent -> [BinLogMeta]
tmColumnMeta TableMapEvent
tme) BitMap
pmap forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [BinLogMeta] -> BitMap -> Get [BinLogValue]
getBinLogRow (TableMapEvent -> [BinLogMeta]
tmColumnMeta TableMapEvent
tme) BitMap
pmap')
Get Bool
isEmpty
getPresentMap :: Int -> Int -> Get BitMap
getPresentMap :: Int -> Int -> Get BitMap
getPresentMap Int
plen Int
poffset = do
ByteString
pmap <- Int -> Get ByteString
getByteString Int
plen
let pmap' :: ByteString
pmap' = if ByteString -> Bool
B.null ByteString
pmap
then ByteString
B.empty
else HasCallStack => ByteString -> ByteString
B.init ByteString
pmap ByteString -> Word8 -> ByteString
`B.snoc` (HasCallStack => ByteString -> Word8
B.last ByteString
pmap forall a. Bits a => a -> a -> a
.&. Word8
0xFF forall a. Bits a => a -> Int -> a
`shiftR` (Int
7 forall a. Num a => a -> a -> a
- Int
poffset))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> BitMap
BitMap ByteString
pmap')