posix-socket-0.3: Bindings to the POSIX socket API

Safe HaskellNone
LanguageHaskell98

System.Posix.Socket

Contents

Description

POSIX sockets.

Synopsis

Socket types

data Socket f Source #

Socket of a particular family.

Instances

Eq (Socket f) Source # 

Methods

(==) :: Socket f -> Socket f -> Bool #

(/=) :: Socket f -> Socket f -> Bool #

withSocketFd :: MonadBase IO μ => Socket f -> (Fd -> IO α) -> μ α Source #

Lock the socket and pass the underlying file descriptor to the given action.

unsafeSocketFd :: MonadBase IO μ => Socket f -> μ Fd Source #

Get the underlying file descriptor.

unsafeSocketFromFd :: MonadBase IO μ => Fd -> μ (Socket f) Source #

Use file descriptor as a socket.

class SockAddr (SockFamilyAddr f) => SockFamily f where Source #

Socket family.

Minimal complete definition

sockFamilyCode

Associated Types

type SockFamilyAddr f Source #

Methods

sockFamilyCode :: Proxy f -> CInt Source #

Socket family code.

class SockAddr a where Source #

Socket address.

Methods

sockAddrMaxSize :: Proxy a -> Int Source #

Maximum size of a socket address.

sockAddrSize :: a -> Int Source #

Size of a particular socket address.

peekSockAddr Source #

Arguments

:: Ptr a

Buffer

-> Int

Buffer size

-> IO a 

Read socket address from a memory buffer.

pokeSockAddr Source #

Arguments

:: Ptr a

Buffer of sufficient size

-> a

The address to poke

-> IO () 

Write socket address to a memory buffer.

pattern SOCK_STREAM :: SockType Source #

See socket(2).

pattern SOCK_DGRAM :: SockType Source #

See socket(2).

pattern SOCK_RAW :: SockType Source #

See socket(2).

pattern SOCK_RDM :: SockType Source #

See socket(2).

pattern SOCK_SEQPACKET :: SockType Source #

See socket(2).

defaultSockProto :: SockProto Source #

Default socket protocol (corresponds to 0).

class Storable (SockOptRaw o) => SockOpt o where Source #

Socket option.

Minimal complete definition

sockOptRaw, sockOptValue, sockOptLevel, sockOptCode

Associated Types

type SockOptValue o Source #

Option value type

type SockOptRaw o Source #

FFI-level option value type

type SockOptReadable o :: Bool Source #

Whether option is readable

type SockOptWritable o :: Bool Source #

Whether option is writable

Methods

sockOptRaw :: Proxy o -> SockOptValue o -> SockOptRaw o Source #

Convert to FFI-level value

sockOptValue :: Proxy o -> SockOptRaw o -> SockOptValue o Source #

Convert from FFI-level value

sockOptLevel :: Proxy o -> CInt Source #

Option protocol level

sockOptCode :: Proxy o -> CInt Source #

Option code

Instances

SockOpt SO_REUSEADDR Source # 
SockOpt SO_KEEPALIVE Source # 
SockOpt SO_ERROR Source # 

pattern MSG_PEEK :: MsgFlags Source #

See recvmsg(2) and sendmsg(2).

pattern MSG_TRUNC :: MsgFlags Source #

See recvmsg(2) and sendmsg(2).

pattern MSG_OOB :: MsgFlags Source #

See recvmsg(2) and sendmsg(2).

pattern MSG_DONTROUTE :: MsgFlags Source #

See recvmsg(2) and sendmsg(2).

Socket operations

Creating and connecting

socket :: (SockFamily f, MonadBase IO μ) => Proxy f -> SockType -> SockProto -> μ (Socket f) Source #

Create a socket. The underlying file descriptor is non-blocking. All blocking operations are done via the GHC event manager. See socket(2).

getSockOpt :: (SockOpt o, SockOptReadable o ~ True, MonadBase IO μ) => Socket f -> Proxy o -> μ (SockOptValue o) Source #

Get socket option value. See getsockopt(2).

setSockOpt :: (SockOpt o, SockOptWritable o ~ True, MonadBase IO μ) => Socket f -> Proxy o -> SockOptValue o -> μ () Source #

Set socket option value. See setsockopt(2).

bind :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> SockFamilyAddr f -> μ () Source #

Bind socket to the specified address. See bind(2).

connect :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> SockFamilyAddr f -> μ () Source #

Connect socket to the specified address. This operation blocks. See connect(2).

tryConnect :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> SockFamilyAddr f -> μ Bool Source #

Try to connect socket without blocking. On success True is returned. If the connection did not succeed immediately, False is returned. See connect(2).

listen :: MonadBase IO μ => Socket f -> Int -> μ () Source #

Listen for connections on the given socket. See listen(2).

accept :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> μ (Socket f, SockFamilyAddr f) Source #

Accept a connection on the given socket. This operation blocks. See accept(2).

tryAccept :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> μ (Maybe (Socket f, SockFamilyAddr f)) Source #

Try to accept a connection on the given socket without blocking. On success the accepted socket and the peer address are returned. See accept(2).

getLocalAddr :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> μ (SockFamilyAddr f) Source #

