Module erlang

An implementation of the Erlang/OTP erlang module, for functions that are not already defined as NIFs.

Data Types

demonitor_option()


demonitor_option() = flush | {flush, boolean()} | info | {info, boolean()}

float_format_option()


float_format_option() = {decimals, Decimals::0..57} | {scientific, Decimals::0..57} | compact

heap_growth_strategy()


heap_growth_strategy() = bounded_free | minimum | fibonacci

mem_type()


mem_type() = binary

spawn_option()


spawn_option() = {min_heap_size, pos_integer()} | {max_heap_size, pos_integer()} | {atomvm_heap_growth, heap_growth_strategy()} | link | monitor

time_unit()


time_unit() = second | millisecond | microsecond

timestamp()


timestamp() = {MegaSecs::non_neg_integer(), Secs::non_neg_integer(), MicroSecs::non_neg_integer}

Function Index

apply/3 Returns the result of applying Function in Module to Args.
atom_to_binary/2 Convert an atom to a binary.
atom_to_list/1 Convert an atom to a string.
binary_to_atom/2 Convert a binary to atom.
binary_to_integer/1 Parse the text in a given binary as an integer.
binary_to_list/1 Convert a binary to a list of bytes.
binary_to_term/1Decode a term that was previously encodes with term_to_binary/1 This function should be mostly compatible with its Erlang/OTP counterpart.
demonitor/1 Remove a monitor.
demonitor/2 Remove a monitor, with options.
display/1 Print a term to stdout.
erase/1 Erase a key from the process dictionary.
exit/1 Raises an exception of class exit with reason Reason.
exit/2 Send an exit signal to target process.
float_to_binary/1 Convert a float to a binary.
float_to_binary/2 Convert a float to a binary.
float_to_list/1 Convert a float to a string.
float_to_list/2 Convert a float to a string.
fun_to_list/1 Create a string representing a function.
function_exported/3 Determine if a function is exported.
garbage_collect/0 Run a garbage collect in current process.
garbage_collect/1 Run a garbage collect in a given process.
get/1 Return a value associated with a given key in the process dictionary.
get_module_info/1 Get info for a given module.
get_module_info/2 Get specific info for a given module.
group_leader/0 Return the pid of the group leader of caller.
group_leader/2Set the group leader for a given process.
integer_to_binary/1 Convert an integer to a binary.
integer_to_binary/2 Convert an integer to a binary.
integer_to_list/1 Convert an integer to a string.
integer_to_list/2 Convert an integer to a string.
iolist_to_binary/1 Convert an IO list to binary.
is_map/1 Return true if Map is a map; false, otherwise.
is_map_key/2 Return true if Key is associated with a value in Map; false, otherwise.
is_process_alive/1 Determine if a process is alive.
link/1 Link current process with a given process.
list_to_atom/1 Convert a string into an atom.
list_to_binary/1 Convert a list into a binary.
list_to_existing_atom/1 Convert a string into an atom.
list_to_integer/1 Convert a string (list of characters) to integer.
list_to_tuple/1 Convert a list to a tuple with the same size.
localtime/0Return the current time and day for system local timezone.
make_ref/0 Create a new reference.
map_get/2 Get the value in Map associated with Key, if it exists.
map_size/1Returns the size of (i.e., the number of entries in) the map.
max/2 Return the maximum value of two terms.
md5/1 Computes the MD5 hash of an input binary, as defined by https://www.ietf.org/rfc/rfc1321.txt.
memory/1 Return the amount of memory (in bytes) used of the specified type.
min/2 Return the minimum value of two terms.
monitor/2 Create a monitor on a process or on a port.
monotonic_time/1 Return the monotonic time in the specified units.
open_port/2 Open a port.
pid_to_list/1 Create a string representing a pid.
process_flag/2 Set a flag for the current process.
process_info/2 Return process information.
processes/0 Return a list of all current processes.
put/2 Store a value with a given key in the process dictionary.
ref_to_list/1 Create a string representing a reference.
register/2 Register a name for a given process.
send/2 Send a message to a given process.
send_after/3 Send Msg to Dest after Time ms.
spawn/1 Create a new process.
spawn/3 Create a new process by calling exported Function from Module with Args.
spawn_link/1 Create a new process and link it.
spawn_link/3 Create a new process by calling exported Function from Module with Args and link it.
spawn_opt/2 Create a new process.
spawn_opt/4 Create a new process by calling exported Function from Module with Args.
start_timer/3 Start a timer, and send {timeout, TimerRef, Msg} to Dest after Time ms, where TimerRef is the reference returned from this function.
system_flag/2 Update system flags.
system_info/1 Return system information.
system_time/1 Get the current system time in provided unit.
term_to_binary/1Encode a term to a binary that can later be decoded with binary_to_term/1.
timestamp/0Return the timestamp in {MegaSec, Sec, MicroSec} format.
universaltime/0Return the current time and day for UTC.
unlink/1 Unlink current process from a given process.
unregister/1 Lookup a process by name.
whereis/1 Lookup a process by name.

