Module esp

ESP32-specific APIs.

Description

This module contains functions that are specific to the ESP32 platform.

Data Types

esp_partition()


esp_partition() = {binary(), esp_partition_type(), esp_partition_subtype(), esp_partition_address(), esp_partition_size(), esp_partition_props()}

esp_partition_address()


esp_partition_address() = 0..134217728

esp_partition_props()


esp_partition_props() = []

esp_partition_size()


esp_partition_size() = 0..134217728

esp_partition_subtype()


esp_partition_subtype() = 0..254

esp_partition_type()


esp_partition_type() = 0..254

esp_reset_reason()


esp_reset_reason() = esp_rst_unknown | esp_rst_poweron | esp_rst_ext | esp_rst_sw | esp_rst_panic | esp_rst_int_wdt | esp_rst_task_wdt | esp_rst_wdt | esp_rst_deepsleep | esp_rst_brownout | esp_rst_sdio

esp_wakeup_cause()


esp_wakeup_cause() = sleep_wakeup_ext0 | sleep_wakeup_ext1 | sleep_wakeup_timer | sleep_wakeup_touchpad | sleep_wakeup_ulp | sleep_wakeup_gpio | sleep_wakeup_uart | sleep_wakeup_wifi | sleep_wakeup_cocpu | sleep_wakeup_cocpu_trap_trig | sleep_wakeup_bt

interface()


interface() = wifi_sta | wifi_softap

mac()


mac() = binary()

task_wdt_config()


task_wdt_config() = {TimeoutMS::pos_integer(), IdleCoreMask::non_neg_integer(), TriggerPanic::boolean()}

task_wdt_user_handle()

abstract datatype: task_wdt_user_handle()

Function Index

deep_sleep/0Put the esp32 into deep sleep.
deep_sleep/1Put the esp32 into deep sleep.
freq_hz/0 Return the clock frequency on the chip.
get_default_mac/0 Retrieve the default MAC address of the ESP32 device.
get_mac/1 Return the network MAC address of the specified interface.
nvs_erase_all/0(Deprecated.) Equivalent to nvs_erase_all(?ATOMVM_NVS_NS).
nvs_erase_all/1 Erase all values in the specified namespace.
nvs_erase_key/1(Deprecated.) Equivalent to nvs_erase_key(?ATOMVM_NVS_NS, Key).
nvs_erase_key/2 Erase the value associated with a key.
nvs_fetch_binary/2 Get the binary value associated with a key, or undefined, if there is no value associated with this key.
nvs_get_binary/1(Deprecated.) Equivalent to nvs_get_binary(?ATOMVM_NVS_NS, Key).
nvs_get_binary/2 Get the binary value associated with a key, or undefined, if there is no value associated with this key.
nvs_get_binary/3 Get the binary value associated with a key, or Default, if there is no value associated with this key.
nvs_put_binary/3 Set an binary value associated with a key.
nvs_reformat/0 Reformat the entire NVS partition.
nvs_set_binary/2(Deprecated.) Equivalent to nvs_set_binary(?ATOMVM_NVS_NS, Key, Value).
nvs_set_binary/3(Deprecated.) Set an binary value associated with a key.
partition_list/0 Gets the list of partitions as tuples, such as {name, type, subtype, offset, size, props}.
reset_reason/0 Returns the reason for the restart.
restart/0 Restarts the ESP device.
rtc_slow_get_binary/0 Get the binary currently stored in RTC slow memory.
rtc_slow_set_binary/1 Store a binary to RTC slow memory.
sleep_enable_ext0_wakeup/2
sleep_enable_ext1_wakeup/2
sleep_enable_ulp_wakeup/0
sleep_get_wakeup_cause/0 Returns the cause for the wakeup.
task_wdt_add_user/1 Register a user of the task watchdog timer.
task_wdt_deinit/0 Deinitialize the task watchdog timer Available with ESP-IDF 5.0 or higher.
task_wdt_delete_user/1 Unsubscribe a given user from the task watchdog timer.
task_wdt_init/1 Initialize the task watchdog timer with a configuration Available with ESP-IDF 5.0 or higher.
task_wdt_reconfigure/1 Update the configuration of the task watchdog timer Available with ESP-IDF 5.0 or higher.
task_wdt_reset_user/1 Reset the timer a previously registered user.

