Erlang for Python Programmers

Introduction

There has been a lot of interest in the Erlang language in the last few years. Its model of programming relies on concurrent processes that communicate only by sending and receiving messages to each other. These processes are built using a fairly simple functional language that requires a different mind-set than the one we are used to when programming in imperative languages like Python, Ruby or Java.

In this project, we will explore some simple examples of this functional way of programming in both Erlang and in Python. Erlang, like other functional languages such as ML or Haskell, is quite restrictive in constructs we can use. We can write equivalent Python programs with the same restrictions, and in the process leverage our knowledge of Python to a better understanding of Erlang and functional programming in general.

In a second part of this project, we'll explore Erlang's concurrency and message passing features. We'll adapt an example from the logic circuits project, building a composite logic gate using instances of a single simple Nand gate. Instead of each gate being a Python object instance, in Erlang they will each be a seperate concurrent process. Message passing will connect the circuits.

In what may be a third part of the project, we will look at more sophisticated techniques of functional programming such as higher-order functions.

Here are links to the Python and Erlang code.

Replacing Iteration with Recursion

Let's look at a simple factorial function using a "while" loop.

def factorialOld(n) :
    ans = 1
    while n > 1 :
        ans = ans * n
        n   = n - 1
    return ans
>>> import samples
>>> samples.factorialOld(5)
120

Now, in Erlang, such an approach will simply not do. Interation using a "while" or "for" keyword is not allowed. Secondly, a variable may not take multiple values. The reasons for these restrictions will be clear in a bit.

So let's rewrite the factorial function using recursion.

def factorial(n) :
    if n == 0 : return 1
    else      : return n * factorial(n-1)

And run it

>>> import samples
>>> samples.factorial(5)
120

Now that should be pretty straightforward. You might be complaining that the variable "n" really does take on different values, a different one at each level of recursion. But, actually "n" is a different variable at each level. All variables are "assigned" only as a new level of recursion takes place. Within a level, the single value property is intact.

But why all the fuss?

Well, not being able to change a variables "binding" (a term more accurate than "value") means that, within a level of recursion, the relationship between the variables is constant and will not "swim around". The computation is much simpler to analyze and far less error prone. Many subtle errors, maybe most, arise from variables that interact with other with different values at different times. The timing of when each variable is set relative to the others leads to surprising complexity. In the bad old days of GOTO spaghetti code (before even structured programming) most code modifications would introduce new bugs.

Once the variables become fixed, giving up loops within a specific recursion level is actually no longer a big deal because the reason we wanted the loops was to change the value of one or more variables and their relationship with each other.

So now let's look at the factorial function in Erlang.

factorial(0) -> 1;
factorial(N) -> N * factorial(N-1).

Now this may seem strange if you are not used to pattern matching. Basically, there are two cases that in Python we addressed with an "if/else" inside a single function definition. Here pattern matching happens on the outside, instead. If the argument to the factorial call is zero, then a one is returned, no explicit "return" keyword is required. Otherwise, the variable "N" is bound to the argument and the result, from evaluating "N * factorial(N-1)", is returned. It is basically the same logic as in the Python version.

And here is how we can test this erlang version.

chris@ubuntu:~/projects/erlang$ erl
Erlang (BEAM) emulator version 5.6.3
Eshell V5.6.3  (abort with ^G)
1> c(samples).
{ok,samples}
2> samples:factorial(20).
2432902008176640000

Line 1 "c(samples)." compiles "samples.erl" and will return error messages if there are problems. Basically the same as a Python "import". Line 2 runs the function "factorial" in the module "samples". Notice the ":" seperates the module name from the function name, where Python uses a ".". Also notice the ending "." after each statement.

Some Basics of Erlang Syntax.

Just a few things to keep in mind. Once you are used to it, Erlang is actually a surprisingly simple language. This is not at all complete, but enough for what we are working with right now.

  • "->" sets up a conditional and in Python we would always find a ":" in its place.
  • "." ends a statement. It will consist of one or more clauses seperated by a ";". Within a statement only one clause will be chosen, the first whose pattern matches the input.
  • Within a clause there may be multiple expressions seperated by ",". They will be evaluated sequentially. The value last expression evaluated in a statement is returned to the caller.
  • Variables in Erlang begin with an uppercase character. For convenience we'll use the same variable names in our Python equivalent programs.
  • Words starting with a lower case letter represent symbols in Erlang that simply stand for themselves. In Python, we generally use strings for this purpose. We won't use symbols (or tuples) until part 2.

