posix-api-0.2.0.0: posix bindings

Safe HaskellNone
LanguageHaskell2010

Posix.Socket

Contents

Description

Types and functions related to the POSIX sockets API. Unusual characteristics:

  • Any time the standard calls for socklen_t, we use CInt instead. Linus Torvalds writes that "Any sane library must have socklen_t be the same size as int. Anything else breaks any BSD socket layer stuff."
  • Send and receive each have several variants. They are distinguished by the safeunsafe FFI use and by the AddrByteArray/MutableByteArray buffer type. They all call send or recv exactly once. They do not repeatedly make syscalls like some of the functions in network. Users who want that behavior need to build on top of this package.
  • There are no requirements on the pinnedness of ByteArray arguments passed to any of these functions. If wrappers of the safe FFI are passed unpinned ByteArray arguments, they will copy the contents into pinned memory before invoking the foreign function.
Synopsis

Functions

Socket

uninterruptibleSocket Source #

Arguments

:: Domain

Communications domain (e.g. internet, unix)

-> Type

Socket type (e.g. datagram, stream) with flags

-> Protocol

Protocol

-> IO (Either Errno Fd) 

Create an endpoint for communication, returning a file descriptor that refers to that endpoint. The POSIX specification includes more details. No special preparation is required before calling this function. The author believes that it cannot block for a prolonged period of time.

Socket Pair

uninterruptibleSocketPair Source #

Arguments

:: Domain

Communications domain (probably unix)

-> Type

Socket type (e.g. datagram, stream) with flags

-> Protocol

Protocol

-> IO (Either Errno (Fd, Fd)) 

Create an unbound pair of connected sockets in a specified domain, of a specified type, under the protocol optionally specified by the protocol argument. The POSIX specification includes more details. No special preparation is required before calling this function. The author believes that it cannot block for a prolonged period of time.

Bind

uninterruptibleBind Source #

Arguments

:: Fd

Socket

-> SocketAddress

Socket address, extensible tagged union

-> IO (Either Errno ()) 

Assign a local socket address address to a socket identified by descriptor socket that has no local socket address assigned. The POSIX specification includes more details. The SocketAddress represents the sockaddr pointer argument, together with its socklen_t size, as a byte array. This allows bind to be used with sockaddr extensions on various platforms. No special preparation is required before calling this function. The author believes that it cannot block for a prolonged period of time.

Connect

connect Source #

Arguments

:: Fd

Fd

-> SocketAddress

Socket address, extensible tagged union

-> IO (Either Errno ()) 

Connect the socket to the specified socket address. The POSIX specification includes more details.

uninterruptibleConnect Source #

Arguments

:: Fd

Fd

-> SocketAddress

Socket address, extensible tagged union

-> IO (Either Errno ()) 

Connect the socket to the specified socket address. The POSIX specification includes more details. The only sensible way to use this is to give a nonblocking socket as the argument.

Listen

uninterruptibleListen Source #

Arguments

:: Fd

Socket

-> CInt

Backlog

-> IO (Either Errno ()) 

Mark the socket as a passive socket, that is, as a socket that will be used to accept incoming connection requests using accept. The POSIX specification includes more details. No special preparation is required before calling this function. The author believes that it cannot block for a prolonged period of time.

Accept

accept Source #

Arguments

:: Fd

Listening socket

-> CInt

Maximum socket address size

-> IO (Either Errno (CInt, SocketAddress, Fd))

Peer information and connected socket

Extract the first connection on the queue of pending connections. The POSIX specification includes more details. This function's type differs slightly from the specification:

int accept(int socket, struct sockaddr *restrict address, socklen_t *restrict address_len);

Instead of requiring the caller to prepare buffers through which information is returned, this haskell binding to accept prepares those buffers internally. This eschews C's characteristic buffer-passing in favor of the Haskell convention of allocating internally and returning.

More specifically, this binding lacks an argument corresponding to the sockaddr buffer from the specification. That mutable buffer is allocated internally, resized and frozen upon a success, and returned along with the file descriptor of the accepted socket. The size of this buffer is determined by the second argument (maximum socket address size). This size argument is also writen to the address_len buffer, which is also allocated internally. The size returned through this pointer is used to resize the sockaddr buffer, which is then frozen so that an immutable SocketAddress is returned to the end user.

For applications uninterested in the peer (described by sockaddr), POSIX accept allows the null pointer to be passed as both address and address_len. This behavior is provided by accept_.

uninterruptibleAccept Source #

Arguments

:: Fd

Listening socket

-> CInt

Maximum socket address size

-> IO (Either Errno (CInt, SocketAddress, Fd))

