sockets-0.1.0.0: High-level network sockets

Safe HaskellNone
LanguageHaskell2010

Socket.Datagram.IPv4.Undestined

Contents

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 
Instances
Eq Socket Source # 
Instance details

Defined in Socket.Datagram.IPv4.Undestined

Methods

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

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

Ord Socket Source # 
Instance details

Defined in Socket.Datagram.IPv4.Undestined

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

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.

receive Source #

Arguments

:: Socket

Socket

-> Int

Maximum size of datagram to receive

-> IO (Either SocketException (Endpoint, ByteArray)) 

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.

Exceptions

data SocketException Source #

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

Constructors

SocketException 

Fields

data Context Source #

The function that behaved unexpectedly.

Instances
Eq Context Source # 
Instance details

Defined in Socket

Methods

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

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

Show Context Source # 
Instance details

Defined in Socket

data Reason Source #

A description of the unexpected behavior.

Constructors

MessageTruncated !Int !Int

The datagram did not fit in the buffer. This can happen while sending or receiving. Fields: buffer size, datagram size.

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

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

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.

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.

Instances
Eq Reason Source # 
Instance details

Defined in Socket

Methods

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

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

Show Reason Source # 
Instance details

Defined in Socket

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
      (remote,ByteArray payload) <- unhandled (receive sock 1024)
      BC.putStrLn ("Datagram from " <> BC.pack (show remote))
      BC.putStr (SB.fromShort (SB.SBS payload))

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