Watching Recursion

Let's modify our earlier Python version of the factorial function to watch it in action. To make it easier to compare the Python and Erlang versions, I'm going to start capitilizing the Python variable names.

def factorialD(N) :
    print "Entering", N
    if N == 0 : Ans = 1
    else      : Ans = N * factorialD(N-1)
    print "Returning", N, Ans
    return Ans
>>> import samples
>>> samples.factorialD(5)
Entering 5
Entering 4
Entering 3
Entering 2
Entering 1
Entering 0
Returning 0 1
Returning 1 1
Returning 2 2
Returning 3 6
Returning 4 24
Returning 5 120
120
>>>

Notice that we progress down the recursive rabbit hole, and finally reaching the bottom, and then on the way back up actually do the computation.

Accumulators and Tail Recursion

Now let's try another version of the factorial function. Again, we'll place a print statement stratigically so we can follow the action.

def factorial2(N, ACC=1) :
    print "Entering with", N, ACC
    if N == 0 : return ACC
    else      : return factorial2(N-1, ACC*N)
>>> import samples
>>> samples.factorial2(5)
Entering with 5 1
Entering with 4 5
Entering with 3 20
Entering with 2 60
Entering with 1 120
Entering with 0 120
120
>>>

Now the computation is done on the way down through the recursion, carrying the partial result along in ACC. The final result is simply popped back up through the nested returns. Notice that by using a named parameter for ACC in our Python version, it can be omitted on the initial call and will be automatically assigned the correct initial value.

Now, if the Erlang compiler (not Python) can detect that for all clauses in a function, no actual computation takes place after each recursive return, it will simply not push the call stack down for new invocations, but rather reuse the stack space of the previous one. This is called "tail recursion". It has two big advantages. It is more efficient, just a single return instead of many redundant ones, and it makes infinite recursion possible without overflowing the stack. And infinite recursion is the only way in Erlang to have an infinite loop. Here is the Erlang version of our tail recursive "factorial".

factorial2(N)     -> factorial2(N,1).
factorial2(0,ACC) -> ACC;
factorial2(N,ACC) -> factorial2(N-1, ACC*N).

Notice that there are two function definitions, each ending with a period. The first takes a single argument and is the called from the outside. The definition with two arguments carries the accumulated result and finally returns it. This second definition satisfies the conditions for tail recursion. Remember that we made ACC a named argument in the Python version to get roughly the same effect. Here is a sample run of the Erlang code.

6> c(samples).
{ok,samples}
7> samples:factorial2(6).
720

List Processing

Consider the following dialog with the Erlang interactive shell.

Eshell V5.6.3  (abort with ^G)
1> A = [1,2,3,4].
[1,2,3,4]
2> [H|T] = A.
[1,2,3,4]
3> H.
1
4> T.
[2,3,4]

An Erlang list looks very much like a Python one. In line 1 the variable A is bound to the list [1,2,3,4]. In line 2 we can really see that "=" is no simple assignment operator. It rather tries to unify the left and right hand sides, assigning values to unbound variables as needed. In this case the unbound variable H is set to the head of the list, "1" and T is to the tail. The pipe character "|" has a special meaning. As in Python, commas in Erlang seperate items in the list but "|" seperates the first item from all the rest.

In Erlang, this syntax can also be used on the right hand side to build lists. Consider.

2> [4 | [5,6,7]].
[4,5,6,7]

Here, we are supplying the head and tail and the "|" operator combines them to a single list.

Python does not have anything like the "|" operator, but we can emulate the action easily.

"[H|T] = L" in Erlang becomes "H=L[0]; T=L[1:]" in Python.

"L = [H|T]" in Erlang becomes "L = [H]+T" in Python.

Both Python and Erlang can concatenate lists. Python simply uses the "+" operator. In Erlang the operator is "++".

In Python

>>> [1,2,3] + [5,6,7]
[1, 2, 3, 5, 6, 7]
>>>

And in Erlang

Eshell V5.6.3  (abort with ^G)
1> [1,2,3] ++ [6,7,8].
[1,2,3,6,7,8]
2>

Let's look at a simple example using lists. We will sum the elements which are assumed to be numbers. Here's two Python versions, the second one is tail recursive.

def sum(L) :
    if not L : return 0
    else     : return L[0] + sum(L[1:])

def suma(L, Acc=0) :
    if not L : return Acc
    else     : return suma(L[1:], Acc+L[0])

Let's test them quickly

