[erlang-questions] Joe

Ivan Carmenates García co7eb@REDACTED
Tue Mar 5 18:11:42 CET 2013


I'm still digesting the permutation algorithm I will come up with a reply
soon... I hope.




-----Mensaje original-----
De: Richard A. O'Keefe [mailto:ok@REDACTED] 
Enviado el: lunes, 04 de marzo de 2013 20:32
Para: Ivan Carmenates García
CC: erlang-questions@REDACTED
Asunto: Re: [erlang-questions] Joe


On 5/03/2013, at 8:05 AM, Ivan Carmenates García wrote:

> Hi all, I’m reading the Making Reliable Distributed Systems in the
Presence of Software Errors by Joe Armstrong Thesis of 2003 and I found this
little algorithm using list of compression and there is no way I can
understand how internally it work.

That's "list comPREHENSION" and yes there is a way.

> perms([]) -> [[]];
> perms(L) -> [[H|T] || H <- L, T <- perms(L--[H])].

to generate the permutations of a list:
   if the list is empty []
      the permutations of [] are [X] where X = []
   if the list L is not empty
       for each element H of L
          form the list L' by deleting H from L
          let P be the list of all permutations of L'
          for each T in P (for each T being a permutation of L without X)
              add H to the front of T
              [H|T] is a permutation of L
       collect all those permutations as the answer

or in Smalltalk:
    Array
      methods:
        allPermutations
          |r|
          r := OrderedCollection new.
          self isEmpty
            ifTrue:  [r add: self]
            ifFalse: [
              self do: [:each |
                (self copyWithout: each) allPermutations do:
[:eachPermutation |
                  r add: (eachPermutation copyWith: each)]]].
          ^r

Test
(1 to: 4) asArray allPermutations
=> an OrderedCollection(
   #(4 3 2 1) #(3 4 2 1) #(4 2 3 1) #(2 4 3 1) #(3 2 4 1) #(2 3 4 1)
   #(4 3 1 2) #(3 4 1 2) #(4 1 3 2) #(1 4 3 2) #(3 1 4 2) #(1 3 4 2)
   #(4 2 1 3) #(2 4 1 3) #(4 1 2 3) #(1 4 2 3) #(2 1 4 3) #(1 2 4 3)
   #(3 2 1 4) #(2 3 1 4) #(3 1 2 4) #(1 3 2 4) #(2 1 3 4) #(1 2 3 4))

If you look at the Smalltalk code, you will see
 (1) an "_ isEmpty ifTrue: [_] ifFalse: [_]"
     which is done in Erlang with two clauses, one of which matches the
     empty list and the second which will be given anything but the empty
     list to match
 (2) an outer "_ do: [:each | _]" loop that iterates over the elements of
     the array.  The equivalent in Erlang is "H <- L".
 (3) an inner "_ allPermutations do: [:eachPermutation | _] loop that
     iterates over the permutations of (self copyWithout: each).
     The equivalent in Erlang is "T <- permutations(L -- [H])
 (4) (eachPermutation copyWith: each) is added to the result that is built
     up.  The equivalent in Erlang is [[H|T] || _].

So whenever you have Pattern <- expression in a list comprehension, you have
a loop over the elements of the expression, and whenever you have more than
one of them, you have nested loops, the leftmost outermost and the rightmost
innermost.

Another approach is to trace what's going on.
You can use the functions in the 'dbg' module to do tracing.
It has a lot to offer.  But for a simple case like this, adding your own
code isn't hard:

permutations(L) ->
   traced_permutations(L, 0).

traced_permutations(L, Depth) ->
    format("~*c~w => ~n", [Depth,32,L]),
    R = traced_permutations_body(L, Depth+1),
    format("~*c => ~w~n", [Depth,32,R]),
    R.

traced_permutations_body([], _) ->
    [[]];
traced_permutations_body(L, Depth) ->
    [[H|T] || H <- L, T <- traced_permutations(L--[H], Depth)].

2> perms:permutations([1,2,3]).
[1,2,3] =>
 [2,3] =>
  [3] => 
   [] => 
    => [[]]
   => [[3]]
  [2] => 
   [] => 
    => [[]]
   => [[2]]
  => [[2,3],[3,2]]
 [1,3] =>
  [3] => 
   [] => 
    => [[]]
   => [[3]]
  [1] => 
   [] => 
    => [[]]
   => [[1]]
  => [[1,3],[3,1]]
 [1,2] =>
  [2] => 
   [] => 
    => [[]]
   => [[2]]
  [1] => 
   [] => 
    => [[]]
   => [[1]]
  => [[1,2],[2,1]]
 => [[1,2,3],[1,3,2],[2,1,3],[2,3,1],[3,1,2],[3,2,1]]
[[1,2,3],[1,3,2],[2,1,3],[2,3,1],[3,1,2],[3,2,1]]



>  
> I did figure out that the recursion does first I mean the call to the
function T <- perms(L--[H]) but step by step I can not follow.
> First, the function is called using [1,2,3] list so [[1|T] || H <- L, 
> T <- perms([1,2,3]--[1] = [2,3])] [[1|[2|T]] || H <- L, T <- 
> perms([2,3]--[2] = [3])] [[1|[2|[3|T]]] || H <- L, T <- perms([3]--[3] 
> = [])] [[1|[2|[3|[]]]] || H <- L, T <- [])]
>  
> And now what! What’s the next step?
>  
> I changed the code in order to print the steps so I can understand but
even with that the debug is so confuse. Because the order changes, maybe
because of the recursive thing.
> But I don’t understand why in the head the value 1 is repeated to 
> yield the next value [[1,2,3), [1,3,2], 
]
>  
> perms([]) -> [[]];
> perms(L) ->
>       io:format("L = ~p~n", [L]),
>       [[{H,io:format("H = ~p - ", [H])}| {T, io:format("T = ~p~n", [T])}]
|| H <- L, T <- perms(L--[H])].

