Module proc_lib

An implementation of the Erlang/OTP proc_lib interface.

Description

This module implements a strict subset of the Erlang/OTP proc_lib interface.

Data Types

start_spawn_option()


start_spawn_option() = {min_heap_size, pos_integer()} | {max_heap_size, pos_integer()} | {atomvm_heap_growth, erlang:atomvm_heap_growth_strategy()} | link

Function Index

init_ack/1 Callback to signal that initialization succeeded.
init_ack/2 Callback to signal that initialization succeeded.
initial_call/1 Get the initial call for a given process or false if it's not available.
spawn/1Restricted set of spawn options.
spawn/3 Spawn a new process and initialize it.
spawn_link/1Equivalent to spawn_link(erlang, apply, [Fun, []]).
spawn_link/3 Spawn and atomically link a new process and initialize it.
start/3Equivalent to start(Module, Function, Args, infinity).
start/4Equivalent to start(Module, Function, Args, Timeout, []).
start/5 Start a new process synchronously.
start_link/3Equivalent to start_link(Module, Function, Args, infinity).
start_link/4Equivalent to start_link(Module, Function, Args, Timeout, []).
start_link/5 Start a new process synchronously and atomically link it.
start_monitor/3Equivalent to start_monitor(Module, Function, Args, infinity).
start_monitor/4Equivalent to start_monitor(Module, Function, Args, Timeout, []).
start_monitor/5 Start a new process synchronously and atomically link it.
translate_initial_call/1 Get the initial call for a given process or {proc_lib, init_p, 5} if it's not available.

Function Details

init_ack/1


init_ack(Result::any()) -> ok

Result: result sent back to parent

Callback to signal that initialization succeeded.

init_ack/2


init_ack(Parent::pid(), Result::any()) -> ok

Parent: parent process
Result: result sent back to parent

Callback to signal that initialization succeeded.

initial_call/1


initial_call(Process::pid()) -> {module(), atom(), [atom()]} | false

Process: process to get the initial call for

returns: false until we support process_info(Pid, dictionary)

Get the initial call for a given process or false if it’s not available. Arguments are replaced with atoms.

spawn/1


spawn(Fun::fun(() -> any())) -> pid()

Equivalent to spawn(erlang, apply, [Fun, []]).

Restricted set of spawn options. monitor is not supported.

spawn/3


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

Module: of the function to call
Function: to call
Args: arguments to pass to the function

Spawn a new process and initialize it.

start/3


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

Equivalent to start(Module, Function, Args, infinity).

start/4


start(Module::module(), Function::atom(), Args::[any()], Timeout::timeout()) -> any()

Equivalent to start(Module, Function, Args, Timeout, []).

start/5


start(Module::module(), Function::atom(), Args::[any()], Timeout::timeout(), SpawnOpts::[start_spawn_option()]) -> any()

Module: the module in which the callbacks are defined
Function: to call for initialization
Args: arguments to pass to the function
Timeout: timeout for the initialization to be done
SpawnOpts: options passed to spawn. monitor is not allowed.

Start a new process synchronously. Wait for the process to call init_ack/1,2 or init_fail/2,3.

start_monitor/3


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

Equivalent to start_monitor(Module, Function, Args, infinity).

start_monitor/4


start_monitor(Module::module(), Function::atom(), Args::[any()], Timeout::timeout()) -> any()

Equivalent to start_monitor(Module, Function, Args, Timeout, []).

start_monitor/5


start_monitor(Module::module(), Function::atom(), Args::[any()], Timeout::timeout(), SpawnOpts::[start_spawn_option()]) -> any()

Module: the module in which the callbacks are defined
Function: to call for initialization
Args: arguments to pass to the function
Timeout: timeout for the initialization to be done
SpawnOpts: options passed to spawn_link. monitor is not allowed.

Start a new process synchronously and atomically link it. Wait for the process to call init_ack/1,2 or init_fail/2,3.

translate_initial_call/1


translate_initial_call(Process::pid()) -> {module(), atom(), non_neg_integer()}

Process: process to get the initial call for

returns: {proc_lib, init_p, 5} until we support process_info(Pid, dictionary)

Get the initial call for a given process or {proc_lib, init_p, 5} if it’s not available.