Peer information and connected socket

See accept. This uses the unsafe FFI. Consequently, it does not not need to allocate pinned memory. It only makes sense to call this on a nonblocking socket.

accept_ Source #

Arguments

:: Fd

Listening socket

-> IO (Either Errno Fd)

Connected socket

A variant of accept that does not provide the user with a SocketAddress detailing the peer.

Get Socket Name

uninterruptibleGetSocketName Source #

Arguments

:: Fd

Socket

-> CInt

Maximum socket address size

-> IO (Either Errno (CInt, SocketAddress)) 

Retrieve the locally-bound name of the specified socket. The POSIX specification of getsockname includes more details.

Get Socket Option

uninterruptibleGetSocketOption Source #

Arguments

:: Fd

Socket

-> Level

Socket level

-> OptionName 
-> CInt

Maximum option value size

-> IO (Either Errno (CInt, OptionValue)) 

Retrieve the value for the option specified by the Option argument for the socket specified by the Fd argument. The POSIX specification of getsockopt includes more details.

Close

close Source #

Arguments

:: Fd

Socket

-> IO (Either Errno ()) 

Close a socket. The POSIX specification includes more details. This uses the safe FFI.

uninterruptibleClose Source #

Arguments

:: Fd

Socket

-> IO (Either Errno ()) 

Close a socket. This uses the unsafe FFI. According to the POSIX specification, "If fildes refers to a socket, close() shall cause the socket to be destroyed. If the socket is in connection-mode, and the SO_LINGER option is set for the socket with non-zero linger time, and the socket has untransmitted data, then close() shall block for up to the current linger interval until all data is transmitted."

uninterruptibleErrorlessClose Source #

Arguments

:: Fd

Socket

-> IO () 

Close a socket with the unsafe FFI. Do not check for errors. It is only appropriate to use this when a socket is being closed to handle an exceptional case. Since the user will want the propogate the original exception, the exception provided by uninterruptibleClose would just be discarded. This function allows us to potentially avoid an additional FFI call to getErrno.

Shutdown

uninterruptibleShutdown :: Fd -> ShutdownType -> IO (Either Errno ()) Source #

Shutdown a socket. This uses the unsafe FFI.

Send

send Source #

Arguments

:: Fd

Connected socket

-> Addr

Source address

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from an address over a network socket. This is not guaranteed to send the entire length. This uses the safe FFI since it may block indefinitely.

sendByteArray Source #

Arguments

:: Fd

Socket

-> ByteArray

Source byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a byte array over a network socket. Users may specify an offset and a length to send fewer bytes than are actually present in the array. Since this uses the safe FFI, it allocates a pinned copy of the bytearry if it was not already pinned.

sendMutableByteArray Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Source byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a mutable byte array over a network socket. Users may specify an offset and a length to send fewer bytes than are actually present in the array. Since this uses the safe FFI, it allocates a pinned copy of the bytearry if it was not already pinned.

uninterruptibleSend Source #

Arguments

:: Fd

Socket

-> Addr

Source address

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from an address over a network socket. This uses the unsafe FFI. Users of this function should be sure to set flags that prohibit this from blocking. On Linux this is accomplished with O_NONBLOCK. It is often desirable to call threadWaitWrite on a nonblocking socket before calling unsafeSend on it.

uninterruptibleSendByteArray Source #

Arguments

:: Fd

Socket

-> ByteArray

Source byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a byte array over a network socket. This uses the unsafe FFI; considerations pertaining to sendUnsafe apply to this function as well. Users may specify a length to send fewer bytes than are actually present in the array.

uninterruptibleSendMutableByteArray Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Source mutable byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a mutable byte array over a network socket. This uses the unsafe FFI; considerations pertaining to sendUnsafe apply to this function as well. Users specify an offset and a length to send fewer bytes than are actually present in the array.

Send To

uninterruptibleSendToByteArray Source #

Arguments

:: Fd

Socket

-> ByteArray

Source byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> SocketAddress

Socket Address

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a byte array over an unconnected network socket. This uses the unsafe FFI; considerations pertaining to sendToUnsafe apply to this function as well. The offset and length arguments cause a slice of the byte array to be sent rather than the entire byte array.

uninterruptibleSendToMutableByteArray Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Source byte array

-> CInt

Offset into source array

-> CSize

Length in bytes

-> MessageFlags Send

Flags

-> SocketAddress

Socket Address

-> IO (Either Errno CSize)

Number of bytes pushed to send buffer

Send data from a mutable byte array over an unconnected network socket. This uses the unsafe FFI; considerations pertaining to sendToUnsafe apply to this function as well. The offset and length arguments cause a slice of the mutable byte array to be sent rather than the entire byte array.

