Guide to Prolog Programming

© Roman Barták, 1998

Home
Prolog in Examples
Prolog Data Structures

Previous | Contents | Next

Graphs in Prolog


[representation] [coloring] [search]
[
generate&test] [backtracking] [forward checking] | [simple search] [Dijkstra]

Graph is another data structure that is widely used in current algorithms. In this lecture we will describe a representation of graphs in Prolog and we will develop some programs for typical graph operations (coloring, search).


Representation

Graph is usually defined as pair (V,E), where V is a set of vertices and E is a set of edges. There are many possible representations of graphs in Prolog, we will show two of them.

Representation A keeps vertices and edges in two different lists (sets):

g([Vertex, ...],[e(Vertex1,Vertex2,Value), ...])

Note, that this representation is appropriate for directed graphs as well as for non-directed graphs. In case of non-directed graphs, one can add each non-directed edge e(V1,V2,H) as two directed edges e(V1,V2,H), e(V2,V1,H) or, better, it is possible to adjust the access procedure edge (defined below).

Representation B is based on idea of neighbourhood and graph is represented as a list of vertices and its neighbourhood.

[Vertex-[Vertex2-Value, ...], ...]

In this case, the representation of non-directed graphs contains each edge two times.

Here is the procedure for access to edges in Representation A.

edge(g(Es,Vs),V1,V2,Value):-
   member(e(V1,V2,Value),Vs).

If the graph is non-directed, the procedure edge can be adjusted in a following way:

edge(g(Es,Vs),V1,V2,Value):-
   member(e(V1,V2,Value),Vs) ; member(e(V2,V1,Value),Vs).

Here is the procedure edge for Representation B.

edge(Graph,V1,V2,Value):-
   member(V1-NB,Graph),
   member(V2-Value,NB).

Now, it is possible to define procedure for finding neighbourhood of the vertex using procedure edge.

neighbourhood(Graph,V,NB):-
   setof(V1-E,edge(Graph,V,V1,E),NB).

In case of Representation B it is better (more efficient) to define neighbourhood directly.

neighbourhood(Graph,V,NB):-
   member(V-NB,Graph).

Note, that some graphs does not use values of edges while other graphs assign values also to vertices. In these cases, the above procedures have to be rewritten accordingly.


Coloring

The goal of graph coloring is to add a color (from limited palette of colors) to each vertex in such a way that the adjacent vertices (via edge) have assigned different colors. Even if the graph coloring seems to be a theoretical-only problem, the algorithms for graph coloring are widelly used in practical applications (constraint satisfaction).

In this lecture we will present three algorithms for graph coloring. We start with naive algorithm that implements generate and test method in rough form. Then we improve the algorithm by joining the generate and test phases into one procedure. Finally, we implement a more sophisticated method called forward checking.

The following program uses generate and test method to color vertices of graph. First, the color is assigned to each vertex and then the program tests the validity of coloring.

% coloring1(+Graph,+Colors,-Coloring)
coloring1(g(Vs,Es),Colors,Coloring):-
   gener(Vs,Colors,Coloring),
   test(Es,Coloring).
   
% gener(+Vertices,+Colors,-Coloring)
gener([],_,[]).
gener([V|Vs],Colors,[V-C|T]):-
   member(C,Colors), % non-deterministic generator of colors
   gener(Vs,Colors,T).
   
% test(+Edges,+Coloring)
test([],_).
test([e(V1,V2)|Es],Coloring):-
   member(V1-C1,Coloring), % find color of vertex V1
   member(V2-C2,Coloring), % find color of vertex V2
   C1\=C2,                 % test the difference of colors
   test(Es,Coloring).

The above program is not very efficient because it generates many wrong colorings which are rejected in the testing phase. In addition, the generator leaves out the conflicting vertices and it generates other colorings independently of the conflict.

It is clear that we can test validity of coloring during generation of colors. Following program joins generation and testing into one procedure. Note, that we use accumulator to save the partial coloring.

% coloring2(+Graph,+Colors,-Coloring)
coloring2(g(Vs,Es),Colors,Coloring):-
   gat(Vs,Es,Colors,[],Coloring).   % generate and test
   
% gat(Vertices,Edges,Colors,ColoredVertices,FinalColoring)
gat([],_,_,Coloring,Coloring).
gat([V|Vs],Es,Cs,Acc,Coloring):-
   member(C,Cs),          % generate color for vertex V
   test2(Es,V,C,Acc),     % test the validity of current coloring
   gat(Vs,Es,Cs,[V-C|Acc],Coloring).
   
% test2(+Edges,+Vertex,+Color,+CurrentColoring)
test2([],_,_,_).
test2([e(V1,V2)|Es],V,C,CColoring):-
   (V=V1 -> (member(V2-C2,CColoring) -> C\=C2 ; true)
    ;(V=V2 -> (member(V1-C1,CColoring) -> C\=C1 ; true)
     ;true)),
   test2(Es,V,C,CColoring).

The above program uses backtracking to find another valid coloring, but it is not able to detect conflict before the conflict really occurs, i.e., after assigning the color to the second vertex of the conflicting edge.

It is possible to improve behaviour of the algorithm by forward checking of conflicts. First, we assign the set of all possible colors to each vertex (prep). Then, we choose one vertex and its color (from the set of possible colors assigned to this vertex) and we remove this color from all adjacent vertices (fc), i.e., we remove (some) future conflicts. Therefore, we know that the assigned color is not in conflict with already colored vertices.

Note, that as the forward checking adds some addtional overhead to the algorithm, it is possible that the classical backtracking could be more efficient in some cases. Also, the efficiency of forward checking algorithm depends on the strategy of choosing variables and colors for assignment.

