Safe Haskell | None |
---|---|
Language | Haskell2010 |
Module exports interface for running a node over a socket over TCP / IP.
Synopsis
- data ConnectionTable (m :: Type -> Type) addr
- data ConnectionTableRef
- data ValencyCounter (m :: Type -> Type)
- data NetworkMutableState addr = NetworkMutableState {
- nmsConnectionTable :: ConnectionTable IO addr
- nmsPeerStates :: StrictTVar IO (PeerStates IO addr)
- data SomeResponderApplication addr bytes (m :: Type -> Type) b where
- SomeResponderApplication :: forall (muxMode :: Mode) addr bytes (m :: Type -> Type) a b. HasResponder muxMode ~ 'True => OuroborosApplicationWithMinimalCtx muxMode addr bytes m a b -> SomeResponderApplication addr bytes m b
- newNetworkMutableState :: IO (NetworkMutableState addr)
- newNetworkMutableStateSTM :: STM (NetworkMutableState addr)
- cleanNetworkMutableState :: NetworkMutableState addr -> IO ()
- data AcceptedConnectionsLimit = AcceptedConnectionsLimit {}
- data ConnectionId addr = ConnectionId {
- localAddress :: !addr
- remoteAddress :: !addr
- withServerNode :: forall vNumber vData t fd addr b. (Ord vNumber, Typeable vNumber, Show vNumber, Ord addr) => Snocket IO fd addr -> MakeBearer IO fd -> (fd -> addr -> IO ()) -> NetworkServerTracers addr vNumber -> NetworkMutableState addr -> AcceptedConnectionsLimit -> addr -> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString -> ProtocolTimeLimits (Handshake vNumber Term) -> VersionDataCodec Term vNumber vData -> HandshakeCallbacks vData -> Versions vNumber vData (SomeResponderApplication addr ByteString IO b) -> ErrorPolicies -> (addr -> Async Void -> IO t) -> IO t
- withServerNode' :: forall vNumber vData t fd addr b. (Ord vNumber, Typeable vNumber, Show vNumber, Ord addr) => Snocket IO fd addr -> MakeBearer IO fd -> NetworkServerTracers addr vNumber -> NetworkMutableState addr -> AcceptedConnectionsLimit -> fd -> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString -> ProtocolTimeLimits (Handshake vNumber Term) -> VersionDataCodec Term vNumber vData -> HandshakeCallbacks vData -> Versions vNumber vData (SomeResponderApplication addr ByteString IO b) -> ErrorPolicies -> (addr -> Async Void -> IO t) -> IO t
- data ConnectToArgs fd addr vNumber vData = ConnectToArgs {
- ctaHandshakeCodec :: Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString
- ctaHandshakeTimeLimits :: ProtocolTimeLimits (Handshake vNumber Term)
- ctaVersionDataCodec :: VersionDataCodec Term vNumber vData
- ctaConnectTracers :: NetworkConnectTracers addr vNumber
- ctaHandshakeCallbacks :: HandshakeCallbacks vData
- connectToNode :: forall (muxMode :: Mode) vNumber vData fd addr a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) => Snocket IO fd addr -> MakeBearer IO fd -> ConnectToArgs fd addr vNumber vData -> (fd -> IO ()) -> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) -> Maybe addr -> addr -> IO (Either SomeException (Either a b))
- connectToNodeWithMux :: forall (muxMode :: Mode) vNumber vData fd addr a b x. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) => Snocket IO fd addr -> MakeBearer IO fd -> ConnectToArgs fd addr vNumber vData -> (fd -> IO ()) -> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) -> Maybe addr -> addr -> (ConnectionId addr -> vNumber -> vData -> OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b -> Mux muxMode IO -> Async () -> IO x) -> IO x
- connectToNodeSocket :: forall (muxMode :: Mode) vNumber vData a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) => IOManager -> ConnectToArgs Socket SockAddr vNumber vData -> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode SockAddr ByteString IO a b) -> Socket -> IO (Either SomeException (Either a b))
- connectToNode' :: forall (muxMode :: Mode) vNumber vData fd addr a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) => Snocket IO fd addr -> MakeBearer IO fd -> ConnectToArgs fd addr vNumber vData -> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) -> fd -> IO (Either SomeException (Either a b))
- connectToNodeWithMux' :: forall (muxMode :: Mode) vNumber vData fd addr a b x. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) => Snocket IO fd addr -> MakeBearer IO fd -> ConnectToArgs fd addr vNumber vData -> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) -> fd -> (ConnectionId addr -> vNumber -> vData -> OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b -> Mux muxMode IO -> Async () -> IO x) -> IO x
- configureSocket :: Socket -> Maybe SockAddr -> IO ()
- configureSystemdSocket :: Tracer IO SystemdSocketTracer -> Socket -> SockAddr -> IO ()
- data SystemdSocketTracer = SocketOptionNotSet SocketOption
- data NetworkConnectTracers addr vNumber = NetworkConnectTracers {
- nctMuxTracer :: Tracer IO (WithBearer (ConnectionId addr) Trace)
- nctHandshakeTracer :: Tracer IO (WithBearer (ConnectionId addr) (TraceSendRecv (Handshake vNumber Term)))
- nullNetworkConnectTracers :: NetworkConnectTracers addr vNumber
- debuggingNetworkConnectTracers :: (Show addr, Show vNumber) => NetworkConnectTracers addr vNumber
- data NetworkServerTracers addr vNumber = NetworkServerTracers {
- nstMuxTracer :: Tracer IO (WithBearer (ConnectionId addr) Trace)
- nstHandshakeTracer :: Tracer IO (WithBearer (ConnectionId addr) (TraceSendRecv (Handshake vNumber Term)))
- nstErrorPolicyTracer :: Tracer IO (WithAddr addr ErrorPolicyTrace)
- nstAcceptPolicyTracer :: Tracer IO AcceptConnectionsPolicyTrace
- nullNetworkServerTracers :: NetworkServerTracers addr vNumber
- debuggingNetworkServerTracers :: (Show addr, Show vNumber) => NetworkServerTracers addr vNumber
- data AcceptConnectionsPolicyTrace
- fromSnocket :: forall fd addr. Ord addr => ConnectionTable IO addr -> Snocket IO fd addr -> fd -> IO (Socket addr fd)
- beginConnection :: forall vNumber vData addr st fd. (Ord vNumber, Typeable vNumber, Show vNumber) => MakeBearer IO fd -> Tracer IO (WithBearer (ConnectionId addr) Trace) -> Tracer IO (WithBearer (ConnectionId addr) (TraceSendRecv (Handshake vNumber Term))) -> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString -> ProtocolTimeLimits (Handshake vNumber Term) -> VersionDataCodec Term vNumber vData -> HandshakeCallbacks vData -> (Time -> addr -> st -> STM (AcceptConnection st vNumber vData addr IO ByteString)) -> BeginConnection addr fd st ()
- data HandshakeCallbacks vData = HandshakeCallbacks {}
- data PeerStates (m :: Type -> Type) addr
- newConnectionTable :: MonadSTM m => m (ConnectionTable m addr)
- refConnection :: (MonadSTM m, Ord addr) => ConnectionTable m addr -> addr -> ConnectionDirection -> ValencyCounter m -> m ConnectionTableRef
- addConnection :: forall (m :: Type -> Type) addr. (MonadSTM m, Ord addr) => ConnectionTable m addr -> addr -> addr -> ConnectionDirection -> Maybe (ValencyCounter m) -> STM m ()
- removeConnection :: (MonadSTM m, Ord addr) => ConnectionTable m addr -> addr -> addr -> ConnectionDirection -> m ()
- newValencyCounter :: forall (m :: Type -> Type) addr. MonadSTM m => ConnectionTable m addr -> Int -> STM m (ValencyCounter m)
- addValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m ()
- remValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m ()
- waitValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m ()
- readValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m Int
- sockAddrFamily :: SockAddr -> Family
High level socket interface
data ConnectionTable (m :: Type -> Type) addr Source #
data ConnectionTableRef Source #
ConnectionTableCreate | No connection to peer exists, attempt to create one. |
ConnectionTableExist | A connection to the peer existed, either from another subscriber or the peer opened one towards us. |
ConnectionTableDuplicate | This subscriber already has counted a connection to this peer. It must try another target. |
Instances
Show ConnectionTableRef Source # | |
Defined in Ouroboros.Network.Server.ConnectionTable showsPrec :: Int -> ConnectionTableRef -> ShowS # show :: ConnectionTableRef -> String # showList :: [ConnectionTableRef] -> ShowS # |
data ValencyCounter (m :: Type -> Type) Source #
ValencyCounter represents how many active connections we have towards a given peer. It starts out with a positive value representing a desired number of connections for a specific subscription worker. It can become negative, for example if a peer opens multiple connections to us. The vcId is unique per ConnectionTable and ensures that we won't count the same connection twice.
Instances
Eq (ValencyCounter m) Source # | |
Defined in Ouroboros.Network.Server.ConnectionTable (==) :: ValencyCounter m -> ValencyCounter m -> Bool # (/=) :: ValencyCounter m -> ValencyCounter m -> Bool # | |
Ord (ValencyCounter m) Source # | |
Defined in Ouroboros.Network.Server.ConnectionTable compare :: ValencyCounter m -> ValencyCounter m -> Ordering # (<) :: ValencyCounter m -> ValencyCounter m -> Bool # (<=) :: ValencyCounter m -> ValencyCounter m -> Bool # (>) :: ValencyCounter m -> ValencyCounter m -> Bool # (>=) :: ValencyCounter m -> ValencyCounter m -> Bool # max :: ValencyCounter m -> ValencyCounter m -> ValencyCounter m # min :: ValencyCounter m -> ValencyCounter m -> ValencyCounter m # |
data NetworkMutableState addr Source #
Mutable state maintained by the network component.
NetworkMutableState | |
|
data SomeResponderApplication addr bytes (m :: Type -> Type) b where Source #
Wrapper for OuroborosResponderApplication and OuroborosInitiatorAndResponderApplication.
SomeResponderApplication :: forall (muxMode :: Mode) addr bytes (m :: Type -> Type) a b. HasResponder muxMode ~ 'True => OuroborosApplicationWithMinimalCtx muxMode addr bytes m a b -> SomeResponderApplication addr bytes m b |
newNetworkMutableState :: IO (NetworkMutableState addr) Source #
newNetworkMutableStateSTM :: STM (NetworkMutableState addr) Source #
cleanNetworkMutableState :: NetworkMutableState addr -> IO () Source #
Clean PeerStates
within NetworkMutableState
every 200s
data AcceptedConnectionsLimit Source #
Policy which governs how to limit the number of accepted connections.
AcceptedConnectionsLimit | |
|
Instances
data ConnectionId addr Source #
Connection is identified by local and remote address.
TODO: the type variable which this data type fills in is called peerid
. We
should renamed to connectionId
.
ConnectionId | |
|
Instances
:: forall vNumber vData t fd addr b. (Ord vNumber, Typeable vNumber, Show vNumber, Ord addr) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> (fd -> addr -> IO ()) | callback to configure a socket |
-> NetworkServerTracers addr vNumber | |
-> NetworkMutableState addr | |
-> AcceptedConnectionsLimit | |
-> addr | |
-> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString | |
-> ProtocolTimeLimits (Handshake vNumber Term) | |
-> VersionDataCodec Term vNumber vData | |
-> HandshakeCallbacks vData | |
-> Versions vNumber vData (SomeResponderApplication addr ByteString IO b) | The mux application that will be run on each incoming connection from
a given address. Note that if |
-> ErrorPolicies | |
-> (addr -> Async Void -> IO t) | callback which takes the |
-> IO t |
Run a server application. It will listen on the given address for incoming connection, otherwise like withServerNode'.
:: forall vNumber vData t fd addr b. (Ord vNumber, Typeable vNumber, Show vNumber, Ord addr) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> NetworkServerTracers addr vNumber | |
-> NetworkMutableState addr | |
-> AcceptedConnectionsLimit | |
-> fd | a configured socket to be used be the server. The server will call
|
-> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString | |
-> ProtocolTimeLimits (Handshake vNumber Term) | |
-> VersionDataCodec Term vNumber vData | |
-> HandshakeCallbacks vData | |
-> Versions vNumber vData (SomeResponderApplication addr ByteString IO b) | The mux application that will be run on each incoming connection from
a given address. Note that if |
-> ErrorPolicies | |
-> (addr -> Async Void -> IO t) | callback which takes the |
-> IO t |
Run a server application on the provided socket. The socket must be ready to accept connections.
The server thread runs using withAsync
function, which means
that it will terminate when the callback terminates or throws an exception.
TODO: we should track connections in the state and refuse connections from peers we are already connected to. This is also the right place to ban connection from peers which misbehaved.
The server will run handshake protocol on each incoming connection. We
assume that each version negotiation message should fit into
(~5k bytes).maxTransmissionUnit
Note: it will open a socket in the current thread and pass it to the spawned thread which runs the server. This makes it useful for testing, where we need to guarantee that a socket is open before we try to connect to it.
data ConnectToArgs fd addr vNumber vData Source #
Common arguments of various variants of connectToNode
.
ConnectToArgs | |
|
:: forall (muxMode :: Mode) vNumber vData fd addr a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> ConnectToArgs fd addr vNumber vData | |
-> (fd -> IO ()) | configure socket |
-> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) | |
-> Maybe addr | local address; the created socket will bind to it |
-> addr | remote address |
-> IO (Either SomeException (Either a b)) |
Connect to a remote node. It is using bracket to enclose the underlying socket acquisition. This implies that when the continuation exits the underlying bearer will get closed.
The connection will start with handshake protocol sending Versions
to the
remote peer. It must fit into
(~5k bytes).maxTransmissionUnit
Exceptions thrown by MuxApplication
are rethrown by connectToNode
.
:: forall (muxMode :: Mode) vNumber vData fd addr a b x. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> ConnectToArgs fd addr vNumber vData | |
-> (fd -> IO ()) | configure socket |
-> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) | application to run over the connection ^ remote address |
-> Maybe addr | |
-> addr | |
-> (ConnectionId addr -> vNumber -> vData -> OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b -> Mux muxMode IO -> Async () -> IO x) | callback which has access to ConnectionId, negotiated protocols, mux
handle created for that connection and an NOTE: when the callback returns or errors, the mux thread will be killed. |
-> IO x |
A version connectToNode
which allows one to control which mini-protocols
to execute on a given connection.
:: forall (muxMode :: Mode) vNumber vData a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) | |
=> IOManager | |
-> ConnectToArgs Socket SockAddr vNumber vData | |
-> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode SockAddr ByteString IO a b) | application to run over the connection |
-> Socket | |
-> IO (Either SomeException (Either a b)) |
:: forall (muxMode :: Mode) vNumber vData fd addr a b. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> ConnectToArgs fd addr vNumber vData | a configured socket to use to connect to a remote service provider |
-> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) | application to run over the connection |
-> fd | |
-> IO (Either SomeException (Either a b)) |
Connect to a remote node using an existing socket. It is up to to caller to ensure that the socket is closed in case of an exception.
The connection will start with handshake protocol sending Versions
to the
remote peer. It must fit into
(~5k bytes).maxTransmissionUnit
Exceptions thrown by
are rethrown by MuxApplication
.connectTo
connectToNodeWithMux' Source #
:: forall (muxMode :: Mode) vNumber vData fd addr a b x. (Ord vNumber, Typeable vNumber, Show vNumber, HasInitiator muxMode ~ 'True) | |
=> Snocket IO fd addr | |
-> MakeBearer IO fd | |
-> ConnectToArgs fd addr vNumber vData | |
-> Versions vNumber vData (OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b) | application to run over the connection ^ a configured socket to use to connect to a remote service provider |
-> fd | |
-> (ConnectionId addr -> vNumber -> vData -> OuroborosApplicationWithMinimalCtx muxMode addr ByteString IO a b -> Mux muxMode IO -> Async () -> IO x) | callback which has access to ConnectionId, negotiated protocols, mux
handle created for that connection and an NOTE: when the callback returns or errors, the mux thread will be killed. |
-> IO x |
Socket configuration
configureSystemdSocket :: Tracer IO SystemdSocketTracer -> Socket -> SockAddr -> IO () Source #
Configure sockets passed through systemd socket activation.
Currently ReuseAddr
and Linger
options are not configurable with
'systemd.socket', these options are set by this function. For other socket
options we only trace if they are not set.
data SystemdSocketTracer Source #
Instances
Show SystemdSocketTracer Source # | |
Defined in Ouroboros.Network.Socket showsPrec :: Int -> SystemdSocketTracer -> ShowS # show :: SystemdSocketTracer -> String # showList :: [SystemdSocketTracer] -> ShowS # |
Traces
data NetworkConnectTracers addr vNumber Source #
Tracer used by connectToNode
(and derivatives, like
connectTo
or
'Ouroboros.Network.NodeToClient.connectTo).
NetworkConnectTracers | |
|
nullNetworkConnectTracers :: NetworkConnectTracers addr vNumber Source #
debuggingNetworkConnectTracers :: (Show addr, Show vNumber) => NetworkConnectTracers addr vNumber Source #
data NetworkServerTracers addr vNumber Source #
Tracers required by a server which handles inbound connections.
NetworkServerTracers | |
|
nullNetworkServerTracers :: NetworkServerTracers addr vNumber Source #
debuggingNetworkServerTracers :: (Show addr, Show vNumber) => NetworkServerTracers addr vNumber Source #
data AcceptConnectionsPolicyTrace Source #
Trace for the AcceptConnectionsLimit
policy.
ServerTraceAcceptConnectionRateLimiting DiffTime Int | |
ServerTraceAcceptConnectionHardLimit Word32 | |
ServerTraceAcceptConnectionResume Int |
Instances
Show AcceptConnectionsPolicyTrace Source # | |
Defined in Ouroboros.Network.Server.RateLimiting showsPrec :: Int -> AcceptConnectionsPolicyTrace -> ShowS # show :: AcceptConnectionsPolicyTrace -> String # showList :: [AcceptConnectionsPolicyTrace] -> ShowS # | |
Eq AcceptConnectionsPolicyTrace Source # | |
Ord AcceptConnectionsPolicyTrace Source # | |
Defined in Ouroboros.Network.Server.RateLimiting compare :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> Ordering # (<) :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> Bool # (<=) :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> Bool # (>) :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> Bool # (>=) :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> Bool # max :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace # min :: AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace -> AcceptConnectionsPolicyTrace # |
Helper function for creating servers
:: forall fd addr. Ord addr | |
=> ConnectionTable IO addr | |
-> Snocket IO fd addr | |
-> fd | socket or handle |
-> IO (Socket addr fd) |
Make a server-compatible socket from a network socket.
:: forall vNumber vData addr st fd. (Ord vNumber, Typeable vNumber, Show vNumber) | |
=> MakeBearer IO fd | |
-> Tracer IO (WithBearer (ConnectionId addr) Trace) | |
-> Tracer IO (WithBearer (ConnectionId addr) (TraceSendRecv (Handshake vNumber Term))) | |
-> Codec (Handshake vNumber Term) DeserialiseFailure IO ByteString | |
-> ProtocolTimeLimits (Handshake vNumber Term) | |
-> VersionDataCodec Term vNumber vData | |
-> HandshakeCallbacks vData | |
-> (Time -> addr -> st -> STM (AcceptConnection st vNumber vData addr IO ByteString)) | either accept or reject a connection. |
-> BeginConnection addr fd st () |
Accept or reject incoming connection based on the current state and address of the incoming connection.
Re-export of HandshakeCallbacks
Re-export of PeerStates
data PeerStates (m :: Type -> Type) addr Source #
Map from addresses to PeerState
s; it will be be shared in a StrictTVar
.
Abstracting t
is useful for tests, the IO
version will use Time IO
.
Instances
Show addr => Show (PeerStates IO addr) Source # | |
Defined in Ouroboros.Network.Subscription.PeerState | |
Eq addr => Eq (PeerStates IO addr) Source # | |
Defined in Ouroboros.Network.Subscription.PeerState (==) :: PeerStates IO addr -> PeerStates IO addr -> Bool # (/=) :: PeerStates IO addr -> PeerStates IO addr -> Bool # |
Re-export connection table functions
newConnectionTable :: MonadSTM m => m (ConnectionTable m addr) Source #
refConnection :: (MonadSTM m, Ord addr) => ConnectionTable m addr -> addr -> ConnectionDirection -> ValencyCounter m -> m ConnectionTableRef Source #
:: forall (m :: Type -> Type) addr. (MonadSTM m, Ord addr) | |
=> ConnectionTable m addr | |
-> addr | |
-> addr | |
-> ConnectionDirection | |
-> Maybe (ValencyCounter m) | Optional ValencyCounter, used by subscription worker and set to Nothing when called by a local server. |
-> STM m () |
Insert a new connection into the ConnectionTable.
removeConnection :: (MonadSTM m, Ord addr) => ConnectionTable m addr -> addr -> addr -> ConnectionDirection -> m () Source #
:: forall (m :: Type -> Type) addr. MonadSTM m | |
=> ConnectionTable m addr | |
-> Int | Desired valency, that is number of connections a subscription worker will attempt to maintain. |
-> STM m (ValencyCounter m) |
Create a new ValencyCounter
addValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m () Source #
Add a connection.
remValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m () Source #
Remove a connection.
waitValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m () Source #
Wait until ValencyCounter becomes positive, used for detecting when we can create new connections.
readValencyCounter :: forall (m :: Type -> Type). MonadSTM m => ValencyCounter m -> STM m Int Source #
Returns current ValencyCounter value, represent the number of additional connections that can be created. May be negative.
Auxiliary functions
sockAddrFamily :: SockAddr -> Family Source #