{-# LANGUAGE DeriveGeneric #-}
module Network.Transport
(
Transport(..)
, EndPoint(..)
, Connection(..)
, Event(..)
, ConnectionId
, Reliability(..)
, MulticastGroup(..)
, EndPointAddress(..)
, MulticastAddress(..)
, ConnectHints(..)
, defaultConnectHints
, TransportError(..)
, NewEndPointErrorCode(..)
, ConnectErrorCode(..)
, NewMulticastGroupErrorCode(..)
, ResolveMulticastGroupErrorCode(..)
, SendErrorCode(..)
, EventErrorCode(..)
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS (copy)
import qualified Data.ByteString.Char8 as BSC (unpack)
import Control.DeepSeq (NFData(rnf))
import Control.Exception (Exception)
import Control.Applicative ((<$>))
import Data.Typeable (Typeable)
import Data.Binary (Binary(..))
import Data.Hashable
import Data.Word (Word64)
import Data.Data (Data)
import GHC.Generics (Generic)
data Transport = Transport {
Transport
-> IO (Either (TransportError NewEndPointErrorCode) EndPoint)
newEndPoint :: IO (Either (TransportError NewEndPointErrorCode) EndPoint)
, Transport -> IO ()
closeTransport :: IO ()
}
data EndPoint = EndPoint {
EndPoint -> IO Event
receive :: IO Event
, EndPoint -> EndPointAddress
address :: EndPointAddress
, EndPoint
-> EndPointAddress
-> Reliability
-> ConnectHints
-> IO (Either (TransportError ConnectErrorCode) Connection)
connect :: EndPointAddress -> Reliability -> ConnectHints -> IO (Either (TransportError ConnectErrorCode) Connection)
, EndPoint
-> IO
(Either (TransportError NewMulticastGroupErrorCode) MulticastGroup)
newMulticastGroup :: IO (Either (TransportError NewMulticastGroupErrorCode) MulticastGroup)
, EndPoint
-> MulticastAddress
-> IO
(Either
(TransportError ResolveMulticastGroupErrorCode) MulticastGroup)
resolveMulticastGroup :: MulticastAddress -> IO (Either (TransportError ResolveMulticastGroupErrorCode) MulticastGroup)
, EndPoint -> IO ()
closeEndPoint :: IO ()
}
data Connection = Connection {
Connection
-> [ByteString] -> IO (Either (TransportError SendErrorCode) ())
send :: [ByteString] -> IO (Either (TransportError SendErrorCode) ())
, Connection -> IO ()
close :: IO ()
}
data Event =
Received {-# UNPACK #-} !ConnectionId [ByteString]
| ConnectionClosed {-# UNPACK #-} !ConnectionId
| ConnectionOpened {-# UNPACK #-} !ConnectionId Reliability EndPointAddress
| ReceivedMulticast MulticastAddress [ByteString]
| EndPointClosed
| ErrorEvent (TransportError EventErrorCode)
deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, Event -> Event -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq, forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic)
instance Binary Event
type ConnectionId = Word64
data Reliability =
ReliableOrdered
| ReliableUnordered
| Unreliable
deriving (Int -> Reliability -> ShowS
[Reliability] -> ShowS
Reliability -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Reliability] -> ShowS
$cshowList :: [Reliability] -> ShowS
show :: Reliability -> String
$cshow :: Reliability -> String
showsPrec :: Int -> Reliability -> ShowS
$cshowsPrec :: Int -> Reliability -> ShowS
Show, Reliability -> Reliability -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Reliability -> Reliability -> Bool
$c/= :: Reliability -> Reliability -> Bool
== :: Reliability -> Reliability -> Bool
$c== :: Reliability -> Reliability -> Bool
Eq, Typeable, forall x. Rep Reliability x -> Reliability
forall x. Reliability -> Rep Reliability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Reliability x -> Reliability
$cfrom :: forall x. Reliability -> Rep Reliability x
Generic)
instance Binary Reliability
data MulticastGroup = MulticastGroup {
MulticastGroup -> MulticastAddress
multicastAddress :: MulticastAddress
, MulticastGroup -> IO ()
deleteMulticastGroup :: IO ()
, MulticastGroup -> Maybe Int
maxMsgSize :: Maybe Int
, MulticastGroup -> [ByteString] -> IO ()
multicastSend :: [ByteString] -> IO ()
, MulticastGroup -> IO ()
multicastSubscribe :: IO ()
, MulticastGroup -> IO ()
multicastUnsubscribe :: IO ()
, MulticastGroup -> IO ()
multicastClose :: IO ()
}
newtype EndPointAddress = EndPointAddress { EndPointAddress -> ByteString
endPointAddressToByteString :: ByteString }
deriving (EndPointAddress -> EndPointAddress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndPointAddress -> EndPointAddress -> Bool
$c/= :: EndPointAddress -> EndPointAddress -> Bool
== :: EndPointAddress -> EndPointAddress -> Bool
$c== :: EndPointAddress -> EndPointAddress -> Bool
Eq, Eq EndPointAddress
EndPointAddress -> EndPointAddress -> Bool
EndPointAddress -> EndPointAddress -> Ordering
EndPointAddress -> EndPointAddress -> EndPointAddress
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EndPointAddress -> EndPointAddress -> EndPointAddress
$cmin :: EndPointAddress -> EndPointAddress -> EndPointAddress
max :: EndPointAddress -> EndPointAddress -> EndPointAddress
$cmax :: EndPointAddress -> EndPointAddress -> EndPointAddress
>= :: EndPointAddress -> EndPointAddress -> Bool
$c>= :: EndPointAddress -> EndPointAddress -> Bool
> :: EndPointAddress -> EndPointAddress -> Bool
$c> :: EndPointAddress -> EndPointAddress -> Bool
<= :: EndPointAddress -> EndPointAddress -> Bool
$c<= :: EndPointAddress -> EndPointAddress -> Bool
< :: EndPointAddress -> EndPointAddress -> Bool
$c< :: EndPointAddress -> EndPointAddress -> Bool
compare :: EndPointAddress -> EndPointAddress -> Ordering
$ccompare :: EndPointAddress -> EndPointAddress -> Ordering
Ord, Typeable, Typeable EndPointAddress
EndPointAddress -> DataType
EndPointAddress -> Constr
(forall b. Data b => b -> b) -> EndPointAddress -> EndPointAddress
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> EndPointAddress -> u
forall u. (forall d. Data d => d -> u) -> EndPointAddress -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EndPointAddress
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EndPointAddress -> c EndPointAddress
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EndPointAddress)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EndPointAddress)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> EndPointAddress -> m EndPointAddress
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> EndPointAddress -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> EndPointAddress -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> EndPointAddress -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EndPointAddress -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r
gmapT :: (forall b. Data b => b -> b) -> EndPointAddress -> EndPointAddress
$cgmapT :: (forall b. Data b => b -> b) -> EndPointAddress -> EndPointAddress
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EndPointAddress)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EndPointAddress)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EndPointAddress)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EndPointAddress)
dataTypeOf :: EndPointAddress -> DataType
$cdataTypeOf :: EndPointAddress -> DataType
toConstr :: EndPointAddress -> Constr
$ctoConstr :: EndPointAddress -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EndPointAddress
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EndPointAddress
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EndPointAddress -> c EndPointAddress
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EndPointAddress -> c EndPointAddress
Data, Eq EndPointAddress
Int -> EndPointAddress -> Int
EndPointAddress -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: EndPointAddress -> Int
$chash :: EndPointAddress -> Int
hashWithSalt :: Int -> EndPointAddress -> Int
$chashWithSalt :: Int -> EndPointAddress -> Int
Hashable)
instance Binary EndPointAddress where
put :: EndPointAddress -> Put
put = forall t. Binary t => t -> Put
put forall b c a. (b -> c) -> (a -> b) -> a -> c
. EndPointAddress -> ByteString
endPointAddressToByteString
get :: Get EndPointAddress
get = ByteString -> EndPointAddress
EndPointAddress forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BS.copy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
instance Show EndPointAddress where
show :: EndPointAddress -> String
show = ByteString -> String
BSC.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. EndPointAddress -> ByteString
endPointAddressToByteString
instance NFData EndPointAddress where rnf :: EndPointAddress -> ()
rnf EndPointAddress
x = EndPointAddress
x seq :: forall a b. a -> b -> b
`seq` ()
newtype MulticastAddress = MulticastAddress { MulticastAddress -> ByteString
multicastAddressToByteString :: ByteString }
deriving (MulticastAddress -> MulticastAddress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MulticastAddress -> MulticastAddress -> Bool
$c/= :: MulticastAddress -> MulticastAddress -> Bool
== :: MulticastAddress -> MulticastAddress -> Bool
$c== :: MulticastAddress -> MulticastAddress -> Bool
Eq, Eq MulticastAddress
MulticastAddress -> MulticastAddress -> Bool
MulticastAddress -> MulticastAddress -> Ordering
MulticastAddress -> MulticastAddress -> MulticastAddress
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MulticastAddress -> MulticastAddress -> MulticastAddress
$cmin :: MulticastAddress -> MulticastAddress -> MulticastAddress
max :: MulticastAddress -> MulticastAddress -> MulticastAddress
$cmax :: MulticastAddress -> MulticastAddress -> MulticastAddress
>= :: MulticastAddress -> MulticastAddress -> Bool
$c>= :: MulticastAddress -> MulticastAddress -> Bool
> :: MulticastAddress -> MulticastAddress -> Bool
$c> :: MulticastAddress -> MulticastAddress -> Bool
<= :: MulticastAddress -> MulticastAddress -> Bool
$c<= :: MulticastAddress -> MulticastAddress -> Bool
< :: MulticastAddress -> MulticastAddress -> Bool
$c< :: MulticastAddress -> MulticastAddress -> Bool
compare :: MulticastAddress -> MulticastAddress -> Ordering
$ccompare :: MulticastAddress -> MulticastAddress -> Ordering
Ord, forall x. Rep MulticastAddress x -> MulticastAddress
forall x. MulticastAddress -> Rep MulticastAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MulticastAddress x -> MulticastAddress
$cfrom :: forall x. MulticastAddress -> Rep MulticastAddress x
Generic)
instance Binary MulticastAddress
instance Show MulticastAddress where
show :: MulticastAddress -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. MulticastAddress -> ByteString
multicastAddressToByteString
data ConnectHints = ConnectHints {
ConnectHints -> Maybe Int
connectTimeout :: Maybe Int
}
defaultConnectHints :: ConnectHints
defaultConnectHints :: ConnectHints
defaultConnectHints = ConnectHints {
connectTimeout :: Maybe Int
connectTimeout = forall a. Maybe a
Nothing
}
data TransportError error = TransportError error String
deriving (Int -> TransportError error -> ShowS
forall error. Show error => Int -> TransportError error -> ShowS
forall error. Show error => [TransportError error] -> ShowS
forall error. Show error => TransportError error -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransportError error] -> ShowS
$cshowList :: forall error. Show error => [TransportError error] -> ShowS
show :: TransportError error -> String
$cshow :: forall error. Show error => TransportError error -> String
showsPrec :: Int -> TransportError error -> ShowS
$cshowsPrec :: forall error. Show error => Int -> TransportError error -> ShowS
Show, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall error x.
Rep (TransportError error) x -> TransportError error
forall error x.
TransportError error -> Rep (TransportError error) x
$cto :: forall error x.
Rep (TransportError error) x -> TransportError error
$cfrom :: forall error x.
TransportError error -> Rep (TransportError error) x
Generic)
instance (Binary error) => Binary (TransportError error)
instance (Typeable err, Show err) => Exception (TransportError err)
instance Eq error => Eq (TransportError error) where
TransportError error
err1 String
_ == :: TransportError error -> TransportError error -> Bool
== TransportError error
err2 String
_ = error
err1 forall a. Eq a => a -> a -> Bool
== error
err2
data NewEndPointErrorCode =
NewEndPointInsufficientResources
| NewEndPointFailed
deriving (Int -> NewEndPointErrorCode -> ShowS
[NewEndPointErrorCode] -> ShowS
NewEndPointErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewEndPointErrorCode] -> ShowS
$cshowList :: [NewEndPointErrorCode] -> ShowS
show :: NewEndPointErrorCode -> String
$cshow :: NewEndPointErrorCode -> String
showsPrec :: Int -> NewEndPointErrorCode -> ShowS
$cshowsPrec :: Int -> NewEndPointErrorCode -> ShowS
Show, Typeable, NewEndPointErrorCode -> NewEndPointErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool
$c/= :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool
== :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool
$c== :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool
Eq)
data ConnectErrorCode =
ConnectNotFound
| ConnectInsufficientResources
| ConnectTimeout
| ConnectFailed
deriving (Int -> ConnectErrorCode -> ShowS
[ConnectErrorCode] -> ShowS
ConnectErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectErrorCode] -> ShowS
$cshowList :: [ConnectErrorCode] -> ShowS
show :: ConnectErrorCode -> String
$cshow :: ConnectErrorCode -> String
showsPrec :: Int -> ConnectErrorCode -> ShowS
$cshowsPrec :: Int -> ConnectErrorCode -> ShowS
Show, Typeable, ConnectErrorCode -> ConnectErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectErrorCode -> ConnectErrorCode -> Bool
$c/= :: ConnectErrorCode -> ConnectErrorCode -> Bool
== :: ConnectErrorCode -> ConnectErrorCode -> Bool
$c== :: ConnectErrorCode -> ConnectErrorCode -> Bool
Eq)
data NewMulticastGroupErrorCode =
NewMulticastGroupInsufficientResources
| NewMulticastGroupFailed
| NewMulticastGroupUnsupported
deriving (Int -> NewMulticastGroupErrorCode -> ShowS
[NewMulticastGroupErrorCode] -> ShowS
NewMulticastGroupErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewMulticastGroupErrorCode] -> ShowS
$cshowList :: [NewMulticastGroupErrorCode] -> ShowS
show :: NewMulticastGroupErrorCode -> String
$cshow :: NewMulticastGroupErrorCode -> String
showsPrec :: Int -> NewMulticastGroupErrorCode -> ShowS
$cshowsPrec :: Int -> NewMulticastGroupErrorCode -> ShowS
Show, Typeable, NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool
$c/= :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool
== :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool
$c== :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool
Eq)
data ResolveMulticastGroupErrorCode =
ResolveMulticastGroupNotFound
| ResolveMulticastGroupFailed
| ResolveMulticastGroupUnsupported
deriving (Int -> ResolveMulticastGroupErrorCode -> ShowS
[ResolveMulticastGroupErrorCode] -> ShowS
ResolveMulticastGroupErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolveMulticastGroupErrorCode] -> ShowS
$cshowList :: [ResolveMulticastGroupErrorCode] -> ShowS
show :: ResolveMulticastGroupErrorCode -> String
$cshow :: ResolveMulticastGroupErrorCode -> String
showsPrec :: Int -> ResolveMulticastGroupErrorCode -> ShowS
$cshowsPrec :: Int -> ResolveMulticastGroupErrorCode -> ShowS
Show, Typeable, ResolveMulticastGroupErrorCode
-> ResolveMulticastGroupErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolveMulticastGroupErrorCode
-> ResolveMulticastGroupErrorCode -> Bool
$c/= :: ResolveMulticastGroupErrorCode
-> ResolveMulticastGroupErrorCode -> Bool
== :: ResolveMulticastGroupErrorCode
-> ResolveMulticastGroupErrorCode -> Bool
$c== :: ResolveMulticastGroupErrorCode
-> ResolveMulticastGroupErrorCode -> Bool
Eq)
data SendErrorCode =
SendClosed
| SendFailed
deriving (Int -> SendErrorCode -> ShowS
[SendErrorCode] -> ShowS
SendErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendErrorCode] -> ShowS
$cshowList :: [SendErrorCode] -> ShowS
show :: SendErrorCode -> String
$cshow :: SendErrorCode -> String
showsPrec :: Int -> SendErrorCode -> ShowS
$cshowsPrec :: Int -> SendErrorCode -> ShowS
Show, Typeable, SendErrorCode -> SendErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendErrorCode -> SendErrorCode -> Bool
$c/= :: SendErrorCode -> SendErrorCode -> Bool
== :: SendErrorCode -> SendErrorCode -> Bool
$c== :: SendErrorCode -> SendErrorCode -> Bool
Eq)
data EventErrorCode =
EventEndPointFailed
| EventTransportFailed
| EventConnectionLost EndPointAddress
deriving (Int -> EventErrorCode -> ShowS
[EventErrorCode] -> ShowS
EventErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventErrorCode] -> ShowS
$cshowList :: [EventErrorCode] -> ShowS
show :: EventErrorCode -> String
$cshow :: EventErrorCode -> String
showsPrec :: Int -> EventErrorCode -> ShowS
$cshowsPrec :: Int -> EventErrorCode -> ShowS
Show, Typeable, EventErrorCode -> EventErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventErrorCode -> EventErrorCode -> Bool
$c/= :: EventErrorCode -> EventErrorCode -> Bool
== :: EventErrorCode -> EventErrorCode -> Bool
$c== :: EventErrorCode -> EventErrorCode -> Bool
Eq, forall x. Rep EventErrorCode x -> EventErrorCode
forall x. EventErrorCode -> Rep EventErrorCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EventErrorCode x -> EventErrorCode
$cfrom :: forall x. EventErrorCode -> Rep EventErrorCode x
Generic)
instance Binary EventErrorCode