Socket

This is the main module of the network package supposed to be used with either Network.Socket.ByteString or Network.Socket.ByteString.Lazy for sending/receiving. Here are two minimal example programs using the TCP/IP protocol:
  • a server that echoes all data that it receives back
  • a client using it
-- Echo server program
module Main (main) where

import Control.Concurrent (forkFinally)
import qualified Control.Exception as E
import Control.Monad (unless, forever, void)
import qualified Data.ByteString as S
import qualified Data.List.NonEmpty as NE
import Network.Socket
import Network.Socket.ByteString (recv, sendAll)

main :: IO ()
main = runTCPServer Nothing "3000" talk
where
talk s = do
msg <- recv s 1024
unless (S.null msg) $ do
sendAll s msg
talk s

-- from the "network-run" package.
runTCPServer :: Maybe HostName -> ServiceName -> (Socket -> IO a) -> IO a
runTCPServer mhost port server = withSocketsDo $ do
addr <- resolve
E.bracket (open addr) close loop
where
resolve = do
let hints = defaultHints {
addrFlags = [AI_PASSIVE]
, addrSocketType = Stream
}
NE.head <$> getAddrInfo (Just hints) mhost (Just port)
open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
setSocketOption sock ReuseAddr 1
withFdSocket sock setCloseOnExecIfNeeded
bind sock $ addrAddress addr
listen sock 1024
return sock
loop sock = forever $ E.bracketOnError (accept sock) (close . fst)
$ \(conn, _peer) -> void $
-- 'forkFinally' alone is unlikely to fail thus leaking @conn@,
-- but 'E.bracketOnError' above will be necessary if some
-- non-atomic setups (e.g. spawning a subprocess to handle
-- @conn@) before proper cleanup of @conn@ is your case
forkFinally (server conn) (const $ gracefulClose conn 5000)
{-# LANGUAGE OverloadedStrings #-}
-- Echo client program
module Main (main) where

import qualified Control.Exception as E
import qualified Data.ByteString.Char8 as C
import qualified Data.List.NonEmpty as NE
import Network.Socket
import Network.Socket.ByteString (recv, sendAll)

main :: IO ()
main = runTCPClient "127.0.0.1" "3000" $ \s -> do
sendAll s "Hello, world!"
msg <- recv s 1024
putStr "Received: "
C.putStrLn msg

-- from the "network-run" package.
runTCPClient :: HostName -> ServiceName -> (Socket -> IO a) -> IO a
runTCPClient host port client = withSocketsDo $ do
addr <- resolve
E.bracket (open addr) close client
where
resolve = do
let hints = defaultHints { addrSocketType = Stream }
NE.head <$> getAddrInfo (Just hints) (Just host) (Just port)
open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
connect sock $ addrAddress addr
return sock
The proper programming model is that one Socket is handled by a single thread. If multiple threads use one Socket concurrently, unexpected things would happen. There is one exception for multiple threads vs a single Socket: one thread reads data from a Socket only and the other thread writes data to the Socket only.
Basic type for a socket.
Container for widgets from other processes
A GSocket is a low-level networking primitive. It is a more or less direct mapping of the BSD socket API in a portable GObject based API. It supports both the UNIX socket implementations and winsock2 on Windows. GSocket is the platform independent base upon which the higher level network primitives are based. Applications are not typically meant to use it directly, but rather through classes like SocketClient, SocketService and SocketConnection. However there may be cases where direct use of GSocket is useful. GSocket implements the Initable interface, so if it is manually constructed by e.g. Object.new() you must call initableInit and check the results before using the object. This is done automatically in socketNew and socketNewFromFd, so these functions can return NULL. Sockets operate in two general modes, blocking or non-blocking. When in blocking mode all operations (which don’t take an explicit blocking parameter) block until the requested operation is finished or there is an error. In non-blocking mode all calls that would block return immediately with a G_IO_ERROR_WOULD_BLOCK error. To know when a call would successfully run you can call socketConditionCheck, or socketConditionWait. You can also use Socket.create_source() and attach it to a [typegLib.MainContext] to get callbacks when I/O is possible. Note that all sockets are always set to non blocking mode in the system, and blocking mode is emulated in GSocket. When working in non-blocking mode applications should always be able to handle getting a G_IO_ERROR_WOULD_BLOCK error even when some other function said that I/O was possible. This can easily happen in case of a race condition in the application, but it can also happen for other reasons. For instance, on Windows a socket is always seen as writable until a write returns G_IO_ERROR_WOULD_BLOCK. GSockets can be either connection oriented or datagram based. For connection oriented types you must first establish a connection by either connecting to an address or accepting a connection from another address. For connectionless socket types the target/source address is specified or received in each I/O operation. All socket file descriptors are set to be close-on-exec. Note that creating a GSocket causes the signal SIGPIPE to be ignored for the remainder of the program. If you are writing a command-line utility that uses GSocket, you may need to take into account the fact that your program will not automatically be killed if it tries to write to stdout after it has been closed. Like most other APIs in GLib, GSocket is not inherently thread safe. To use a GSocket concurrently from multiple threads, you must implement your own locking.

Nagle’s algorithm

Since GLib 2.80, GSocket will automatically set the TCP_NODELAY option on all G_SOCKET_TYPE_STREAM sockets. This disables Nagle’s algorithm as it typically does more harm than good on modern networks. If your application needs Nagle’s algorithm enabled, call socketSetOption after constructing a GSocket to enable it:

c code

socket = g_socket_new (…, G_SOCKET_TYPE_STREAM, …);
if (socket != NULL)
{
g_socket_set_option (socket, IPPROTO_TCP, TCP_NODELAY, FALSE, &local_error);
// handle error if needed
}
Since: 2.22
Memory-managed wrapper type.
Osc over Udp/Tcp implementation.
This module provides socket based streaming APIs to to receive connections from remote hosts, and to read and write from and to network sockets. For basic socket types and non-streaming operations please consult the Network.Socket module of the network package.

Examples

To write a server, use the accept stream to start listening for connections from clients. accept generates a stream of connected sockets. We can map an effectful action on this socket stream to handle the connections. The action would typically use socket reading and writing operations to communicate with the remote host. We can read/write a stream of bytes or a stream of chunks of bytes (Array). Following is a short example of a concurrent echo server. Please note that this example can be written even more succinctly by using higher level operations from Streamly.Network.Inet.TCP module.
>>> :set -XFlexibleContexts

>>> 

>>> import Data.Function ((&))

>>> import Network.Socket

>>> import Streamly.Network.Socket (SockSpec(..))

>>> 

>>> import qualified Streamly.Data.Fold as Fold

>>> import qualified Streamly.Data.Stream.Prelude as Stream

>>> import qualified Streamly.Network.Socket as Socket

>>> 

>>> :{
main :: IO ()
main = do
let spec = SockSpec
{ sockFamily = AF_INET
, sockType   = Stream
, sockProto  = defaultProtocol
, sockOpts   = []
}
addr = SockAddrInet 8090 (tupleToHostAddress (0,0,0,0))
in server spec addr
where
server spec addr =
Socket.accept maxListenQueue spec addr
& Stream.parMapM (Stream.eager True) (Socket.forSocketM echo)
& Stream.fold Fold.drain
echo sk =
Socket.readChunks sk -- Stream IO (Array Word8)
& Stream.fold (Socket.writeChunks sk) -- IO ()
:}

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.
>>> import qualified Streamly.Network.Socket as Socket

See Also

D-Bus sockets are used for communication between two peers. In this model, there is no "bus" or "client", simply two endpoints sending messages. Most users will want to use the DBus.Client module instead.
An open socket to another process. Messages can be sent to the remote peer using send, or received using receive.
A 0MQ Socket.
A 0MQ Socket.
The ZMQ socket, parameterised by SocketType and belonging to a particular ZMQ thread.
Container for AtkPlug objects from other processes Together with Plug, Socket provides the ability to embed accessibles from one process into another in a fashion that is transparent to assistive technologies. Socket works as the container of Plug, embedding it using the method socketEmbed. Any accessible contained in the Plug will appear to the assistive technologies as being inside the application that created the Socket. The communication between a Socket and a Plug is done by the IPC layer of the accessibility framework, normally implemented by the D-Bus based implementation of AT-SPI (at-spi2). If that is the case, at-spi-atk2 is the responsible to implement the abstract methods plugGetId and socketEmbed, so an ATK implementor shouldn't reimplement them. The process that contains the Plug is responsible to send the ID returned by atk_plug_id() to the process that contains the Socket, so it could call the method socketEmbed in order to embed it. For the same reasons, an implementor doesn't need to implement objectGetNAccessibleChildren and objectRefAccessibleChild. All the logic related to those functions will be implemented by the IPC layer. See [classatkPlug]
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Control.Exception ( bracket, catch )
import Control.Monad ( forever )

import System.Socket
import System.Socket.Family.Inet6
import System.Socket.Type.Stream
import System.Socket.Protocol.TCP

main :: IO ()
main = bracket
( socket :: IO (Socket Inet6 Stream TCP) )
( \s-> do
close s
putStrLn "Listening socket closed."
)
( \s-> do
setSocketOption s (ReuseAddress True)
setSocketOption s (V6Only False)
bind s (SocketAddressInet6 inet6Any 8080 0 0)
listen s 5
putStrLn "Listening socket ready..."
forever $ acceptAndHandle s `catch` \e-> print (e :: SocketException)
)

acceptAndHandle :: Socket Inet6 Stream TCP -> IO ()
acceptAndHandle s = bracket
( accept s )
( \(p, addr)-> do
close p
putStrLn $ "Closed connection to " ++ show addr
)
( \(p, addr)-> do
putStrLn $ "Accepted connection from " ++ show addr
sendAll p "Hello world!" msgNoSignal
)
A generic socket type. Use socket to create a new socket. The socket is just an MVar-wrapped file descriptor. The Socket constructor is exported trough the unsafe module in order to make this library easily extensible, but it is usually not necessary nor advised to work directly on the file descriptor. If you do, the following rules must be obeyed:
  • Make sure not to deadlock. Use withMVar or similar.
  • The lock must not be held during a blocking call. This would make it impossible to send and receive simultaneously or to close the socket.
  • The lock must be held when calling operations that use the file descriptor. Otherwise the socket might get closed or even reused by another thread/capability which might result in reading from or writing on a totally different socket. This is a security nightmare!
  • The socket is non-blocking and all the code relies on that assumption. You need to use GHC's eventing mechanism primitives to block until something happens. The former rules forbid to use threadWaitRead as it does not separate between registering the file descriptor (for which the lock must be held) and the actual waiting (for which you must not hold the lock). Also see this thread and read the library code to see how the problem is currently circumvented.
A generic socket type. Use socket to create a new socket. The socket is just an MVar-wrapped file descriptor. The Socket constructor is exported trough the unsafe module in order to make this library easily extensible, but it is usually not necessary nor advised to work directly on the file descriptor. If you do, the following rules must be obeyed:
  • Make sure not to deadlock. Use withMVar or similar.
  • The lock must not be held during a blocking call. This would make it impossible to send and receive simultaneously or to close the socket.
  • The lock must be held when calling operations that use the file descriptor. Otherwise the socket might get closed or even reused by another thread/capability which might result in reading from or writing on a totally different socket. This is a security nightmare!
  • The socket is non-blocking and all the code relies on that assumption. You need to use GHC's eventing mechanism primitives to block until something happens. The former rules forbid to use threadWaitRead as it does not separate between registering the file descriptor (for which the lock must be held) and the actual waiting (for which you must not hold the lock). Also see this thread and read the library code to see how the problem is currently circumvented.