Function Details

deep_sleep/0


deep_sleep() -> no_return()

Put the esp32 into deep sleep. This function never returns. Program is restarted and wake up reason can be inspected to determine how the esp32 was woken up.

deep_sleep/1


deep_sleep(SleepMS::non_neg_integer()) -> no_return()

SleepMS: time to deep sleep in milliseconds

Put the esp32 into deep sleep. This function never returns. Program is restarted and wake up reason can be inspected to determine if the esp32 was woken by the timeout or by another cause.

freq_hz/0


freq_hz() -> non_neg_integer()

returns: Clock frequency (in hz)

Return the clock frequency on the chip

get_default_mac/0


get_default_mac() -> {ok, mac()} | {error, atom()}

returns: The default MAC address of the ESP32 device.

Retrieve the default MAC address of the ESP32 device. This function accesses the EFUSE memory of the ESP32 and reads the factory-programmed MAC address.

The mac address is returned as a 6-byte binary, per the IEEE 802 family of specifications.

get_mac/1


get_mac(Interface::interface()) -> mac()

Interface: the ESP32 network interface

returns: The network MAC address of the specified interface

Return the network MAC address of the specified interface.

The mac address is returned as a 6-byte binary, per the IEEE 802 family of specifications.

nvs_erase_all/0


nvs_erase_all() -> ok

This function is deprecated: Please do not use this function.

Equivalent to nvs_erase_all(?ATOMVM_NVS_NS).

nvs_erase_all/1


nvs_erase_all(Namespace::atom()) -> ok

Namespace: NVS namespace

returns: ok

Erase all values in the specified namespace.

nvs_erase_key/1


nvs_erase_key(Key::atom()) -> ok

Key: NVS key

returns: ok

This function is deprecated: Please do not use this function.

Equivalent to nvs_erase_key(?ATOMVM_NVS_NS, Key).

nvs_erase_key/2


nvs_erase_key(Namespace::atom(), Key::atom()) -> ok

Namespace: NVS namespace
Key: NVS key

returns: ok

Erase the value associated with a key. If a value does not exist for the specified key, no action is performed.

nvs_fetch_binary/2


nvs_fetch_binary(Namespace::atom(), Key::atom()) -> {ok, binary()} | {error, not_found} | {error, atom()}

Namespace: NVS namespace
Key: NVS key

returns: tagged tuple with binary value associated with this key in NV storage, {error, not_found} if there is no value associated with this key, or in general {error, Reason} for any other error.

Get the binary value associated with a key, or undefined, if there is no value associated with this key.

nvs_get_binary/1


nvs_get_binary(Key::atom()) -> binary() | undefined

This function is deprecated: Please do not use this function.

Equivalent to nvs_get_binary(?ATOMVM_NVS_NS, Key).

nvs_get_binary/2


nvs_get_binary(Namespace::atom(), Key::atom()) -> binary() | undefined

Namespace: NVS namespace
Key: NVS key

returns: binary value associated with this key in NV storage, or undefined if there is no value associated with this key.

Get the binary value associated with a key, or undefined, if there is no value associated with this key.

nvs_get_binary/3


nvs_get_binary(Namespace::atom(), Key::atom(), Default::binary()) -> binary() | undefined

Namespace: NVS namespace
Key: NVS key
Default: default binary value, if Key is not set in Namespace

returns: binary value associated with this key in NV storage, or Default if there is no value associated with this key.

Get the binary value associated with a key, or Default, if there is no value associated with this key.

nvs_put_binary/3


nvs_put_binary(Namespace::atom(), Key::atom(), Value::binary()) -> ok

Namespace: NVS namespace
Key: NVS key
Value: binary value

returns: ok

Set an binary value associated with a key. If a value exists for the specified key, it is over-written.

nvs_reformat/0


nvs_reformat() -> ok

returns: ok

Reformat the entire NVS partition. WARNING. This will result in deleting all NVS data and should be used with extreme caution!

