Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.Transport
Contents
Description
Network Transport
Synopsis
- data Transport = Transport {}
- data EndPoint = EndPoint {
- receive :: IO Event
- address :: EndPointAddress
- connect :: EndPointAddress -> Reliability -> ConnectHints -> IO (Either (TransportError ConnectErrorCode) Connection)
- newMulticastGroup :: IO (Either (TransportError NewMulticastGroupErrorCode) MulticastGroup)
- resolveMulticastGroup :: MulticastAddress -> IO (Either (TransportError ResolveMulticastGroupErrorCode) MulticastGroup)
- closeEndPoint :: IO ()
- data Connection = Connection {
- send :: [ByteString] -> IO (Either (TransportError SendErrorCode) ())
- close :: IO ()
- data Event
- type ConnectionId = Word64
- data Reliability
- data MulticastGroup = MulticastGroup {
- multicastAddress :: MulticastAddress
- deleteMulticastGroup :: IO ()
- maxMsgSize :: Maybe Int
- multicastSend :: [ByteString] -> IO ()
- multicastSubscribe :: IO ()
- multicastUnsubscribe :: IO ()
- multicastClose :: IO ()
- newtype EndPointAddress = EndPointAddress {}
- newtype MulticastAddress = MulticastAddress {}
- data ConnectHints = ConnectHints {}
- defaultConnectHints :: ConnectHints
- data TransportError error = TransportError error String
- data NewEndPointErrorCode
- data ConnectErrorCode
- data NewMulticastGroupErrorCode
- data ResolveMulticastGroupErrorCode
- data SendErrorCode
- data EventErrorCode
Types
To create a network abstraction layer, use one of the
Network.Transport.*
packages.
Constructors
Transport | |
Fields
|
Network endpoint.
Constructors
EndPoint | |
Fields
|
data Connection Source #
Lightweight connection to an endpoint.
Constructors
Connection | |
Fields
|
Event on an endpoint.
Constructors
Received !ConnectionId [ByteString] | Received a message |
ConnectionClosed !ConnectionId | Connection closed |
ConnectionOpened !ConnectionId Reliability EndPointAddress | Connection opened
|
ReceivedMulticast MulticastAddress [ByteString] | Received multicast |
EndPointClosed | The endpoint got closed (manually, by a call to closeEndPoint or closeTransport) |
ErrorEvent (TransportError EventErrorCode) | An error occurred |
Instances
type ConnectionId = Word64 Source #
Connection data ConnectHintsIDs enable receivers to distinguish one connection from another.
data Reliability Source #
Reliability guarantees of a connection.
Constructors
ReliableOrdered | |
ReliableUnordered | |
Unreliable |
Instances
Generic Reliability Source # | |||||
Defined in Network.Transport Associated Types
| |||||
Show Reliability Source # | |||||
Defined in Network.Transport Methods showsPrec :: Int -> Reliability -> ShowS # show :: Reliability -> String # showList :: [Reliability] -> ShowS # | |||||
Binary Reliability Source # | |||||
Defined in Network.Transport | |||||
Eq Reliability Source # | |||||
Defined in Network.Transport | |||||
type Rep Reliability Source # | |||||
Defined in Network.Transport type Rep Reliability = D1 ('MetaData "Reliability" "Network.Transport" "network-transport-0.5.7-1YdNpZpLcpdHoYUipKag3Y" 'False) (C1 ('MetaCons "ReliableOrdered" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ReliableUnordered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unreliable" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MulticastGroup Source #
Multicast group.
Constructors
MulticastGroup | |
Fields
|
newtype EndPointAddress Source #
EndPointAddress of an endpoint.
Constructors
EndPointAddress | |
Fields |
Instances
Data EndPointAddress Source # | |
Defined in Network.Transport Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndPointAddress -> c EndPointAddress # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndPointAddress # toConstr :: EndPointAddress -> Constr # dataTypeOf :: EndPointAddress -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EndPointAddress) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndPointAddress) # gmapT :: (forall b. Data b => b -> b) -> EndPointAddress -> EndPointAddress # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndPointAddress -> r # gmapQ :: (forall d. Data d => d -> u) -> EndPointAddress -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EndPointAddress -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndPointAddress -> m EndPointAddress # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndPointAddress -> m EndPointAddress # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndPointAddress -> m EndPointAddress # | |
Show EndPointAddress Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> EndPointAddress -> ShowS # show :: EndPointAddress -> String # showList :: [EndPointAddress] -> ShowS # | |
Binary EndPointAddress Source # | |
Defined in Network.Transport Methods put :: EndPointAddress -> Put # get :: Get EndPointAddress # putList :: [EndPointAddress] -> Put # | |
NFData EndPointAddress Source # | |
Defined in Network.Transport Methods rnf :: EndPointAddress -> () # | |
Eq EndPointAddress Source # | |
Defined in Network.Transport Methods (==) :: EndPointAddress -> EndPointAddress -> Bool # (/=) :: EndPointAddress -> EndPointAddress -> Bool # | |
Ord EndPointAddress Source # | |
Defined in Network.Transport Methods compare :: EndPointAddress -> EndPointAddress -> Ordering # (<) :: EndPointAddress -> EndPointAddress -> Bool # (<=) :: EndPointAddress -> EndPointAddress -> Bool # (>) :: EndPointAddress -> EndPointAddress -> Bool # (>=) :: EndPointAddress -> EndPointAddress -> Bool # max :: EndPointAddress -> EndPointAddress -> EndPointAddress # min :: EndPointAddress -> EndPointAddress -> EndPointAddress # | |
Hashable EndPointAddress Source # | |
Defined in Network.Transport |
newtype MulticastAddress Source #
EndPointAddress of a multicast group.
Constructors
MulticastAddress | |
Fields |
Instances
Generic MulticastAddress Source # | |||||
Defined in Network.Transport Associated Types
Methods from :: MulticastAddress -> Rep MulticastAddress x # to :: Rep MulticastAddress x -> MulticastAddress # | |||||
Show MulticastAddress Source # | |||||
Defined in Network.Transport Methods showsPrec :: Int -> MulticastAddress -> ShowS # show :: MulticastAddress -> String # showList :: [MulticastAddress] -> ShowS # | |||||
Binary MulticastAddress Source # | |||||
Defined in Network.Transport Methods put :: MulticastAddress -> Put # get :: Get MulticastAddress # putList :: [MulticastAddress] -> Put # | |||||
Eq MulticastAddress Source # | |||||
Defined in Network.Transport Methods (==) :: MulticastAddress -> MulticastAddress -> Bool # (/=) :: MulticastAddress -> MulticastAddress -> Bool # | |||||
Ord MulticastAddress Source # | |||||
Defined in Network.Transport Methods compare :: MulticastAddress -> MulticastAddress -> Ordering # (<) :: MulticastAddress -> MulticastAddress -> Bool # (<=) :: MulticastAddress -> MulticastAddress -> Bool # (>) :: MulticastAddress -> MulticastAddress -> Bool # (>=) :: MulticastAddress -> MulticastAddress -> Bool # max :: MulticastAddress -> MulticastAddress -> MulticastAddress # min :: MulticastAddress -> MulticastAddress -> MulticastAddress # | |||||
type Rep MulticastAddress Source # | |||||
Defined in Network.Transport type Rep MulticastAddress = D1 ('MetaData "MulticastAddress" "Network.Transport" "network-transport-0.5.7-1YdNpZpLcpdHoYUipKag3Y" 'True) (C1 ('MetaCons "MulticastAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "multicastAddressToByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Hints
defaultConnectHints :: ConnectHints Source #
Default hints for connecting
Error codes
data TransportError error Source #
Errors returned by Network.Transport API functions consist of an error code and a human readable description of the problem
Constructors
TransportError error String |
Instances
(Typeable err, Show err) => Exception (TransportError err) Source # | Although the functions in the transport API never throw TransportErrors (but return them explicitly), application code may want to turn these into exceptions. | ||||
Defined in Network.Transport Methods toException :: TransportError err -> SomeException # fromException :: SomeException -> Maybe (TransportError err) # displayException :: TransportError err -> String # | |||||
Generic (TransportError error) Source # | |||||
Defined in Network.Transport Associated Types
Methods from :: TransportError error -> Rep (TransportError error) x # to :: Rep (TransportError error) x -> TransportError error # | |||||
Show error => Show (TransportError error) Source # | |||||
Defined in Network.Transport Methods showsPrec :: Int -> TransportError error -> ShowS # show :: TransportError error -> String # showList :: [TransportError error] -> ShowS # | |||||
Binary error => Binary (TransportError error) Source # | |||||
Defined in Network.Transport Methods put :: TransportError error -> Put # get :: Get (TransportError error) # putList :: [TransportError error] -> Put # | |||||
Eq error => Eq (TransportError error) Source # | When comparing errors we ignore the human-readable strings | ||||
Defined in Network.Transport Methods (==) :: TransportError error -> TransportError error -> Bool # (/=) :: TransportError error -> TransportError error -> Bool # | |||||
type Rep (TransportError error) Source # | |||||
Defined in Network.Transport type Rep (TransportError error) = D1 ('MetaData "TransportError" "Network.Transport" "network-transport-0.5.7-1YdNpZpLcpdHoYUipKag3Y" 'False) (C1 ('MetaCons "TransportError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 error) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
data NewEndPointErrorCode Source #
Errors during the creation of an endpoint
Constructors
NewEndPointInsufficientResources | Not enough resources |
NewEndPointFailed | Failed for some other reason |
Instances
Show NewEndPointErrorCode Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> NewEndPointErrorCode -> ShowS # show :: NewEndPointErrorCode -> String # showList :: [NewEndPointErrorCode] -> ShowS # | |
Eq NewEndPointErrorCode Source # | |
Defined in Network.Transport Methods (==) :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool # (/=) :: NewEndPointErrorCode -> NewEndPointErrorCode -> Bool # |
data ConnectErrorCode Source #
Connection failure
Constructors
ConnectNotFound | Could not resolve the address |
ConnectInsufficientResources | Insufficient resources (for instance, no more sockets available) |
ConnectTimeout | Timeout |
ConnectFailed | Failed for other reasons (including syntax error) |
Instances
Show ConnectErrorCode Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> ConnectErrorCode -> ShowS # show :: ConnectErrorCode -> String # showList :: [ConnectErrorCode] -> ShowS # | |
Eq ConnectErrorCode Source # | |
Defined in Network.Transport Methods (==) :: ConnectErrorCode -> ConnectErrorCode -> Bool # (/=) :: ConnectErrorCode -> ConnectErrorCode -> Bool # |
data NewMulticastGroupErrorCode Source #
Failure during the creation of a new multicast group
Constructors
NewMulticastGroupInsufficientResources | Insufficient resources |
NewMulticastGroupFailed | Failed for some other reason |
NewMulticastGroupUnsupported | Not all transport implementations support multicast |
Instances
Show NewMulticastGroupErrorCode Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> NewMulticastGroupErrorCode -> ShowS # show :: NewMulticastGroupErrorCode -> String # showList :: [NewMulticastGroupErrorCode] -> ShowS # | |
Eq NewMulticastGroupErrorCode Source # | |
Defined in Network.Transport Methods (==) :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool # (/=) :: NewMulticastGroupErrorCode -> NewMulticastGroupErrorCode -> Bool # |
data ResolveMulticastGroupErrorCode Source #
Failure during the resolution of a multicast group
Constructors
ResolveMulticastGroupNotFound | Multicast group not found |
ResolveMulticastGroupFailed | Failed for some other reason (including syntax error) |
ResolveMulticastGroupUnsupported | Not all transport implementations support multicast |
Instances
Show ResolveMulticastGroupErrorCode Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> ResolveMulticastGroupErrorCode -> ShowS # show :: ResolveMulticastGroupErrorCode -> String # showList :: [ResolveMulticastGroupErrorCode] -> ShowS # | |
Eq ResolveMulticastGroupErrorCode Source # | |
Defined in Network.Transport |
data SendErrorCode Source #
Failure during sending a message
Constructors
SendClosed | Connection was closed |
SendFailed | Send failed for some other reason |
Instances
Show SendErrorCode Source # | |
Defined in Network.Transport Methods showsPrec :: Int -> SendErrorCode -> ShowS # show :: SendErrorCode -> String # showList :: [SendErrorCode] -> ShowS # | |
Eq SendErrorCode Source # | |
Defined in Network.Transport Methods (==) :: SendErrorCode -> SendErrorCode -> Bool # (/=) :: SendErrorCode -> SendErrorCode -> Bool # |
data EventErrorCode Source #
Error codes used when reporting errors to endpoints (through receive)
Constructors
EventEndPointFailed | Failure of the entire endpoint |
EventTransportFailed | Transport-wide fatal error |
EventConnectionLost EndPointAddress | We lost connection to another endpoint Although Network.Transport provides multiple independent lightweight connections between endpoints, those connections cannot fail independently: once one connection has failed, all connections, in both directions, must now be considered to have failed; they fail as a "bundle" of connections, with only a single "bundle" of connections per endpoint at any point in time. That is, suppose there are multiple connections in either direction between endpoints A and B, and A receives a notification that it has lost contact with B. Then A must not be able to send any further messages to B on existing connections. Although B may not realize immediately that its connection to A has been broken, messages sent by B on existing connections should not be delivered, and B must eventually get an EventConnectionLost message, too. Moreover, this event must be posted before A has successfully reconnected (in other words, if B notices a reconnection attempt from A, it must post the EventConnectionLost before acknowledging the connection from A) so that B will not receive events about new connections or incoming messages from A without realizing that it got disconnected. If B attempts to establish another connection to A before it realized that it got disconnected from A then it's okay for this connection attempt to fail, and the EventConnectionLost to be posted at that point, or for the EventConnectionLost to be posted and for the new connection to be considered the first connection of the "new bundle". |
Instances
Generic EventErrorCode Source # | |||||
Defined in Network.Transport Associated Types
Methods from :: EventErrorCode -> Rep EventErrorCode x # to :: Rep EventErrorCode x -> EventErrorCode # | |||||
Show EventErrorCode Source # | |||||
Defined in Network.Transport Methods showsPrec :: Int -> EventErrorCode -> ShowS # show :: EventErrorCode -> String # showList :: [EventErrorCode] -> ShowS # | |||||
Binary EventErrorCode Source # | |||||
Defined in Network.Transport Methods put :: EventErrorCode -> Put # get :: Get EventErrorCode # putList :: [EventErrorCode] -> Put # | |||||
Eq EventErrorCode Source # | |||||
Defined in Network.Transport Methods (==) :: EventErrorCode -> EventErrorCode -> Bool # (/=) :: EventErrorCode -> EventErrorCode -> Bool # | |||||
type Rep EventErrorCode Source # | |||||
Defined in Network.Transport type Rep EventErrorCode = D1 ('MetaData "EventErrorCode" "Network.Transport" "network-transport-0.5.7-1YdNpZpLcpdHoYUipKag3Y" 'False) (C1 ('MetaCons "EventEndPointFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventTransportFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventConnectionLost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress)))) |