module Database.MySQL.Connection where
import Control.Applicative
import Control.Exception (Exception, bracketOnError,
throwIO, catch, SomeException)
import Control.Monad
import qualified Crypto.Hash as Crypto
import qualified Data.Binary as Binary
import qualified Data.Binary.Put as Binary
import Data.Bits
import qualified Data.ByteArray as BA
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 Data.IORef (IORef, newIORef, readIORef,
writeIORef)
import Data.Typeable
import Data.Word
import Database.MySQL.Protocol.Auth
import Database.MySQL.Protocol.Command
import Database.MySQL.Protocol.Packet
import Network.Socket (HostName, PortNumber)
import System.IO.Streams (InputStream)
import qualified System.IO.Streams as Stream
import qualified System.IO.Streams.TCP as TCP
import qualified Data.Connection as TCP
data MySQLConn = MySQLConn {
MySQLConn -> InputStream Packet
mysqlRead :: {-# UNPACK #-} !(InputStream Packet)
, MySQLConn -> Packet -> IO ()
mysqlWrite :: (Packet -> IO ())
, MySQLConn -> IO ()
mysqlCloseSocket :: IO ()
, MySQLConn -> IORef Bool
isConsumed :: {-# UNPACK #-} !(IORef Bool)
}
data ConnectInfo = ConnectInfo
{ ConnectInfo -> HostName
ciHost :: HostName
, ConnectInfo -> PortNumber
ciPort :: PortNumber
, ConnectInfo -> ByteString
ciDatabase :: ByteString
, ConnectInfo -> ByteString
ciUser :: ByteString
, ConnectInfo -> ByteString
ciPassword :: ByteString
, ConnectInfo -> Word8
ciCharset :: Word8
} deriving Int -> ConnectInfo -> ShowS
[ConnectInfo] -> ShowS
ConnectInfo -> HostName
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
showList :: [ConnectInfo] -> ShowS
$cshowList :: [ConnectInfo] -> ShowS
show :: ConnectInfo -> HostName
$cshow :: ConnectInfo -> HostName
showsPrec :: Int -> ConnectInfo -> ShowS
$cshowsPrec :: Int -> ConnectInfo -> ShowS
Show
defaultConnectInfo :: ConnectInfo
defaultConnectInfo :: ConnectInfo
defaultConnectInfo = HostName
-> PortNumber
-> ByteString
-> ByteString
-> ByteString
-> Word8
-> ConnectInfo
ConnectInfo HostName
"127.0.0.1" PortNumber
3306 ByteString
"" ByteString
"root" ByteString
"" Word8
utf8_general_ci
defaultConnectInfoMB4 :: ConnectInfo
defaultConnectInfoMB4 :: ConnectInfo
defaultConnectInfoMB4 = HostName
-> PortNumber
-> ByteString
-> ByteString
-> ByteString
-> Word8
-> ConnectInfo
ConnectInfo HostName
"127.0.0.1" PortNumber
3306 ByteString
"" ByteString
"root" ByteString
"" Word8
utf8mb4_unicode_ci
utf8_general_ci :: Word8
utf8_general_ci :: Word8
utf8_general_ci = Word8
33
utf8mb4_unicode_ci :: Word8
utf8mb4_unicode_ci :: Word8
utf8mb4_unicode_ci = Word8
224
bUFSIZE :: Int
bUFSIZE :: Int
bUFSIZE = Int
16384
connect :: ConnectInfo -> IO MySQLConn
connect :: ConnectInfo -> IO MySQLConn
connect = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConnectInfo -> IO (Greeting, MySQLConn)
connectDetail
connectDetail :: ConnectInfo -> IO (Greeting, MySQLConn)
connectDetail :: ConnectInfo -> IO (Greeting, MySQLConn)
connectDetail (ConnectInfo HostName
host PortNumber
port ByteString
db ByteString
user ByteString
pass Word8
charset)
= forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError IO TCPConnection
open forall a. Connection a -> IO ()
TCP.close forall {a}. Connection a -> IO (Greeting, MySQLConn)
go
where
open :: IO TCPConnection
open = HostName -> PortNumber -> Int -> IO TCPConnection
connectWithBufferSize HostName
host PortNumber
port Int
bUFSIZE
go :: Connection a -> IO (Greeting, MySQLConn)
go Connection a
c = do
let is :: InputStream ByteString
is = forall a. Connection a -> InputStream ByteString
TCP.source Connection a
c
InputStream Packet
is' <- InputStream ByteString -> IO (InputStream Packet)
decodeInputStream InputStream ByteString
is
Packet
p <- InputStream Packet -> IO Packet
readPacket InputStream Packet
is'
Greeting
greet <- forall a. Binary a => Packet -> IO a
decodeFromPacket Packet
p
let auth :: Auth
auth = ByteString -> ByteString -> ByteString -> Word8 -> Greeting -> Auth
mkAuth ByteString
db ByteString
user ByteString
pass Word8
charset Greeting
greet
forall {p} {a}. Binary p => Connection a -> p -> IO ()
write Connection a
c forall a b. (a -> b) -> a -> b
$ forall a. Binary a => Word8 -> a -> Packet
encodeToPacket Word8
1 Auth
auth
Packet
q <- InputStream Packet -> IO Packet
readPacket InputStream Packet
is'
if Packet -> Bool
isOK Packet
q
then do
IORef Bool
consumed <- forall a. a -> IO (IORef a)
newIORef Bool
True
let waitNotMandatoryOK :: IO ()
waitNotMandatoryOK = forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch
(forall (f :: * -> *) a. Functor f => f a -> f ()
void (InputStream Packet -> IO OK
waitCommandReply InputStream Packet
is'))
((\ SomeException
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()) :: SomeException -> IO ())
conn :: MySQLConn
conn = InputStream Packet
-> (Packet -> IO ()) -> IO () -> IORef Bool -> MySQLConn
MySQLConn InputStream Packet
is'
(forall {p} {a}. Binary p => Connection a -> p -> IO ()
write Connection a
c)
(Command -> (Packet -> IO ()) -> IO ()
writeCommand Command
COM_QUIT (forall {p} {a}. Binary p => Connection a -> p -> IO ()
write Connection a
c) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
waitNotMandatoryOK forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Connection a -> IO ()
TCP.close Connection a
c)
IORef Bool
consumed
forall (m :: * -> *) a. Monad m => a -> m a
return (Greeting
greet, MySQLConn
conn)
else forall a. Connection a -> IO ()
TCP.close Connection a
c forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Binary a => Packet -> IO a
decodeFromPacket Packet
q 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
connectWithBufferSize :: HostName -> PortNumber -> Int -> IO TCPConnection
connectWithBufferSize HostName
h PortNumber
p Int
bs = HostName -> PortNumber -> IO (Socket, SockAddr)
TCP.connectSocket HostName
h PortNumber
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> (Socket, SockAddr) -> IO TCPConnection
TCP.socketToConnection Int
bs
write :: Connection a -> p -> IO ()
write Connection a
c p
a = forall a. Connection a -> ByteString -> IO ()
TCP.send Connection a
c forall a b. (a -> b) -> a -> b
$ Put -> ByteString
Binary.runPut forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Binary t => t -> Put
Binary.put forall a b. (a -> b) -> a -> b
$ p
a
mkAuth :: ByteString -> ByteString -> ByteString -> Word8 -> Greeting -> Auth
mkAuth :: ByteString -> ByteString -> ByteString -> Word8 -> Greeting -> Auth
mkAuth ByteString
db ByteString
user ByteString
pass Word8
charset Greeting
greet =
let salt :: ByteString
salt = Greeting -> ByteString
greetingSalt1 Greeting
greet ByteString -> ByteString -> ByteString
`B.append` Greeting -> ByteString
greetingSalt2 Greeting
greet
scambleBuf :: ByteString
scambleBuf = ByteString -> ByteString -> ByteString
scramble ByteString
salt ByteString
pass
in Word32
-> Word32
-> Word8
-> ByteString
-> ByteString
-> ByteString
-> Auth
Auth Word32
clientCap Word32
clientMaxPacketSize Word8
charset ByteString
user ByteString
scambleBuf ByteString
db
where
scramble :: ByteString -> ByteString -> ByteString
scramble :: ByteString -> ByteString -> ByteString
scramble ByteString
salt ByteString
pass'
| ByteString -> Bool
B.null ByteString
pass' = ByteString
B.empty
| Bool
otherwise = [Word8] -> ByteString
B.pack (forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
B.zipWith forall a. Bits a => a -> a -> a
xor ByteString
sha1pass ByteString
withSalt)
where sha1pass :: ByteString
sha1pass = ByteString -> ByteString
sha1 ByteString
pass'
withSalt :: ByteString
withSalt = ByteString -> ByteString
sha1 (ByteString
salt ByteString -> ByteString -> ByteString
`B.append` ByteString -> ByteString
sha1 ByteString
sha1pass)
sha1 :: ByteString -> ByteString
sha1 :: ByteString -> ByteString
sha1 = forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
Crypto.hash :: ByteString -> Crypto.Digest Crypto.SHA1)
decodeInputStream :: InputStream ByteString -> IO (InputStream Packet)
decodeInputStream :: InputStream ByteString -> IO (InputStream Packet)
decodeInputStream InputStream ByteString
is = forall a. IO (Maybe a) -> IO (InputStream a)
Stream.makeInputStream forall a b. (a -> b) -> a -> b
$ do
ByteString
bs <- Int -> InputStream ByteString -> IO ByteString
Stream.readExactly Int
4 InputStream ByteString
is
let len :: Int64
len = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString
bs ByteString -> Int -> Word8
`B.unsafeIndex` Int
0)
forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString
bs ByteString -> Int -> Word8
`B.unsafeIndex` Int
1) forall a. Bits a => a -> Int -> a
`shiftL` Int
8
forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString
bs ByteString -> Int -> Word8
`B.unsafeIndex` Int
2) forall a. Bits a => a -> Int -> a
`shiftL` Int
16
seqN :: Word8
seqN = ByteString
bs ByteString -> Int -> Word8
`B.unsafeIndex` Int
3
ByteString
body <- forall {t}.
Integral t =>
[ByteString] -> t -> InputStream ByteString -> IO ByteString
loopRead [] Int64
len InputStream ByteString
is
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
$ Int64 -> Word8 -> ByteString -> Packet
Packet Int64
len Word8
seqN ByteString
body
where
loopRead :: [ByteString] -> t -> InputStream ByteString -> IO ByteString
loopRead [ByteString]
acc t
0 InputStream ByteString
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
L.fromChunks (forall a. [a] -> [a]
reverse [ByteString]
acc)
loopRead [ByteString]
acc t
k InputStream ByteString
is' = do
Maybe ByteString
bs <- forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream ByteString
is'
case Maybe ByteString
bs of Maybe ByteString
Nothing -> forall e a. Exception e => e -> IO a
throwIO NetworkException
NetworkException
Just ByteString
bs' -> do let l :: t
l = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
bs')
if t
l forall a. Ord a => a -> a -> Bool
>= t
k
then do
let (ByteString
a, ByteString
rest) = Int -> ByteString -> (ByteString, ByteString)
B.splitAt (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
k) ByteString
bs'
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Bool
B.null ByteString
rest) (forall a. a -> InputStream a -> IO ()
Stream.unRead ByteString
rest InputStream ByteString
is')
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
L.fromChunks (forall a. [a] -> [a]
reverse (ByteString
aforall a. a -> [a] -> [a]
:[ByteString]
acc))
else do
let k' :: t
k' = t
k forall a. Num a => a -> a -> a
- t
l
t
k' seq :: forall a b. a -> b -> b
`seq` [ByteString] -> t -> InputStream ByteString -> IO ByteString
loopRead (ByteString
bs'forall a. a -> [a] -> [a]
:[ByteString]
acc) t
k' InputStream ByteString
is'
close :: MySQLConn -> IO ()
close :: MySQLConn -> IO ()
close (MySQLConn InputStream Packet
_ Packet -> IO ()
_ IO ()
closeSocket IORef Bool
_) = IO ()
closeSocket
ping :: MySQLConn -> IO OK
ping :: MySQLConn -> IO OK
ping = forall a b c. (a -> b -> c) -> b -> a -> c
flip MySQLConn -> Command -> IO OK
command Command
COM_PING
command :: MySQLConn -> Command -> IO OK
command :: MySQLConn -> Command -> IO OK
command conn :: MySQLConn
conn@(MySQLConn InputStream Packet
is Packet -> IO ()
os IO ()
_ IORef Bool
_) Command
cmd = do
MySQLConn -> IO ()
guardUnconsumed MySQLConn
conn
Command -> (Packet -> IO ()) -> IO ()
writeCommand Command
cmd Packet -> IO ()
os
InputStream Packet -> IO OK
waitCommandReply InputStream Packet
is
{-# INLINE command #-}
waitCommandReply :: InputStream Packet -> IO OK
waitCommandReply :: InputStream Packet -> IO OK
waitCommandReply InputStream Packet
is = do
Packet
p <- InputStream Packet -> IO Packet
readPacket InputStream Packet
is
if | 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
| Packet -> Bool
isOK Packet
p -> forall a. Binary a => Packet -> IO a
decodeFromPacket Packet
p
| Bool
otherwise -> forall e a. Exception e => e -> IO a
throwIO (Packet -> UnexpectedPacket
UnexpectedPacket Packet
p)
{-# INLINE waitCommandReply #-}
waitCommandReplys :: InputStream Packet -> IO [OK]
waitCommandReplys :: InputStream Packet -> IO [OK]
waitCommandReplys InputStream Packet
is = do
Packet
p <- InputStream Packet -> IO Packet
readPacket InputStream Packet
is
if | 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
| Packet -> Bool
isOK Packet
p -> do OK
ok <- forall a. Binary a => Packet -> IO a
decodeFromPacket Packet
p
if OK -> Bool
isThereMore OK
ok
then (OK
ok forall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputStream Packet -> IO [OK]
waitCommandReplys InputStream Packet
is
else forall (m :: * -> *) a. Monad m => a -> m a
return [OK
ok]
| Bool
otherwise -> forall e a. Exception e => e -> IO a
throwIO (Packet -> UnexpectedPacket
UnexpectedPacket Packet
p)
{-# INLINE waitCommandReplys #-}
readPacket :: InputStream Packet -> IO Packet
readPacket :: InputStream Packet -> IO Packet
readPacket InputStream Packet
is = forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream Packet
is forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall e a. Exception e => e -> IO a
throwIO NetworkException
NetworkException)
(\ p :: Packet
p@(Packet Int64
len Word8
_ ByteString
bs) -> if Int64
len forall a. Ord a => a -> a -> Bool
< Int64
16777215 then forall (m :: * -> *) a. Monad m => a -> m a
return Packet
p else Int64 -> [ByteString] -> IO Packet
go Int64
len [ByteString
bs])
where
go :: Int64 -> [ByteString] -> IO Packet
go Int64
len [ByteString]
acc = forall a. InputStream a -> IO (Maybe a)
Stream.read InputStream Packet
is forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall e a. Exception e => e -> IO a
throwIO NetworkException
NetworkException)
(\ (Packet Int64
len' Word8
seqN ByteString
bs) -> do
let len'' :: Int64
len'' = Int64
len forall a. Num a => a -> a -> a
+ Int64
len'
acc' :: [ByteString]
acc' = ByteString
bsforall a. a -> [a] -> [a]
:[ByteString]
acc
if Int64
len' forall a. Ord a => a -> a -> Bool
< Int64
16777215
then forall (m :: * -> *) a. Monad m => a -> m a
return (Int64 -> Word8 -> ByteString -> Packet
Packet Int64
len'' Word8
seqN ([ByteString] -> ByteString
L.concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ [ByteString]
acc'))
else Int64
len'' seq :: forall a b. a -> b -> b
`seq` Int64 -> [ByteString] -> IO Packet
go Int64
len'' [ByteString]
acc'
)
{-# INLINE readPacket #-}
writeCommand :: Command -> (Packet -> IO ()) -> IO ()
writeCommand :: Command -> (Packet -> IO ()) -> IO ()
writeCommand Command
a Packet -> IO ()
writePacket = let bs :: ByteString
bs = Put -> ByteString
Binary.runPut (Command -> Put
putCommand Command
a) in
forall {t}. Int64 -> Word8 -> ByteString -> t -> IO ()
go (forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
L.length ByteString
bs)) Word8
0 ByteString
bs Packet -> IO ()
writePacket
where
go :: Int64 -> Word8 -> ByteString -> t -> IO ()
go Int64
len Word8
seqN ByteString
bs t
writePacket' = do
if Int64
len forall a. Ord a => a -> a -> Bool
< Int64
16777215
then Packet -> IO ()
writePacket (Int64 -> Word8 -> ByteString -> Packet
Packet Int64
len Word8
seqN ByteString
bs)
else do
let (ByteString
bs', ByteString
rest) = Int64 -> ByteString -> (ByteString, ByteString)
L.splitAt Int64
16777215 ByteString
bs
seqN' :: Word8
seqN' = Word8
seqN forall a. Num a => a -> a -> a
+ Word8
1
len' :: Int64
len' = Int64
len forall a. Num a => a -> a -> a
- Int64
16777215
Packet -> IO ()
writePacket (Int64 -> Word8 -> ByteString -> Packet
Packet Int64
16777215 Word8
seqN ByteString
bs')
Word8
seqN' seq :: forall a b. a -> b -> b
`seq` Int64
len' seq :: forall a b. a -> b -> b
`seq` Int64 -> Word8 -> ByteString -> t -> IO ()
go Int64
len' Word8
seqN' ByteString
rest t
writePacket'
{-# INLINE writeCommand #-}
guardUnconsumed :: MySQLConn -> IO ()
guardUnconsumed :: MySQLConn -> IO ()
guardUnconsumed (MySQLConn InputStream Packet
_ Packet -> IO ()
_ IO ()
_ IORef Bool
consumed) = do
Bool
c <- forall a. IORef a -> IO a
readIORef IORef Bool
consumed
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
c (forall e a. Exception e => e -> IO a
throwIO UnconsumedResultSet
UnconsumedResultSet)
{-# INLINE guardUnconsumed #-}
writeIORef' :: IORef a -> a -> IO ()
writeIORef' :: forall a. IORef a -> a -> IO ()
writeIORef' IORef a
ref a
x = a
x seq :: forall a b. a -> b -> b
`seq` forall a. IORef a -> a -> IO ()
writeIORef IORef a
ref a
x
{-# INLINE writeIORef' #-}
data NetworkException = NetworkException deriving (Typeable, Int -> NetworkException -> ShowS
[NetworkException] -> ShowS
NetworkException -> HostName
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
showList :: [NetworkException] -> ShowS
$cshowList :: [NetworkException] -> ShowS
show :: NetworkException -> HostName
$cshow :: NetworkException -> HostName
showsPrec :: Int -> NetworkException -> ShowS
$cshowsPrec :: Int -> NetworkException -> ShowS
Show)
instance Exception NetworkException
data UnconsumedResultSet = UnconsumedResultSet deriving (Typeable, Int -> UnconsumedResultSet -> ShowS
[UnconsumedResultSet] -> ShowS
UnconsumedResultSet -> HostName
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
showList :: [UnconsumedResultSet] -> ShowS
$cshowList :: [UnconsumedResultSet] -> ShowS
show :: UnconsumedResultSet -> HostName
$cshow :: UnconsumedResultSet -> HostName
showsPrec :: Int -> UnconsumedResultSet -> ShowS
$cshowsPrec :: Int -> UnconsumedResultSet -> ShowS
Show)
instance Exception UnconsumedResultSet
data ERRException = ERRException ERR deriving (Typeable, Int -> ERRException -> ShowS
[ERRException] -> ShowS
ERRException -> HostName
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
showList :: [ERRException] -> ShowS
$cshowList :: [ERRException] -> ShowS
show :: ERRException -> HostName
$cshow :: ERRException -> HostName
showsPrec :: Int -> ERRException -> ShowS
$cshowsPrec :: Int -> ERRException -> ShowS
Show)
instance Exception ERRException
data UnexpectedPacket = UnexpectedPacket Packet deriving (Typeable, Int -> UnexpectedPacket -> ShowS
[UnexpectedPacket] -> ShowS
UnexpectedPacket -> HostName
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
showList :: [UnexpectedPacket] -> ShowS
$cshowList :: [UnexpectedPacket] -> ShowS
show :: UnexpectedPacket -> HostName
$cshow :: UnexpectedPacket -> HostName
showsPrec :: Int -> UnexpectedPacket -> ShowS
$cshowsPrec :: Int -> UnexpectedPacket -> ShowS
Show)
instance Exception UnexpectedPacket