nvs_set_binary/2


nvs_set_binary(Key::atom(), Value::binary()) -> ok

This function is deprecated: Please use nvs_put_binary instead.

Equivalent to nvs_set_binary(?ATOMVM_NVS_NS, Key, Value).

nvs_set_binary/3


nvs_set_binary(Namespace::atom(), Key::atom(), Value::binary()) -> ok

Namespace: NVS namespace
Key: NVS key
Value: binary value

returns: ok

This function is deprecated: Please use nvs_put_binary instead.

Set an binary value associated with a key. If a value exists for the specified key, it is over-written.

partition_list/0


partition_list() -> [esp_partition()]

returns: List of partitions

Gets the list of partitions as tuples, such as {name, type, subtype, offset, size, props}. Type and subtype are integers as described in esp-idf documentation.

reset_reason/0


reset_reason() -> esp_reset_reason()

returns: the reason for the restart

Returns the reason for the restart

restart/0


restart() -> ok

Restarts the ESP device

rtc_slow_get_binary/0


rtc_slow_get_binary() -> binary()

returns: the currently stored binary in RTC slow memory.

Get the binary currently stored in RTC slow memory. Must not be called unless the binary was stored with rtc_slow_set_binary/1. A limited checksum is ran and this function may throw badarg if the checksum is not valid.

rtc_slow_set_binary/1


rtc_slow_set_binary(Bin::binary()) -> ok

Bin: binary to be stored in RTC slow memory

returns: ok

Store a binary to RTC slow memory. This memory is not erased on software reset and deep sleeps.

sleep_enable_ext0_wakeup/2


sleep_enable_ext0_wakeup(Pin::pos_integer(), Level::0..1) -> ok | error

returns: Configure ext0 wakeup

sleep_enable_ext1_wakeup/2


sleep_enable_ext1_wakeup(Mask::non_neg_integer(), Mode::0..1) -> ok | error

returns: Configure ext1 wakeup

sleep_enable_ulp_wakeup/0


sleep_enable_ulp_wakeup() -> ok | error

returns: Enable ulp wakeup

sleep_get_wakeup_cause/0


sleep_get_wakeup_cause() -> undefined | esp_wakeup_cause() | error

returns: the cause for the wake up

Returns the cause for the wakeup

task_wdt_add_user/1


task_wdt_add_user(Username::iodata()) -> {ok, task_wdt_user_handle()} | {error, any()}

Username: name of the user

returns: the handle to use with task_wdt_reset_user/1 or an error tuple.

Register a user of the task watchdog timer. Available with ESP-IDF 5.0 or higher.

task_wdt_deinit/0


task_wdt_deinit() -> ok | {error, any()}

returns: ok or an error tuple if tasks are subscribed (beyond idle tasks) or if the timer is not initialized

Deinitialize the task watchdog timer Available with ESP-IDF 5.0 or higher.

task_wdt_delete_user/1


task_wdt_delete_user(UserHandle::task_wdt_user_handle()) -> ok | {error, any()}

UserHandle: handle for the user, obtained from task_wdt_add_user/1

returns: ok or an error tuple

Unsubscribe a given user from the task watchdog timer. Available with ESP-IDF 5.0 or higher.

task_wdt_init/1


task_wdt_init(Config::task_wdt_config()) -> ok | {error, already_started} | {error, any()}

Config: configuration for the watchdog timer

returns: ok or an error tuple

Initialize the task watchdog timer with a configuration Available with ESP-IDF 5.0 or higher.

task_wdt_reconfigure/1


task_wdt_reconfigure(Config::task_wdt_config()) -> ok | {error, noproc} | {error, any()}

Config: configuration for the watchdog timer

returns: ok or an error tuple

Update the configuration of the task watchdog timer Available with ESP-IDF 5.0 or higher.

task_wdt_reset_user/1


task_wdt_reset_user(UserHandle::task_wdt_user_handle()) -> ok | {error, any()}

UserHandle: handle for the user, obtained from task_wdt_add_user/1

returns: ok or an error tuple

Reset the timer a previously registered user. Available with ESP-IDF 5.0 or higher.