| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Socket.Datagram.Uninterruptible.Bytes
Synopsis
- send :: Socket Connected a -> Bytes -> IO (Either (SendException Uninterruptible) ())
- sendToIPv4 :: Socket Unconnected (Internet V4) -> Peer -> Bytes -> IO (Either (SendException Uninterruptible) ())
- receive :: Socket c a -> Int -> IO (Either (ReceiveException Uninterruptible) ByteArray)
- receiveFromIPv4 :: Socket Unconnected (Internet V4) -> Int -> IO (Either (ReceiveException Uninterruptible) Message)
- receiveMany :: Socket Unconnected (Internet V4) -> PeerlessSlab -> IO (Either (ReceiveException Uninterruptible) (UnliftedArray ByteArray))
- receiveManyFromIPv4 :: Socket Unconnected (Internet V4) -> IPv4Slab -> IO (Either (ReceiveException Uninterruptible) (SmallArray Message))
- data Message = Message {}
- data Peer = Peer {}
- data ReceiveException (a :: Interruptibility) where
- ReceiveTruncated :: forall (a :: Interruptibility). !Int -> ReceiveException a
- ReceiveInterrupted :: forall (a :: Interruptibility). ReceiveException Interruptible
- data PeerlessSlab = PeerlessSlab {}
- data IPv4Slab = IPv4Slab {}
- newPeerlessSlab :: Int -> Int -> IO PeerlessSlab
- newIPv4Slab :: Int -> Int -> IO IPv4Slab
Send
Arguments
| :: Socket Connected a | Socket with designated peer |
| -> Bytes | Slice of a buffer |
| -> IO (Either (SendException Uninterruptible) ()) |
Send a datagram using a socket with a pre-designated peer. This
refers to a datagram socket for which POSIX connect has locked
down communication to an individual peer.
Receive
Arguments
| :: Socket c a | Socket |
| -> Int | Maximum datagram size |
| -> IO (Either (ReceiveException Uninterruptible) ByteArray) |
Receive a datagram, discarding the peer address. This can be used with datagram sockets of any family. It is usable with both connected and unconnected datagram sockets.
Arguments
| :: Socket Unconnected (Internet V4) | IPv4 socket without designated peer |
| -> Int | Maximum datagram size |
| -> IO (Either (ReceiveException Uninterruptible) Message) |
Receive Many
Arguments
| :: Socket Unconnected (Internet V4) | Socket |
| -> PeerlessSlab | Buffers for reception |
| -> IO (Either (ReceiveException Uninterruptible) (UnliftedArray ByteArray)) |
Arguments
| :: Socket Unconnected (Internet V4) | Socket |
| -> IPv4Slab | Buffers for reception |
| -> IO (Either (ReceiveException Uninterruptible) (SmallArray Message)) |
Types
data ReceiveException (a :: Interruptibility) where #
Constructors
| ReceiveTruncated :: forall (a :: Interruptibility). !Int -> ReceiveException a | |
| ReceiveInterrupted :: forall (a :: Interruptibility). ReceiveException Interruptible |
Instances
| Eq (ReceiveException i) | |
Defined in Socket.Datagram Methods (==) :: ReceiveException i -> ReceiveException i -> Bool # (/=) :: ReceiveException i -> ReceiveException i -> Bool # | |
| Show (ReceiveException i) | |
Defined in Socket.Datagram Methods showsPrec :: Int -> ReceiveException i -> ShowS # show :: ReceiveException i -> String # showList :: [ReceiveException i] -> ShowS # | |
| Typeable i => Exception (ReceiveException i) | |
Defined in Socket.Datagram Methods toException :: ReceiveException i -> SomeException # fromException :: SomeException -> Maybe (ReceiveException i) # displayException :: ReceiveException i -> String # | |
Slabs
Types
data PeerlessSlab #
Constructors
| PeerlessSlab | |
Fields | |
Constructors
| IPv4Slab | |
Fields | |
Functions
newPeerlessSlab :: Int -> Int -> IO PeerlessSlab #