In his soon-to-be-published book, Joe Armstrong proposes the following exercise:
Write a ring benchmark. Create N processes in a ring. Send a message round the ring M times. So that a total of N * M messages get sent. Time how long this takes for different values of N and M.
and he adds
Write a similar program in some other programming language you are familiar with. Compare the results. Write a Blog and publish the results on the Internet!
Since i happen to be learning Erlang and, besides, know of another programming language providing Erlang-like primitives, i thought i’d take Joe’s bait and give you a little taste of how Erlang feels to a newcomer.
This is my implementation of the ring in Erlang. If you’re an Erlang hacker, be prepared to be scared: this is my first longer-than-ten-lines program–but, please, do not hesitate to criticize it as deserved!.
-module(ring).
-export([make_ring/2]).
make_ring(N, M) -> spawn(fun() -> sender(N, M) end).
sender(N, M) ->
FirstPid = self(),
NextPid = spawn(fun() -> tunnel(N, 2, FirstPid) end),
statistics(runtime),
statistics(wall_clock),
do_times(M, 0, fun(I) -> NextPid ! I end),
NextPid ! done,
receive done -> done end,
{_, Time1} = statistics(runtime),
{_, Time2} = statistics(wall_clock),
U1 = Time1 * 1000,
U2 = Time2 * 1000,
io:format("Total time=~p (~p) microseconds~n", [U1, U2]).
do_times(N, N, _) -> done;
do_times(N, J, Fun) -> Fun(J), do_times(N, J+1, Fun).
tunnel(N, N, FirstPid) -> tunnel(FirstPid);
tunnel(N, J, FirstPid) ->
tunnel(spawn(fun() -> tunnel(N, J+1, FirstPid) end)).
tunnel(Pid) ->
receive
done -> Pid ! done;
Any -> Pid ! Any, tunnel(Pid)
end.
Here you can see some of Erlang’s niceties: first class, anonymous functions (using the fun() -> [body] end
lambda constructor); function definition by cases (a la Haskell: guards are also admitted) and pattern matching; message mailboxes using receive
(also using pattern matching) and the send operator !
; easy process creation with spawn
; and the pretty no-frills but extremely convenient module system (one would write ring:make_ring(A,B)
to call our ring launcher: the Erlang shell will find and load the ring
module as long as the file is in the load path). You may also have noticed that there is no variable mutations, or that lower case atoms (like done
) are automatically interpreted as symbols. Tuples also make an appearance: they are constructed using braces (as in {_, Time1}
) and you assign values to its components, again, by pattern matching. And, oh, those tail recursive calls to tunnel
and do_times
are properly optimized by the Erlang interpreter.
Although the above is just a subset of the language’s features, it’s enough to show why i like Erlang: it reminds me of Scheme in many ways, while borrowing some interesting bits from ML languages and even Prolog. On top of it, it fulfills Alan Perlis desideratum on programming languages: it changes the way you think, as recently noticed by one of my favourite bloggers. (It is also worth mentioning that Erlang comes charged with a pretty nice library, excellently documented, that has recently gained a slick search interface.)
But back to Joe’s problem. As it happens, there’s ‘one other language i’m familiar with’ (Scheme) that provides and Erlang-like library (Gambit‘s Termite), and rewriting the program was a breeze:
(define (make-ring n m) (spawn (lambda () (sender n m))))
(define (sender n m)
(define (display-time msg start end)
(display (list msg (- end start)))
(newline))
(let* ((fist-pid (self))
(next-pid (spawn (lambda () (tunnel n 2 fist-pid))))
(rt (real-time))
(ct (cpu-time)))
(let loop ((m m))
(cond ((= 0 m)
(! next-pid 'done)
(recv ('done
(let ((nct (cpu-time))
(nrt (real-time)))
(display-time "CPU time: " ct nct)
(display-time "Real time: " rt nrt)))))
(else (! next-pid m)
(loop (- m 1)))))))
(define (tunnel n j first-pid)
(cond ((= n j) (send-recv first-pid))
(else (send-recv (spawn (lambda ()
(tunnel n (+ 1 j) first-pid)))))))
(define (send-recv pid)
(recv
('done (! pid 'done))
(x (! pid x) (send-recv pid))))
If you’re a Schemer, you’ll readily understand the code above, which uses the same primitives as Erlang: !
, recv
(since receive
is taken in Gambit) and spawn
.
What about the comparison? Well, i love Scheme and, to my biased eyes, Gambit’s version is more beautiful. So let’s move to something that is not in the eye of the beholder: speed. Running ring:make_ring(5000, 1000)
in my laptop gives the following output:
Total time=970000 (1520000) microseconds
while typing (make-ring 5000 1000)
at the Gambit’s interpreter prompt yields:
CPU time: 19.442507999999997 secs
Real time: 19.780327081680298 secs
So, the Scheme interpreter is about 20 times slower than the Erlang interpreter (the factor seems to be more or less constant when you change the number of processes or messages sent). But Gambit has a secret weapon: it’s a Scheme to C compiler (why, it’s actually called Gambit-C!). So I compiled my program and ran it, with the following result:
CPU time: 2.3031090000000005 secs
Real time: 2.3484270572662354 secs
The interpreted Erlang code is still more than twice quicker than the compiled C code. Not bad: the more i look at that Erlang program, the more beautiful it looks!
Of course, this is just a toy benchmark which says nearly nothing about the real performance of either Erlang or Termite. I just thought it could be a way of whetting your appetite and get you started in these to systems that i’m just discovering. Googling for Erlang and Termite will direct you to several recent blog entries discussing them and helping you to join the fun, but, lest you miss it, let me recommend this Termite mini-tutorial by Marc Feeley.
And again, if you discover any of the silly things i could do better in the programs above, please leave a comment: i’m just learning!