Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Listener
- data Connection
- data Endpoint = Endpoint {}
- withListener :: Endpoint -> (Listener -> Word16 -> IO a) -> IO (Either SocketException a)
- withAccepted :: Listener -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException a)
- withConnection :: Endpoint -> (Connection -> IO a) -> IO (Either SocketException a)
- forkAccepted :: Listener -> (Either SocketException a -> IO ()) -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException ThreadId)
- forkAcceptedUnmasked :: Listener -> (Either SocketException a -> IO ()) -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException ThreadId)
- sendByteArray :: Connection -> ByteArray -> IO (Either SocketException ())
- sendByteArraySlice :: Connection -> ByteArray -> Int -> Int -> IO (Either SocketException ())
- sendMutableByteArray :: Connection -> MutableByteArray RealWorld -> IO (Either SocketException ())
- sendMutableByteArraySlice :: Connection -> MutableByteArray RealWorld -> Int -> Int -> IO (Either SocketException ())
- receiveByteArray :: Connection -> Int -> IO (Either SocketException ByteArray)
- receiveBoundedByteArray :: Connection -> Int -> IO (Either SocketException ByteArray)
- receiveMutableByteArray :: Connection -> MutableByteArray RealWorld -> IO (Either SocketException ())
- data SocketException = SocketException {}
- data Context
- data Reason
Types
data Connection Source #
A connection-oriented stream socket.
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.
Bracketed
withListener :: Endpoint -> (Listener -> Word16 -> IO a) -> IO (Either SocketException a) Source #
withAccepted :: Listener -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException a) Source #
Accept a connection on the listener and run the supplied callback
on it. This closes the connection when the callback finishes or if
an exception is thrown. Since this function blocks the thread until
the callback finishes, it is only suitable for stream socket clients
that handle one connection at a time. The variant forkAcceptedUnmasked
is preferrable for servers that need to handle connections concurrently
(most use cases).
:: Endpoint | Remote endpoint |
-> (Connection -> IO a) | Callback to consume connection |
-> IO (Either SocketException a) |
Establish a connection to a server.
forkAccepted :: Listener -> (Either SocketException a -> IO ()) -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException ThreadId) Source #
Accept a connection on the listener and run the supplied callback in
a new thread. Prefer forkAcceptedUnmasked
unless the masking state
needs to be preserved for the callback. Such a situation seems unlikely
to the author.
forkAcceptedUnmasked :: Listener -> (Either SocketException a -> IO ()) -> (Connection -> Endpoint -> IO a) -> IO (Either SocketException ThreadId) Source #
Accept a connection on the listener and run the supplied callback in
a new thread. The masking state is set to Unmasked
when running the
callback.
Communicate
:: Connection | Connection |
-> ByteArray | Buffer (will be sliced) |
-> IO (Either SocketException ()) |
:: Connection | Connection |
-> ByteArray | Buffer (will be sliced) |
-> Int | Offset into payload |
-> Int | Lenth of slice into buffer |
-> IO (Either SocketException ()) |
:: Connection | Connection |
-> MutableByteArray RealWorld | Buffer (will be sliced) |
-> IO (Either SocketException ()) |
sendMutableByteArraySlice Source #
:: Connection | Connection |
-> MutableByteArray RealWorld | Buffer (will be sliced) |
-> Int | Offset into payload |
-> Int | Lenth of slice into buffer |
-> IO (Either SocketException ()) |
:: Connection | Connection |
-> Int | Number of bytes to receive |
-> IO (Either SocketException ByteArray) |
Receive exactly the given number of bytes. If the remote application
shuts down its end of the connection before sending the required
number of bytes, this returns
.Left
(SocketException
Receive
RemoteShutdown
)
receiveBoundedByteArray Source #
:: Connection | Connection |
-> Int | Maximum number of bytes to receive |
-> IO (Either SocketException ByteArray) |
Receive up to the given number of bytes. If the remote application
shuts down its end of the connection instead of sending any bytes,
this returns
.Left
(SocketException
Receive
RemoteShutdown
)
receiveMutableByteArray :: Connection -> MutableByteArray RealWorld -> IO (Either SocketException ()) Source #
Receive a number of bytes exactly equal to the size of the mutable
byte array. If the remote application shuts down its end of the
connection before sending the required number of bytes, this returns
.Left
(SocketException
Receive
RemoteShutdown
)
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. |