Function Details

apply/3


apply(Module::module(), Function::function(), Args::[term()]) -> term()

Module: Name of module
Function: Exported function name
Args: Parameters to pass to function (max 6)

returns: Returns the result of Module:Function(Args).

Returns the result of applying Function in Module to Args. The applied function must be exported from Module. The arity of the function is the length of Args. Example:

              > apply(lists, reverse, [[a, b, c]]).
           [c,b,a]
           > apply(erlang, atom_to_list, ['AtomVM']).
           "AtomVM"

If the number of arguments are known at compile time, the call is better written as Module:Function(Arg1, Arg2, …, ArgN).

atom_to_binary/2


atom_to_binary(Atom::atom(), Encoding::latin1) -> binary()

Atom: Atom to convert
Encoding: Encoding for conversion

returns: a binary with the atom’s name

Convert an atom to a binary. Only latin1 encoding is supported.

atom_to_list/1


atom_to_list(Atom::atom()) -> string()

Atom: Atom to convert

returns: a string with the atom’s name

Convert an atom to a string.

binary_to_atom/2


binary_to_atom(Binary::binary(), Encoding::latin1) -> atom()

Binary: Binary to convert to atom
Encoding: encoding for conversion

returns: an atom from passed binary

Convert a binary to atom. Only latin1 encoded is supported.

binary_to_integer/1


binary_to_integer(Binary::binary()) -> integer()

Binary: Binary to parse for integer

returns: the integer represented by the binary

Parse the text in a given binary as an integer.

binary_to_list/1


binary_to_list(Binary::binary()) -> [byte()]

Binary: Binary to convert to list

returns: a list of bytes from the binary

Convert a binary to a list of bytes.

binary_to_term/1


binary_to_term(Binary::binary()) -> any()

Binary: binary to decode

returns: A term decoded from passed binary

Decode a term that was previously encodes with term_to_binary/1 This function should be mostly compatible with its Erlang/OTP counterpart. Unlike modern Erlang/OTP, resources are currently serialized as empty binaries and cannot be unserialized.

demonitor/1


demonitor(Monitor::reference()) -> true

Monitor: reference of monitor to remove

returns: true

Remove a monitor

demonitor/2


demonitor(Monitor::reference(), Options::[demonitor_option()]) -> boolean()

Monitor: reference of monitor to remove

returns: true

Remove a monitor, with options. If flush, monitor messages are flushed and guaranteed to not be received. If info, return true if monitor was removed, false if it was not found. If both options are provivded, return false if flush was needed.

display/1


display(Term::any()) -> true

Term: term to print

returns: true

Print a term to stdout.

erase/1


erase(Key::any()) -> any()

Key: key to erase from the process dictionary

returns: the previous value associated with this key or undefined

Erase a key from the process dictionary.

exit/1


exit(Reason::any()) -> no_return()

Reason: reason for exit

Raises an exception of class exit with reason Reason. The exception can be caught. If it is not, the process exits. If the exception is not caught the signal is sent to linked processes. In this case, if Reason is kill, it is not transformed into killed and linked processes can trap it (unlike exit/2).

exit/2


exit(Process::pid(), Reason::any()) -> true

Process: target process
Reason: reason for exit

returns: true

Send an exit signal to target process. The consequences of the exit signal depends on Reason, on whether Process is self() or another process and whether target process is trapping exit. If Reason is not kill nor normal:

  • If target process is not trapping exits, it exits with Reason

  • If traget process is trapping exits, it receives a message {'EXIT', From, Reason} where From is the caller of exit/2.

