Erlang Basics
Erlang is a general-purpose programming language and a runtime environment. It has built-in support for concurrency, distribution and fault-tolerance.
These are my notes taken while learning about its basics and reading through Learn you some Erlang for Great Good! by Fred Hebert. It is available online.
The document covers only the very introduction to Erlang. OTP and application design are outside of the scope.
Table of Contents
1 Overview
Whenever somebody starts talking about building robust distributed systems in .NET, Java, Go etc, then that is the response they can get (from HN):
…basically re-creating Erlang from the ground up, except half broken and not learning from Erlang's 20-30 year history
Joe Armstrong's thesis is said to capture these lessons, but it is 295 page doctorate thesis. A shorter version is in one of his talks.
The other sources include Erlang Factory talks, books Learn You Some Erlang, Joe's, etc.
They say, that these lessons can be summarized as:
- CPUs aren't getting faster these days, so we are stuck building distributed and highly concurrent systems.
- These systems are better to be fault-tolerant. Especially we don't want a single corner-case scenario (triggered by an unlucky user) to bring down system for millions of the other connected clients.
- This tolerance can be achieved by composing systems from components, isolated to prevent failure from spreading.
- Isolation can be achieved via:
- A runtime that prevents memory sharing (OS Processes or Erlang VM, except that Erlang allows to have millions of procs).
- Proving that memory can't be shared (Rust's compiler can do this, making sure that you will not have data races. This is really exciting).
- Running in a container, VM or different PC. Keep in mind: a service running on a single machine isn't fault-tolerant.
- Isolated components need to communicate (they can't share memory), this can be achieved by sending messages. Such approach is called "actor model". Besides Erlang, there are many libraries and frameworks supporting it: Orleans, Akka etc
- Erlang is special, since it has:
- very light-weight processes which could be restarted very quickly (300 words each and take microseconds to create);
- ability for processes to monitor the other processes;
- communication only via messages which are copied, passed asynchronously and could easily go to another node.
- In addition to processes and actors, Erlang also comes with:
- Functional programming approach: no side effects, immutable data, explicit state updates. This makes code more explicit.
- Open Telecom Platform is a collection of middleware, libraries and tools (including an application server). It could be used to build, monitor and distribute these components.
- Monitoring and debugging capabilities. You could connect to Erlang VM node to inspect, trace, debug or even update code. All that without stopping a system.
- Decades worth of experience of building such systems. For example, Erlang is used heavily by Motorola, Ericsson, T-Mobile, Amazon, Yahoo, Facebook etc.
- Elixir is Erlang-esque language with improved code organization
capabilities (source):
- Compile-time macros (which work on AST)
- Pipeline operator
- Polymorphism via protocols
- Mix tool (to like npm for node.js)
- It still runs on Erlang VM
How hard is it to start developing Erlang?
2 Erlang basics
2.1 Getting started
- Install On OSX
brew install erlang
. - Launch REPL
erl
. - Abort
Ctrl+G
thenq
orq().
2.2 Immutable variables
All variables are immutable and named PascalCase
. They are assigned
for the first time using the pattern matching operator =
.
> One = 1. > Two = One + 1.
2.3 Atoms
Atoms are constant literals, with a backing 4 or 8 byte integer. They
are written in lowercase
or with_understore
. They are used in
pattern matching.
2.4 Boolean algebra
Erlang has the usual boolean comparison operators and
, or
, xor
,
not
. These operators always evaluate both sides of the equation,
while andalso
and orelse
are shortcut operators.
2.5 Comparison and Equality
Equality operators are freaky: =:=
and =/=
. They test for precise
equality.
Comparison operators are slightly lighter: ==
and /=
, they are
more relaxed. For example:
> 1 =:= 1.0. False > 1 == 1.0. True
The other comparison operators are just slightly weird: <
, >
, =<
and >=
.
2.6 Tuples
Tuples group multiple items together: {point,10,5}
. You can also
destructure a tuple via pattern matching to an unbound variable:
> Point = {point,10,5}. {point,10,5} > {point,X,Y}=Point. {point,10,5} > X. 10
Tuples could be nested easily: {point,{10,5}}
.
2.7 Lists
Lists in erlang are constructed like [E1,E2,...E3]
and could have
different elements inside: [1,2,{point,{3,4}},4.5]
.
There is a catch. Strings in erlang are also lists of numbers. If all numbers in a list could represent a letter, then erlang will print it as string.
To glue lists together use ++
and to split --
:
> [1,2,3] ++ [4,5]. [1,2,3,4,5]. > [1,2,3] -- [1,2]. [3]
These operations are right-associative, meaning that they are done from right to left:
> [1,2,3]--[1,2]--[3]. [3]
You can use [Head|Tail]
pattern to compose lists (adding head is
fast in erlang) and also to descructure them, where |
is called a
cons. In fact, any list can be constructed with [E1|[E2|[E3]]]
.
Note, that we can construct an improper list [2|3]
, which will throw
errors.
2.8 List comprehensions
List comprehensions allow to generate and modify lists in a conscise way:
~[Expr || Gen1, Gen2...., Cond1, Cond2...]~.
For example:
> [{X,Y}||X<-[1,2],Y<-[1,2],X==Y]. [{1,2},{2,2}]
We can also use pattern matching and existing lists:
> Weather = [{ufa,sun},{moscow,rain},{odessa,fog},{spb,rain}]. [{ufa,sun},{moscow,rain},{odessa,fog},{spb,rain}] > Rainy = [City || {City,rain} <-Weather]. [moscow, spb]
2.9 Binary Data
To express binary data we can use:
- hexadecimal notation:
16#AACCEE
. - bit syntax:
<<16#AACCEE:24>>
(put these bytes into 24 bit space).
For example:
% declare a bunch of bytes > Bytes = <<13,234,12,34,41,1,151>>. % Take first byte and treat the rest as binary > <<First:8,Rest/binary>> = Bytes.
In general, binary segment could be described as:
- Value
- Value:Size
- Value/TypeSpecifier
- Value:Size/TypeSpecifier
Where Size is in bits, if TypeSpecifier is not provided. The latter could be a hyphen-separated list of:
- Type: integer (default), float, binary, bitstring, bits, utf8, utf16, utf32, bytes (synonym for binary), bits (synonym for bitstring).
- Sign: signed and unsigned (default), matters only for integer.
- Endianness: big (default), little and native (from the current CPU). This applies for integer, utf16, utf32 or float.
- Unit: this is written
unit:integer
, where the value must be between 1 and 256. It is used for field alignment.
Given that, it is trivial to parse TCP segment:
<< SourcePort:16, DestinationPort:16, AckNumber:32, DataOffset:4, _Reserved:4, Flags:8, WindowSize:16, CheckSum: 16, UrgentPointer:16, Payload/binary >> = SomeBinary.
2.10 Binary Operations
Erlang has a common set of operators:
bsr
andbsl
- bit shift left/right.band
,bor
,bxor
,bnot
2.11 Binary strings
Binary strings are a bolted abstraction on top of lists: <<"Some
string">>
. It is hard to pattern-match them, so they are mainly used
for text storage.
2.12 Binary comprehensions
You can deal with binaries using a special form of comprehension syntax.
% Let us define some bytes > Pixels = <<123,34,21,45,102,32,65,61,62>>. <<123,34,21,45,102,32,65,61,62>> % Read them as a sequence of RGBS > RGBs = [ {R,G,B} || <<R:8,G:8,B:8>> <= Pixels ]. [{123,34,21},{45,102,32},{65,61,62}] % convert these RGBs back to bits > Bits = << <<R:8,G:8,B:8>> || {R,G,B} <- RGBs >>. <<123,34,21,45,102,32,65,61,62>>
3 Modules
3.1 Defining
Erlang modules are represented as files with a bunch of attributes in
-name(Attribute)
form. The only required attribute is name:
-module(useless)
, it should match to the file name without the
extension.
-module(useless). -export([add/2, multiply/2]). add(A,B) -> A + B. multiply(A,B) -> A * B.
3.2 Compiling
In order to compile a module:
- in command line:
erlc flags module.erl
; - in shell or a module:
compile:file(module.erl)
; - in shell:
c(useless).
; - in Emacs buffer:
C-c C-k
(it will also load the module in REPL).
3.3 Referencing
We call functions from the other modules as
module:function(args)
. In order to importn the namespace:
-import(Module, [Function1/Arity, ..., FunctionN/Arity]).
3.4 Macros
Macros in Erlang are similar to compiler directives. They are defined
as -define(MACRO,SomeValue).
(where SomeValue
is True
if
skipped), and could be referenced in the code as ?MACRO
.
We also have some predefined macros:
- ?MODULE - current module as an atom
- ?FILE - current file name as a string
- ?LINE - current line as an integer
Macros can be tested: ifdef
, else
and endif
. For example, you
could provide a debugging macro:
-ifdef(DEBUGMODULE). -define(DEBUG(S), io:format("dbg: "++S)). -else. -define(DEBUG(S), ok). -endif. ?DEBUG("entering some function")
If DEBUGMODULE
macro is defined, then we will have debugging,
otherwise we will have an ok
atom.
3.5 Metadata
Compiler will capture all module metadata and make them available in
module_info/0
function, for example useless:module_info()
.
4 Functions
4.1 Pattern matching
Erlang provides pattern matching in the form of multiple function
clauses separated by ;
.
function(X) -> Expression; function(Y) -> Expression; function(_) -> Expression.
We can match on lists in the patterns:
head([Head|_]) -> Head; head([]) -> [].
We can do even fancier stuff, by destructuring in function head:
add({Date = {YYYY,MM,DD}, Increment = {days, Days}}) -> {YYYY,MM,DD+Days}.
4.2 Guards
Guards are additional that can go in function head to make it more specific. The syntax is like this:
% constrain by Expr1 (must be true) function(args) when Expr1 -> Expression. % Expr1 and Expr2 must be true function(args) when Expr1, Expr2 -> Expression. % Expr1 or Expr2 must be true function(args) when Expr1; Expr2 -> Expression.
You can also use andalso
and orelse
inside guards. They are
similar, but can be nested, however shortcut operators can fail
(normal guard can proceed even if the first argument fails with
exception).
Guards will not accept user-defined functions! This is done to guarantee that we don't get any side effects there.
4.3 Guard patterns (ifs)
Guard patterns are defined with if
inside functions, they share the
syntax. They must have catch-all clause, though:
some(A) -> if A =:= 1 -> one; true -> something_else end.
Generally, if patterns were written to get benefit if case
statement
(below) but without the need to write full syntax.
4.4 Case … if
Case allows to have normal pattern matching inside a function.
case Arg of: Pattern [Guards] -> Expression; Pattern [Guards] -> Expression; _ -> Expression end.
In essence, this expression could be rewritten as
fun (Pattern) [Guards] -> Expression; fun (Pattern) [Guards] -> Expression; fun (_) -> Expression.
4.5 Choosing between guards, if and case
Just use whichever makes the code more simple. Performance differences are negligible.
4.6 Bound and unbound variables
Bound and unbound variables behave differently when we do pattern matching:
- unbound - attaches value to them;
- bound - error, unless new value is the same as the old one.
5 Types
Erlang has a dynamic type system.
This is aligned with a general belief that a failure in one subsystem shouldn't bring the others down. Erlang worries more about keeping the systems running, that trying to have error-free code. It is easier to do hot code reloading in a system with dynamic typing.
Erlang is also strongly typed, performing type checks at runtime. For
example 1 + lama
would throw an error.
5.1 Type conversions
Type conversions in Erlang are implemented with BIFs in erlang module:
> erlang:list_to_integer("54"). 54 > erlang:integer_to_list(42). "42" > erlang:atom_to_list(atom). "atom"
There are many more conversions of this type.
5.2 Type-test BIFs
Type-test BIFs are special BIFs that can be used in guard clauses:
is_binary
, is_atom
etc. They help to write declarative code:
Func(Arg) when is_atom(Arg) -> atom; Func(Arg) when is_binary(Arg) -> binary; ...
6 Recursion
Erlang has functions that can call themselves - recursive functions. That is the looping construct (aside from list comprehensions) that exists in the language.
6.1 Basics
It is usually advised to start writing a recursive function from a base case (a well known scenario, when recursion terminates).
Here is an example of function that calculates length of the list:
len([]) -> 0; len([_]) -> 1; len([_|Tail]) -> 1+len(Tail).
6.2 Tail recursion
Tail recursion aims to eleminate stacking of recursive operations as they happen by reducing them as they happen. Erlang could optimize tail calls.
Let's rewrite our function to transform it into a tail recursion:
tail_len(N) -> tail_len(0,N). tail_len(Acc,[]) -> Acc; tail_len(Acc,[_]) -> Acc+1; tail_len(Acc,[_,Tail]) -> tail_len(Acc+1,Tail).
If function is calling itself in a tail position (last expression to be evaluated is the function itelf), then Erlang VM could avoid storing current stack frame. This is called tail call optimization (a specific case of last call optimization).
Such optimizations make tail recursions useful and alvoid wasting a lot of memory. Even if tail call optimization doesn't work, large per-process stack of Erlang VM could help to handle some scenarios.
6.3 More recursive functions
Just to get into the habit.
repeat/2
function:
repeat(0,_) -> []; repeat(N,X) when N > 0 -> [X|repeat(N-1,X)].
and tail-recursive function:
tail_repeat(N,X) -> tail_repeat([], N, X). tail_repeat(L, 0, _) -> L; tail_repeat(L, N, X) when N > 0 -> tail_repeat([X | L], N-1, X).
Tail-recursive reverse function (note, that there is a BIF
lists:reverse/1
):
reverse(L) -> tail_reverse([],L). tail_reverse(Acc, []) -> Acc; tail_reverse(Acc, [H|T]) -> tail_reverse([H|Acc], T).
Tail-recursive sublist function:
head(L,N) -> reverse(head([], L, N)). head(Acc, _, 0) -> Acc; head(Acc, [], _) -> Acc; head(Acc, [H|T], N) -> head([H|Acc], T, N-1).
7 Higher order functions
Higher order function is a function which can accept reference to another function as an argument.
7.1 Basics
Let's define a map/2
function:
map(_, []) -> []; map(F, [H|T]) -> [F(H)|map(F,T)].
If we put it into a useless
module and also add inc(X)->X+1
, then:
> useless:map(fun useless:/1, [1,2,3]). [2,3,4]
7.2 Anonymous functions
Always declaring functions can be boring, hence the inline version.
> Fn = fun(A) -> A end. #Fun<erl_eval.6.90072148> > Fn(1). 1
In general an anonymous function can be declared as:
fun(Arg1) -> Expr1, Expr2, ... Expr N; (Args2) -> Expr1, Expr2, ... Expr N; (Args3) -> Expr1, Expr2, ... Expr N end
In erlang anonymous functions inherit the scope that they have been declared in. We can have closures (capturing some variables that were a part of the scope).
In the shell:
> Var = 1. 1. > Closure = fun() -> Var end. #Fun.... > Closure(). 1
Assigning function to a variable
Fx = fun useless:is_odd/2
7.3 More function helpers
Just a bunch of common helpers:
lists:reverse/1
;lists:map/2
(Select
in LINQ);lists:filter/2
(Where
in LINQ);lists:foldl/3
(Aggregate
, starting left);lists:foldr/3
;all/2
andany/2
;dropwhile/2
andtakewhile/2
;partition/2
- generates two lists, where predicate matches and not;flatten/1
- select many.
8 Exceptions
There are 3 types of exceptions in erlang: errors, exits and throws.
8.1 Error
Errors can be created by erlang:error(Reason)
. They will abort
execution of the function and return a stack trace with all the arguments.
8.2 Internal Exits
These are called with exit/1
. They don't have a stack trace and are
generally used to pass "last breath" information between the
processes.
8.3 Throws
Throws (created by throw/1
) are used to control the excecution
flow. They can also be used for non-local returns in deep recursion
(e.g. deep function would throw exception for a top-level function to
catch and return a default value to the user).
8.4 Catching exceptions
Exceptions can be handled with try...of...catch
block:
try Expression of SuccessPattern -> Expression; SuccessPattern -> Expression catch TypeOfError:ExceptionPattern -> Expression; TypeOfError:ExceptionPattern -> Expression end.
where TypeOfError
can be: error
, throw
or exit
, defaulting to
throw
if skipped.
There also is a special catch-all pattern: _:_
, which will handle
any exception type.
Expression between try...of
could be a function or just a whole
bunch of expressions: Expr1, Expr2... ExprN
. This section is called
protected.
It is also possible to have finally
block, which can't retrun any
value but would be used for its side effects (e.g. closing a file). It
is called after
in erlang.
The protected section can't be tail-recursive, since the VM would keep
a reference, in case an exception shows up. Code between catch..of
isn't protected and could be tail-recursive, unless after
block is
specified.
8.5 Catch construct
This is a weird one. Keyword catch
could be used alone to capture
all either exception or a good result out of an expression: catch
Expression
.
9 Common data structures
9.1 Records
Records are a hack that were added to the language later. They provide a syntactic sugar on top of the ordinary typles.
9.1.1 Defining Records
Records are defined as module attributes:
-module(record). -compile(export_all). -record(creature, { name, color, life=1, attack=0, abilities=[] }).
This is a creature with some fields and default values.
first_creature() -> #creature{ name="Zombie", color=black, attack=1, abilities=[drain_life] }.
If we try running the code, tuple would be visible:
> record:first_creature(). {creature,"Zombie",black,1,1,[drain_life]}
Ok, these are the raw tuples. Let's load record definitions into the
shell by rr(Module)
:
> rr(record). [creature] > record:first_creature(). #creature{name = "Zombie",color = black,life = 1,attack = 1, abilities = [drain_life]}
There are a few erlang shell helpers to deal with records:
rd(Name, Definition)
- define records in the shell, as if this were a module attribute;rf()
,rf(Name)
andrf([Names])
- flush all records, specific one or a list;rl()
,rl(Name)
andrl([Names])
- print shell records in a copy-pasteable way.
9.1.2 Reading values
You can read values from a record either via pattern matching (as if they were a tuple) or via a helping syntax (which is like an object cast):
> Zombie#creature.name. "Zombie"
Things could get pretty messy, if we have nested records (each one has to be cast separately).
On the bright side, we get a nice and short pattern matching (without the need to write full tuple declaration):
damage(#creature{life=Life, name=Name}, Damage) when Damage >= Life -> "Die " ++ Name; damage(#creature{color=black,name=Name}, Damage) -> "Suffer you, black " ++ Name.
Then, in the console:
> record:damage(Zombie,0). "Suffer you, black Zombie" > record:damage(Zombie,1). "Die, Zombie"
9.1.3 Updating Records
Records would be useless, if we couldn't update them:
real_damage(Meat = #creature{life=Life}, Damage) when Damage < Life -> Remaining=Life-Damage, Meat#creature{life=Remaining}.
This syntax is just a short-cut for calling erlang:setelement/3
behind the scenes.
Then, deal some damage in console manually and via the function:
> ZombieKing = Zombie#creature{life=5}. #creature{name = "Zombie",color = black,life = 5,attack = 1, abilities = [drain_life]} > record:real_damage(ZombieKing, 2). #creature{name = "Zombie",color = black,life = 3,attack = 1, abilities = [drain_life]}
9.1.4 Sharing records
Theoretically, it is possible to share records by declaring them inside a shared header file, which would then be included in the other erlang files:
% just some header file -record(damage, {amount = 1, color}).
This block could be included into the original module, and then used normally:
-include("header.hrl"). black_damage(Amount) -> #damage{amount = Amount, color = black}.
Now, reload the records and test the command:
> rr(record). [creature,damage] > record:black_damage(1). #damage{amount = 1,color = black}
However, sharing records between modules like this isn't a good idea. It exposes fragile data structure implementations (guts) to the outside world and is as bad as sharing database between multiple services.
A better approach would be to expose getter and setter functions, which would allow manipulating records while hiding the implementation details.
9.2 Key/Value Stores
For storing small amounts of data we have a property list (proplist) and an ordered dictionary (orddict).
9.2.1 Proplist
Prolist is a loose bag of [{Key,Value}...]
useful for storing small
amounts of data. You create it by constructing manually, update in a
light-weight manner by appending a new item NewList =
[NewItem|OldList]
. Then you can use methods in prolists
module to
lookup, replace, compact etc.
Proplists are defined very loosely and are usually used for managing configuration settings.
9.2.2 Orddict
orddict
module provides a more formal key-value store that works
well for up to 75 elements:
- unique keys that are also ordered;
- faster lookups;
- items must respect strict {Key,Value} structure.
It is best to avoid manipulating the orddict
instance directly and
rely on the methods:
new/0
andfrom_list/1
to create;store/3
to save;find/2
,fetch/2
to get;erase/2
to delete.
9.2.3 Dict vs gb-tree
dict
module exposes the same interface as orddict
. It works well
for larger datasets and also has fold/2
method.
gb_tree
is a rebalancing tree with slow insertions (updates and
reads are rather fast). It provides more direct access to the data
structure (e.g. allows to perform updates without checks) but doesn't
have fold/2
(requires using iterators on a subtree instead).
9.3 Other data structures
9.3.1 Sets
Erlang has for main modules to deal with sets:
ordsets
- slowest, but the most simple, implemented as ordered list;sets
- same interface asordsets
but scales better and has faster reads, supports=:=
operator;gb_sets
- same interface, but provides more fine-grained control;sofs
- sets of sets, for mathematical reasoning.
9.3.2 Graphs
Erlang allows manipulating with graphs via:
digraph
- construction and manipulation of a directed graph;digraph-utils
- navigation, testing of these graphs.
Also sofs
module allows converting families to the graphs and back.
9.3.3 Queues
Queues in erlang are FIFO, provided by queue
module. Internally they
are implemented as two lists:
- add to first list;
- pop from the second list;
- when second list is empty - reverse the first and swap them.
APIs could be split in 3 groups:
- basic:
new/0
,in/2
andout/1
; - advanced:
peek/1
,drop/1
,reverse/1
etc; - Okasaki API: you probably don't need it.
10 Concurrency
Concurrency is when two tasks can run at the same time, but don't necessarily do (e.g. multi-tasking on a single core). Parallelism is when these tasks do run at the same time (e.g. on multi-core machine).
Erlang had concurrency from the very beginning, parallelism was possible by running erlang on multiple machines. Modern multi-core systems allow parallelism on a single machine.
However, your parallel program goes only as fast as its slowest sequential part. Erlang wouldn't be a good fit for all problems.
10.1 Spawning Processes
A process in erlang is just a function that can be scheduled to run
via spawn/1
. This function returns pid in form of <0.160.0>
which can be used to communicate with the process.
The process terminates when the function returns.
BIF self/0
returns the pid of the current process.
10.2 Message passing
You send messages with !
(bang) operator, which works in form of
Pid ! hello
and returns a message (so that it can be passed to
multiple processes).
10.3 Receiving messages
You can dump all messages via flush/0
which would simply print
them. For real work use receive
expression, which looks similar to
case
pattern matching:
receive Pattern1 when Guard -> Expr1; Pattern2 when Guard -> Expr2; Pattern3 -> Expr3; _ -> Expr4 end.
Let's write us a small module:
-module(spell). -compile(export_all). cast() -> receive {heal, Amount} -> io:format("Healing ~p~n",[Amount]); {damage, Amount} -> io:format("Ouch for ~p~n", [Amount]); _ -> io:format("WTF?~n") end.
This function could be launched either via spawn(fun spell:cast/0)
or via a helper spawn(spell, cast, [])
, which takes a module,
function and arguments.
Once launched, cast
would sit around waiting for the receive
to
get a message. It will process it and terminate.
> S1 = spawn(spell, cast, []). <0.181.0> > S1 ! {boom}. WTF? {boom}
The only way to know if the recipient is alive and got message is by sending a reply. We can do that by packaging return address into a tuple.
cast2() -> receive {From, heal, Amount} -> io:format("Healing ~p~n",[Amount]), From ! "healing!"; {From,damage, Amount} -> io:format("Ouch for ~p~n", [Amount]), From ! "damage"; _ -> io:format("WTF?~n") end.
Then run in a shell:
> spawn(spell,cast2,[]) ! {self(), heal,2}. Healing 2 {<0.155.0>,heal,2} > flush(). Shell got "healing!" ok
Now we just need to make sure that the process can process more than one message. We can do that by making it tail-recursive:
summon(Life) -> receive {From,damage, Amount} when Amount >= Life -> % no recursion here io:format("Dead! ~p~n", [Amount]), From ! {self(), "dead"}; {From,damage, Amount} -> io:format("Ouch! ~p~n", [Amount]), From ! {self(), "this hurts!"}, summon(Life - Amount); {From, heal, Amount} -> io:format("Healing ~p~n",[Amount]), From ! {self(), "healing!"}, summon(Life + Amount); _ -> io:format("WTF?~n"), summon(Life) end.
The process will continue running till we damage it too much. Note that we also pass the state through that recursion.
10.4 Better design
Message structure is a bit like internal implementation detail. Do we really need to expose it that much? Let's encapsulate the details.
summon_wolf() -> spawn(?MODULE, summon, [3]). fireball(Pid) -> Pid ! { self(), damage, 2}, receive {_, Message} -> Message end. ointment(Pid) -> Pid ! { self(), heal, 1}, receive {_, Message} -> Message end.
This hides all the dirty details and allows us to focus damage dealing:
0> Wolf = spell:summon_wolf(). <0.289.0> > spell:fireball(Wolf). Ouch! 2 "this hurts!" > spell:fireball(Wolf). Dead! 2 "dead"
10.5 Timeouts
There is a problem. If we send spell:fireball/1
to a non-existent
process (or the dead one) from our shell, then it will freeze. We are
stuck in a receive deadlock.
To work around the issue, receive
has an after Timeout
construct:
fireball2(Pid) -> Pid ! { self(), damage, 2}, receive {_, Message} -> Message after 1000 -> timeout end. ointment2(Pid) -> Pid ! { self(), heal, 1}, receive {_, Message} -> Message after 1000 -> timeout end.
After also can accept infinity
atom (in case timeout is passed as an
argument and we want to wait forever).
There are two special cases - sleeping (receive
without any
patterns) and trying to get messages without waiting (receive
with
zero timeout).
10.6 Selective receive
We can perform a selective receive by ignoring some messages (which puts them into a save queue for later processing). This is done via:
important() -> receive {Priority, Message} when Priority > 10 -> [Message | important()] after 0 -> normal() end. normal() -> receive {_, Message} -> [Message, normal()] after 0 -> [] end.
The approach has a pitfall: selective receive puts non-matching messages into a special save queue, which is then traversed on each message.
We can work around that by:
- provide a catch-all Unexpected variable which will log and discard;
- store messages in min-heap,
gb_trees
module or whichever structure is applicable.
11 Errors and Processes
11.1 Terminating a process
When a process terminates, it always terminates with an exit reason,
which can be of any term. If exit reason is atom normal
then the
process terminated normally.
A process can terminate:
- when a run-time error occurs with
{Reason,Stack}
; - terminate by itself by calling
exit(Reason)
,error(Reason, [Args])
,fault(Reason, [Args])
; - when exit signal is received with a reason other than
normal
.
Terminating processes emit exit signals to all linked
processes. These kill a process, unless the reason is normal
.
A process can call exit(Pid, Reason)
to emit an exit signal
with Reason
to the target process. Sender is unaffected.
11.2 Links
You can link/1
current process to another by PID, making them emit
exit signals to each other on termination. Linking is idempotent.
Note, that in link(spawn(Function))
spawned process could finish
before link is established. It is better to use atomic spawn_link/1
.
11.3 Traps
A process can be configured to trap incoming exit signals and convert
them into messages of {'Exit', FromPid, Reason}
that are put into
mailbox.
One exception - if a reason is kill
(e.g. from exit(Pid, kill)
),
then this will bypass the trap and kill the process. Upon termination,
an exit signal with killed
is sent to all linked processed (to
avoid killing them unconditionally).
11.4 Monitors
Monitors are a unidirectional way to monitor if the process is alive
and when it goes down. A process can setup a monitor via
monitor(process, Pid)
which would return Ref
reference to the
monitor. That reference could be used to demonitor/1
the process.
When a monitored process dies, we get a message:
{'DOWN', Ref, process, Pid, Reason}
If the process didn't exist in the first place we would get the
message immediately with Reason
set to noproc
.
11.5 Naming processes
To give a process a name, use erlang:register(Name,Pid)
. If the
process dies, it will loose its name. Or you can use unregister/1
to
do it manually. Then, use whereis(Name)
to get Pid (or an
undefined
).
Published: August 26, 2015.
Next post in Opinionated Tech story: Go: The Good Parts
🤗 Check out my newsletter! It is about building products with ChatGPT and LLMs: latest news, technical insights and my journey. Check out it out