Module gen_tcp

A partial implementation of the Erlang/OTP gen_tcp interface.

Description

This module provides an implementation of a subset of the functionality of the Erlang/OTP gen_tcp interface. It is designed to be API-compatible with gen_tcp, with exceptions noted below.

This interface may be used to send and receive TCP packets, as either binaries or strings. Active and passive modes are supported for receiving data.

Caveats:

  • Limited support for socket tuning parameters

  • No support for controlling_process/2

Note. Port drivers for this interface are not supportedon all AtomVM platforms.

Data Types

connect_option()


connect_option() = option()

listen_option()


listen_option() = option()

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

accept/1 Accept a connection on a listening socket.
accept/2 Accept a connection on a listening socket.
close/1 Close the socket.
connect/3 Connect to a TCP endpoint on the specified address and port.
controlling_process/2 Assign a controlling process to the socket.
listen/2 Create a server-side listening socket.
recv/2 Receive a packet over a TCP socket from a source address/port.
recv/3 Receive a packet over a TCP socket from a source address/port.
send/2 Send data over the specified socket to a TCP endpoint.

Function Details

accept/1


accept(Socket::inet:socket()) -> {ok, Socket::inet:socket()} | {error, Reason::reason()}

returns: a connection-based (tcp) socket that can be used for reading and writing

Accept a connection on a listening socket.

accept/2


accept(Socket::inet:socket(), Timeout::timeout()) -> {ok, Socket::inet:socket()} | {error, Reason::reason()}

Timeout: amount of time in milliseconds to wait for a connection

returns: a connection-based (tcp) socket that can be used for reading and writing

Accept a connection on a listening socket.

close/1


close(Socket::inet:socket()) -> ok

Socket: the socket to close

returns: ok.

Close the socket.

connect/3


connect(Address::inet:ip_address() | inet:hostname(), Port::inet:port_number(), Options::[connect_option()]) -> {ok, Socket::inet:socket()} | {error, Reason::reason()}

Address: the address to which to connect
Port: the port to which to connect
Options: options for controlling the behavior of the socket (see below)

returns: {ok, Socket} | {error, Reason}

Connect to a TCP endpoint on the specified address and port.

If successful, this function will return a Socket which can be used with the send/2 and recv/2 and recv/3 functions in this module.

The following options are supported:

  • active Active mode (default: true)

  • buffer Size of the receive buffer to use in active mode (default: 512)

  • binary data is received as binaries (as opposed to lists)

  • list data is received as lists (default)

If the socket is connected in active mode, then the calling process will receive messages of the form {tcp, Socket, Packet} when data is received on the socket. If active mode is set to false, then applications need to explicitly call one of the recv operations in order to receive data on the socket.

controlling_process/2


controlling_process(Socket::inet:socket(), Pid::pid()) -> ok | {error, Reason::reason()}

Socket: the socket to which to assign the pid
Pid: 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.

listen/2


listen(Port::inet:port_number(), Options::[listen_option()]) -> {ok, Socket::inet:socket()} | {error, Reason::reason()}

Port: the port number on which to listen. 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: a listening socket, which is appropriate for use in accept/1

Create a server-side listening socket.

This function is currently unimplemented

recv/2


recv(Socket::inet:socket(), Length::non_neg_integer()) -> {ok, packet()} | {error, Reason::reason()}

Equivalent to recv(Socket, Length, infinity).

Receive a packet over a TCP socket from a source address/port.

recv/3


recv(Socket::inet:socket(), Length::non_neg_integer(), Timeout::non_neg_integer()) -> {ok, packet()} | {error, Reason::reason()}

Socket: the socket over which to receive a packet
Length: the maximum length to read of the received packet
Timeout: the amount of time to wait for a packet to arrive

returns: {ok, Packet} | {error, Reason}

Receive a packet over a TCP socket from a source address/port.

This function is used when the socket is not created in active mode. The received packet data returned from this call, and should be of length no greater than the specified length. This function will return {error, closed} if the server gracefully terminates the server side of the connection.

This call will block until data is received or a timeout occurs.

Note. Currently, the Timeout parameter isignored.

send/2


send(Socket::inet:socket(), Packet::packet()) -> ok | {error, Reason::reason()}

Socket: The Socket obtained via connect/3
Packet: the data to send

returns: ok | {error, Reason}

Send data over the specified socket to a TCP endpoint.

If successful, this function will return the atom ok; otherwise, an error with a reason.