Z-IO-0.1.4.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

Contents

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 socket FD but don't care about which port or interface you're using, use SocketAddrInet portAny inetAny when initUDP.
  • Prefer recvUDPLoop because it can reuse receive buffer.
Synopsis

TCP Client

data UDP Source #

UDP socket client.

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

Instances
Show UDP Source # 
Instance details

Defined in Z.IO.Network.UDP

Methods

showsPrec :: Int -> UDP -> ShowS #

show :: UDP -> String #

showList :: [UDP] -> ShowS #

initUDP :: HasCallStack => 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

defaultUDPConfig :: UDPConfig Source #

UDPConfig 512 Nothing

data UDPFlag where Source #

Bundled Patterns

pattern UDP_DEFAULT :: UDPFlag 
pattern UDP_IPV6ONLY :: UDPFlag 
pattern UDP_REUSEADDR :: UDPFlag 
Instances
Eq UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: UDPFlag -> UDPFlag -> Bool #

(/=) :: UDPFlag -> UDPFlag -> Bool #

Num UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UDPFlag :: Type -> Type #

Methods

from :: UDPFlag -> Rep UDPFlag x #

to :: Rep UDPFlag x -> UDPFlag #

FiniteBits UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UDPFlag -> Value #

EncodeJSON UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: UDPFlag -> Builder () #

FromValue UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UDPFlag = D1 (MetaData "UDPFlag" "Z.IO.UV.FFI" "Z-IO-0.1.4.0-IfRX4KH4mesBaX238HlX2d" True) (C1 (MetaCons "UDPFlag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt)))

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.

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 # 
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

data Membership where Source #

Bundled Patterns

pattern JOIN_GROUP :: Membership 
pattern LEAVE_GROUP :: Membership 
Instances
Eq Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Show Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep Membership :: Type -> Type #

ToValue Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: Membership -> Value #

EncodeJSON Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: Membership -> Builder () #

FromValue Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep Membership = D1 (MetaData "Membership" "Z.IO.UV.FFI" "Z-IO-0.1.4.0-IfRX4KH4mesBaX238HlX2d" True) (C1 (MetaCons "Membership" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt)))

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.