sockets-0.4.0.0: High-level network sockets

Safe HaskellNone
LanguageHaskell2010

Socket.Stream.IPv4

Contents

Synopsis

Types

data Listener Source #

A socket that listens for incomming connections.

newtype Connection #

Constructors

Connection Fd 

data Peer #

Constructors

Peer 

Fields

Instances
Eq Peer 
Instance details

Defined in Socket.IPv4

Methods

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

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

Show Peer 
Instance details

Defined in Socket.IPv4

Methods

showsPrec :: Int -> Peer -> ShowS #

show :: Peer -> String #

showList :: [Peer] -> ShowS #

Bracketed

withListener :: Peer -> (Listener -> Word16 -> IO a) -> IO (Either SocketException a) Source #

Open a socket that is used to listen for inbound connections.

withAccepted Source #

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).

withConnection Source #

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.

forkAccepted Source #

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.

forkAcceptedUnmasked Source #

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 True give up and return Left AcceptInterrupted.

-> 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

Expand

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.

  1. 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 or TVar. To complete graceful termination, the application must block until the counter reaches zero.
  2. These semantics cannot be provided without building in counter as a TVar. When abandon becomes True, 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 the abandon 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 ReceiveException (a :: Interruptibility) where #

data ConnectException (a :: Family) (b :: Interruptibility) where #

data AcceptException (a :: Interruptibility) where #

Type Arguments

data Family #

Constructors

Internet Version 
Unix 

data Version #

Constructors

V4 
V6 

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 or Connection exactly once to close underlying file descriptor.
  • The Listener or Connection 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 resulting Listener exactly once to close underlying file descriptor.
  • The Listener cannot be used after being given as an argument to unlistener.

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_.

connect Source #

Arguments

:: Peer

Remote endpoint

-> IO (Either (ConnectException (Internet V4) Uninterruptible) Connection) 

Open a socket and connect to a peer. Requirements:

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.

interruptibleAccept Source #

Arguments

:: TVar Bool

Interrupted. If this becomes True give up and return Left AcceptInterrupted.

-> Listener 
-> IO (Either (AcceptException Interruptible) (Connection, Peer)) 

Listen for an inbound connection. Can be interrupted by an STM-style interrupt.