If Reason is kill, the target process exits with Reason changed to killed. If Reason is normal and Process is not self():

  • If target process is not trapping exits, nothing happens.

  • If traget process is trapping exits, it receives a message {'EXIT', From, normal} where From is the caller of exit/2.

If Reason is normal and Process is self():

  • If target process is not trapping exits, it exits with normal.

  • If traget process is trapping exits, it receives a message {'EXIT', From, normal} where From is the caller of exit/2.

float_to_binary/1


float_to_binary(Float::float()) -> binary()

Float: Float to convert

returns: a binary with a text representation of the float

Convert a float to a binary.

float_to_binary/2


float_to_binary(Float::float(), Options::[float_format_option()]) -> binary()

Float: Float to convert
Options: Options for conversion

returns: a binary with a text representation of the float

Convert a float to a binary.

float_to_list/1


float_to_list(Float::float()) -> string()

Float: Float to convert

returns: a string with a text representation of the float

Convert a float to a string.

float_to_list/2


float_to_list(Float::float(), Options::[float_format_option()]) -> string()

Float: Float to convert
Options: Options for conversion

returns: a string with a text representation of the float

Convert a float to a string.

fun_to_list/1


fun_to_list(Fun::function()) -> string()

Fun: function to convert to a string

returns: a string representation of the function

Create a string representing a function.

function_exported/3


function_exported(Module::module(), Function::atom(), Arity::arity()) -> boolean()

Module: module to test
Function: function to test
Arity: arity to test

returns: true if Module exports a Function with this Arity

Determine if a function is exported

garbage_collect/0


garbage_collect() -> true

returns: true

Run a garbage collect in current process

garbage_collect/1


garbage_collect(Pid::pid()) -> boolean()

Pid: pid of the process to garbage collect

returns: true or false if the process no longer exists

Run a garbage collect in a given process. The function returns before the garbage collect actually happens.

get/1


get(Key::any()) -> any()

Key: key in the process dictionary

returns: value associated with this key or undefined

Return a value associated with a given key in the process dictionary

get_module_info/1


get_module_info(Module::atom()) -> [{atom(), any()}]

Module: module to get info for

returns: A list of module info tuples

Get info for a given module. This function is not meant to be called directly but through Module:module_info/0 exported function.

get_module_info/2


get_module_info(Module::atom(), InfoKey::atom()) -> any()

Module: module to get info for
InfoKey: info to get

returns: A term representing info for given module

Get specific info for a given module. This function is not meant to be called directly but through Module:module_info/1 exported function. Supported info keys are module, exports, compile and attributes.

group_leader/0


group_leader() -> pid()

returns: Pid of group leader or self() if no group leader is set.

Return the pid of the group leader of caller.

group_leader/2


group_leader(Leader::pid(), Pid::pid()) -> true

Leader: pid of process to set as leader
Pid: pid of process to set a Leader

returns: true

Set the group leader for a given process.

integer_to_binary/1


integer_to_binary(Integer::integer()) -> binary()

Integer: integer to convert to a binary

returns: a binary with a text representation of the integer

Convert an integer to a binary.

integer_to_binary/2


integer_to_binary(Integer::integer(), Base::2..36) -> binary()

Integer: integer to convert to a binary
Base: base for representation

returns: a binary with a text representation of the integer

Convert an integer to a binary.

integer_to_list/1


integer_to_list(Integer::integer()) -> string()

Integer: integer to convert to a string

returns: a string representation of the integer

Convert an integer to a string.

integer_to_list/2


integer_to_list(Integer::integer(), Base::2..36) -> string()

Integer: integer to convert to a string
Base: base for representation

returns: a string representation of the integer

Convert an integer to a string.

iolist_to_binary/1


iolist_to_binary(IOList::iolist()) -> binary()

IOList: IO list to convert to binary

returns: a binary with the bytes of the IO list

Convert an IO list to binary.

is_map/1


is_map(Map::map()) -> boolean()

Map: the map to test

returns: true if Map is a map; false, otherwise.

Return true if Map is a map; false, otherwise.

This function may be used in a guard expression.

is_map_key/2


