Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types and functions related to the POSIX sockets API. Unusual characteristics:
- Any time the standard calls for
socklen_t
, we useCInt
instead. Linus Torvalds writes that "Any sane library must havesocklen_t
be the same size asint
. 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
Addr
ByteArray
/MutableByteArray
buffer type. They all callsend
orrecv
exactly once. They do not repeatedly make syscalls like some of the functions innetwork
. 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 unpinnedByteArray
arguments, they will copy the contents into pinned memory before invoking the foreign function.
Synopsis
- uninterruptibleSocket :: Domain -> Type -> Protocol -> IO (Either Errno Fd)
- uninterruptibleSocketPair :: Domain -> Type -> Protocol -> IO (Either Errno (Fd, Fd))
- uninterruptibleBind :: Fd -> SocketAddress -> IO (Either Errno ())
- connect :: Fd -> SocketAddress -> IO (Either Errno ())
- uninterruptibleConnect :: Fd -> SocketAddress -> IO (Either Errno ())
- uninterruptibleListen :: Fd -> CInt -> IO (Either Errno ())
- accept :: Fd -> CInt -> IO (Either Errno (CInt, SocketAddress, Fd))
- uninterruptibleAccept :: Fd -> CInt -> IO (Either Errno (CInt, SocketAddress, Fd))
- accept_ :: Fd -> IO (Either Errno Fd)
- uninterruptibleGetSocketName :: Fd -> CInt -> IO (Either Errno (CInt, SocketAddress))
- uninterruptibleGetSocketOption :: Fd -> Level -> OptionName -> CInt -> IO (Either Errno (CInt, OptionValue))
- close :: Fd -> IO (Either Errno ())
- uninterruptibleClose :: Fd -> IO (Either Errno ())
- uninterruptibleErrorlessClose :: Fd -> IO ()
- uninterruptibleShutdown :: Fd -> ShutdownType -> IO (Either Errno ())
- send :: Fd -> Addr -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- sendByteArray :: Fd -> ByteArray -> CInt -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- sendMutableByteArray :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- uninterruptibleSend :: Fd -> Addr -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- uninterruptibleSendByteArray :: Fd -> ByteArray -> CInt -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- uninterruptibleSendMutableByteArray :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Send -> IO (Either Errno CSize)
- uninterruptibleSendToByteArray :: Fd -> ByteArray -> CInt -> CSize -> MessageFlags Send -> SocketAddress -> IO (Either Errno CSize)
- uninterruptibleSendToMutableByteArray :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Send -> SocketAddress -> IO (Either Errno CSize)
- receive :: Fd -> Addr -> CSize -> MessageFlags Receive -> IO (Either Errno CSize)
- receiveByteArray :: Fd -> CSize -> MessageFlags Receive -> IO (Either Errno ByteArray)
- uninterruptibleReceive :: Fd -> Addr -> CSize -> MessageFlags Receive -> IO (Either Errno CSize)
- uninterruptibleReceiveMutableByteArray :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Receive -> IO (Either Errno CSize)
- uninterruptibleReceiveFromMutableByteArray :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Receive -> CInt -> IO (Either Errno (CInt, SocketAddress, CSize))
- uninterruptibleReceiveFromMutableByteArray_ :: Fd -> MutableByteArray RealWorld -> CInt -> CSize -> MessageFlags Receive -> IO (Either Errno CSize)
- hostToNetworkLong :: Word32 -> Word32
- hostToNetworkShort :: Word16 -> Word16
- networkToHostLong :: Word32 -> Word32
- networkToHostShort :: Word16 -> Word16
- newtype Domain = Domain CInt
- newtype Type = Type CInt
- newtype Protocol = Protocol CInt
- newtype OptionName = OptionName CInt
- newtype OptionValue = OptionValue ByteArray
- newtype Level = Level CInt
- newtype MessageFlags :: Message -> Type where
- MessageFlags :: CInt -> MessageFlags m
- newtype ShutdownType = ShutdownType CInt
- newtype SocketAddress = SocketAddress ByteArray
- data SocketAddressInternet = SocketAddressInternet {}
- newtype SocketAddressUnix = SocketAddressUnix {}
- encodeSocketAddressInternet :: SocketAddressInternet -> SocketAddress
- encodeSocketAddressUnix :: SocketAddressUnix -> SocketAddress
- decodeSocketAddressInternet :: SocketAddress -> Maybe SocketAddressInternet
- sizeofSocketAddressInternet :: CInt
- unix :: Domain
- unspecified :: Domain
- internet :: Domain
- internet6 :: Domain
- stream :: Type
- datagram :: Type
- raw :: Type
- sequencedPacket :: Type
- defaultProtocol :: Protocol
- rawProtocol :: Protocol
- icmp :: Protocol
- tcp :: Protocol
- udp :: Protocol
- ip :: Protocol
- ipv6 :: Protocol
- peek :: MessageFlags Receive
- outOfBand :: MessageFlags m
- waitAll :: MessageFlags Receive
- read :: ShutdownType
- write :: ShutdownType
- readWrite :: ShutdownType
- levelSocket :: Level
- optionError :: OptionName
Functions
Socket
uninterruptibleSocket Source #
:: Domain | Communications domain (e.g. |
-> Type | Socket type (e.g. |
-> 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 #
:: Domain | Communications domain (probably |
-> Type | Socket type (e.g. |
-> 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
:: 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
:: 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 #
:: 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 #
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
:: 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 #
:: 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.
A variant of accept
that does not provide the user with a
SocketAddress
detailing the peer.
Get Socket Name
uninterruptibleGetSocketName Source #
Retrieve the locally-bound name of the specified socket. The
POSIX specification
of getsockname
includes more details.
Get Socket Option
uninterruptibleGetSocketOption Source #
:: 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 a socket. The POSIX specification includes more details. This uses the safe FFI.
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 #
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
:: 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.
:: 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.
:: 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.
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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
:: 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.
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 #
:: 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 #
:: 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 #
:: 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 |
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 #
:: 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
A socket communications domain, sometimes referred to as a family. The spec
mandates AF_UNIX
, AF_UNSPEC
, and AF_INET
.
A socket type. The spec mandates SOCK_STREAM
, SOCK_DGRAM
,
and SOCK_SEQPACKET
. Other types may be available on a per-platform
basis.
newtype OptionName Source #
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.
MessageFlags :: CInt -> MessageFlags m |
Instances
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.
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.
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
.
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
unspecified :: Domain Source #
The AF_UNSPEC
communications domain.
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
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.
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
)