Module gen_udp
An implementation of the Erlang/OTP gen_udp interface.
Description
This module provides an implementation of a subset of the functionality of the Erlang/OTP gen_udp interface. It is designed to be API-compatible with gen_udp, with exceptions noted below.
This interface may be used to send and receive UDP packets, as either binaries or strings. Active and passive modes are supported for receiving data.
Caveats:
Currently no support for IPv6
Currently limited support for socket tuning parameters
Currently no support for closing sockets
Note. Port drivers for this interface are not supportedon all AtomVM platforms.
Data Types
option()
option() = {active, boolean()} | {buffer, pos_integer()} | {timeout, timeout()} | list | binary | {binary, boolean()} | {inet_backend, inet | socket}
packet()
packet() = string() | binary()
reason()
reason() = term()
Function Index
close/1 | Close the socket. |
controlling_process/2 | Assign a controlling process to the socket. |
open/1 | Create a UDP socket. |
open/2 | Create a UDP socket. |
recv/2 | Receive a packet over a UDP socket from a source address/port. |
recv/3 | Receive a packet over a UDP socket from a source address/port. |
send/4 | Send a packet over a UDP socket to a target address/port. |
Function Details
close/1
close(Socket::inet:socket()) -> ok
Socket
: the socket to close
returns: ok
Close the socket.
controlling_process/2
controlling_process(Socket::inet:socket(), Pid::pid()) -> ok | {error, Reason::reason()}
Socket
: the socket to which to assign the pidPid
: Pid to which to send messages
returns: ok | {error, Reason}.
Assign a controlling process to the socket. The controlling process will receive messages from the socket.
This function will return {error, not_owner}
if the calling process
is not the current controlling process.
By default, the controlling process is the process associated with the creation of the Socket.
open/1
open(PortNum::inet:port_number()) -> {ok, inet:socket()} | {error, Reason::reason()}
Equivalent to open(PortNum, [])
.
Create a UDP socket. This function will instantiate a UDP socket that may be used to send or receive UDP messages.
open/2
open(PortNum::inet:port_number(), Options::[option()]) -> {ok, inet:socket()} | {error, Reason::reason()}
PortNum
: the port number to bind to. Specify 0 to use an OS-assigned
port number, which can then be retrieved via the inet:port/1
function.Options
: A list of configuration parameters.
returns: an opaque reference to the socket instance, used in subsequent commands.
throws bad_arg
Create a UDP socket. This function will instantiate a UDP socket that may be used to send or receive UDP messages. This function will raise an exception with the bad_arg atom if there is no socket driver supported for the target platform.
Note. The Params argument is currently ignored.
recv/2
recv(Socket::inet:socket(), Length::non_neg_integer()) -> {ok, {inet:ip_address(), inet:port_number(), packet()}} | {error, reason()}
Equivalent to recv(Socket, Length, infinity)
.
Receive a packet over a UDP socket from a source address/port.
recv/3
recv(Socket::inet:socket(), Length::non_neg_integer(), Timeout::timeout()) -> {ok, {inet:ip_address(), inet:port_number(), packet()}} | {error, reason()}
Socket
: the socket over which to receive a packetLength
: the maximum length to read of the received packetTimeout
: the amount of time to wait for a packet to arrive
returns: {ok, {Address, Port, Packet}} | {error, Reason}
Receive a packet over a UDP socket from a source address/port. The address and port of the received packet, as well as the received packet data, are returned from this call. This call will block until data is received or a timeout occurs.
Note. Currently Length and Timeout parameters areignored.
Note. Currently the length of the received packetis limited to 128 bytes.
send/4
send(Socket::inet:socket(), Address::inet:ip_address(), PortNum::inet:port_number(), Packet::packet()) -> ok | {error, reason()}
Socket
: the socket over which to send a packetAddress
: the target address to which to send the packetPortNum
: the port on target address to which to send the packetPacket
: the packet of data to send
returns: ok | {error, Reason}
Send a packet over a UDP socket to a target address/port.
Note. Currently only ipv4 addresses are supported.