Copyright | (c) 2018 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
A socket is a handle to a protocol endpoint.
This module provides APIs to read and write streams and arrays to and from network sockets. Sockets may be connected or unconnected. Connected sockets can only send or recv data to/from the connected endpoint, therefore, APIs for connected sockets do not need to explicitly specify the remote endpoint. APIs for unconnected sockets need to explicitly specify the remote endpoint.
Programmer Notes
Read IO requests to connected stream sockets are performed in chunks of
defaultChunkSize
. Unless specified
otherwise in the API, writes are collected into chunks of
defaultChunkSize
before they are
written to the socket. APIs are provided to control the chunking behavior.
import qualified Streamly.Network.Socket as SK
For additional, experimental APIs take a look at Streamly.Internal.Network.Socket module.
Synopsis
- data SockSpec = SockSpec {
- sockFamily :: !Family
- sockType :: !SocketType
- sockProto :: !ProtocolNumber
- sockOpts :: ![(SocketOption, Int)]
- accept :: MonadIO m => Unfold m (Int, SockSpec, SockAddr) Socket
- read :: MonadIO m => Unfold m Socket Word8
- readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8
- readChunks :: MonadIO m => Unfold m Socket (Array Word8)
- readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Socket) (Array Word8)
- write :: MonadIO m => Socket -> Fold m Word8 ()
- writeWithBufferOf :: MonadIO m => Int -> Socket -> Fold m Word8 ()
- writeChunks :: (MonadIO m, Storable a) => Socket -> Fold m (Array a) ()
Socket Specification
Specify the socket protocol details.
SockSpec | |
|
Accept Connections
accept :: MonadIO m => Unfold m (Int, SockSpec, SockAddr) Socket Source #
Unfold a three tuple (listenQLen, spec, addr)
into a stream of connected
protocol sockets corresponding to incoming connections. listenQLen
is the
maximum number of pending connections in the backlog. spec
is the socket
protocol and options specification and addr
is the protocol address where
the server listens for incoming connections.
Since: 0.7.0
Read
read :: MonadIO m => Unfold m Socket Word8 Source #
Unfolds a Socket
into a byte stream. IO requests to the socket are
performed in sizes of
defaultChunkSize
.
Since: 0.7.0
readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8 Source #
Unfolds the tuple (bufsize, socket)
into a byte stream, read requests
to the socket are performed using buffers of bufsize
.
Since: 0.7.0
readChunks :: MonadIO m => Unfold m Socket (Array Word8) Source #
Unfolds a socket into a stream of Word8
arrays. Requests to the socket
are performed using a buffer of size
defaultChunkSize
. The
size of arrays in the resulting stream are therefore less than or equal to
defaultChunkSize
.
Since: 0.7.0
readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Socket) (Array Word8) Source #
Unfold the tuple (bufsize, socket)
into a stream of Word8
arrays.
Read requests to the socket are performed using a buffer of size bufsize
.
The size of an array in the resulting stream is always less than or equal to
bufsize
.
Since: 0.7.0
Write
write :: MonadIO m => Socket -> Fold m Word8 () Source #
Write a byte stream to a socket. Accumulates the input in chunks of
up to defaultChunkSize
bytes before writing.
write =writeWithBufferOf
defaultChunkSize
Since: 0.7.0