Solutions for Session 6

Accumulating parameters

  1. list_length_2(List,Length) :-
    	list_length_acc(List,Length,0).
    
    list_length_acc([], Length, Length).
    list_length_acc([_Head|Tail], Length, Acc):-
            Acc1 is Acc +1,
            list_length_acc(Tail, Length, Acc1).
    
    The call tree for the query ?- list_length([a,b,c],L). to the non-tail-recursive predicate is here.
    The call tree for the query ?- list_length_2([a,b,c],L). to the tail-recursive predicate defined above is here.
  2. get_doubles(List, Doubles):-
            get_doubles_acc(List, Doubles, [], []).
            % 3th arg = elements that we have seen once before so far, 4th arg = elements that we have seen twice or more before so far
    
    get_doubles_acc([], Doubles, _, Doubles).
    
    get_doubles_acc([El|T],Result,Singles,Doubles):- % we have seen the element El twice (or more) before
            member(El,Doubles), !,
            get_doubles_acc(T,Result,Singles,Doubles).
    
    get_doubles_acc([El|T],Result,Singles,Doubles):- % we have seen the element El once before
            member(El,Singles), remove(El,Singles,NewSingles), !,
            get_doubles_acc(T,Result,NewSingles,[El | Doubles]).
    
    get_doubles_acc([El|T],Result,Singles,Doubles):- % we have not seen the element El before
             get_doubles_acc(T,Result,[El | Singles],Doubles).
    
    We can make this a bit more efficient by writing a predicate that does "member" and "remove" at the same time:
    % member_remove/3 checks whether an element occurs in a list and removes the element 
    % we assume that the list does not contain doubles
    member_remove(El , [El|Tail], Tail).
    member_remove(El1, [El2|Tail], [El2| NewTail]):-
            member_remove(El1, Tail, NewTail).
    
    Like this we can merge the calls member(El,Singles), remove(El,Singles,NewSingles) in the fourth clause into one single call to member_remove(El,Singles,NewSingles).
  3. frequence(List, Table):-
            frequence_acc(List, Table, []).
    
    frequence_acc([], Table, Table).
    frequence_acc([El|Tail], Table, Acc):-
            member_remove(occur(El, Numb), Acc, Remainder),!,
            Numb1 is Numb +1,
            frequence_acc(Tail, Table, [occur(El, Numb1)|Remainder]).
    frequence_acc([El|Tail], Table, Acc):-
            frequence_acc(Tail, Table, [occur(El, 1)|Acc]).
    
  4. Remember from session 2 that the easiest way to calculate fibonacci numbers is as follows:

    fibo(1,1).
    fibo(2,1).
    fibo(N,FibN):-
    	N>2,
    	Prev is N - 1,
    	Prev2 is N - 2,
    	fibo(Prev,FibPrev),
    	fibo(Prev2,FibPrev2),
    	FibN is FibPrev + FibPrev2.
    
    As explained in session 2, a lot of redundant calculations are done in this way. The faster version with accumulating parameters looks as follows.
    fibo(N,Fib):-
    	fib(1,N,1,1,Fib).
    
    fib(Count,DesiredNb,CurrentFib,_,Result):-
    	Count = DesiredNb,
    	CurrentFib = Result. 
    fib(Count,DesiredNb,CurrentFib,NextFib,Result):-
    	Count < DesiredNb,
    	NewCount is Count + 1,
    	NextNextFib is CurrentFib + NextFib,
    	fib(NewCount,DesiredNb,NextFib,NextNextFib,Result).
    
    The trick here was to use two accumulators (the third and fourth argument of the fib predicate) because a fibonacci number is defined as the sum of the two previous fibonacci numbers.
    The meaning of the five arguments of the predicate fib is the following. The first argument indicates which step we are in (e.g. if it is 1 we are in the first step). The second argument indicates which fibonacci number we eventually want to compute (e.g. if it is 5 we want to compute the fifth fibonacci number); this is also the total number of steps we will need. The third argument is the fibonacci number for the current step (e.g. if we are in the third step, this will be the third fibonacci number). The fourth argument is the fibonacci number for the next step (e.g. if we are in the third step, this will be the fourth fibonacci number). The fifth argument is where we will return the solution when the recursion has finished.

Graphs

  1. arc(From,To,Graph) :-
    	member(From/To,Graph).
    
  2. triple_arc(X,Y,Graph):-
    	arc(X,U,Graph),
    	arc(U,V,Graph),
    	arc(V,Y,Graph).
    
  3. connected(X,X,_).
    connected(X,Y,Graph) :-
    	arc(Z,Y,Graph), 
    	connected(X,Z,Graph).
    
    Make sure not to write the recursive case as below or you could get infinite loops (even for acyclic graphs e.g. ?- connected(a,c,[a/b,c/d]).:
    connected(X,Y,Graph):-
            connected(Z,Y,Graph),
            arc(X,Z,Graph).
    
  4. find_path(X,Y,Path,Graph) :-
            find_path_acc(X,Y,Path,[Y],Graph).
    
    find_path_acc(X,X,Path,Path,_).
    find_path_acc(X,Y,Path,Acc,G) :-
    	arc(Z,Y,G), 
    	find_path_acc(X,Z,Path,[Z|Acc],G).
    
  5. The following definition of find_path_2/4 will never go into an infinite loop.
    find_path_2(X,Y,Path,Graph) :-
            find_path_acc_2(X,Y,Path,[Y],Graph).
    
    find_path_acc_2(X,X,Path,Path,_).
    find_path_acc_2(X,Y,Path,Acc,G) :-
    	arc(Z,Y,G), not(member(Z,Acc)),
    	find_path_acc_2(X,Z,Path,[Z|Acc],G).
    
    Note that the only difference with the previous definition is the call to not(member(Z,Acc)) in the recursive case. The idea is simply to make sure that you never go into a node again if you already visited it before (i.e. if it was already in Acc).

    We can now simply define connected_2/3 as follows:

    connected_2(X,Y,Graph):-
            find_path_2(X,Y,_,Graph).
    

    Here are two queries to illustrate the difference between connected_2/3 and the original connected/3:

    ?- connected(d,c,[a/b,b/c,c/a,d/c]).
    ERROR: Out of local stack
    ?- connected_2(d,c,[a/b,b/c,c/a,d/c]).
    Yes
    
  6. For undirected graphs, simply replace the original definition of arc/3 by:
    arc(From,To,Graph) :-
    	member(From/To,Graph).
    arc(From,To,Graph) :-   
            member(To/From,Graph).
    
    All other predicates can now stay the same as for directed graphs.