is_map_key(Key::term(), Map::map()) -> boolean()

Key: the key
Map: the map

returns: true if Key is associated with a value in Map; false, otherwise.

Return true if Key is associated with a value in Map; false, otherwise.

This function raises a {badmap, Map} error if Map is not a map.

This function may be used in a guard expression.

is_process_alive/1


is_process_alive(Pid::pid()) -> boolean()

Pid: pid of the process to test

returns: true if the process is alive, false otherwise

Determine if a process is alive

list_to_atom/1


list_to_atom(String::string()) -> atom()

String: string to convert to an atom

returns: an atom from the string

Convert a string into an atom. Unlike Erlang/OTP 20+, atoms are limited to ISO-8859-1 characters. The VM currently aborts if passed unicode characters. Atoms are also limited to 255 characters. Errors with system_limit_atom if the passed string is longer.

See also: list_to_existing_atom/1.

list_to_binary/1


list_to_binary(IOList::iolist()) -> binary()

IOList: iolist to convert to binary

returns: a binary composed of bytes and binaries from the list

Convert a list into a binary. Errors with badarg if the list is not an iolist.

list_to_existing_atom/1


list_to_existing_atom(String::string()) -> atom()

String: string to convert to an atom

returns: an atom from the string

Convert a string into an atom. This function will error with badarg if the atom does not exist

See also: list_to_atom/1.

list_to_integer/1


list_to_integer(String::string()) -> integer()

String: string to convert to integer

returns: an integer value from its string representation

Convert a string (list of characters) to integer. Errors with badarg if the string is not a representation of an integer.

list_to_tuple/1


list_to_tuple(List::[any()]) -> tuple()

List: list to convert to tuple

returns: a tuple with elements of the list

Convert a list to a tuple with the same size.

localtime/0


localtime() -> calendar:datetime()

returns: A tuple representing the current local time.

Return the current time and day for system local timezone.

See also: universaltime/0.

make_ref/0


make_ref() -> reference()

returns: a new reference

Create a new reference

map_get/2


map_get(Key::term(), Map::map()) -> Value::term()

Key: the key to get
Map: the map from which to get the value

returns: the value in Map associated with Key, if it exists.

Get the value in Map associated with Key, if it exists.

This function raises a {badkey, Key} error if ‘Key’ does not occur in Map or a {badmap, Map} if Map is not a map.

This function may be used in a guard expression.

map_size/1


map_size(Map::map()) -> non_neg_integer()

Map: the map

returns: the size of the map

Returns the size of (i.e., the number of entries in) the map

This function raises a {badmap, Map} error if Map is not a map.

This function may be used in a guard expression.

max/2


max(A::any(), B::any()) -> any()

A: any term
B: any term

returns: A if A > B; B, otherwise.

Return the maximum value of two terms

Terms are compared using > and follow the ordering principles defined in https://www.erlang.org/doc/reference_manual/expressions.html#term-comparisons

md5/1


md5(Data::binary()) -> binary()

Data: data to compute hash of, as a binary.

returns: the md5 hash of the input Data, as a 16-byte binary.

Computes the MD5 hash of an input binary, as defined by https://www.ietf.org/rfc/rfc1321.txt

memory/1


memory(Type::mem_type()) -> non_neg_integer()

Type: the type of memory to request

returns: the amount of memory (in bytes) used of the specified type

Return the amount of memory (in bytes) used of the specified type

min/2


min(A::any(), B::any()) -> any()

A: any term
B: any term

returns: A if A < B; B, otherwise.

Return the minimum value of two terms

Terms are compared using < and follow the ordering principles defined in https://www.erlang.org/doc/reference_manual/expressions.html#term-comparisons

monitor/2


monitor(Type::process | port, Pid::pid()) -> reference()

Type: type of monitor to create
Pid: pid of the object to monitor

returns: a monitor reference

Create a monitor on a process or on a port. When the process or the port terminates, the following message is sent to the caller of this function:

  {'DOWN', MonitorRef, Type, Pid, Reason}

Unlike Erlang/OTP, monitors are only supported for processes and ports.

monotonic_time/1


monotonic_time(Unit::time_unit()) -> integer()

Unit: time unit

returns: monotonic time in the specified units

Return the monotonic time in the specified units.

