Z-IO-0.6.1.0: Simple and high performance IO toolkit for Haskell
Copyright(c) Dong Han 2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.Network.UDP

Description

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 when initUDP.
  • Prefer recvUDPLoop because it can reuse receive buffer.
Synopsis

TCP Client

data UDP Source #

UDP socket.

UDP is not a sequential protocol, thus not an instance of 'Input/Output'. Message are received or sent individually, UDP socket is NOT thread safe! Use MVar UDP in multiple threads.

Instances

Instances details
Show UDP Source # 
Instance details

Defined in Z.IO.Network.UDP

Methods

showsPrec :: Int -> UDP -> ShowS #

show :: UDP -> String #

showList :: [UDP] -> ShowS #

Print UDP Source # 
Instance details

Defined in Z.IO.Network.UDP

Methods

toUTF8BuilderP :: Int -> UDP -> Builder () #

initUDP :: UDPConfig -> Resource UDP Source #

Initialize a UDP socket.

data UDPConfig Source #

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.

Constructors

UDPConfig 

Fields

Instances

Instances details
Eq UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Ord UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Show UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Generic UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Associated Types

type Rep UDPConfig :: Type -> Type #

JSON UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Print UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Methods

toUTF8BuilderP :: Int -> UDPConfig -> Builder () #

type Rep UDPConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

type Rep UDPConfig = D1 ('MetaData "UDPConfig" "Z.IO.Network.UDP" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" '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.

Constructors

UDPRecvConfig 

Fields

  • recvMsgSize :: !Int32

    maximum size of a received message

  • recvBatchSize :: !Int

    how many messages we want to receive per uv loop, inside each uv_run, we do batch receiving, increase this number can improve receiving performance, at the cost of memory and potential GHC thread starving.

Instances

Instances details
Eq UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Ord UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Read UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Show UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Generic UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Associated Types

type Rep UDPRecvConfig :: Type -> Type #

JSON UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

Print UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

type Rep UDPRecvConfig Source # 
Instance details

Defined in Z.IO.Network.UDP

type Rep UDPRecvConfig = D1 ('MetaData "UDPRecvConfig" "Z.IO.Network.UDP" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" 'False) (C1 ('MetaCons "UDPRecvConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "recvMsgSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "recvBatchSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))

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. Unlike TCP server from Z.IO.Network.TCPserver, UDP worker function is called on current haskell thread instead of a forked one, if you have heavy computations to do within the worker function, consider using forkBa, or a producer-consumer architecture

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

Instances details
Show ConnectedUDP Source # 
Instance details

Defined in Z.IO.Network.UDP

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

setMembership Source #

Arguments

:: 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.

setSourceMembership Source #

Arguments

:: 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.

setTTL Source #

Arguments

:: HasCallStack 
=> UDP 
-> Int

1 ~ 255

-> IO () 

Set the time to live.

Constants

UDPFlag

Membership