Receive

receive Source #

Arguments

:: Fd

Socket

-> Addr

Source address

-> CSize

Length in bytes

-> MessageFlags Receive

Flags

-> IO (Either Errno CSize) 

Receive data into an address from a network socket. This wraps recv using the safe FFI. When the returned size is zero, there are no additional bytes to receive and the peer has performed an orderly shutdown.

receiveByteArray Source #

Arguments

:: Fd

Socket

-> CSize

Length in bytes

-> MessageFlags Receive

Flags

-> IO (Either Errno ByteArray) 

Receive data into a byte array from a network socket. This wraps recv using the safe FFI. When the returned size is zero, there are no additional bytes to receive and the peer has performed an orderly shutdown.

uninterruptibleReceive Source #

Arguments

:: Fd

Socket

-> Addr

Source address

-> CSize

Length in bytes

-> MessageFlags Receive

Flags

-> IO (Either Errno CSize) 

Receive data into an address from a network socket. This wraps recv using the unsafe FFI. Users of this function should be sure to set flags that prohibit this from blocking. On Linux this is accomplished by setting the MSG_DONTWAIT flag and handling the resulting EAGAIN or EWOULDBLOCK. When the returned size is zero, there are no additional bytes to receive and the peer has performed an orderly shutdown.

uninterruptibleReceiveMutableByteArray Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Destination byte array

-> CInt

Destination offset

-> CSize

Maximum bytes to receive

-> MessageFlags Receive

Flags

-> IO (Either Errno CSize)

Bytes received into array

Receive data into an address from a network socket. This uses the unsafe FFI; considerations pertaining to receiveUnsafe apply to this function as well. Users may specify a length to receive fewer bytes than are actually present in the mutable byte array.

Receive From

uninterruptibleReceiveFromMutableByteArray Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Destination byte array

-> CInt

Destination offset

-> CSize

Maximum bytes to receive

-> MessageFlags Receive

Flags

-> CInt

Maximum socket address size

-> IO (Either Errno (CInt, SocketAddress, CSize))

Remote host, bytes received into array, bytes needed for addrlen.

Receive data into an address from an unconnected network socket. This uses the unsafe FFI. Users may specify an offset into the destination byte array. This function does not resize the buffer.

uninterruptibleReceiveFromMutableByteArray_ Source #

Arguments

:: Fd

Socket

-> MutableByteArray RealWorld

Destination byte array

-> CInt

Destination offset

-> CSize

Maximum bytes to receive

-> MessageFlags Receive

Flags

-> IO (Either Errno CSize)

Number of bytes received into array

Receive data into an address from a network socket. This uses the unsafe FFI. This does not return the socket address of the remote host that sent the packet received.

Byte-Order Conversion

These functions are used to convert IPv4 addresses and ports between network byte order and host byte order. They are essential when working with SocketAddressInternet. To avoid getting in the way of GHC compile-time optimizations, these functions are not actually implemented with FFI calls to htonl and friends. Rather, they are reimplemented in haskell.

hostToNetworkLong :: Word32 -> Word32 Source #

Convert a 32-bit word from host to network byte order (e.g. htonl).

hostToNetworkShort :: Word16 -> Word16 Source #

Convert a 16-bit word from host to network byte order (e.g. htons).

networkToHostLong :: Word32 -> Word32 Source #

Convert a 32-bit word from network to host byte order (e.g. ntohl).

networkToHostShort :: Word16 -> Word16 Source #

Convert a 16-bit word from network to host byte order (e.g. ntohs).

Types

newtype Domain Source #

A socket communications domain, sometimes referred to as a family. The spec mandates AF_UNIX, AF_UNSPEC, and AF_INET.

Constructors

Domain CInt 

newtype Type Source #

A socket type. The spec mandates SOCK_STREAM, SOCK_DGRAM, and SOCK_SEQPACKET. Other types may be available on a per-platform basis.

Constructors

Type CInt 

newtype Protocol Source #

Constructors

Protocol CInt 

newtype OptionName Source #

Constructors

OptionName CInt 

newtype OptionValue Source #

The option_value data.

Constructors

OptionValue ByteArray 

newtype Level Source #

Constructors

Level CInt 

newtype MessageFlags :: Message -> Type where Source #

Receive flags are given by MessageFlags Receive and send flags are given by MessageFlags Send. This is done because there are several flags that are applicable in either a receiving context or a sending context.

Constructors

MessageFlags :: CInt -> MessageFlags m 
Instances
Eq (MessageFlags a) Source # 
Instance details

Defined in Posix.Socket.Types