Monotonic time varies from system to system, and should not be used to determine, for example the wall clock time.

Instead, monotonic time should be used to compute time differences, where the function is guaranteed to return a (not necessarily strictly) monotonically increasing value.

For example, on ESP32 system, monotonic time is reported as the difference from the current time and the time the ESP32 device was started, whereas on UNIX systems the value may vary among UNIX systems (e.g., Linux, macOS, FreeBSD).

open_port/2


open_port(PortName::{spawn, iodata()}, Options::[any()] | map()) -> pid()

PortName: Tuple {spawn, Name} identifying the port
Options: Options, meaningful for the port

returns: A pid identifying the open port

Open a port. Unlike Erlang/OTP, ports are identified by pids.

pid_to_list/1


pid_to_list(Pid::pid()) -> string()

Pid: pid to convert to a string

returns: a string representation of the pid

Create a string representing a pid.

process_flag/2


process_flag(Flag::trap_exit, Value::boolean()) -> pid()

Flag: flag to change
Value: new value of the flag

returns: Previous value of the flag

Set a flag for the current process. When trap_exit is true, exit signals are converted to messages

  {'EXIT', From, Reason}

and the process does not exit if Reason is not normal.

process_info/2


process_info(Pid::pid(), Key::heap_size) -> {heap_size, non_neg_integer()}

Pid: the process pid.
Key: key used to find process information.


process_info(Pid::pid(), Key::total_heap_size) -> {total_heap_size, non_neg_integer()}

Pid: the process pid.
Key: key used to find process information.


process_info(Pid::pid(), Key::stack_size) -> {stack_size, non_neg_integer()}

Pid: the process pid.
Key: key used to find process information.


process_info(Pid::pid(), Key::message_queue_len) -> {message_queue_len, non_neg_integer()}

Pid: the process pid.
Key: key used to find process information.


process_info(Pid::pid(), Key::memory) -> {memory, non_neg_integer()}

Pid: the process pid.
Key: key used to find process information.


process_info(Pid::pid(), Key::links) -> {links, [pid()]}

Pid: the process pid.
Key: key used to find process information.

returns: process information for the specified pid defined by the specified key.

Return process information.

This function returns information about the specified process. The type of information returned is dependent on the specified key.

The following keys are supported:

  • heap_size the number of words used in the heap (integer), including the stack but excluding fragments

  • total_heap_size the number of words used in the heap (integer) including fragments

  • stack_size the number of words used in the stack (integer)

  • message_queue_len the number of messages enqueued for the process (integer)

  • memory the estimated total number of bytes in use by the process (integer)

  • links the list of linked processes

Specifying an unsupported term or atom raises a bad_arg error.

processes/0


processes() -> [pid()]

returns: A list of pids of all processes

Return a list of all current processes. Compared to Erlang/OTP, this function also returns native processes (ports).

put/2


put(Key::any(), Value::any()) -> any()

Key: key to add to the process dictionary
Value: value to store in the process dictionary

returns: the previous value associated with this key or undefined

Store a value with a given key in the process dictionary.

ref_to_list/1


ref_to_list(Ref::reference()) -> string()

Ref: reference to convert to a string

returns: a string representation of the reference

Create a string representing a reference.

register/2


register(Name::atom(), Pid::pid()) -> true

Name: name of the process to register
Pid: pid of the process to register

returns: true

Register a name for a given process. Processes can be registered with several names. Unlike Erlang/OTP, ports are not distinguished from processes. Errors with badarg if the name is already registered.

send/2


send(Pid::pid(), Message) -> Message

Pid: process to send the message to
Message: message to send

returns: the sent message

Send a message to a given process

send_after/3


send_after(Time::non_neg_integer(), Dest::pid() | atom(), Msg::term()) -> reference()

Time: time in milliseconds after which to send the message.
Dest: Pid or server name to which to send the message.
Msg: Message to send to Dest after Time ms.

returns: a reference that can be used to cancel the timer, if desired.

Send Msg to Dest after Time ms.

spawn/1


spawn(Function::function()) -> pid()

Function: function to create a process from

returns: pid of the new process

Create a new process

spawn/3


spawn(Module::module(), Function::atom(), Args::[any()]) -> pid()

