Module uart
Data Types
peripheral()
peripheral() = string() | binary()
The peripheral Name
may be one of: "UART0"
| "UART1"
| "UART2"
| <<"UART0">>
| <<"UART1">>
| <<"UART2">>
.
uart_opts()
uart_opts() = [{tx, Tx_pin::integer()} | {rx, Rx_pin::integer()} | {rts, Rts_pin::integer()} | {cts, Cts_pin::integer()} | {speed, Speed::pos_integer()} | {data_bits, 5..8} | {stop_bits, 1 | 2} | {event_queue_len, Qlen::pos_integer()} | {flow_control, none | hardware | software} | {parity, none | even | odd} | {peripheral, peripheral()} | []]
Function Index
close/1 | Close a port connection to the UART driver. |
open/1 | Open a connection to the UART driver default port. |
open/2 | Open a connection to the UART driver. |
read/1 | Read data from a UART port. |
read/2 | Read data from a UART port. |
write/2 | Write data to a UART port. |
Function Details
close/1
close(Pid::pid()) -> ok | {error, _Reason::term()}
Pid
: of the uart port to be closed
returns: ok.
Close a port connection to the UART driver
This function will close the given port connection to the UART driver.
open/1
open(Opts::uart_opts()) -> Pid::pid() | {error, _Reason::term()}
Opts
: uart configuration options
returns: Pid of the driver.
Open a connection to the UART driver default port
This function will open a connection to the UART driver.
open/2
open(Name::peripheral(), Opts::uart_opts()) -> Pid::pid() | {error, _Reason::term()}
Name
: the uart peripheral to be openedOpts
: uart configuration options
returns: Pid of the driver.
Open a connection to the UART driver
This function will open a connection to the UART driver.
read/1
read(Pid::pid()) -> {ok, Data::iodata()} | {error, _Reason::term()}
Pid
: of the uart port to be read
returns: {ok, Data} or {error, Reason}
Read data from a UART port
This function will return any data that is available, or return
a {error, timeout}
tuple. The driver will sent the next available
data from the UART driver to the process that made the last read.
Example:
Data = case uart:read(Uart) of
{ok, Binary} -> Binary;
{error, timeout} ->
receive
{ok, RecvBinary} -> RecvBinary;
Error -> error(Error)
end;
Error -> error(Error)
end,
Any attempt by another (or the same process) to read from uart before the
next uart payload is sent by the driver will result in {error, ealready}
.
read/2
read(Pid::pid(), Timeout::pos_integer()) -> {ok, Data::iodata()} | {error, _Reason::term()}
Pid
: of the uart port to be readTimeout
: millisecond to wait for data to become available
returns: {ok, Data}
, or {error, Reason}
Read data from a UART port
This function will return any data that is available within the timeout period to the process. After the timeout has expired a new read command may be used regardless of whether the last read was sent a payload. Example:
Data = case uart:read(Uart, 3000) of
{ok, Bin} -> Bin;
{error, timeout} -> <<"">>;
Error -> error_handler_fun(Uart, Error)
end,
Any data sent to the esp32 over uart between reads with a timeout will be lost, so be sure this is what you want. Most applications will want a single process to read from UART and continue to listen until a payload is received, and likely pass the payload off for processing and immediately begin another read.
write/2
write(Pid::pid(), Data::iodata()) -> ok | {error, _Reason::term()}
Pid
: of the uart port to be written toData
: to be written to the given uart port
returns: ok or {error, Reason}
Write data to a UART port
This function will write the given data to the UART port.