Copyright | (c) 2018 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data SockSpec = SockSpec {
- sockFamily :: !Family
- sockType :: !SocketType
- sockProto :: !ProtocolNumber
- sockOpts :: ![(SocketOption, Int)]
- handleWithM :: (MonadMask m, MonadIO m) => (Socket -> m ()) -> Socket -> m ()
- handleWith :: (IsStream t, MonadCatch m, MonadIO m) => Socket -> (Socket -> t m a) -> t m a
- accept :: MonadIO m => Unfold m (Int, SockSpec, SockAddr) Socket
- connections :: MonadAsync m => Int -> SockSpec -> SockAddr -> SerialT m Socket
- read :: MonadIO m => Unfold m Socket Word8
- readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8
- readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Socket) (Array Word8)
- readChunks :: MonadIO m => Unfold m Socket (Array Word8)
- toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Socket -> t m (Array Word8)
- toChunks :: (IsStream t, MonadIO m) => Socket -> t m (Array Word8)
- toBytes :: (IsStream t, MonadIO m) => Socket -> t m Word8
- write :: MonadIO m => Socket -> Fold m Word8 ()
- writeWithBufferOf :: MonadIO m => Int -> Socket -> Fold m Word8 ()
- fromChunks :: (MonadIO m, Storable a) => Socket -> SerialT m (Array a) -> m ()
- fromBytesWithBufferOf :: MonadIO m => Int -> Socket -> SerialT m Word8 -> m ()
- fromBytes :: MonadIO m => Socket -> SerialT m Word8 -> m ()
- writeChunk :: Storable a => Socket -> Array a -> IO ()
- writeChunks :: (MonadIO m, Storable a) => Socket -> Fold m (Array a) ()
- writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Socket -> Fold m (Array a) ()
- writeStrings :: MonadIO m => (SerialT m Char -> SerialT m Word8) -> Socket -> Fold m String ()
Documentation
Specify the socket protocol details.
SockSpec | |
|
Use a socket
handleWithM :: (MonadMask m, MonadIO m) => (Socket -> m ()) -> Socket -> m () Source #
runs the monadic computation handleWithM
socket actact
passing the
socket handle to it. The handle will be closed on exit from handleWithM
,
whether by normal termination or by raising an exception. If closing the
handle raises an exception, then this exception will be raised by
handleWithM
rather than any exception raised by act
.
Since: 0.7.0
handleWith :: (IsStream t, MonadCatch m, MonadIO m) => Socket -> (Socket -> t m a) -> t m a Source #
Like handleWithM
but runs a streaming computation instead of a monadic
computation.
Since: 0.7.0
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
connections :: MonadAsync m => Int -> SockSpec -> SockAddr -> SerialT m Socket Source #
Start a TCP stream server that listens for connections on the supplied server address specification (address family, local interface IP address and port). The server generates a stream of connected sockets. The first argument is the maximum number of pending connections in the backlog.
Internal
Read from connection
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
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
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
toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Socket -> t m (Array Word8) Source #
toChunksWithBufferOf size h
reads a stream of arrays from file handle h
.
The maximum size of a single array is limited to size
.
fromHandleArraysUpto
ignores the prevailing TextEncoding
and NewlineMode
on the Handle
.
toChunks :: (IsStream t, MonadIO m) => Socket -> t m (Array Word8) Source #
toChunks h
reads a stream of arrays from socket handle h
.
The maximum size of a single array is limited to defaultChunkSize
.
Since: 0.7.0
toBytes :: (IsStream t, MonadIO m) => Socket -> t m Word8 Source #
Generate a stream of elements of the given type from a socket. The stream ends when EOF is encountered.
Since: 0.7.0
Write to connection
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
writeWithBufferOf :: MonadIO m => Int -> Socket -> Fold m Word8 () Source #
Write a byte stream to a socket. Accumulates the input in chunks of specified number of bytes before writing.
Since: 0.7.0
fromChunks :: (MonadIO m, Storable a) => Socket -> SerialT m (Array a) -> m () Source #
Write a stream of arrays to a handle.
Since: 0.7.0
fromBytesWithBufferOf :: MonadIO m => Int -> Socket -> SerialT m Word8 -> m () Source #
Like write
but provides control over the write buffer. Output will
be written to the IO device as soon as we collect the specified number of
input elements.
Since: 0.7.0
fromBytes :: MonadIO m => Socket -> SerialT m Word8 -> m () Source #
Write a byte stream to a file handle. Combines the bytes in chunks of size
up to defaultChunkSize
before writing. Note that the write behavior
depends on the IOMode
and the current seek position of the handle.
Since: 0.7.0
writeChunk :: Storable a => Socket -> Array a -> IO () Source #
Write an Array to a file handle.
Since: 0.7.0
writeChunks :: (MonadIO m, Storable a) => Socket -> Fold m (Array a) () Source #
Write a stream of arrays to a socket. Each array in the stream is written to the socket as a separate IO request.
Since: 0.7.0
writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Socket -> Fold m (Array a) () Source #
writeChunksWithBufferOf bufsize socket
writes a stream of arrays
to socket
after coalescing the adjacent arrays in chunks of bufsize
.
We never split an array, if a single array is bigger than the specified size
it emitted as it is. Multiple arrays are coalesed as long as the total size
remains below the specified size.
Since: 0.7.0