Module: module of the function to create a process from
Function: name of the function to create a process from
Args: arguments to pass to the function to create a process from

returns: pid of the new process

Create a new process by calling exported Function from Module with Args.

spawn_opt/2


spawn_opt(Function::function(), Options::[spawn_option()]) -> pid() | {pid(), reference()}

Function: function to create a process from
Options: additional options.

returns: pid of the new process

Create a new process.

spawn_opt/4


spawn_opt(Module::module(), Function::atom(), Args::[any()], Options::[spawn_option()]) -> pid() | {pid(), reference()}

Module: module of the function to create a process from
Function: name of the function to create a process from
Args: arguments to pass to the function to create a process from
Options: additional options.

returns: pid of the new process

Create a new process by calling exported Function from Module with Args.

start_timer/3


start_timer(Time::non_neg_integer(), Dest::pid() | atom(), Msg::term()) -> reference()

Time: time in milliseconds after which to send the timeout message.
Dest: Pid or server name to which to send the timeout message.
Msg: Message to send to Dest after Time ms.

returns: a reference that can be used to cancel the timer, if desired.

Start a timer, and send {timeout, TimerRef, Msg} to Dest after Time ms, where TimerRef is the reference returned from this function.

system_flag/2


system_flag(Key::atom(), Value::term()) -> term()

Key: key used to change system flag.
Value: value to change

returns: previous value of the flag.

Update system flags.

This function allows to modify system flags at runtime.

The following key is supported on SMP builds:

  • schedulers_online the number of schedulers online

Specifying an unsupported atom key will result in a bad_arg error. Specifying a term that is not an atom will result in a bad_arg error.

system_info/1


system_info(Key::atom()) -> term()

Key: key used to find system information.

returns: system information defined by the specified key.

Return system information.

This function returns information about the system on which AtomVM is running. The type of information returned is dependent on the specified key.

The following keys are supported on all platforms:

  • process_count the number of processes running in the node (integer)

  • port_count the number of ports running in the node (integer)

  • atom_count the number of atoms currently allocated (integer)

  • system_architecture the processor and OS architecture (binary)

  • version the version of the AtomVM executable image (binary)

  • wordsize the number of bytes in a machine word on the current platform (integer)

  • schedulers the number of schedulers, equal to the number of online processors (integer)

  • schedulers_online the current number of schedulers (integer)

The following keys are supported on the ESP32 platform:

  • esp32_free_heap_size the number of (noncontiguous) free bytes in the ESP32 heap (integer)

  • esp_largest_free_block the number of the largest contiguous free bytes in the ESP32 heap (integer)

  • esp_get_minimum_free_size the smallest number of free bytes in the ESP32 heap since boot (integer)

Additional keys may be supported on some platforms that are not documented here.

Specifying an unsupported atom key will results in returning the atom ‘undefined’.

Specifying a term that is not an atom will result in a bad_arg error.

system_time/1


system_time(Unit::time_unit()) -> non_neg_integer()

Unit: Unit to return system time in

returns: An integer representing system time

Get the current system time in provided unit.

term_to_binary/1


term_to_binary(Term::any()) -> binary()

Term: term to encode

returns: A binary encoding passed term.

Encode a term to a binary that can later be decoded with binary_to_term/1. This function should be mostly compatible with its Erlang/OTP counterpart. Unlike modern Erlang/OTP, resources are currently serialized as empty binaries.

timestamp/0


timestamp() -> erlang:timestamp()

returns: A tuple representing the current timestamp.

Return the timestamp in {MegaSec, Sec, MicroSec} format. This the old format returned by erlang:now/0. Please note that the latter which is deprecated in Erlang/OTP is not implemented by AtomVM.

See also: monotonic_time/1, system_time/1.

universaltime/0


universaltime() -> calendar:datetime()

returns: A tuple representing the current universal time.

Return the current time and day for UTC.

See also: localtime/0.

unregister/1


unregister(Name::atom()) -> true

Name: name to unregister

returns: true

Lookup a process by name. Unlike Erlang/OTP, ports are not distinguished from processes. Errors with badarg if the name is not registered.

whereis/1


whereis(Name::atom()) -> pid() | undefined

Name: name of the process to locate

returns: undefined or the pid of the registered process

Lookup a process by name.