>>> import samples
>>> samples.sum([1,2,3,4,5])
15
>>> samples.suma([1,2,3,4,5])
15
>>>

And the Erlang version are basically the same.

sum([]) -> 0;
sum([H|T]) ->  H + sum(T).

suma(L) -> suma(L,0).
suma([],Acc)    -> Acc;
suma([H|T],Acc) -> suma(T, Acc+H).

Let's run it in the Erlang shell

Eshell V5.6.3  (abort with ^G)
1> c(samples.erl).
{ok,samples}
2> samples:sum([1,2,3,4,5,6]).
21
3> samples:suma([1,2,3,4,5,6]).
21
4>

Quicksort in Python and Erlang

Finally, let's look at the classic Quicksort algorithm in both Python and Erlang.

The algorithm is beautifull in its simple recursion and may remind you of the "Tower of Hanoi", another project on this site. Basically, a list of items is seperated into two lists based on picking a random element from the list, which we call the pivot. Items greater than the pivot go to one list and those less than to the other. Those equal to the pivot, if any, are assigned uniformily to one of the two lists. Here is a Python version of the split function, using only recursion. (no while loop)

def split(P, L, A=[], B=[]) :
    if   not L : return [A,B]
    H = L[0]                # H and T assigned only once
    T = L[1:]
    if H <= P : return split(P, T, [H]+A, B    )
    else      : return split(P, T, A,     [H]+B)

Take a deep breath. This is the trickiest bit of code you'll see here. The recursion is replacing what would normally be a while loop. Each recursive call operates on the tail of the previous call, assigning the head to one of the two output lists. The output lists are carried the recursion and the whole thing is nicely tail recursive.

A sample run

>>> samples.split(5,[1,2,3,4,5,6,7,8,9])
[[5, 4, 3, 2, 1], [9, 8, 7, 6]]
>>>

Once we have the function to split lists, the sort itself is not difficult. To sort a list, including the recursive sub-lists, we just use the head of the list as the pivot, split the tail into two lists, sort each of them and finally recombine everthing with Python list concatenation. Here is the code.

def sort(L) :
    if not L : return []
    H = L[0]                # H and T assigned only once
    T = L[1:]
    [A,B] = split(H,T)
    print "Pivot %s: %s --> %s %s" % (H,T,A,B)
    return sort(A) + [H] + sort(B)

To make it a little more interesting, we print the results of each split; the pivot value, the input list and the outputs.

>>> samples.sort([5,4,3,6,7,8,4,3])
Pivot 5: [4, 3, 6, 7, 8, 4, 3] --> [3, 4, 3, 4] [8, 7, 6]
Pivot 3: [4, 3, 4] --> [3] [4, 4]
Pivot 3: [] --> [] []
Pivot 4: [4] --> [4] []
Pivot 4: [] --> [] []
Pivot 8: [7, 6] --> [6, 7] []
Pivot 6: [7] --> [] [7]
Pivot 7: [] --> [] []
[3, 3, 4, 4, 5, 6, 7, 8]
>>>

Finally, let's see the whole program in Erlang.

split(P,L) -> split(P,L,[],[]).

split(_,[],A,B) -> [A,B];
split(P,[H|T],A,B) when H =< P -> split(P,T,[H|A],  B);
split(P,[H|T],A,B)             -> split(P,T,   A,[H|B]).


sort( []   ) -> [];
sort([H|T])  ->
        [A,B] = split(H,T),
        io:format("Pivot ~p: ~p ~p ~p~n",[H,T,A,B]),
        sort(A) ++ [H] ++ sort(B).

And here's it in action.

Eshell V5.6.3  (abort with ^G)
1> samples:sort([5,4,3,6,7,8,4,3]).
Pivot 5: [4,3,6,7,8,4,3] [3,4,3,4] [8,7,6]
Pivot 3: [4,3,4] [3] [4,4]
Pivot 3: [] [] []
Pivot 4: [4] [4] []
Pivot 4: [] [] []
Pivot 8: [7,6] [6,7] []
Pivot 6: [7] [] [7]
Pivot 7: [] [] []
[3,3,4,4,5,6,7,8]
2>

Conclusion

Of course, there is much more to Erlang what's shown here. But in my experience, getting very familiar with this particular pattern of programming was the necessary first step in working with functional programs. If you are new to this, I would suggest that you give yourself some challenges, for example, zip two lists together or append two lists without using the "+" or "++" operators. You'll make lots of mistakes (and find them) but that is often a necessary part of the learning process. Good Luck and have fun.

.