streamly-0.10.1: Streaming, dataflow programming and declarative concurrency
Copyright(c) 2019 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityreleased
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Network.Inet.TCP

Description

Combinators to build Inet/IPv4/TCP clients and servers.

>>> import qualified Streamly.Network.Inet.TCP as TCP

Examples

Following is a short example of a concurrent echo server.

>>> import Control.Monad.Catch (finally)
>>> import Data.Function ((&))
>>> import Network.Socket (Socket)
>>> 
>>> import qualified Network.Socket as Net
>>> import qualified Streamly.Data.Fold as Fold
>>> import qualified Streamly.Data.Stream.Prelude as Stream
>>> import qualified Streamly.Network.Inet.TCP as TCP
>>> import qualified Streamly.Network.Socket as Socket
>>> 
>>> :{
main :: IO ()
main =
      TCP.accept 8091                            -- Stream IO Socket
    & Stream.parMapM id (handleExceptions echo)  -- Stream IO ()
    & Stream.fold Fold.drain                     -- IO ()
    where
    echo :: Socket -> IO ()
    echo sk =
          Socket.readChunksWith 32768 sk      -- Stream IO (Array Word8)
        & Stream.fold (Socket.writeChunks sk) -- IO ()
    handleExceptions :: (Socket -> IO ()) -> Socket -> IO ()
    handleExceptions f sk = finally (f sk) (Net.close sk)
:}
Synopsis

Accept Connections

Streams

accept :: MonadIO m => PortNumber -> Stream m Socket Source #

Start a TCP stream server that binds on the IPV4 address 0.0.0.0 and listens for TCP connections from remote hosts on the specified server port. The server generates a stream of connected sockets.

>>> accept = TCP.acceptOnAddr (0,0,0,0)

Pre-release

acceptLocal :: MonadIO m => PortNumber -> Stream m Socket Source #

Like accept but binds on the localhost IPv4 address 127.0.0.1. The server can only be accessed from the local host, it cannot be accessed from other hosts on the network.

>>> acceptLocal = TCP.acceptOnAddr (127,0,0,1)

Pre-release

acceptOnAddr :: MonadIO m => (Word8, Word8, Word8, Word8) -> PortNumber -> Stream m Socket Source #

Like accept but binds on the specified IPv4 address.

>>> acceptOnAddr = TCP.acceptOnAddrWith []

Pre-release

acceptOnAddrWith :: MonadIO m => [(SocketOption, Int)] -> (Word8, Word8, Word8, Word8) -> PortNumber -> Stream m Socket Source #

Like acceptOnAddr but with the ability to specify a list of socket options.

Pre-release

Unfolds

acceptor :: MonadIO m => Unfold m PortNumber Socket Source #

Like acceptorOnAddr but binds on the IPv4 address 0.0.0.0 i.e. on all IPv4 addresses/interfaces of the machine and listens for TCP connections on the specified port.

>>> acceptor = Unfold.first (0,0,0,0) TCP.acceptorOnAddr

acceptorLocal :: MonadIO m => Unfold m PortNumber Socket Source #

Like acceptor but binds on the localhost IPv4 address 127.0.0.1. The server can only be accessed from the local host, it cannot be accessed from other hosts on the network.

>>> acceptorLocal = Unfold.first (127,0,0,1) TCP.acceptorOnAddr

acceptorOnAddr :: MonadIO m => Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Socket Source #

Unfold a tuple (ipAddr, port) into a stream of connected TCP sockets. ipAddr is the local IP address and port is the local port on which connections are accepted.

Connect to Servers

connect :: (Word8, Word8, Word8, Word8) -> PortNumber -> IO Socket Source #

Connect to the specified IP address and port number. Returns a connected socket or throws an exception.

Deprecated

acceptorOnPort :: MonadIO m => Unfold m PortNumber Socket Source #

Deprecated: Use "acceptor" instead.

acceptorOnPortLocal :: MonadIO m => Unfold m PortNumber Socket Source #

Deprecated: Use "acceptorLocal" instead.