Safe Haskell | None |
---|---|
Language | Haskell2010 |
Socket.Stream.IPv4
Synopsis
- data Listener
- newtype Connection = Connection Fd
- data Peer = Peer {}
- withListener :: Peer -> (Listener -> Word16 -> IO a) -> IO (Either SocketException a)
- withAccepted :: Listener -> (Either CloseException () -> a -> IO b) -> (Connection -> Peer -> IO a) -> IO (Either (AcceptException Uninterruptible) b)
- withConnection :: Peer -> (Either CloseException () -> a -> IO b) -> (Connection -> IO a) -> IO (Either (ConnectException (Internet V4) Uninterruptible) b)
- forkAccepted :: Listener -> (Either CloseException () -> a -> IO ()) -> (Connection -> Peer -> IO a) -> IO (Either (AcceptException Uninterruptible) ThreadId)
- forkAcceptedUnmasked :: Listener -> (Either CloseException () -> a -> IO ()) -> (Connection -> Peer -> IO a) -> IO (Either (AcceptException Uninterruptible) ThreadId)
- interruptibleForkAcceptedUnmasked :: TVar Int -> TVar Bool -> Listener -> (Either CloseException () -> a -> IO ()) -> (Connection -> Peer -> IO a) -> IO (Either (AcceptException Interruptible) ThreadId)
- data SendException (a :: Interruptibility) where
- SendShutdown :: forall (a :: Interruptibility). SendException a
- SendReset :: forall (a :: Interruptibility). SendException a
- SendInterrupted :: forall (a :: Interruptibility). !Int -> SendException Interruptible
- data ReceiveException (a :: Interruptibility) where
- ReceiveShutdown :: forall (a :: Interruptibility). ReceiveException a
- ReceiveReset :: forall (a :: Interruptibility). ReceiveException a
- ReceiveInterrupted :: forall (a :: Interruptibility). !Int -> ReceiveException Interruptible
- ReceiveHostUnreachable :: forall (a :: Interruptibility). ReceiveException a
- data ConnectException (a :: Family) (b :: Interruptibility) where
- ConnectFirewalled :: forall (a :: Family) (b :: Interruptibility). ConnectException a b
- ConnectFileDescriptorLimit :: forall (a :: Family) (b :: Interruptibility). ConnectException a b
- ConnectNetworkUnreachable :: forall (a :: Family) (b :: Interruptibility) (v :: Version). ConnectException (Internet v) b
- ConnectHostUnreachable :: forall (a :: Family) (b :: Interruptibility) (v :: Version). ConnectException (Internet v) b
- ConnectEphemeralPortsExhausted :: forall (a :: Family) (b :: Interruptibility). ConnectException a b
- ConnectRefused :: forall (a :: Family) (b :: Interruptibility). ConnectException a b
- ConnectTimeout :: forall (a :: Family) (b :: Interruptibility). ConnectException a b
- ConnectProtocolType :: forall (a :: Family) (b :: Interruptibility). ConnectException Unix b
- ConnectInterrupted :: forall (a :: Family) (b :: Interruptibility). ConnectException a Interruptible
- data SocketException
- data AcceptException (a :: Interruptibility) where
- AcceptConnectionAborted :: forall (a :: Interruptibility). AcceptException a
- AcceptFileDescriptorLimit :: forall (a :: Interruptibility). AcceptException a
- AcceptFirewalled :: forall (a :: Interruptibility). AcceptException a
- AcceptInterrupted :: forall (a :: Interruptibility). AcceptException Interruptible
- data CloseException = ClosePeerContinuedSending
- data Interruptibility
- data Family
- data Version
- listen :: Peer -> IO (Either SocketException (Listener, Word16))
- unlisten :: Listener -> IO ()
- unlisten_ :: Listener -> IO ()
- connect :: Peer -> IO (Either (ConnectException (Internet V4) Uninterruptible) Connection)
- disconnect :: Connection -> IO (Either CloseException ())
- disconnect_ :: Connection -> IO ()
- accept :: Listener -> IO (Either (AcceptException Uninterruptible) (Connection, Peer))
- interruptibleAccept :: TVar Bool -> Listener -> IO (Either (AcceptException Interruptible) (Connection, Peer))
Types
newtype Connection #
Constructors
Connection Fd |
Bracketed
withListener :: Peer -> (Listener -> Word16 -> IO a) -> IO (Either SocketException a) Source #
Open a socket that is used to listen for inbound connections.
Arguments
:: Listener | |
-> (Either CloseException () -> a -> IO b) | Callback to handle an ungraceful close. |
-> (Connection -> Peer -> IO a) | Callback to consume connection. Must not return the connection. |
-> IO (Either (AcceptException Uninterruptible) b) |
Accept a connection on the listener and run the supplied callback
on it. This closes the connection when the callback finishes or if
an exception is thrown. Since this function blocks the thread until
the callback finishes, it is only suitable for stream socket clients
that handle one connection at a time. The variant forkAcceptedUnmasked
is preferrable for servers that need to handle connections concurrently
(most use cases).
Arguments
:: Peer | Remote endpoint |
-> (Either CloseException () -> a -> IO b) | Callback to handle an ungraceful close. |
-> (Connection -> IO a) | Callback to consume connection. Must not return the connection. |
-> IO (Either (ConnectException (Internet V4) Uninterruptible) b) |
Establish a connection to a server.
Arguments
:: Listener | |
-> (Either CloseException () -> a -> IO ()) | Callback to handle an ungraceful close. |
-> (Connection -> Peer -> IO a) | Callback to consume connection. Must not return the connection. |
-> IO (Either (AcceptException Uninterruptible) ThreadId) |
Accept a connection on the listener and run the supplied callback in
a new thread. Prefer forkAcceptedUnmasked
unless the masking state
needs to be preserved for the callback. Such a situation seems unlikely
to the author.
Arguments
:: Listener | |
-> (Either CloseException () -> a -> IO ()) | Callback to handle an ungraceful close. |
-> (Connection -> Peer -> IO a) | Callback to consume connection. Must not return the connection. |
-> IO (Either (AcceptException Uninterruptible) ThreadId) |
Accept a connection on the listener and run the supplied callback in
a new thread. The masking state is set to Unmasked
when running the
callback. Typically, a
is instantiated to ()
.
interruptibleForkAcceptedUnmasked Source #
Arguments
:: TVar Int | Connection counter. Incremented when connection is accepted. Decremented after connection is closed. |
-> TVar Bool | Interrupted. If this becomes |
-> Listener | Connection listener |
-> (Either CloseException () -> a -> IO ()) | Callback to handle an ungraceful close. |
-> (Connection -> Peer -> IO a) | Callback to consume connection. Must not return the connection. |
-> IO (Either (AcceptException Interruptible) ThreadId) |
Accept a connection on the listener and run the supplied callback in
a new thread. The masking state is set to Unmasked
when running the
callback. Typically, a
is instantiated to ()
.
Discussion
Why is the counter
argument present? At first, it seems
like this is something that the API consumer should implement on
top of this library. The argument for the inclusion of the counter
is has two parts: (1) clients supporting graceful termination
always need these semantics and (2) these semantics cannot
be provided without building in counter
as a TVar
.
- Clients supporting graceful termination always need these
semantics. To gracefully bring down a server that has been
accepting connections with a forking function, an application
must wait for all active connections to finish. Since all
connections run on separate threads, this can only be
accomplished by a concurrency primitive. The straightforward
solution is to wrap a counter with either
MVar
orTVar
. To complete graceful termination, the application must block until the counter reaches zero. - These semantics cannot be provided without building in
counter
as aTVar
. Whenabandon
becomesTrue
, graceful termination begins. From this point onward, if at any point the counter reaches zero, the application consuming this API will complete termination. Consequently, we need the guarantee that the counter does not increment after theabandon
transaction completes. If it did increment in this forbidden way (e.g. if it was incremented some unspecified amount of time after a connection was accepted), there would be a race condition in which the application may terminate without giving the newly accepted connection a chance to finish. Fortunately,STM
gives us the composable transaction we need to get this guarantee. To wait for an inbound connection, we use:
(isReady,deregister) <- threadWaitReadSTM fd shouldReceive <- atomically $ do readTVar abandon >>= \case True -> do isReady modifyTVar' counter (+1) pure True False -> pure False
This eliminates the window for the race condition. If a
connection is accepted, the counter is guaranteed to
be incremented _before_ abandon
becomes True
.
However, this code would be more simple and would perform
better if GHC's event manager used TVar instead of STM.
Exceptions
data SendException (a :: Interruptibility) where #
Constructors
SendShutdown :: forall (a :: Interruptibility). SendException a | |
SendReset :: forall (a :: Interruptibility). SendException a | |
SendInterrupted :: forall (a :: Interruptibility). !Int -> SendException Interruptible |
Instances
data ReceiveException (a :: Interruptibility) where #
Constructors
ReceiveShutdown :: forall (a :: Interruptibility). ReceiveException a | |
ReceiveReset :: forall (a :: Interruptibility). ReceiveException a | |
ReceiveInterrupted :: forall (a :: Interruptibility). !Int -> ReceiveException Interruptible | |
ReceiveHostUnreachable :: forall (a :: Interruptibility). ReceiveException a |
Instances
data ConnectException (a :: Family) (b :: Interruptibility) where #
Constructors
ConnectFirewalled :: forall (a :: Family) (b :: Interruptibility). ConnectException a b | |
ConnectFileDescriptorLimit :: forall (a :: Family) (b :: Interruptibility). ConnectException a b | |
ConnectNetworkUnreachable :: forall (a :: Family) (b :: Interruptibility) (v :: Version). ConnectException (Internet v) b | |
ConnectHostUnreachable :: forall (a :: Family) (b :: Interruptibility) (v :: Version). ConnectException (Internet v) b | |
ConnectEphemeralPortsExhausted :: forall (a :: Family) (b :: Interruptibility). ConnectException a b | |
ConnectRefused :: forall (a :: Family) (b :: Interruptibility). ConnectException a b | |
ConnectTimeout :: forall (a :: Family) (b :: Interruptibility). ConnectException a b | |
ConnectProtocolType :: forall (a :: Family) (b :: Interruptibility). ConnectException Unix b | |
ConnectInterrupted :: forall (a :: Family) (b :: Interruptibility). ConnectException a Interruptible |
Instances
data SocketException #
Constructors
SocketPermissionDenied | |
SocketAddressInUse | |
SocketEphemeralPortsExhausted | |
SocketFileDescriptorLimit |
Instances
Show SocketException | |
Defined in Socket.IPv4 Methods showsPrec :: Int -> SocketException -> ShowS # show :: SocketException -> String # showList :: [SocketException] -> ShowS # | |
Exception SocketException | |
Defined in Socket.IPv4 Methods toException :: SocketException -> SomeException # |
data AcceptException (a :: Interruptibility) where #
Constructors
AcceptConnectionAborted :: forall (a :: Interruptibility). AcceptException a | |
AcceptFileDescriptorLimit :: forall (a :: Interruptibility). AcceptException a | |
AcceptFirewalled :: forall (a :: Interruptibility). AcceptException a | |
AcceptInterrupted :: forall (a :: Interruptibility). AcceptException Interruptible |
Instances
data CloseException #
Constructors
ClosePeerContinuedSending |
Instances
Eq CloseException | |
Defined in Socket.Stream Methods (==) :: CloseException -> CloseException -> Bool # (/=) :: CloseException -> CloseException -> Bool # | |
Ord CloseException | |
Defined in Socket.Stream Methods compare :: CloseException -> CloseException -> Ordering # (<) :: CloseException -> CloseException -> Bool # (<=) :: CloseException -> CloseException -> Bool # (>) :: CloseException -> CloseException -> Bool # (>=) :: CloseException -> CloseException -> Bool # max :: CloseException -> CloseException -> CloseException # min :: CloseException -> CloseException -> CloseException # | |
Show CloseException | |
Defined in Socket.Stream Methods showsPrec :: Int -> CloseException -> ShowS # show :: CloseException -> String # showList :: [CloseException] -> ShowS # | |
Exception CloseException | |
Defined in Socket.Stream Methods toException :: CloseException -> SomeException # |
Type Arguments
data Interruptibility #
Constructors
Interruptible | |
Uninterruptible |
Unbracketed
Provided here are the unbracketed functions for the creation and destruction of listeners, outbound connections, and inbound connections. These functions come with pretty serious requirements:
- They may only be called in contexts where exceptions are masked.
- The caller must be sure to call the destruction function every
Listener
orConnection
exactly once to close underlying file descriptor. - The
Listener
orConnection
cannot be used after being given as an argument to the destruction function.
listen :: Peer -> IO (Either SocketException (Listener, Word16)) Source #
Open a socket that can be used to listen for inbound connections. Requirements:
- This function may only be called in contexts where exceptions are masked.
- The caller must be sure to call
unlistener
on the resultingListener
exactly once to close underlying file descriptor. - The
Listener
cannot be used after being given as an argument tounlistener
.
Noncompliant use of this function leads to undefined behavior. Prefer
withListener
unless you are writing an integration with a
resource-management library.
unlisten :: Listener -> IO () Source #
Close a listener. This throws an unrecoverable exception if the socket cannot be closed.
unlisten_ :: Listener -> IO () Source #
Close a listener. This does not check to see whether or not
the operating system successfully closed the socket. It never
throws exceptions of any kind. This should only be preferred
to unlistener
in exception-cleanup contexts where there is
already an exception that will be rethrown. See the implementation
of withListener
for an example of appropriate use of both
unlistener
and unlistener_
.
Arguments
:: Peer | Remote endpoint |
-> IO (Either (ConnectException (Internet V4) Uninterruptible) Connection) |
Open a socket and connect to a peer. Requirements:
- This function may only be called in contexts where exceptions are masked.
- The caller must be sure to call
disconnect
ordisconnect_
on the resultingConnection
exactly once to close underlying file descriptor. - The
Connection
cannot be used after being given as an argument todisconnect
ordisconnect_
.
Noncompliant use of this function leads to undefined behavior. Prefer
withConnection
unless you are writing an integration with a
resource-management library.
disconnect :: Connection -> IO (Either CloseException ()) Source #
Close a connection gracefully, reporting a CloseException
when
the connection has to be terminated by sending a TCP reset. This
uses a combination of shutdown
, recv
, close
to detect when
resets need to be sent.
disconnect_ :: Connection -> IO () Source #
Close a connection. This does not check to see whether or not
the connection was brought down gracefully. It just calls close
and is likely to cause a TCP reset to be sent. It never
throws exceptions of any kind (even if close
fails).
This should only be preferred
to disconnect
in exception-cleanup contexts where there is
already an exception that will be rethrown. See the implementation
of withConnection
for an example of appropriate use of both
disconnect
and disconnect_
.
accept :: Listener -> IO (Either (AcceptException Uninterruptible) (Connection, Peer)) Source #
Listen for an inbound connection.
Arguments
:: TVar Bool | Interrupted. If this becomes |
-> Listener | |
-> IO (Either (AcceptException Interruptible) (Connection, Peer)) |
Listen for an inbound connection. Can be interrupted by an STM-style interrupt.