module Database.MySQL.BinLog
(
SlaveID
, BinLogTracker(..)
, registerPesudoSlave
, dumpBinLog
, RowBinLogEvent(..)
, decodeRowBinLogEvent
, getLastBinLogTracker
, isCheckSumEnabled
, isSemiSyncEnabled
, module Database.MySQL.BinLogProtocol.BinLogEvent
, module Database.MySQL.BinLogProtocol.BinLogValue
, module Database.MySQL.BinLogProtocol.BinLogMeta
) where
import Control.Applicative
import Control.Exception (throwIO)
import Control.Monad
import Data.Binary.Put
import Data.ByteString (ByteString)
import Data.IORef (IORef, newIORef,
readIORef,
writeIORef)
import Data.Text.Encoding (encodeUtf8)
import Data.Word
import Database.MySQL.Base
import Database.MySQL.BinLogProtocol.BinLogEvent
import Database.MySQL.BinLogProtocol.BinLogMeta
import Database.MySQL.BinLogProtocol.BinLogValue
import Database.MySQL.Connection
import GHC.Generics (Generic)
import System.IO.Streams (InputStream)
import qualified System.IO.Streams as Stream
type SlaveID = Word32
data BinLogTracker = BinLogTracker
{ BinLogTracker -> ByteString
btFileName :: {-# UNPACK #-} !ByteString
, BinLogTracker -> Word32
btNextPos :: {-# UNPACK #-} !Word32
} deriving (Int -> BinLogTracker -> ShowS
[BinLogTracker] -> ShowS
BinLogTracker -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinLogTracker] -> ShowS
$cshowList :: [BinLogTracker] -> ShowS
show :: BinLogTracker -> String
$cshow :: BinLogTracker -> String
showsPrec :: Int -> BinLogTracker -> ShowS
$cshowsPrec :: Int -> BinLogTracker -> ShowS
Show, BinLogTracker -> BinLogTracker -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinLogTracker -> BinLogTracker -> Bool
$c/= :: BinLogTracker -> BinLogTracker -> Bool
== :: BinLogTracker -> BinLogTracker -> Bool
$c== :: BinLogTracker -> BinLogTracker -> Bool
Eq, forall x. Rep BinLogTracker x -> BinLogTracker
forall x. BinLogTracker -> Rep BinLogTracker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BinLogTracker x -> BinLogTracker
$cfrom :: forall x. BinLogTracker -> Rep BinLogTracker x
Generic)
registerPesudoSlave :: MySQLConn -> SlaveID -> IO OK
registerPesudoSlave :: MySQLConn -> Word32 -> IO OK
registerPesudoSlave MySQLConn
conn Word32
sid = MySQLConn -> Command -> IO OK
command MySQLConn
conn (Word32
-> ByteString
-> ByteString
-> ByteString
-> Word16
-> Word32
-> Word32
-> Command
COM_REGISTER_SLAVE Word32
sid ByteString
"" ByteString
"" ByteString
"" Word16
0 Word32
0 Word32
0)
dumpBinLog :: MySQLConn
-> SlaveID
-> BinLogTracker
-> Bool
-> IO (FormatDescription, IORef ByteString, InputStream BinLogPacket)
dumpBinLog :: MySQLConn
-> Word32
-> BinLogTracker
-> Bool
-> IO
(FormatDescription, IORef ByteString, InputStream BinLogPacket)
dumpBinLog conn :: MySQLConn
conn@(MySQLConn InputStream Packet
is Packet -> IO ()
wp IO ()
_ IORef Bool
consumed) Word32
sid (BinLogTracker ByteString
initfn Word32
initpos) Bool
wantAck = do
MySQLConn -> IO ()
guardUnconsumed MySQLConn
conn
Bool
checksum <- MySQLConn -> IO Bool
isCheckSumEnabled MySQLConn
conn
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
checksum forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ MySQLConn -> Query -> IO OK
execute_ MySQLConn
conn Query
"SET @master_binlog_checksum = @@global.binlog_checksum"
Bool
semiAck <- MySQLConn -> IO Bool
isSemiSyncEnabled MySQLConn
conn
let needAck :: Bool
needAck = Bool
semiAck Bool -> Bool -> Bool
&& Bool
wantAck
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
needAck forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ MySQLConn -> Query -> IO OK
execute_ MySQLConn
conn Query
"SET @rpl_semi_sync_slave = 1"
Command -> (Packet -> IO ()) -> IO ()
writeCommand (Word32 -> Word16 -> Word32 -> ByteString -> Command
COM_BINLOG_DUMP Word32
initpos Word16
0x00 Word32
sid ByteString
initfn) Packet -> IO ()
wp
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
consumed Bool
False
BinLogPacket
rp <- IO (Maybe BinLogPacket) -> BinLogEventType -> IO BinLogPacket
skipToPacketT (Bool -> Bool -> InputStream Packet -> IO (Maybe BinLogPacket)
readBinLogPacket Bool
checksum Bool
needAck InputStream Packet
is) BinLogEventType
BINLOG_ROTATE_EVENT
RotateEvent
re <- forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket Get RotateEvent
getRotateEvent BinLogPacket
rp
IORef ByteString
fref <- forall a. a -> IO (IORef a)
newIORef (RotateEvent -> ByteString
rFileName RotateEvent
re)
BinLogPacket
p <- IO (Maybe BinLogPacket) -> BinLogEventType -> IO BinLogPacket
skipToPacketT (Bool -> Bool -> InputStream Packet -> IO (Maybe BinLogPacket)
readBinLogPacket Bool
checksum Bool
needAck InputStream Packet
is) BinLogEventType
BINLOG_FORMAT_DESCRIPTION_EVENT
Bool
-> BinLogPacket -> IORef ByteString -> (Packet -> IO ()) -> IO ()
replyAck Bool
needAck BinLogPacket
p IORef ByteString
fref Packet -> IO ()
wp
FormatDescription
fmt <- forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket Get FormatDescription
getFormatDescription BinLogPacket
p
InputStream BinLogPacket
es <- forall a. IO (Maybe a) -> IO (InputStream a)
Stream.makeInputStream forall a b. (a -> b) -> a -> b
$ do
Maybe BinLogPacket
q <- Bool -> Bool -> InputStream Packet -> IO (Maybe BinLogPacket)
readBinLogPacket Bool
checksum Bool
needAck InputStream Packet
is
case Maybe BinLogPacket
q of
Maybe BinLogPacket
Nothing -> forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
consumed Bool
True forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just BinLogPacket
q' -> do forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BinLogPacket -> BinLogEventType
blEventType BinLogPacket
q' forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_ROTATE_EVENT) forall a b. (a -> b) -> a -> b
$ do
RotateEvent
e <- forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket Get RotateEvent
getRotateEvent BinLogPacket
q'
forall a. IORef a -> a -> IO ()
writeIORef' IORef ByteString
fref (RotateEvent -> ByteString
rFileName RotateEvent
e)
Bool
-> BinLogPacket -> IORef ByteString -> (Packet -> IO ()) -> IO ()
replyAck Bool
needAck BinLogPacket
q' IORef ByteString
fref Packet -> IO ()
wp
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BinLogPacket
q
forall (m :: * -> *) a. Monad m => a -> m a
return (FormatDescription
fmt, IORef ByteString
fref, InputStream BinLogPacket
es)
where
skipToPacketT :: IO (Maybe BinLogPacket) -> BinLogEventType -> IO BinLogPacket
skipToPacketT IO (Maybe BinLogPacket)
iop BinLogEventType
typ = do
Maybe BinLogPacket
p <- IO (Maybe BinLogPacket)
iop
case Maybe BinLogPacket
p of
Just BinLogPacket
p' -> do
if BinLogPacket -> BinLogEventType
blEventType BinLogPacket
p' forall a. Eq a => a -> a -> Bool
== BinLogEventType
typ then forall (m :: * -> *) a. Monad m => a -> m a
return BinLogPacket
p' else IO (Maybe BinLogPacket) -> BinLogEventType -> IO BinLogPacket
skipToPacketT IO (Maybe BinLogPacket)
iop BinLogEventType
typ
Maybe BinLogPacket
Nothing -> forall e a. Exception e => e -> IO a
throwIO NetworkException
NetworkException
replyAck :: Bool
-> BinLogPacket -> IORef ByteString -> (Packet -> IO ()) -> IO ()
replyAck Bool
needAck BinLogPacket
p IORef ByteString
fref Packet -> IO ()
wp' = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
needAck Bool -> Bool -> Bool
&& BinLogPacket -> Bool
blSemiAck BinLogPacket
p) forall a b. (a -> b) -> a -> b
$ do
ByteString
fn <- forall a. IORef a -> IO a
readIORef IORef ByteString
fref
Packet -> IO ()
wp' (Word64 -> ByteString -> Packet
makeSemiAckPacket (BinLogPacket -> Word64
blLogPos BinLogPacket
p) ByteString
fn)
makeSemiAckPacket :: Word64 -> ByteString -> Packet
makeSemiAckPacket Word64
pos ByteString
fn = Word8 -> Put -> Packet
putToPacket Word8
0 forall a b. (a -> b) -> a -> b
$ do
Word8 -> Put
putWord8 Word8
0xEF
Word64 -> Put
putWord64le Word64
pos
ByteString -> Put
putByteString ByteString
fn
readBinLogPacket :: Bool -> Bool -> InputStream Packet -> IO (Maybe BinLogPacket)
readBinLogPacket Bool
checksum Bool
needAck InputStream Packet
is' = do
Packet
p <- InputStream Packet -> IO Packet
readPacket InputStream Packet
is'
if | Packet -> Bool
isOK Packet
p -> forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Get a -> Packet -> IO a
getFromPacket (Bool -> Bool -> Get BinLogPacket
getBinLogPacket Bool
checksum Bool
needAck) Packet
p
| Packet -> Bool
isEOF Packet
p -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
| Packet -> Bool
isERR Packet
p -> forall a. Binary a => Packet -> IO a
decodeFromPacket Packet
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall e a. Exception e => e -> IO a
throwIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. ERR -> ERRException
ERRException
data RowBinLogEvent
= RowQueryEvent {-# UNPACK #-} !Word32 !BinLogTracker !QueryEvent'
| RowDeleteEvent {-# UNPACK #-} !Word32 !BinLogTracker !TableMapEvent !DeleteRowsEvent
| RowWriteEvent {-# UNPACK #-} !Word32 !BinLogTracker !TableMapEvent !WriteRowsEvent
| RowUpdateEvent {-# UNPACK #-} !Word32 !BinLogTracker !TableMapEvent !UpdateRowsEvent
deriving (Int -> RowBinLogEvent -> ShowS
[RowBinLogEvent] -> ShowS
RowBinLogEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowBinLogEvent] -> ShowS
$cshowList :: [RowBinLogEvent] -> ShowS
show :: RowBinLogEvent -> String
$cshow :: RowBinLogEvent -> String
showsPrec :: Int -> RowBinLogEvent -> ShowS
$cshowsPrec :: Int -> RowBinLogEvent -> ShowS
Show, RowBinLogEvent -> RowBinLogEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowBinLogEvent -> RowBinLogEvent -> Bool
$c/= :: RowBinLogEvent -> RowBinLogEvent -> Bool
== :: RowBinLogEvent -> RowBinLogEvent -> Bool
$c== :: RowBinLogEvent -> RowBinLogEvent -> Bool
Eq, forall x. Rep RowBinLogEvent x -> RowBinLogEvent
forall x. RowBinLogEvent -> Rep RowBinLogEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowBinLogEvent x -> RowBinLogEvent
$cfrom :: forall x. RowBinLogEvent -> Rep RowBinLogEvent x
Generic)
decodeRowBinLogEvent :: (FormatDescription, IORef ByteString, InputStream BinLogPacket)
-> IO (InputStream RowBinLogEvent)
decodeRowBinLogEvent :: (FormatDescription, IORef ByteString, InputStream BinLogPacket)
-> IO (InputStream RowBinLogEvent)
decodeRowBinLogEvent (FormatDescription
fd', IORef ByteString
fref', InputStream BinLogPacket
is') = forall a. IO (Maybe a) -> IO (InputStream a)
Stream.makeInputStream (FormatDescription
-> IORef ByteString
-> InputStream BinLogPacket
-> IO (Maybe RowBinLogEvent)
loop FormatDescription
fd' IORef ByteString
fref' InputStream BinLogPacket
is')
where
loop :: FormatDescription
-> IORef ByteString
-> InputStream BinLogPacket
-> IO (Maybe RowBinLogEvent)
loop FormatDescription
fd IORef ByteString
fref InputStream BinLogPacket
is = do
Maybe BinLogPacket
p <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream BinLogPacket
is
case Maybe BinLogPacket
p of
Maybe BinLogPacket
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just BinLogPacket
p' -> do
let t :: BinLogEventType
t = BinLogPacket -> BinLogEventType
blEventType BinLogPacket
p'
if | BinLogEventType
t forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_ROWS_QUERY_EVENT -> do
BinLogTracker
tr <- BinLogPacket -> IORef ByteString -> IO BinLogTracker
track BinLogPacket
p' IORef ByteString
fref
QueryEvent'
e <- forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket Get QueryEvent'
getQueryEvent' BinLogPacket
p'
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (Word32 -> BinLogTracker -> QueryEvent' -> RowBinLogEvent
RowQueryEvent (BinLogPacket -> Word32
blTimestamp BinLogPacket
p') BinLogTracker
tr QueryEvent'
e))
| BinLogEventType
t forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_TABLE_MAP_EVENT -> do
TableMapEvent
tme <- forall a. Get a -> BinLogPacket -> IO a
getFromBinLogPacket (FormatDescription -> Get TableMapEvent
getTableMapEvent FormatDescription
fd) BinLogPacket
p'
Maybe BinLogPacket
q <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream BinLogPacket
is
case Maybe BinLogPacket
q of
Maybe BinLogPacket
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just BinLogPacket
q' -> do
let u :: BinLogEventType
u = BinLogPacket -> BinLogEventType
blEventType BinLogPacket
q'
if | BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_WRITE_ROWS_EVENTv1 Bool -> Bool -> Bool
|| BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_WRITE_ROWS_EVENTv2 -> do
BinLogTracker
tr <- BinLogPacket -> IORef ByteString -> IO BinLogTracker
track BinLogPacket
q' IORef ByteString
fref
WriteRowsEvent
e <- forall a. (BinLogEventType -> Get a) -> BinLogPacket -> IO a
getFromBinLogPacket' (FormatDescription
-> TableMapEvent -> BinLogEventType -> Get WriteRowsEvent
getWriteRowEvent FormatDescription
fd TableMapEvent
tme) BinLogPacket
q'
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (Word32
-> BinLogTracker
-> TableMapEvent
-> WriteRowsEvent
-> RowBinLogEvent
RowWriteEvent (BinLogPacket -> Word32
blTimestamp BinLogPacket
q') BinLogTracker
tr TableMapEvent
tme WriteRowsEvent
e))
| BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_DELETE_ROWS_EVENTv1 Bool -> Bool -> Bool
|| BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_DELETE_ROWS_EVENTv2 -> do
BinLogTracker
tr <- BinLogPacket -> IORef ByteString -> IO BinLogTracker
track BinLogPacket
q' IORef ByteString
fref
DeleteRowsEvent
e <- forall a. (BinLogEventType -> Get a) -> BinLogPacket -> IO a
getFromBinLogPacket' (FormatDescription
-> TableMapEvent -> BinLogEventType -> Get DeleteRowsEvent
getDeleteRowEvent FormatDescription
fd TableMapEvent
tme) BinLogPacket
q'
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (Word32
-> BinLogTracker
-> TableMapEvent
-> DeleteRowsEvent
-> RowBinLogEvent
RowDeleteEvent (BinLogPacket -> Word32
blTimestamp BinLogPacket
q') BinLogTracker
tr TableMapEvent
tme DeleteRowsEvent
e))
| BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_UPDATE_ROWS_EVENTv1 Bool -> Bool -> Bool
|| BinLogEventType
u forall a. Eq a => a -> a -> Bool
== BinLogEventType
BINLOG_UPDATE_ROWS_EVENTv2 -> do
BinLogTracker
tr <- BinLogPacket -> IORef ByteString -> IO BinLogTracker
track BinLogPacket
q' IORef ByteString
fref
UpdateRowsEvent
e <- forall a. (BinLogEventType -> Get a) -> BinLogPacket -> IO a
getFromBinLogPacket' (FormatDescription
-> TableMapEvent -> BinLogEventType -> Get UpdateRowsEvent
getUpdateRowEvent FormatDescription
fd TableMapEvent
tme) BinLogPacket
q'
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (Word32
-> BinLogTracker
-> TableMapEvent
-> UpdateRowsEvent
-> RowBinLogEvent
RowUpdateEvent (BinLogPacket -> Word32
blTimestamp BinLogPacket
q') BinLogTracker
tr TableMapEvent
tme UpdateRowsEvent
e))
| Bool
otherwise -> FormatDescription
-> IORef ByteString
-> InputStream BinLogPacket
-> IO (Maybe RowBinLogEvent)
loop FormatDescription
fd IORef ByteString
fref InputStream BinLogPacket
is
| Bool
otherwise -> FormatDescription
-> IORef ByteString
-> InputStream BinLogPacket
-> IO (Maybe RowBinLogEvent)
loop FormatDescription
fd IORef ByteString
fref InputStream BinLogPacket
is
track :: BinLogPacket -> IORef ByteString -> IO BinLogTracker
track BinLogPacket
p IORef ByteString
fref = ByteString -> Word32 -> BinLogTracker
BinLogTracker forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IORef a -> IO a
readIORef IORef ByteString
fref forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. BinLogPacket -> Word64
blLogPos) BinLogPacket
p
getLastBinLogTracker :: MySQLConn -> IO (Maybe BinLogTracker)
getLastBinLogTracker :: MySQLConn -> IO (Maybe BinLogTracker)
getLastBinLogTracker MySQLConn
conn = do
([ColumnDef]
_, InputStream [MySQLValue]
is) <- MySQLConn -> Query -> IO ([ColumnDef], InputStream [MySQLValue])
query_ MySQLConn
conn Query
"SHOW MASTER STATUS"
Maybe [MySQLValue]
row <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream [MySQLValue]
is
forall a. InputStream a -> IO ()
Stream.skipToEof InputStream [MySQLValue]
is
case Maybe [MySQLValue]
row of
Just (MySQLText Text
fn : MySQLInt64U Word64
pos : [MySQLValue]
_) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ByteString -> Word32 -> BinLogTracker
BinLogTracker (Text -> ByteString
encodeUtf8 Text
fn) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
pos)
Maybe [MySQLValue]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
isCheckSumEnabled :: MySQLConn -> IO Bool
isCheckSumEnabled :: MySQLConn -> IO Bool
isCheckSumEnabled MySQLConn
conn = do
([ColumnDef]
_, InputStream [MySQLValue]
is) <- MySQLConn -> Query -> IO ([ColumnDef], InputStream [MySQLValue])
query_ MySQLConn
conn Query
"SHOW GLOBAL VARIABLES LIKE 'binlog_checksum'"
Maybe [MySQLValue]
row <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream [MySQLValue]
is
forall a. InputStream a -> IO ()
Stream.skipToEof InputStream [MySQLValue]
is
case Maybe [MySQLValue]
row of
Just [MySQLValue
_, MySQLText Text
"CRC32"] -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Maybe [MySQLValue]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
isSemiSyncEnabled :: MySQLConn -> IO Bool
isSemiSyncEnabled :: MySQLConn -> IO Bool
isSemiSyncEnabled MySQLConn
conn = do
([ColumnDef]
_, InputStream [MySQLValue]
is) <- MySQLConn -> Query -> IO ([ColumnDef], InputStream [MySQLValue])
query_ MySQLConn
conn Query
"SHOW VARIABLES LIKE 'rpl_semi_sync_master_enabled'"
Maybe [MySQLValue]
row <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream [MySQLValue]
is
forall a. InputStream a -> IO ()
Stream.skipToEof InputStream [MySQLValue]
is
case Maybe [MySQLValue]
row of
Just [MySQLValue
_, MySQLText Text
"ON"] -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Maybe [MySQLValue]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False