Semigroup (MessageFlags m) Source # 
Instance details

Defined in Posix.Socket.Types

Monoid (MessageFlags m) Source # 
Instance details

Defined in Posix.Socket.Types

Bits (MessageFlags a) Source # 
Instance details

Defined in Posix.Socket.Types

newtype ShutdownType Source #

Which end of the socket to shutdown.

Constructors

ShutdownType CInt 

Socket Address

Types

newtype SocketAddress Source #

The sockaddr data. This is an extensible tagged union, so this library has chosen to represent it as byte array. It is up to platform-specific libraries to inhabit this type with values.

Constructors

SocketAddress ByteArray 

data SocketAddressInternet Source #

An address for an Internet socket over IPv4. The POSIX specification mandates three fields:

sa_family_t     sin_family   AF_INET
in_port_t       sin_port     Port number
struct in_addr  sin_addr     IP address

This type omits the first field since is a constant that is only relevant for serialization purposes. The spec also mandates that sin_port and sin_addr be in network byte order, so keep in mind that these values are not immidiately useable.

Constructors

SocketAddressInternet 

Fields

newtype SocketAddressUnix Source #

An address for a UNIX domain socket. The POSIX specification mandates two fields:

sa_family_t  sun_family  Address family. 
char         sun_path[]  Socket pathname. 

However, the first field is omitted since it is always AF_UNIX. It is adding during serialization. Although sun_path is a null-terminated string, SocketAddressUnix should not have a trailing null byte. The conversion function encodeSocketAddressUnix adds the null terminator. The size of path should not equal or exceed the platform-dependent size of sun_path.

Constructors

SocketAddressUnix 

Fields

Encoding

encodeSocketAddressInternet :: SocketAddressInternet -> SocketAddress Source #

Serialize a IPv4 socket address so that it may be passed to bind. This serialization is operating-system dependent.

encodeSocketAddressUnix :: SocketAddressUnix -> SocketAddress Source #

Serialize a unix domain socket address so that it may be passed to bind. This serialization is operating-system dependent. If the path provided by the argument equals or exceeds the size of sun_path (typically in the range 92 to 108 but varies by platform), the socket address will instead be given the empty string as its path. This typically results in bind returning an error code.

Decoding

Sizes

sizeofSocketAddressInternet :: CInt Source #

The size of a serialized internet socket address.

Data Construction

Socket Domains

unix :: Domain Source #

The AF_UNIX communications domain.

unspecified :: Domain Source #

The AF_UNSPEC communications domain.

internet :: Domain Source #

The AF_INET communications domain.

internet6 :: Domain Source #

The AF_INET6 communications domain. POSIX declares raw sockets optional. However, they are included here for convenience. Please open an issue if this prevents this library from compiling on a POSIX-compliant operating system that anyone uses for haskell development.

Socket Types

stream :: Type Source #

The SOCK_STREAM socket type.

datagram :: Type Source #

The SOCK_DGRAM socket type.

raw :: Type Source #

The SOCK_RAW socket type. POSIX declares raw sockets optional. However, they are included here for convenience. Please open an issue if this prevents this library from compiling on a POSIX-compliant operating system that anyone uses for haskell development. Keep in mind that even though raw sockets may exist on all POSIX-compliant operating systems, they may differ in their behavior.

sequencedPacket :: Type Source #

The SOCK_SEQPACKET socket type.

Protocols

defaultProtocol :: Protocol Source #

The default protocol for a socket type.

rawProtocol :: Protocol Source #

The IPPROTO_RAW protocol.

icmp :: Protocol Source #

The IPPROTO_ICMP protocol.

tcp :: Protocol Source #

The IPPROTO_TCP protocol.

udp :: Protocol Source #

The IPPROTO_UDP protocol.

ip :: Protocol Source #

The IPPROTO_IP protocol.

ipv6 :: Protocol Source #

The IPPROTO_IPV6 protocol.

Receive Flags

peek :: MessageFlags Receive Source #

The MSG_PEEK receive flag.

outOfBand :: MessageFlags m Source #

The MSG_OOB receive flag or send flag.

waitAll :: MessageFlags Receive Source #

The MSG_WAITALL receive flag.

Shutdown Types

read :: ShutdownType Source #

Disable further receive operations (e.g. SHUT_RD)

write :: ShutdownType Source #

Disable further send operations (e.g. SHUT_WR)

readWrite :: ShutdownType Source #

Disable further send operations (e.g. SHUT_RDWR)

Socket Levels

levelSocket :: Level Source #

Socket error status (e.g. SOL_SOCKET)

Option Names

optionError :: OptionName Source #

Socket error status (e.g. SO_ERROR)