% coloring3(+Graph,+Colors,-Coloring)
coloring3(g(Vs,Es),Colors,Coloring):-
   prep(Vs,Colors,ColoredVs),
   gtb(ColoredVs,Es,[],Coloring).
   
% prep(+Vertices,+Colors,+SuperColoring)
prep([],_,[]).
prep([V|Vs],Colors,[V-Colors|CVs]):-
   prep(Vs,Colors,CVs).
   
% gtb(+SuperColoring,+Edges,+PartialColoring,-Coloring)
gtb([],_,Coloring,Coloring).
gtb([V-Cs|Vs],Es,Acc,Coloring):-
   member(C,Cs),                  % select only one color
   fc(Es,V,C,Vs,ConstrainedVs),   % forward checking
   gtb(ConstrainedVs,Es,[V-C|Acc],Coloring).
   
% fc(+Edges,+Vertex,+VertexColor,+InputSuperColoring,-OutputSuperColoring)
fc([],_,_,Vs,Vs).
fc([e(V1,V2)|Es],V,C,Vs,ConstrVs):-
   (V=V1 -> constr(Vs,V2,C,NewVs)
    ;(V=V2 -> constr(Vs,V1,C,NewVs)
      ;NewVs=Vs)),
   fc(Es,V,C,NewVs,ConstrVs).
   
% constr(+InputSuperColoring,+Vertex,-VertexForbiddenColor,+OutputSuperColoring)
constr([V-Cs|Vs],V,C,[V-NewCs|Vs]):-
   delete(Cs,C,NewCs),NewCs\=[].
constr([V1-Cs|Vs],V,C,[V1-Cs|NewVs]):-
   V\=V1,
   constr(Vs,V,C,NewVs).
constr([],_,_,[]).
   
delete([],_,[]).
delete([X|T],X,T).
delete([Y|T],X,[Y|NewT]):-
   X\=Y,
   delete(T,X,NewT).

Note, that delete does not fail if the element is not present in the list.


Search

Another popular group of algorithms regarding graphs is search. In this lecture we will present two algorithms: simple search that finds path between two vertices and Dijkstra's algorithm which finds minimal distance/path from one vertex to all vertices.

The following program finds a path from one vertex to another vertex. The same program can be used to find path in both directed and non-directed graphs depending on the definiton of procedure edge. Note, that we use accumulator containing part of path to prevent cycles.

% path(+Graph,+Start,+Stop,-Path)
path(Graph,Start,Stop,Path):-
   path1(Graph,Start,Stop,[Start],Path).
path1(Graph,Stop,Stop,Path,Path).
path1(Graph,Start,Stop,CurrPath,Path):-
   Start\=Stop,
   edge(Graph,Start,Next),
   non_member(Next,CurrPath),
   path1(Graph,Next,Stop,[Next|CurrPath],Path).
   
non_member(_,[]).
non_member(X,[Y|T]):-
   X\=Y,
   non_member(X,T).

Dijkstra's algorithm is a well known algorithm for finding minimal path in graphs with (non-negative) edges. Here is its implementation in Prolog which finds minimal distance to all vertices from given vertex.

% min_dist(+Graph,+Start,-MinDist)
min_dist(Graph,Start,MinDist):-
   dijkstra(Graph,[],[Start-0],MinDist).
   
% dijkstra(+Graph,+ClosedVertices,+OpenVertices,-Distances)
dijkstra(_,MinDist,[],MinDist).
dijkstra(Graph,Closed,Open,MinDist):-
   choose_v(Open,V-D,RestOpen),
   neighbourhood(Graph,V,NB),  % NB is a list of adjacent vertices+distance to V
   diff(NB,Closed,NewNB),
   merge(NewNB,RestOpen,D,NewOpen),
   dijkstra(Graph,[V-D|Closed],NewOpen,MinDist).
   
% choose_v(+OpenVertices,-VertexToExpand,-RestOpenVertices)
choose_v([H|T],MinV,Rest):-
   choose_minv(T,H,MinV,Rest).
choose_minv([],MinV,MinV,[]).
choose_minv([H|T],M,MinV,[H2|Rest]):-
   H=V1-D1, M=V-D,
   (D1<D -> NextM=H,H2=M
          ; NextM=M,H2=H),
   choose_minv(T,NextM,MinV,Rest).
   
% diff(+ListOfVertices,+Closed,-ListOfNonClosedVertices)
diff([],_,[]).
diff([H|T],Closed,L):-
   H=V-D,
   (member(V-_,Closed) -> L=NewT ; L=[H|NewT]),
   diff(T,Closed,NewT).
   
% merge(+ListOfVertices,+OldOpenVertices,-AllOpenVertices)
merge([],L,_,L).
merge([V1-D1|T],Open,D,NewOpen):-
   (remove(Open,V1-D2,RestOpen)
      -> VD is min(D2,D+D1)
       ; RestOpen=Open,VD is D+D1),
   NewOpen=[V1-VD|SubOpen],
   merge(T,RestOpen,D,SubOpen).
   
remove([H|T],H,T).
remove([H|T],X,[H|NT]):-
   H\=X,
   remove(T,X,NT).

Compare the procedure remove with the procedure delete (coloring part). Do you see the difference?

Extend the above program in such a way that it also finds the minimal path (not only the minimal distance) to all vertices.


Graph algorithms can be used to solve many type of problems.

[representation] [coloring] [search]
[
generate&test] [backtracking] [forward checking] | [simple search] [Dijkstra]


Designed and maintained by Roman Barták

Previous | Contents | Next