This would be better as

perms([]) ->
    [[]];
perms(L) ->
    [begin io:format("H = ~w, T = ~w, L = ~w;~n", [H,T,L]), [H|T] end
     || H <- L, T <- perms(L--[H])].

with output

4> perms:perms([1,2,3]).
H = 3, T = [], L = [3];
H = 2, T = [3], L = [2,3];
H = 2, T = [], L = [2];
H = 3, T = [2], L = [2,3];
H = 1, T = [2,3], L = [1,2,3];
H = 1, T = [3,2], L = [1,2,3];
H = 3, T = [], L = [3];
H = 1, T = [3], L = [1,3];
H = 1, T = [], L = [1];
H = 3, T = [1], L = [1,3];
H = 2, T = [1,3], L = [1,2,3];
H = 2, T = [3,1], L = [1,2,3];
H = 2, T = [], L = [2];
H = 1, T = [2], L = [1,2];
H = 1, T = [], L = [1];
H = 2, T = [1], L = [1,2];
H = 3, T = [1,2], L = [1,2,3];
H = 3, T = [2,1], L = [1,2,3];
[[1,2,3],[1,3,2],[2,1,3],[2,3,1],[3,1,2],[3,2,1]]

We can see that in every line [H|T] is a permutation of L.
That's about all we can see, because it's not indented.
In particular, the order in which we see H varying is NOT the order in which
permutations starting with that value of H are *begun* but the order in
which they are *completed*.
[1,2,3] =>
  H<1> = 1, recursive call with [2,3] =>
    H<2> = 2, recursive call with [3] =>
      H<3> = 3, recursive call with [] => [[]]
      => [3|[]]
    => [2|[3]]
    H<2> => 3, recursive call with [2] =>
      H<3> = 2, recursive call with [] => [[]]
      => [2|[]]
    => [3|[2]]
    => [1|[2,3]], [1|[3,2]]
  ...

It's not clear to me what it is that confuses you.
Given a list L, a binding to H is used as many times as there are elements
in L--[H], because the H loop is the outermost one.





More information about the erlang-questions mailing list