network-transport-0.5.6: Network abstraction layer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Transport

Description

Network Transport

Synopsis

Types

data Transport Source #

To create a network abstraction layer, use one of the Network.Transport.* packages.

Constructors

Transport 

Fields

data EndPoint Source #

Network endpoint.

Constructors

EndPoint 

Fields

data Connection Source #

Lightweight connection to an endpoint.

Constructors

Connection 

Fields

data Event Source #

Event on an endpoint.

Constructors

Received !ConnectionId [ByteString]

Received a message

ConnectionClosed !ConnectionId

Connection closed

ConnectionOpened !ConnectionId Reliability EndPointAddress

Connection opened

ConnectionIds need not be allocated contiguously.

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

Instances details
Generic Event Source # 
Instance details

Defined in Network.Transport

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Show Event Source # 
Instance details

Defined in Network.Transport

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Binary Event Source # 
Instance details

Defined in Network.Transport

Methods

put :: Event -> Put #

get :: Get Event #

putList :: [Event] -> Put #

Eq Event Source # 
Instance details

Defined in Network.Transport

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

type Rep Event Source # 
Instance details

Defined in Network.Transport

type Rep Event = D1 ('MetaData "Event" "Network.Transport" "network-transport-0.5.6-4WmRwHnr2PED3ASf68u0Pm" 'False) ((C1 ('MetaCons "Received" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ConnectionId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString])) :+: (C1 ('MetaCons "ConnectionClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ConnectionId)) :+: C1 ('MetaCons "ConnectionOpened" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ConnectionId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Reliability) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress))))) :+: (C1 ('MetaCons "ReceivedMulticast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MulticastAddress) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString])) :+: (C1 ('MetaCons "EndPointClosed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TransportError EventErrorCode))))))

type ConnectionId = Word64 Source #

Connection data ConnectHintsIDs enable receivers to distinguish one connection from another.

data Reliability Source #

Reliability guarantees of a connection.

Instances

Instances details
Generic Reliability Source # 
Instance details

Defined in Network.Transport

Associated Types

type Rep Reliability :: Type -> Type #

Show Reliability Source # 
Instance details

Defined in Network.Transport

Binary Reliability Source # 
Instance details

Defined in Network.Transport

Eq Reliability Source # 
Instance details

Defined in Network.Transport

type Rep Reliability Source # 
Instance details

Defined in Network.Transport

type Rep Reliability = D1 ('MetaData "Reliability" "Network.Transport" "network-transport-0.5.6-4WmRwHnr2PED3ASf68u0Pm" '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.

Instances

Instances details
Data EndPointAddress Source # 
Instance details

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 # 
Instance details

Defined in Network.Transport

Binary EndPointAddress Source # 
Instance details

Defined in Network.Transport

NFData EndPointAddress Source # 
Instance details

Defined in Network.Transport

Methods

rnf :: EndPointAddress -> () #

Eq EndPointAddress Source # 
Instance details

Defined in Network.Transport

Ord EndPointAddress Source # 
Instance details

Defined in Network.Transport

Hashable EndPointAddress Source # 
Instance details

Defined in Network.Transport

newtype MulticastAddress Source #

EndPointAddress of a multicast group.

Instances

Instances details
Generic MulticastAddress Source # 
Instance details

Defined in Network.Transport

Associated Types

type Rep MulticastAddress :: Type -> Type #

Show MulticastAddress Source # 
Instance details

Defined in Network.Transport

Binary MulticastAddress Source # 
Instance details

Defined in Network.Transport

Eq MulticastAddress Source # 
Instance details

Defined in Network.Transport

Ord MulticastAddress Source # 
Instance details

Defined in Network.Transport

type Rep MulticastAddress Source # 
Instance details

Defined in Network.Transport

type Rep MulticastAddress = D1 ('MetaData "MulticastAddress" "Network.Transport" "network-transport-0.5.6-4WmRwHnr2PED3ASf68u0Pm" 'True) (C1 ('MetaCons "MulticastAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "multicastAddressToByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Hints

data ConnectHints Source #

Hints used by connect

Constructors

ConnectHints 

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

Instances details
(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.

Instance details

Defined in Network.Transport

Generic (TransportError error) Source # 
Instance details

Defined in Network.Transport

Associated Types

type Rep (TransportError error) :: Type -> Type #

Methods

from :: TransportError error -> Rep (TransportError error) x #

to :: Rep (TransportError error) x -> TransportError error #

Show error => Show (TransportError error) Source # 
Instance details

Defined in Network.Transport

Methods

showsPrec :: Int -> TransportError error -> ShowS #

show :: TransportError error -> String #

showList :: [TransportError error] -> ShowS #

Binary error => Binary (TransportError error) Source # 
Instance details

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

Instance details

Defined in Network.Transport

Methods

(==) :: TransportError error -> TransportError error -> Bool #

(/=) :: TransportError error -> TransportError error -> Bool #

type Rep (TransportError error) Source # 
Instance details

Defined in Network.Transport

type Rep (TransportError error) = D1 ('MetaData "TransportError" "Network.Transport" "network-transport-0.5.6-4WmRwHnr2PED3ASf68u0Pm" '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

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)

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

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

data SendErrorCode Source #

Failure during sending a message

Constructors

SendClosed

Connection was closed

SendFailed

Send failed for some other reason

Instances

Instances details
Show SendErrorCode Source # 
Instance details

Defined in Network.Transport

Eq SendErrorCode Source # 
Instance details

Defined in Network.Transport

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

Instances details
Generic EventErrorCode Source # 
Instance details

Defined in Network.Transport

Associated Types

type Rep EventErrorCode :: Type -> Type #

Show EventErrorCode Source # 
Instance details

Defined in Network.Transport

Binary EventErrorCode Source # 
Instance details

Defined in Network.Transport

Eq EventErrorCode Source # 
Instance details

Defined in Network.Transport

type Rep EventErrorCode Source # 
Instance details

Defined in Network.Transport

type Rep EventErrorCode = D1 ('MetaData "EventErrorCode" "Network.Transport" "network-transport-0.5.6-4WmRwHnr2PED3ASf68u0Pm" '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))))