socket-0.1.0.0: A binding to the POSIX sockets interface

Copyright(c) Lars Petersen 2015
LicenseMIT
Maintainerinfo@lars-petersen.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

System.Socket

Contents

Description

{-# LANGUAGE OverloadedStrings #-}
module Main where

import System.Socket
import Data.ByteString
import Control.Monad
import Control.Concurrent

main :: IO ()
main = do
  s <- socket :: IO (Socket SockAddrIn STREAM TCP)
  bind s (SockAddrIn 8080 (pack [127,0,0,1]))
  listen s 5
  forever $ do
    (peer,addr) <- accept s
    forkIO $ do
      send peer "Hello world!"
      close peer

Synopsis

Operations

socket

socket :: (Address a, Type t, Protocol p) => IO (Socket a t p) Source

Creates a new socket.

Whereas the underlying POSIX socket function takes 3 parameters, this library encodes this information in the type variables. This rules out several kinds of errors and escpecially simplifies the handling of addresses (by using associated type families). Examples:

-- create a IPv4-UDP-datagram socket
sock <- socket :: IO (Socket SockAddrIn DGRAM UDP)
-- create a IPv6-TCP-streaming socket
sock6 <- socket :: IO (Socket SockAddrIn6 STREAM TCP)
  • This operation sets up a finalizer that automatically closes the socket when the garbage collection decides to collect it. This is just a fail-safe. You might still run out of file descriptors as there's no guarantee about when the finalizer is run. You're advised to manually close the socket when it's no longer needed.
  • This operation configures the socket non-blocking to work seamlessly with the runtime system's event notification mechanism.
  • This operation can safely deal with asynchronous exceptions without leaking file descriptors.
  • This operation throws SocketExceptions:
EAFNOSUPPORT
The socket domain is not supported.
EMFILE
The process is out file descriptors.
ENFILE
The system is out file descriptors.
EPROTONOSUPPORT
The socket protocol is not supported (for this socket domain).
EPROTOTYPE
The socket type is not supported by the protocol.
EACCES
The process is lacking necessary privileges.
ENOMEM
Insufficient memory.

bind

bind :: (Address a, Type t, Protocol p) => Socket a t p -> a -> IO () Source

Bind a socket to an address.

  • Calling bind on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • It is assumed that c_bind never blocks and therefore EINPROGRESS, EALREADY and EINTR don't occur. This assumption is supported by the fact that the Linux manpage doesn't mention any of these errors, the Posix manpage doesn't mention the last one and even MacOS' implementation will never fail with any of these when the socket is configured non-blocking as argued here.
  • The following SocketExceptions are relevant and might be thrown (see man bind for more exceptions regarding SockAddrUn sockets):
EADDRINUSE
The address is in use.
EADDRNOTAVAIL
The address is not available.
EBADF
Not a valid file descriptor.
EINVAL
Socket is already bound and cannot be re-bound or the socket has been shut down.
ENOBUFS
Insufficient resources.
EOPNOTSUPP
The socket type does not support binding.
EACCES
The address is protected and the process is lacking permission.
EISCONN
The socket is already connected.
ELOOP
More than {SYMLOOP_MAX} symbolic links were encountered during resolution of the pathname in address.
ENAMETOOLONG
The length of a pathname exceeds {PATH_MAX}, or pathname resolution of a symbolic link produced an intermediate result with a length that exceeds {PATH_MAX}.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EAFNOSUPPORT
The address family is invalid.
ENOTSOCK
The file descriptor is not a socket.
EINVAL
Address length does not match address family.

listen

listen :: (Address a, Type t, Protocol p) => Socket a t p -> Int -> IO () Source

Accept connections on a connection-mode socket.

  • Calling listen on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • The second parameter is called backlog and sets a limit on how many unaccepted connections the socket implementation shall queue. A value of 0 leaves the decision to the implementation.
  • This operation throws SocketExceptions:
EBADF
Not a valid file descriptor (only after socket has been closed).
EDESTADDRREQ
The socket is not bound and the protocol does not support listening on an unbound socket.
EINVAL
The socket is already connected or has been shut down.
ENOTSOCK
The file descriptor is not a socket (should be impossible).
EOPNOTSUPP
The protocol does not support listening.
EACCES
The process is lacking privileges.
ENOBUFS
Insufficient resources.

accept

accept :: (Address a, Type t, Protocol p) => Socket a t p -> IO (Socket a t p, a) Source

Accept a new connection.

  • Calling accept on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • This operation configures the new socket non-blocking (TODO: use accept4 if available).
  • This operation sets up a finalizer for the new socket that automatically closes the socket when the garbage collection decides to collect it. This is just a fail-safe. You might still run out of file descriptors as there's no guarantee about when the finalizer is run. You're advised to manually close the socket when it's no longer needed.
  • This operation catches EAGAIN, EWOULDBLOCK and EINTR internally and retries automatically.
  • This operation throws SocketExceptions:
EBADF
Not a valid file descriptor (only after the socket has been closed).
ECONNABORTED
A connection has been aborted.
EINVAL
The socket is not accepting/listening.
EMFILE
The process is out file descriptors.
ENFILE
The system is out file descriptors.
ENOBUFS
No buffer space available.
ENOMEM
Out of memory.
ENOSOCK
Not a valid socket descriptor (should be impossible).
EOPNOTSUPP
The socket type does not support accepting connections.
EPROTO
Generic protocol error.

connect

connect :: (Address a, Type t, Protocol p) => Socket a t p -> a -> IO () Source

Connects to an remote address.

  • Calling connect on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • This function returns as soon as a connection has either been established or refused. A failed connection attempt does not throw an exception if EINTR or EINPROGRESS were caught internally. The operation just unblocks and returns in this case. The approach is to just try to read or write the socket and eventually fail there instead. Also see these considerations for an explanation. EINTR and EINPROGRESS are handled internally and won't be thrown.
  • The following SocketExceptions are relevant and might be thrown if the OS was able to decide the connection request synchronously:
EADDRNOTAVAIL
The address is not available.
EBADF
The file descriptor is invalid.
ECONNREFUSED
The target was not listening or refused the connection.
EISCONN
The socket is already connected.
ENETUNREACH
The network is unreachable.
ETIMEDOUT
The connect timed out before a connection was established.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EAFNOTSUPPORT
Address family does not match the socket.
ENOTSOCK
The descriptor is not a socket.
EPROTOTYPE
The address type does not match the socket.

send

send :: (Address a, Type t, Protocol p) => Socket a t p -> ByteString -> MsgFlags -> IO Int Source

Send a message on a connected socket.

  • Calling send on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • The operation returns the number of bytes sent.
  • EAGAIN, EWOULDBLOCK and EINTR and handled internally and won't be thrown.
  • The flag MSG_NOSIGNAL is set to supress signals which are pointless.
  • The following SocketExceptions are relevant and might be thrown:
EBADF
The file descriptor is invalid.
ECONNRESET
The peer forcibly closed the connection.
EDESTADDREQ
Remote address has not been set, but is required.
EMSGSIZE
The message is too large to be sent all at once, but the protocol requires this.
ENOTCONN
The socket is not connected.
EPIPE
The socket is shut down for writing or the socket is not connected anymore.
EACCESS
The process is lacking permissions.
EIO
An I/O error occured while writing to the filesystem.
ENETDOWN
The local network interface is down.
ENETUNREACH
No route to network.
ENOBUFS
Insufficient resources to fulfill the request.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EOPNOTSUPP
The specified flags are not supported.
ENOTSOCK
The descriptor does not refer to a socket.

sendTo

sendTo :: (Address a, Type t, Protocol p) => Socket a t p -> ByteString -> MsgFlags -> a -> IO Int Source

Send a message on a socket with a specific destination address.

  • Calling sendTo on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • The operation returns the number of bytes sent.
  • EAGAIN, EWOULDBLOCK and EINTR and handled internally and won't be thrown.
  • The flag MSG_NOSIGNAL is set to supress signals which are pointless.
  • The following SocketExceptions are relevant and might be thrown:
EBADF
The file descriptor is invalid.
ECONNRESET
The peer forcibly closed the connection.
EDESTADDREQ
Remote address has not been set, but is required.
EMSGSIZE
The message is too large to be sent all at once, but the protocol requires this.
ENOTCONN
The socket is not connected.
EPIPE
The socket is shut down for writing or the socket is not connected anymore.
EACCESS
The process is lacking permissions.
EDESTADDRREQ
The destination address is required.
EHOSTUNREACH
The destination host cannot be reached.
EIO
An I/O error occured.
EISCONN
The socket is already connected.
ENETDOWN
The local network is down.
ENETUNREACH
No route to the network.
ENUBUFS
Insufficient resources to fulfill the request.
ENOMEM
Insufficient memory to fulfill the request.
ELOOP
AF_UNIX only.
ENAMETOOLONG
AF_UNIX only.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EAFNOTSUPP
The address family does not match.
EOPNOTSUPP
The specified flags are not supported.
ENOTSOCK
The descriptor does not refer to a socket.
EINVAL
The address len does not match.

recv

recv :: (Address a, Type t, Protocol p) => Socket a t p -> Int -> MsgFlags -> IO ByteString Source

Receive a message on a connected socket.

  • Calling recv on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • The operation takes a buffer size in bytes a first parameter which limits the maximum length of the returned ByteString.
  • EAGAIN, EWOULDBLOCK and EINTR and handled internally and won't be thrown.
  • The following SocketExceptions are relevant and might be thrown:
EBADF
The file descriptor is invalid.
ECONNRESET
The peer forcibly closed the connection.
ENOTCONN
The socket is not connected.
ETIMEDOUT
The connection timed out.
EIO
An I/O error occured while writing to the filesystem.
ENOBUFS
Insufficient resources to fulfill the request.
ENONMEM
Insufficient memory to fulfill the request.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EOPNOTSUPP
The specified flags are not supported.
ENOTSOCK
The descriptor does not refer to a socket.

recvFrom

recvFrom :: forall a t p. (Address a, Type t, Protocol p) => Socket a t p -> Int -> MsgFlags -> IO (ByteString, a) Source

Receive a message on a socket and additionally yield the peer address.

  • Calling recvFrom on a closed socket throws EBADF even if the former file descriptor has been reassigned.
  • The operation takes a buffer size in bytes a first parameter which limits the maximum length of the returned ByteString.
  • EAGAIN, EWOULDBLOCK and EINTR and handled internally and won't be thrown.
  • The following SocketExceptions are relevant and might be thrown:
EBADF
The file descriptor is invalid.
ECONNRESET
The peer forcibly closed the connection.
ENOTCONN
The socket is not connected.
ETIMEDOUT
The connection timed out.
EIO
An I/O error occured while writing to the filesystem.
ENOBUFS
Insufficient resources to fulfill the request.
ENONMEM
Insufficient memory to fulfill the request.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EOPNOTSUPP
The specified flags are not supported.
ENOTSOCK
The descriptor does not refer to a socket.

close

close :: (Address a, Type t, Protocol p) => Socket a t p -> IO () Source

Closes a socket.

  • This operation is idempotent and thus can be performed more than once without throwing an exception. If it throws an exception it is presumably a not recoverable situation and the process should exit.
  • This operation does not block.
  • This operation wakes up all threads that are currently blocking on this socket. All other threads are guaranteed not to block on operations on this socket in the future. Threads that perform operations other than close on this socket will fail with EBADF after the socket has been closed (close replaces the Fd in the MVar with -1 to reliably avoid use-after-free situations).
  • The following SocketExceptions are relevant and might be thrown:
EIO
An I/O error occured while writing to the filesystem.
  • The following SocketExceptions are theoretically possible, but should not occur if the library is correct:
EBADF
The file descriptor is invalid.

Sockets

data Socket d t p Source

A generic socket type. Also see socket for details.

The socket is just an MVar-wrapped file descriptor. It is exposed 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 totally different connection. 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 seperate 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.

Addresses

SockAddrUn

SockAddrIn

SockAddrIn6

Types

STREAM

data STREAM Source

Instances

DGRAM

data DGRAM Source

Instances

SEQPACKET

Protocols

UDP

data UDP Source

Instances

TCP

data TCP Source

Instances

SCTP

data SCTP Source

Instances

MsgFlags

msgEOR

msgOOB

msgNOSIGNAL

getSockOpt / setSockOpt

class GetSockOpt o where Source

Methods

getSockOpt :: Socket f t p -> IO o Source

class SetSockOpt o where Source

Methods

setSockOpt :: Socket f t p -> o -> IO () Source

Generic socket options

SO_ACCEPTCONN

SocketException