sockets-0.3.0.0: High-level network sockets

Safe HaskellNone
LanguageHaskell2010

Socket.Datagram.IPv4.Undestined

Contents

Description

Internet datagram sockets without a fixed destination.

Synopsis

Types

newtype Socket Source #

A connectionless datagram socket that may communicate with many different endpoints on a datagram-by-datagram basis.

Constructors

Socket Fd 

data Endpoint Source #

An endpoint for an IPv4 socket, connection, or listener. Everything is in host byte order, and the user is not responisble for performing any conversions.

Constructors

Endpoint 

Fields

Instances
Eq Endpoint Source # 
Instance details

Defined in Socket.IPv4

Show Endpoint Source # 
Instance details

Defined in Socket.IPv4

data Message Source #

Constructors

Message 

Fields

Instances
Eq Message Source # 
Instance details

Defined in Socket.Datagram.IPv4.Undestined.Internal

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Show Message Source # 
Instance details

Defined in Socket.Datagram.IPv4.Undestined.Internal

Establish

withSocket Source #

Arguments

:: Endpoint

Address and port to use

-> (Socket -> Word16 -> IO a)

Callback providing the socket and the chosen port

-> IO (Either SocketException a) 

Open a socket and run the supplied callback on it. This closes the socket when the callback finishes or when an exception is thrown. Do not return the socket from the callback. This leads to undefined behavior. If the address 0.0.0.0 is used, the socket receives on all network interfaces. If the port 0 is used, an unused port is chosen by the operating system. The callback provides the chosen port (or if the user specified a non-zero port, the chosen port will be that value).

Communicate

send Source #

Arguments

:: Socket

Socket

-> Endpoint

Remote IPv4 address and port

-> ByteArray

Buffer (will be sliced)

-> Int

Offset into payload

-> Int

Lenth of slice into buffer

-> IO (Either SocketException ()) 

Send a slice of a bytearray to the specified endpoint.

sendMutableByteArraySlice Source #

Arguments

:: Socket

Socket

-> Endpoint

Remote IPv4 address and port

-> MutableByteArray RealWorld

Buffer (will be sliced)

-> Int

Offset into payload

-> Int

Lenth of slice into buffer

-> IO (Either (SendException Uninterruptible) ()) 

Send a slice of a bytearray to the specified endpoint.

receiveByteArray Source #

Arguments

:: Socket

Socket

-> Int

Maximum size of datagram to receive

-> IO (Either (ReceiveException Uninterruptible) Message) 

Receive a datagram into a freshly allocated bytearray.

receiveMutableByteArraySlice_ Source #

Arguments

:: Socket

Socket

-> MutableByteArray RealWorld

Buffer

-> Int

Offset into buffer

-> Int

Maximum size of datagram to receive

-> IO (Either SocketException Int) 

Receive a datagram into a mutable byte array, ignoring information about the remote endpoint. Returns the actual number of bytes present in the datagram. Precondition: buffer_length - offset >= max_datagram_length.

receiveMany Source #

Arguments

:: Socket

Socket

-> Int

Maximum number of datagrams to receive

-> Int

Maximum size of each datagram to receive

-> IO (Either SocketException (Array Message)) 

Receive up to the specified number of datagrams into freshly allocated byte arrays. When there are many datagrams present on the receive buffer, this is more efficient than calling receive repeatedly. The array is guaranteed to have at least one message.

The byte arrays in the resulting messages are always pinned.

receiveManyUnless Source #

Arguments

:: STM ()

If this completes, give up on receiving

-> Socket

Socket

-> Int

Maximum number of datagrams to receive

-> Int

Maximum size of each datagram to receive

-> IO (Either SocketException (Array Message)) 

This has the same behavior as receiveMany. However, it also takes an STM action that it attempts to run while the event manager is waiting for the socket to be ready for a reads. If the supplied action finishes first, this abandons the attempt to receive datagrams and returns Left ReceptionAbandoned.

Exceptions

data SocketException Source #

Represents any unexpected behaviors that a function working on a socket, connection, or listener can exhibit.

Constructors

SentMessageTruncated !Int

The datagram did not fit in the buffer. This can happen while sending. The field is the size of the number of bytes in the datagram that were successfully copied into the send buffer.

ReceivedMessageTruncated !Int

The datagram did not fit in the buffer. This can happen while receiving. The field is the original size of the datagram that was was truncated while copying it into the buffer.

SocketAddressSize

The socket address was not the expected size. This exception indicates a bug in this library or (less likely) in the operating system.

SocketAddressFamily !CInt

The socket address had an unexpected family. This exception indicates a bug in this library or (less likely) in the operating system. The int argument is the actual family found in the socket address.

OptionValueSize

The option value was not the expected size. This exception indicates a bug in this library or (less likely) in the operating system.

NegativeBytesRequested

The user requested a negative number of bytes in a call to a receive function.

ReceptionAbandoned

This happens when the Unless variant of a function is used and the STM action completes before the socket is ready for a read.

RemoteNotShutdown

The remote end sent more data when it was expected to send a shutdown.

RemoteShutdown

The remote end has shutdown its side of the full-duplex connection. This can happen receive is called on a stream socket. This is not necessarily a bad thing. Many protocols use shutdown to indicate that no more data is available. These protocols can be contrasted with protocols that send a length representing a number of expected bytes.

ErrorCode !CInt

Any error code from the operating system that this library does not expect or recognize. Consult your operating system manual for details about the error code.

Examples

Print every UDP packet that we receive. This terminates, closing the socket, after receiving ten packets. This code throws any exception that happens. This is commonly a useful behavior since most exceptions cannot be handled gracefully.

import qualified Data.ByteString.Char8 as BC
import Control.Monad (replicateM_)
import qualified Data.ByteString.Short.Internal as SB

udpStdoutServer :: IO ()
udpStdoutServer = do
  unhandled $ withSocket (Endpoint IPv4.loopback 0) $ \sock port -> do
    BC.putStrLn ("Receiving datagrams on 127.0.0.1:" <> BC.pack (show port))
    replicateM_ 10 $ do
    DIU.Message sender (ByteArray contents) <- unhandled (DIU.receive sock 1024)
      BC.putStrLn ("Datagram from " <> BC.pack (show sender))
      BC.putStr (SB.fromShort (SB.SBS contents))

unhandled :: Exception e => IO (Either e a) -> IO a
unhandled action = action >>= either throwIO pure