Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Socket = Socket Fd
- data Endpoint = Endpoint {}
- withSocket :: Endpoint -> (Socket -> Word16 -> IO a) -> IO (Either SocketException a)
- send :: Socket -> Endpoint -> ByteArray -> Int -> Int -> IO (Either SocketException ())
- receive :: Socket -> Int -> IO (Either SocketException (Endpoint, ByteArray))
- receiveMutableByteArraySlice_ :: Socket -> MutableByteArray RealWorld -> Int -> Int -> IO (Either SocketException Int)
- data SocketException = SocketException {}
- data Context
- data Reason
Types
A connectionless datagram socket that may communicate with many different endpoints on a datagram-by-datagram basis.
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.
Establish
:: 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
:: 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.
:: Socket | Socket |
-> Int | Maximum size of datagram to receive |
-> IO (Either SocketException (Endpoint, ByteArray)) |
Receive a datagram into a freshly allocated bytearray.
receiveMutableByteArraySlice_ Source #
:: 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.
Instances
Eq SocketException Source # | |
Defined in Socket (==) :: SocketException -> SocketException -> Bool # (/=) :: SocketException -> SocketException -> Bool # | |
Show SocketException Source # | |
Defined in Socket showsPrec :: Int -> SocketException -> ShowS # show :: SocketException -> String # showList :: [SocketException] -> ShowS # | |
Exception SocketException Source # | |
Defined in Socket |
The function that behaved unexpectedly.
A description of the unexpected behavior.
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 |
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 (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