Copyright | (c) Dong Han 2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides an API for creating UDP sender and receiver.
- Socket FD is created lazily if no local address is provided, that means various functions
that need FD will throw bad FD exception if you
initUDP
with no local address e.g.setTTL
. - If you want to create a socket FD but don't care about which port or interface you're using,
use
SocketAddrIPv4
portAny
ipv4Any
wheninitUDP
. - Prefer
recvUDPLoop
because it can reuse receive buffer.
Synopsis
- data UDP
- initUDP :: UDPConfig -> Resource UDP
- data UDPConfig = UDPConfig {
- udpSendMsgSize :: !Int
- udpLocalAddr :: Maybe (SocketAddr, UDPFlag)
- defaultUDPConfig :: UDPConfig
- sendUDP :: HasCallStack => UDP -> SocketAddr -> Bytes -> IO ()
- data UDPRecvConfig = UDPRecvConfig {
- recvMsgSize :: !Int32
- recvBatchSize :: !Int
- defaultUDPRecvConfig :: UDPRecvConfig
- recvUDPLoop :: HasCallStack => UDPRecvConfig -> UDP -> ((Maybe SocketAddr, Bool, Bytes) -> IO a) -> IO ()
- recvUDP :: HasCallStack => UDPRecvConfig -> UDP -> IO [(Maybe SocketAddr, Bool, Bytes)]
- getSockName :: HasCallStack => UDP -> IO SocketAddr
- data ConnectedUDP
- connectUDP :: HasCallStack => UDP -> SocketAddr -> IO ConnectedUDP
- disconnectUDP :: HasCallStack => ConnectedUDP -> IO UDP
- getPeerName :: HasCallStack => ConnectedUDP -> IO SocketAddr
- sendConnectedUDP :: HasCallStack => ConnectedUDP -> Bytes -> IO ()
- setMembership :: HasCallStack => UDP -> CBytes -> CBytes -> Membership -> IO ()
- setSourceMembership :: HasCallStack => UDP -> CBytes -> CBytes -> CBytes -> Membership -> IO ()
- setMulticastLoop :: HasCallStack => UDP -> Bool -> IO ()
- setMulticastTTL :: HasCallStack => UDP -> Int -> IO ()
- setMulticastInterface :: HasCallStack => UDP -> CBytes -> IO ()
- setBroadcast :: HasCallStack => UDP -> Bool -> IO ()
- setTTL :: HasCallStack => UDP -> Int -> IO ()
- type UDPFlag = CInt
- pattern UDP_DEFAULT :: UDPFlag
- pattern UDP_IPV6ONLY :: UDPFlag
- pattern UDP_REUSEADDR :: UDPFlag
- type Membership = CInt
- pattern JOIN_GROUP :: Membership
- pattern LEAVE_GROUP :: Membership
TCP Client
UDP options.
Though technically message length field in the UDP header is a max of 65535, but large packets could be more likely dropped by routers, usually a packet(IPV4) with a payload <= 508 bytes is considered safe.
UDPConfig | |
|
Instances
Eq UDPConfig Source # | |
Ord UDPConfig Source # | |
Defined in Z.IO.Network.UDP | |
Show UDPConfig Source # | |
Generic UDPConfig Source # | |
ToValue UDPConfig Source # | |
Defined in Z.IO.Network.UDP | |
EncodeJSON UDPConfig Source # | |
Defined in Z.IO.Network.UDP encodeJSON :: UDPConfig -> Builder () # | |
FromValue UDPConfig Source # | |
ShowT UDPConfig Source # | |
Defined in Z.IO.Network.UDP toUTF8BuilderP :: Int -> UDPConfig -> Builder () # | |
type Rep UDPConfig Source # | |
Defined in Z.IO.Network.UDP type Rep UDPConfig = D1 ('MetaData "UDPConfig" "Z.IO.Network.UDP" "Z-IO-0.2.0.0-9WozHvkV8CCkBNKN4MqC3" 'False) (C1 ('MetaCons "UDPConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "udpSendMsgSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "udpLocalAddr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (SocketAddr, UDPFlag))))) |
defaultUDPConfig :: UDPConfig Source #
UDPConfig 512 Nothing
sendUDP :: HasCallStack => UDP -> SocketAddr -> Bytes -> IO () Source #
Send a UDP message to target address.
WARNING: A InvalidArgument
with errno UV_EMSGSIZE
will be thrown
if message is larger than sendMsgSize
.
data UDPRecvConfig Source #
Receiving buffering config.
UDPRecvConfig | |
|
Instances
defaultUDPRecvConfig :: UDPRecvConfig Source #
UDPRecvConfig 512 6
recvUDPLoop :: HasCallStack => UDPRecvConfig -> UDP -> ((Maybe SocketAddr, Bool, Bytes) -> IO a) -> IO () Source #
Recv UDP message within a loop
Loop receiving can be faster since it can reuse receiving buffer.
recvUDP :: HasCallStack => UDPRecvConfig -> UDP -> IO [(Maybe SocketAddr, Bool, Bytes)] Source #
Recv messages from UDP socket, return source address if available, and a Bool
to indicate if the message is partial (larger than receive buffer size).
getSockName :: HasCallStack => UDP -> IO SocketAddr Source #
Get the local IP and port of the UDP
.
Connected UDP Client
data ConnectedUDP Source #
Wrapper for a connected UDP
.
Instances
Show ConnectedUDP Source # | |
Defined in Z.IO.Network.UDP showsPrec :: Int -> ConnectedUDP -> ShowS # show :: ConnectedUDP -> String # showList :: [ConnectedUDP] -> ShowS # |
connectUDP :: HasCallStack => UDP -> SocketAddr -> IO ConnectedUDP Source #
Associate the UDP handle to a remote address and port, so every message sent by this handle is automatically sent to that destination
disconnectUDP :: HasCallStack => ConnectedUDP -> IO UDP Source #
Disconnect the UDP handle from a remote address and port.
getPeerName :: HasCallStack => ConnectedUDP -> IO SocketAddr Source #
Get the remote IP and port on ConnectedUDP
.
sendConnectedUDP :: HasCallStack => ConnectedUDP -> Bytes -> IO () Source #
Send a UDP message with a connected UDP.
WARNING: A InvalidArgument
with errno UV_EMSGSIZE
will be thrown
if message is larger than sendMsgSize
.
multicast and broadcast
:: HasCallStack | |
=> UDP | |
-> CBytes | Multicast address to set membership for. |
-> CBytes | Interface address. |
-> Membership | UV_JOIN_GROUP | UV_LEAVE_GROUP |
-> IO () |
Set membership for a multicast group.
:: HasCallStack | |
=> UDP | |
-> CBytes | Multicast address to set membership for. |
-> CBytes | Interface address. |
-> CBytes | Source address. |
-> Membership | UV_JOIN_GROUP | UV_LEAVE_GROUP |
-> IO () |
Set membership for a source-specific multicast group.
setMulticastLoop :: HasCallStack => UDP -> Bool -> IO () Source #
Set IP multicast loop flag. Makes multicast packets loop back to local sockets.
setMulticastTTL :: HasCallStack => UDP -> Int -> IO () Source #
Set the multicast ttl.
setMulticastInterface :: HasCallStack => UDP -> CBytes -> IO () Source #
Set the multicast interface to send or receive data on.
setBroadcast :: HasCallStack => UDP -> Bool -> IO () Source #
Set broadcast on or off.
Constants
UDPFlag
pattern UDP_DEFAULT :: UDPFlag Source #
pattern UDP_IPV6ONLY :: UDPFlag Source #
pattern UDP_REUSEADDR :: UDPFlag Source #
Membership
type Membership = CInt Source #
pattern JOIN_GROUP :: Membership Source #
pattern LEAVE_GROUP :: Membership Source #