Haki Terror
Haki Terror

Reputation: 363

Prolog , find neighbors of a graph

Given a graph

G = [1 - 5, 2 - 4, 2 - 6, 3 - 4, 3 - 6, 3 - 9, 4 - 7, 5 - 7, 6 - 7, 6 - 8, 6 - 9]

I must find all neighbors for each node , and create a list with this form

Graph   = [(1, [5]), (2, [4, 6]), (3, [4, 6, 9]), (4, [2, 3, 7]), (5, [1, 7]), (6, [2, 3, 7, 8, 9]), (7, [4, 5, 6]), (8, [6]), (9, [3, 6])].

Here is my approach :

search_for_neighbors(Ne,V,Ne,V).
search_for_neighbors(V,V,Ne,Ne).
search_for_neighbors(_,_,_,0).

neigh(_,[],_).
neigh(N,[(V - Ne)|T],Graph) :-
   neigh(N,T,Graph1),
   search_for_neighbors(N,V,Ne,Result),
   add_first(Result,Graph1,Graph).

allneigh(0,_,_).
allneigh(N,G,L) :-
   N1 is N - 1,
   allneigh(N1,G,L1),
   neigh(N,G,L2),
   add_last((N,L2),L1,L).

add_first(0, L, L).
add_first(X, L, [X|L]). 

add_last(X, [], [X]).
add_last(X, [Y|L1], [Y|L2]):- add_last(X,L1,L2).

I run my Prolog code :

?- allneigh(9,[1 - 5, 2 - 4, 2 - 6, 3 - 4, 3 - 6, 3 - 9, 4 - 7, 5 - 7, 6 - 7, 6 - 8, 6 - 9],G).

And this is my result ,

G = [(1, [5|_464]), (2, [4, 6|_508]), (3, [4, 6, 9|_556]), (4, [2, 3, 7|_606]), (5, [1, 7|_658]), (6, [2, 3, 7, 8, 9|_712]), (7, [4, 5, 6|_769]), (8, [6|_827]), (9, [3, 6|_883])]

Why do I have this behavior ?

Upvotes: 0

Views: 564

Answers (2)

joel76
joel76

Reputation: 5675

Another way is to use foldl :

:- use_module(library(lambda)).

all_neighbors(G, N) :-
    foldl(\X^Y^Z^(X = A - B,
                 (   select((A,V), Y, Y1)
                 ->   append(V, [B], V1),
                      sort([(A,V1) | Y1], Y2)
                 ;   sort([(A,[B])| Y], Y2)),
                 (   select((B,W), Y2, Y3)
                 ->   append(W, [A], V2),
                     sort([(B,V2)|Y3], Z)
                 ;   sort([(B,[A]) | Y2], Z))),
          G, [], N).

The result

 ?- all_neighbors( [1-5,2-4,2-6,3-4,3-6,3-9,4-7,5-7,6-7,6-8,6-9], N).
 N = [(1,[5]),(2,[4,6]),(3,[4,6,9]),(4,[2,3,7]),(5,[1,7]),(6,[2,3,7,8,9]),(7,[4,5,6]),(8,[6]),(9,[3,6])].

Upvotes: 1

willeM_ Van Onsem
willeM_ Van Onsem

Reputation: 476614

Short answer: because of the second underscore (_) in the first line of neigh/3:

neigh(_,[],_).
%          ^ culprint

Since you do recursion on that part, all lists you generate are open ended:

?- neigh(N,[1 - 5, 2 - 4, 2 - 6, 3 - 4, 3 - 6, 3 - 9, 4 - 7, 5 - 7, 6 - 7, 6 - 8, 6 - 9],L).
N = 9,
L = [3, 6|_G4581] ;
N = 9,
L = [0, 3, 6|_G4581] ;
N = 9,
L = [0, 3, 6|_G4581] ;
N = 9,
L = [0, 0, 3, 6|_G4581] ;

You can perform a quick fix by using an empty list, like:

neigh(_,[],[]).

But there are more issues:

  • add_first/3 backtracks even if you add 0, since the second line of add_first/3 does not exclude X being 0.
  • why do you generate an 0 anyway?

In general I would say the code is not much "declarative" and uses a lot of conventions (like using an 0) to filter out corner cases and edge cases. You also use add_last/3, etc. which is usually something you want to avoid since it is quite inefficient.

Solution using builtins

Let us first define a helper function range(N,L). that for a given N, generates a list L=[1,2,...,N]:

range(N,L) :-
    range(1,N,L).

range(I,N,[]) :-
    I > N.
range(I,N,[I|L]) :-
    I =< N,
    I1 is I+1,
    range(I1,N,L).

Now we can use a complex one-liner to construct such a graph:

allneigh(N,G,L) :-
    range(N,Vs),
    findall((X,Ys),
        setof(Y,(member(X,Vs),(member(X-Y,G);member(Y-X,G))),Ys),
    L).

Which gives:

?- allneigh(9,[1 - 5, 2 - 4, 2 - 6, 3 - 4, 3 - 6, 3 - 9, 4 - 7, 5 - 7, 6 - 7, 6 - 8, 6 - 9],G).
G = [ (1, [5]), (2, [4, 6]), (3, [4, 6, 9]), (4, [2, 3, 7]), (5, [1, 7]), (6, [2, 3|...]), (7, [4|...]), (8, [...]), (..., ...)] [write]
G = [ (1, [5]), (2, [4, 6]), (3, [4, 6, 9]), (4, [2, 3, 7]), (5, [1, 7]), (6, [2, 3, 7, 8, 9]), (7, [4, 5, 6]), (8, [6]), (9, [3, 6])] ;

(the second line is only the output written in full).

Upvotes: 2

Related Questions