Get the local address. See getsockname(2).

getRemoteAddr :: forall f μ. (SockFamily f, MonadBase IO μ) => Socket f -> μ (SockFamilyAddr f) Source #

Get the remote address. See getpeername(2).

Receiving messages

hasOobData :: MonadBase IO μ => Socket f -> μ Bool Source #

Check if socket has out-of-band data. See sockatmark(3).

recvBufs Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [(Ptr Word8, Int)]

Memory buffers

-> MsgFlags

Message flags

-> μ (Int, MsgFlags)

Received message length and flags

Receive a message from a connected socket, possibly utilizing multiple memory buffers. See recvmsg(2).

recvBuf Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Ptr α

Buffer pointer

-> Int

Buffer length

-> MsgFlags

Message flags

-> μ (Int, MsgFlags)

Received message length and flags

Receive a message from a connected socket. This operation blocks. See recvmsg(2).

recv' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Int

Maximum message length

-> MsgFlags

Message flags

-> μ (ByteString, MsgFlags)

Received message contents and flags

Receive a message from a connected socket. This operation blocks. See recvmsg(2).

recv Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Int

Maximum message length

-> μ ByteString

Received message contents

Receive a message from a connected socket. This operation blocks. See recvmsg(2).

recvBufsFrom Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [(Ptr Word8, Int)]

Memory buffers

-> MsgFlags

Message flags

-> μ (SockFamilyAddr f, Int, MsgFlags)

Received message source address, length, and flags

Receive a message from an unconnected socket, possibly utilizing multiple memory buffers. This operation blocks. See recvmsg(2).

recvBufFrom Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Ptr α

Buffer pointer

-> Int

Buffer length

-> MsgFlags

Message flags

-> μ (SockFamilyAddr f, Int, MsgFlags)

Received message source address, length, and flags

Receive a message from an unconnected socket. This operation blocks. See recvmsg(2).

recvFrom' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Int

Maximum message length

-> MsgFlags

Message flags

-> μ (SockFamilyAddr f, ByteString, MsgFlags)

Received message source address, contents, and flags

Receive a message from an unconnected socket. This operation blocks. See recvmsg(2).

recvFrom Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Int

Maximum message length

-> μ (SockFamilyAddr f, ByteString)

Received message source address and contents

Receive a message from an unconnected socket. This operation blocks. See recvmsg(2).

Sending messages

sendBufs Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [(Ptr Word8, Int)]

Memory buffers

-> MsgFlags

Message flags

-> μ Int

The number of bytes sent

Send a message split into several memory buffers on a connected socket. This operation blocks. See sendmsg(2).

sendMany' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [ByteString]

Message contents

-> MsgFlags

Message flags

-> μ Int

The number of bytes sent

Send a message split into several ByteStrings on a connected socket. This operation blocks. See sendmsg(2).

sendMany Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [ByteString]

Message contents

-> μ Int

The number of bytes sent

Send a message split into several ByteStrings on a connected socket. This operation blocks. See sendmsg(2).

sendBuf Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Ptr α

Buffer pointer

-> Int

Buffer length

-> MsgFlags

Message flags

-> μ Int

The number of bytes sent

Send a message on a connected socket. This operation blocks. See sendmsg(2).

send' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> ByteString

Message contents

-> MsgFlags

Message flags

-> μ Int

The number of bytes sent

Send a message on a connected socket. This operation blocks. See sendmsg(2).

send Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> ByteString

Message contents

-> μ Int

The number of bytes sent

Send a message on a connected socket. This operation blocks. See sendmsg(2).

sendBufsTo Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [(Ptr Word8, Int)]

Memory buffers

-> MsgFlags

Message flags

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message split into several memory buffers on an unconnected socket. This operation blocks. See sendmsg(2).

sendManyTo' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [ByteString]

Message contents

-> MsgFlags

Message flags

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message split into several ByteStrings on an unconnected socket. This operation blocks. See sendmsg(2).

sendManyTo Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> [ByteString]

Message contents

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message split into several ByteStrings on an unconnected socket. This operation blocks. See sendmsg(2).

sendBufTo Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> Ptr α

Buffer pointer

-> Int

Buffer length

-> MsgFlags

Message flags

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message on an unconnected socket. This operation blocks. See sendmsg(2).

sendTo' Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> ByteString

Message contents

-> MsgFlags

Message flags

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message on an unconnected socket. This operation blocks. See sendmsg(2).

sendTo Source #

Arguments

:: (SockFamily f, MonadBase IO μ) 
=> Socket f

The socket

-> ByteString

Message contents

-> SockFamilyAddr f

Message destination address

-> μ Int

The number of bytes sent

Send a message on an unconnected socket. This operation blocks. See sendmsg(2).

Closing

pattern SHUT_RD :: SockOps Source #

An alias for RecvSockOps.

pattern SHUT_WR :: SockOps Source #

An alias for SendSockOps.

pattern SHUT_RDWR :: SockOps Source #

An alias for AllSockOps.

shutdown :: MonadBase IO μ => Socket f -> SockOps -> μ () Source #

Shut down a part of a full-duplex connection. See shutdown(2).

close :: MonadBase IO μ => Socket f -> μ () Source #

Close the socket. See close(2).