% The following program finds all the paths between 2 nodes of a directed % graph. The example graph is already built into the program. % To obtain all the paths between nodes X and Y invoke the following predicate: % paths(X,Y,P). % The list of all paths will be outputted to the file named f. So please % ensure that you do not own such a file. % The global stack and the local stack sizes need to be initialized to 1000k % each. e(1,1,4). e(1,2,3). e(1,4,1). e(2,3,3). e(3,5,3). e(4,5,1). e(5,1,7). e(5,4,2). e(5,5,6). member(X,[X|_]). member(X,[_|Y]) :- member(X,Y). append([],L,L). append([X|L1],L2,[X|L3]) :- append(L1,L2,L3). rev([],[]). rev([H|T],L) :- rev(T,Z),append(Z,[H],L). rem([X],X). rem([X|Y],Z) :- rem(Y,P1),append(X,P1,Z). out([]). out([X|Y]) :- ppath(X),out(Y). ppath([X,Y]) :- write(X),write(' cost='),write(Y),nl. findall(X,G,_) :- asserta(found(mark)), call(G), asserta(found(X)), fail. findall(_,_,L) :- collect_found([],M),!,L = M. collect_found(S,L) :- getnext(X),!,collect_found([X|S],L). collect_found(L,L). getnext(X) :- retract(found(X)),!,X \== mark. legalnode(X,Trail,Y) :- e(X,Y,_),not(member(Y,Trail)). path(Start,Dest,[Route,D]) :- path1([[Start]],Dest,R),rev(R,Route),cost(Route,D). path1([First|Rest],Dest,First) :- First = [Dest|_]. path1([[Last|Trail]|Others],Dest,Route) :- findall([Z,Last|Trail],legalnode(Last,Trail,Z),List), append(Others,List,Newroutes), path1(Newroutes,Dest,Route). cost([X,Y],D) :- e(X,Y,D). cost([X,Y|Z],D) :- e(X,Y,N1),cost([Y|Z],N2),D is N1 + N2. paths(X,Y,P) :- findall(P1,bagof(Z,path(X,Y,Z),P1),P2),rem(P2,P),nl,tell(f),out(P).