table of contents
erl(1) | User Commands | erl(1) |
NAME¶
erl - Start the Erlang runtime system
DESCRIPTION¶
The erl program starts an Erlang runtime system. The exact details (for example, whether erl is a script or a program and which other programs it calls) are system-dependent.
NOTE: If you are using Erlang/OTP 25 or earlier on Windows and want to start an Erlang system with full shell support, you should use werl.exe. See the Erlang/OTP 25 documentation for details on how to do that.
erl <arguments>¶
Starts an Erlang runtime system.
The arguments can be divided into emulator flags, flags, and plain arguments:
As indicated by the name, emulator flags control the behavior of the emulator.
The init process itself interprets some of these flags, the init flags. It also stores any remaining flags, the user flags. The latter can be retrieved by calling init:get_argument/1.
A small number of "-" flags exist, which now actually are emulator flags, see the description below.
Examples:
-
% erl +W w -sname arnie +R 9 -s my_init -extra +bertie (arnie@host)1> init:get_argument(sname). {ok,[["arnie"]]} (arnie@host)2> init:get_plain_arguments(). ["+bertie"]
Here +W w and +R 9 are emulator flags. -s my_init is an init flag, interpreted by init. -sname arnie is a user flag, stored by init. It is read by Kernel and causes the Erlang runtime system to become distributed. Finally, everything after -extra (that is, +bertie) is considered as plain arguments.
-
% erl -myflag 1 1> init:get_argument(myflag). {ok,[["1"]]} 2> init:get_plain_arguments(). []
Here the user flag -myflag 1 is passed to and stored by the init process. It is a user-defined flag, presumably used by some user-defined application.
Flags¶
In the following list, init flags are marked "(init flag)". Unless otherwise specified, all other flags are user flags, for which the values can be retrieved by calling init:get_argument/1. Notice that the list of user flags is not exhaustive, there can be more application-specific flags that instead are described in the corresponding application documentation.
-- (init flag)
-Application Par Val
-args_file FileName
The file FileName is to be a plain text file and can contain comments and command-line arguments. A comment begins with a # character and continues until the next end of line character. Backslash (\) is used as quoting character. All command-line arguments accepted by erl are allowed, also flag -args_file FileName. Be careful not to cause circular dependencies between files containing flag -args_file, though.
The flag -extra is treated in special way. Its scope ends at the end of the file. Arguments following an -extra flag are moved on the command line into the -extra section, that is, the end of the command line following after an -extra flag.
-async_shell_start
-boot File
Defaults to $ROOT/bin/start.boot.
-boot_var Var Dir
-code_path_cache
-compile Mod1 Mod2 ...
Not recommended; use erlc instead.
-config Config [Config ...]
-configfd FD [FD ...]
A configuration file descriptor will be read until its end and will then be closed.
The content of a configuration file descriptor is stored so that it can be reused when init:restart/0 or init:restart/1 is called.
The parameter -configfd 0 implies -noinput.
NOTE: It is not recommended to use file descriptors 1 (standard output), and 2 (standard error) together with -configfd as these file descriptors are typically used to print information to the console the program is running in.
Examples (Unix shell):
-
$ erl \ -noshell \ -configfd 3 \ -eval \ <(echo '[{kernel, [{logger_level, warning}]}].') {ok,warning}
-
$ echo '[{kernel, [{logger_level, warning}]}].' > test1.config $ echo '[{kernel, [{logger_level, error}]}].' > test2.config $ erl \ -noshell \ -configfd 3 \ -configfd 4 \ -eval \ 3< test1.config 4< test2.config {ok,error}
-connect_all false
-cookie Cookie
-detached
-disable-feature feature
-dist_listen true|false
-emu_args
-emu_flavor emu|jit|smp
-emu_type Type
-enable-feature feature
-env Variable Value
-
% erl -env DISPLAY gin:0
In this example, an Erlang runtime system is started with environment variable DISPLAY set to gin:0.
-epmd_module Module (init flag)
-erl_epmd_port Port (init flag)
-eval Expr (init flag)
-extra (init flag)
-heart
-hidden
-hosts Hosts
The IP addresses must be specified in the standard form (four decimal numbers separated by periods, for example, "150.236.20.74"). Hosts names are not acceptable, but a broadcast address (preferably limited to the local network) is.
-id Id
-init_debug
-instr (emulator flag)
-loader Loader
If Loader is something else, the user-supplied Loader port program is started.
-make
-man Module
-mode interactive | embedded
-name Name
The node name will be Name@Host, where Host is the fully qualified host name of the current host. For short names, use flag -sname instead.
If Name is set to undefined the node will be started in a special mode optimized to be the temporary client of another node. The node will then request a dynamic node name from the first node it connects to. Read more in Dynamic Node Name.
WARNING: Starting a distributed node without also specifying -proto_dist inet_tls will expose the node to attacks that may give the attacker complete access to the node and in extension the cluster. When using un-secure distributed nodes, make sure that the network is configured to keep potential attackers out.
-no_epmd
This option ensures that the Erlang runtime system does not start epmd and does not start the erl_epmd process for distribution either.
This option only works if Erlang is started as a distributed node with the -proto_dist option using an alternative protocol for Erlang distribution which does not rely on epmd for node registration and discovery. For more information, see How to implement an Alternative Carrier for the Erlang Distribution.
-noinput
-noshell
-nostick
-oldshell
-pa Dir1 Dir2 ...
As an alternative to -pa, if several directories are to be prepended to the code path and the directories have a common parent directory, that parent directory can be specified in environment variable ERL_LIBS; see code.
-pz Dir1 Dir2 ...
-path Dir1 Dir2 ...
-proto_dist Proto
inet_tcp
inet_tls
inet6_tcp
For example, to start up IPv6 distributed nodes:
-
% erl -name test@ipv6node.example.com -proto_dist inet6_tcp
-remsh Node
If no -name or -sname is given the node will be started using -sname undefined. If Node does not contain a hostname, one is automatically taken from -name or -sname
NOTE: Before OTP-23 the user needed to supply a valid -sname or -name for -remsh to work. This is still the case if the target node is not running OTP-23 or later.
NOTE: The connecting node needs to have a proper shell with terminal emulation. This means that UNIX users must use an Erlang compiled with terminal capabilities and before Erlang/OTP 25 Windows users must use werl.
-rsh Program
-S Mod [Func [Arg1, Arg2, ...]] (init flag)
-run Mod [Func [Arg1, Arg2, ...]] (init flag)
-s Mod [Func [Arg1, Arg2, ...]] (init flag)
-setcookie Cookie
-setcookie Node Cookie
-shutdown_time Time
-sname Name
This is sometimes the only way to run distributed Erlang if the Domain Name System (DNS) is not running. No communication can exist between nodes running with flag -sname and those running with flag -name, as node names must be unique in distributed Erlang systems.
If Name is set to undefined the node will be started in a special mode optimized to be the temporary client of another node. The node will then request a dynamic node name from the first node it connects to. Read more in Dynamic Node Name.
WARNING: Starting a distributed node without also specifying -proto_dist inet_tls will expose the node to attacks that may give the attacker complete access to the node and in extension the cluster. When using un-secure distributed nodes, make sure that the network is configured to keep potential attackers out.
-start_epmd true | false
This only applies if Erlang is started as a distributed node, i.e. if -name or -sname is specified. Otherwise, epmd is not started even if -start_epmd true is given.
Note that a distributed node will fail to start if epmd is not running.
-version (emulator flag)
Emulator Flags¶
erl invokes the code for the Erlang emulator (virtual machine), which supports the following flags:
+a size
+A size
+B [c | d | i]
If option c is used with oldshell on Unix, Ctrl-C will restart the shell process rather than interrupt it.
+c true | false
true
false
For backward compatibility, the boolean value can be omitted. This is interpreted as +c false.
+C no_time_warp | single_time_warp | multi_time_warp
no_time_warp
single_time_warp
multi_time_warp
+d
Option +d instructs the emulator to produce only a core dump and no crash dump if an internal error is detected.
Calling erlang:halt/1 with a string argument still produces a crash dump. On Unix systems, sending an emulator process a SIGUSR1 signal also forces a crash dump.
+dcg DecentralizedCounterGroupsLimit
When the number of schedulers is less than or equal to the limit, each scheduler has its own group. When the number of schedulers is larger than the groups limit, schedulers share groups. Shared groups degrade the performance for updating counters while many reader groups degrade the performance for reading counters. So, the limit is a tradeoff between performance for update operations and performance for read operations. Each group consumes 64 bytes in each counter.
Note that a runtime system using decentralized counter groups benefits from binding schedulers to logical processors, as the groups are distributed better between schedulers with this option.
This option only affects decentralized counters used for the counters that are keeping track of the memory consumption and the number of terms in ETS tables of type ordered_set with the write_concurrency option activated.
+e Number
+ec
+fnl
For more information about Unicode filenames, see section Unicode Filenames in the STDLIB User's Guide. Notice that this value also applies to command-line parameters and environment variables (see section Unicode in Environment and Parameters in the STDLIB User's Guide).
+fnu[{w|i|e}]
The +fnu switch can be followed by w, i, or e to control how wrongly encoded filenames are to be reported:
Notice that file:read_link/1 always returns an error if the link points to an invalid filename.
For more information about Unicode filenames, see section Unicode Filenames in the STDLIB User's Guide. Notice that this value also applies to command-line parameters and environment variables (see section Unicode in Environment and Parameters in the STDLIB User's Guide).
+fna[{w|i|e}]
The +fna switch can be followed by w, i, or e. This has effect if the locale settings cause the behavior of +fnu to be selected; see the description of +fnu above. If the locale settings cause the behavior of +fnl to be selected, then w, i, or e have no effect.
For more information about Unicode filenames, see section Unicode Filenames in the STDLIB User's Guide. Notice that this value also applies to command-line parameters and environment variables (see section Unicode in Environment and Parameters in the STDLIB User's Guide).
+hms Size
+hmbs Size
+hmax Size
+hmaxel true|false
+hmaxib true|false
+hmaxk true|false
+hpds Size
+hmqd off_heap|on_heap
+IOp PollSets
+IOt PollThreads
A good way to check if more IO poll threads are needed is to use microstate accounting and see what the load of the IO poll thread is. If it is high it could be a good idea to add more threads.
+IOPp PollSetsPercentage
+IOPt PollThreadsPercentage
+IOs true|false
If enabled, file descriptors that are frequently read may be moved to a special pollset used by scheduler threads. The objective is to reduce the number of system calls and thereby CPU load, but it can in some cases increase scheduling latency for individual file descriptor input events.
+JPcover true|false|function|function_counters|line|line_counters
Enables or disables support for coverage when running with the JIT. Defaults to false.
function
function_counters
line
line_counters
true
false
+JPperf true|false|dump|map|fp|no_fp
This option can be combined multiple times to enable several options:
dump
map
fp
no_fp
true
false
For more details about how to run perf see the perf support section in the BeamAsm internal documentation.
+JMsingle true|false
Enables or disables the use of single-mapped RWX memory for JIT code. The default is to map JIT:ed machine code into two regions sharing the same physical pages, where one region is executable but not writable, and the other writable but not executable. As some tools, such as QEMU user mode emulation, cannot deal with the dual mapping, this flags allows it to be disabled. This flag is automatically enabled by the +JPperf flag.
+L
+MFlag Value
+pad true|false
The boolean value used with the +pad parameter determines the default value of the async_dist process flag of newly spawned processes. By default, if no +pad command line option is passed, the async_dist flag will be set to false.
The value used in runtime can be inspected by calling erlang:system_info(async_dist).
+pc Range
Two values are supported for Range:
latin1
unicode
See also io:printable_range/0 in STDLIB.
+P Number
NOTE: The actual maximum chosen may be much larger than the Number passed. Currently the runtime system often, but not always, chooses a value that is a power of 2. This might, however, be changed in the future. The actual value chosen can be checked by calling erlang:system_info(process_limit).
The default value is 1048576
+Q Number
NOTE: The actual maximum chosen may be much larger than the actual Number passed. Currently the runtime system often, but not always, chooses a value that is a power of 2. This might, however, be changed in the future. The actual value chosen can be checked by calling erlang:system_info(port_limit).
The default value used is normally 65536. However, if the runtime system is able to determine maximum amount of file descriptors that it is allowed to open and this value is larger than 65536, the chosen value will increased to a value larger or equal to the maximum amount of file descriptors that can be opened.
On Windows the default value is set to 8196 because the normal OS limitations are set higher than most machines can handle.
+R ReleaseNumber
The distribution mechanism is not backward compatible by default. This flag sets the emulator in compatibility mode with an earlier Erlang/OTP release ReleaseNumber. The release number must be in the range <current release>-2 through <current release>. This limits the emulator, making it possible for it to communicate with Erlang nodes (as well as C and Java nodes) running that earlier release.
NOTE: Ensure that all nodes (Erlang-, C-, and Java nodes) of a distributed Erlang system is of the same Erlang/OTP release, or from two different Erlang/OTP releases X and Y, where all Y nodes have compatibility mode X.
+r
+rg ReaderGroupsLimit
When the number of schedulers is less than or equal to the reader groups limit, each scheduler has its own reader group. When the number of schedulers is larger than the reader groups limit, schedulers share reader groups. Shared reader groups degrade read lock and read unlock performance while many reader groups degrade write lock performance. So, the limit is a tradeoff between performance for read operations and performance for write operations. Each reader group consumes 64 byte in each read/write lock.
Notice that a runtime system using shared reader groups benefits from binding schedulers to logical processors, as the reader groups are distributed better between schedulers.
+S Schedulers:SchedulerOnline
Schedulers can be omitted if :SchedulerOnline is not and conversely. The number of schedulers online can be changed at runtime through erlang:system_flag(schedulers_online, SchedulersOnline).
If Schedulers or SchedulersOnline is specified as a negative number, the value is subtracted from the default number of logical processors configured or logical processors available, respectively.
Specifying value 0 for Schedulers or SchedulersOnline resets the number of scheduler threads or scheduler threads online, respectively, to its default value.
+SP SchedulersPercentage:SchedulersOnlinePercentage
This option interacts with +S settings. For example, on a system with 8 logical cores configured and 8 logical cores available, the combination of the options +S 4:4 +SP 50:25 (in either order) results in 2 scheduler threads (50% of 4) and 1 scheduler thread online (25% of 4).
+SDcpu DirtyCPUSchedulers:DirtyCPUSchedulersOnline
For details, see +S and +SP. By default, the number of dirty CPU scheduler threads created equals the number of normal scheduler threads created, and the number of dirty CPU scheduler threads online equals the number of normal scheduler threads online. DirtyCPUSchedulers can be omitted if :DirtyCPUSchedulersOnline is not and conversely. The number of dirty CPU schedulers online can be changed at runtime through erlang:system_flag(dirty_cpu_schedulers_online, DirtyCPUSchedulersOnline).
The amount of dirty CPU schedulers is limited by the amount of normal schedulers in order to limit the effect on processes executing on ordinary schedulers. If the amount of dirty CPU schedulers was allowed to be unlimited, dirty CPU bound jobs would potentially starve normal jobs.
Typical users of the dirty CPU schedulers are large garbage collections, json protocol encode/decoders written as nifs and matrix manipulation libraries.
You can use msacc in order to see the current load of the dirty CPU schedulers threads and adjust the number used accordingly.
+SDPcpu DirtyCPUSchedulersPercentage:DirtyCPUSchedulersOnlinePercentage
This option interacts with +SDcpu settings. For example, on a system with 8 logical cores configured and 8 logical cores available, the combination of the options +SDcpu 4:4 +SDPcpu 50:25 (in either order) results in 2 dirty CPU scheduler threads (50% of 4) and 1 dirty CPU scheduler thread online (25% of 4).
+SDio DirtyIOSchedulers
The amount of dirty IO schedulers is not limited by the amount of normal schedulers like the amount of dirty CPU schedulers. This since only I/O bound work is expected to execute on dirty I/O schedulers. If the user should schedule CPU bound jobs on dirty I/O schedulers, these jobs might starve ordinary jobs executing on ordinary schedulers.
Typical users of the dirty IO schedulers are reading and writing to files.
You can use msacc in order to see the current load of the dirty IO schedulers threads and adjust the number used accordingly.
+sFlag Value
+sbt BindType
Schedulers can also be bound using flag +stbt. The only difference between these two flags is how the following errors are handled:
If any of these errors occur when +sbt has been passed, the runtime system prints an error message, and refuses to start. If any of these errors occur when +stbt has been passed, the runtime system silently ignores the error, and start up using unbound schedulers.
Valid BindTypes:
u
unbound - Schedulers are not bound to logical processors, that is, the operating system decides where the scheduler threads execute, and when to migrate them. This is the default.
ns
no_spread - Schedulers with close scheduler identifiers are bound as close as possible in hardware.
ts
thread_spread - Thread refers to hardware threads (such as Intel's hyper-threads). Schedulers with low scheduler identifiers, are bound to the first hardware thread of each core, then schedulers with higher scheduler identifiers are bound to the second hardware thread of each core,and so on.
ps
processor_spread - Schedulers are spread like thread_spread, but also over physical processor chips.
s
spread - Schedulers are spread as much as possible.
nnts
no_node_thread_spread - Like thread_spread, but if multiple Non-Uniform Memory Access (NUMA) nodes exist, schedulers are spread over one NUMA node at a time, that is, all logical processors of one NUMA node are bound to schedulers in sequence.
nnps
no_node_processor_spread - Like processor_spread, but if multiple NUMA nodes exist, schedulers are spread over one NUMA node at a time, that is, all logical processors of one NUMA node are bound to schedulers in sequence.
tnnps
thread_no_node_processor_spread - A combination of thread_spread, and no_node_processor_spread. Schedulers are spread over hardware threads across NUMA nodes, but schedulers are only spread over processors internally in one NUMA node at a time.
db
default_bind - Binds schedulers the default way. Defaults to thread_no_node_processor_spread (which can change in the future).
Binding of schedulers is only supported on newer Linux, Solaris, FreeBSD, and Windows systems.
If no CPU topology is available when flag +sbt is processed and BindType is any other type than u, the runtime system fails to start. CPU topology can be defined using flag +sct. Notice that flag +sct can have to be passed before flag +sbt on the command line (if no CPU topology has been automatically detected).
The runtime system does by default not bind schedulers to logical processors.
NOTE: If the Erlang runtime system is the only operating system process that binds threads to logical processors, this improves the performance of the runtime system. However, if other operating system processes (for example another Erlang runtime system) also bind threads to logical processors, there can be a performance penalty instead. This performance penalty can sometimes be severe. If so, you are advised not to bind the schedulers.
How schedulers are bound matters. For example, in situations when there are fewer running processes than schedulers online, the runtime system tries to migrate processes to schedulers with low scheduler identifiers. The more the schedulers are spread over the hardware, the more resources are available to the runtime system in such situations.
NOTE: If a scheduler fails to bind, this is often silently ignored, as it is not always possible to verify valid logical processor identifiers. If an error is reported, it is reported to the error_logger. If you want to verify that the schedulers have bound as requested, call erlang:system_info(scheduler_bindings).
+sbwt none|very_short|short|medium|long|very_long
NOTE: This flag can be removed or changed at any time without prior notice.
+sbwtdcpu none|very_short|short|medium|long|very_long
NOTE: This flag can be removed or changed at any time without prior notice.
+sbwtdio none|very_short|short|medium|long|very_long
NOTE: This flag can be removed or changed at any time without prior notice.
+scl true|false
+scl false is similar to +sub true, but +sub true also balances scheduler utilization between schedulers.
+sct CpuTopology
-
<Id> = integer(); when 0 =< <Id> =< 65535 <IdRange> = <Id>-<Id> <IdOrIdRange> = <Id> | <IdRange> <IdList> = <IdOrIdRange>,<IdOrIdRange> | <IdOrIdRange> <LogicalIds> = L<IdList> <ThreadIds> = T<IdList> | t<IdList> <CoreIds> = C<IdList> | c<IdList> <ProcessorIds> = P<IdList> | p<IdList> <NodeIds> = N<IdList> | n<IdList> <IdDefs> = <LogicalIds><ThreadIds><CoreIds><ProcessorIds><NodeIds> |
<LogicalIds><ThreadIds><CoreIds><NodeIds><ProcessorIds> CpuTopology = <IdDefs>:<IdDefs> | <IdDefs>
Uppercase letters signify real identifiers and lowercase letters signify fake identifiers only used for description of the topology. Identifiers passed as real identifiers can be used by the runtime system when trying to access specific hardware; if they are incorrect the behavior is undefined. Faked logical CPU identifiers are not accepted, as there is no point in defining the CPU topology without real logical CPU identifiers. Thread, core, processor, and node identifiers can be omitted. If omitted, the thread ID defaults to t0, the core ID defaults to c0, the processor ID defaults to p0, and the node ID is left undefined. Either each logical processor must belong to only one NUMA node, or no logical processors must belong to any NUMA nodes.
Both increasing and decreasing <IdRange>s are allowed.
NUMA node identifiers are system wide. That is, each NUMA node on the system must have a unique identifier. Processor identifiers are also system wide. Core identifiers are processor wide. Thread identifiers are core wide.
The order of the identifier types implies the hierarchy of the CPU topology. The valid orders are as follows:
A CPU topology can consist of both processor external, and processor internal NUMA nodes as long as each logical processor belongs to only one NUMA node. If <ProcessorIds> is omitted, its default position is before <NodeIds>. That is, the default is processor external NUMA nodes.
If a list of identifiers is used in an <IdDefs>:
A simple example. A single quad core processor can be described as follows:
-
% erl +sct L0-3c0-3 1> erlang:system_info(cpu_topology). [{processor,[{core,{logical,0}},
{core,{logical,1}},
{core,{logical,2}},
{core,{logical,3}}]}]
A more complicated example with two quad core processors, each processor in its own NUMA node. The ordering of logical processors is a bit weird. This to give a better example of identifier lists:
-
% erl +sct L0-1,3-2c0-3p0N0:L7,4,6-5c0-3p1N1 1> erlang:system_info(cpu_topology). [{node,[{processor,[{core,{logical,0}},
{core,{logical,1}},
{core,{logical,3}},
{core,{logical,2}}]}]},
{node,[{processor,[{core,{logical,7}},
{core,{logical,4}},
{core,{logical,6}},
{core,{logical,5}}]}]}]
As long as real identifiers are correct, it is OK to pass a CPU topology that is not a correct description of the CPU topology. When used with care this can be very useful. This to trick the emulator to bind its schedulers as you want. For example, if you want to run multiple Erlang runtime systems on the same machine, you want to reduce the number of schedulers used and manipulate the CPU topology so that they bind to different logical CPUs. An example, with two Erlang runtime systems on a quad core machine:
-
% erl +sct L0-3c0-3 +sbt db +S3:2 -detached -noinput -noshell -sname one % erl +sct L3-0c0-3 +sbt db +S3:2 -detached -noinput -noshell -sname two
In this example, each runtime system have two schedulers each online, and all schedulers online will run on different cores. If we change to one scheduler online on one runtime system, and three schedulers online on the other, all schedulers online will still run on different cores.
Notice that a faked CPU topology that does not reflect how the real CPU topology looks like is likely to decrease the performance of the runtime system.
For more information, see erlang:system_info(cpu_topology).
+ssrct
NOTE: Reading CPU topology slows down startup when starting many parallel instances of ERTS on systems with large amount of cores; using this flag might speed up execution in such scenarios.
+sfwi Interval
NOTE: This feature has been introduced as a temporary workaround for long-executing native code, and native code that does not bump reductions properly in OTP. When these bugs have been fixed, this flag will be removed.
+spp Bool
+sss size
+sssdcpu size
+sssdio size
+stbt BindType
+sub true|false
+sub true is only supported on systems where the runtime system detects and uses a monotonically increasing high-resolution clock. On other systems, the runtime system fails to start.
+sub true implies +scl false. The difference between +sub true and +scl false is that +scl false does not try to balance the scheduler utilization.
+swct very_eager|eager|medium|lazy|very_lazy
NOTE: This flag can be removed or changed at any time without prior notice.
+sws default|legacy
NOTE: This flag can be removed or changed at any time without prior notice.
+swt very_low|low|medium|high|very_high
NOTE: This flag can be removed or changed at any time without prior notice.
+swtdcpu very_low|low|medium|high|very_high
NOTE: This flag can be removed or changed at any time without prior notice.
+swtdio very_low|low|medium|high|very_high
NOTE: This flag can be removed or changed at any time without prior notice.
+t size
+T Level
Modified timing affects the following:
Process spawning
Context reductions
Input reductions
NOTE: Performance suffers when modified timing is enabled. This flag is only intended for testing and debugging. return_to and return_from trace messages are lost when tracing on the spawn BIFs. This flag can be removed or changed at any time without prior notice.
+v
+V
+W w | i | e
+zFlag Value
+zdbbl size
A larger buffer limit allows processes to buffer more outgoing messages over the distribution. When the buffer limit has been reached, sending processes will be suspended until the buffer size has shrunk. The buffer limit is per distribution channel. A higher limit gives lower latency and higher throughput at the expense of higher memory use.
This limit only affects processes that have disabled fully asynchronous distributed signaling.
+zdntgc time
Node table entries that are not referred linger in the table for at least the amount of time that this parameter determines. The lingering prevents repeated deletions and insertions in the tables from occurring.
+zosrl limit
+zhft limit
If flushing during a halt operation has been ongoing for <timeout> milliseconds, the flushing will be interrupted and the runtime system will be immediately terminated with exit code 255. If halting without flushing, the <timeout> will have no effect on the system.
The value set by this flag can be read by Erlang code by calling erlang:system_info(halt_flush_timeout).
See also the flush_timeout option of the erlang:halt/2 BIF. Note that the shortest timeout of this command line argument and the flush_timeout option will be the actual timeout value in effect.
Since: OTP 27.0
Environment Variables¶
ERL_CRASH_DUMP
ERL_CRASH_DUMP_NICE
Unix systems: If the emulator needs to write a crash dump, it uses the value of this variable to set the nice value for the process, thus lowering its priority. Valid range is 1-39 (higher values are replaced with 39). The highest value, 39, gives the process the lowest priority.
ERL_CRASH_DUMP_SECONDS
Unix systems: This variable gives the number of seconds that the emulator is allowed to spend writing a crash dump. When the given number of seconds have elapsed, the emulator is terminated. ERL_CRASH_DUMP_SECONDS=0
ERL_CRASH_DUMP_SECONDS=S
ERL_CRASH_DUMP_SECONDS=-1
See also heart.
ERL_CRASH_DUMP_BYTES
Introduced in ERTS 8.1.2 (Erlang/OTP 19.2).
ERL_AFLAGS
Flag -extra is treated in a special way. Its scope ends at the end of the environment variable content. Arguments following an -extra flag are moved on the command line into section -extra, that is, the end of the command line following an -extra flag.
ERL_ZFLAGS and ERL_FLAGS
Flag -extra is treated in a special way. Its scope ends at the end of the environment variable content. Arguments following an -extra flag are moved on the command line into section -extra, that is, the end of the command line following an -extra flag.
ERL_LIBS
ERL_EPMD_ADDRESS
ERL_EPMD_PORT
Signals¶
On Unix systems, the Erlang runtime will interpret two types of signals.
SIGUSR1
SIGTERM
Introduced in ERTS 8.3 (Erlang/OTP 19.3)
The signal SIGUSR2 is reserved for internal usage. No other signals are handled.
Configuration¶
The standard Erlang/OTP system can be reconfigured to change the default behavior on startup.
The .erlang startup file
If an .erlang file is found, it is assumed to contain valid Erlang expressions. These expressions are evaluated as if they were input to the shell.
A typical .erlang file contains a set of search paths, for example:
-
io:format("executing user profile in $HOME/.erlang\n",[]). code:add_path("/home/calvin/test/ebin"). code:add_path("/home/hobbes/bigappl-1.2/ebin"). io:format(".erlang rc finished\n",[]).
To include private shell commands, define them in a module user_default and add the following argument as the first line in the .erlang file:
-
code:load_abs("..../user_default").
erl
See Also¶
epmd(1), erl_prim_loader, erts_alloc(3), init, application, auth, code, erl_boot_server, heart, net_kernel, make
erts 15.1.3 | Ericsson AB |