
% a collection of routines to process directed graphs,
%    represented as lists of pairs of the form [ node, adjlist ]
%
% graph(G) - tests that G is a valid graph
% printG(G) - prints G
% add(G, [S,D], NewG) - succeeds if NewG is the graph G with edge [S,D] added,
%                       [S,D] must not previously have been in the graph
% add(G, N, NewG) - succeeds if NewG is the graph G with node N added (with empty adjlist),
%                   node N must not previously have been in the graph

% ----- future work: add the following ------------------------------------------
% dfs(G,N,L) - performs a depth-first search of G from node N,
%              creating a list of all reachable nodes in the order they were first found
% bfs(G,N,L) - performs a breadth-first search of G from node N,
%              creating a list of all reachable nodes in the order they were first found
% reachable(G, S, D) - succeeds if node D is reachable from node S in G
% edge(G, [S,D]) - succeeds if G contains an edge from S to D
% -------------------------------------------------------------------------------

% graph(G)
% --------
% checks G represents a valid graph, i.e.
%   G is a list of pairs, [ N, L ] where
%    - each N is an atom
%    - each L is a list of atoms, each of which represents a node in G
graph(G) :- graphChk(G, G).
graphChk(_, []).
graphChk(G, [[N,L]|Rest]) :-
   node(N), \+ member([N,_], Rest),
   is_list(L), adjlist(L, G), graphChk(G, Rest).
adjlist([], _).
adjlist([N|T], G) :- member([N,_], G), adjlist(T,G).

% node(N)
% -------
% succeeds if N is a valid node label: number, atom, or string
node(N) :- number(N) ; atom(N) ; string(N).

% add(G, N, NewG)
% ---------------
% attempts to add a new node, N, to G (with an empty adjlist) to form NewG
add(G, N, [[N,[]]|G]) :- node(N), \+ member([N,_], G).

% add(G, [S,D], NewG)
% -------------------
% attempts to add a new edge, S->D, to G to form NewG
%    where nodes S,D are already in G
add(G, [S,D], NewG) :- member([D,_], G), addG(G, [S,D], NewG).
addG([[S, AdjL]], [S,D], [[S, NewL]]) :- addE(AdjL, D, NewL).
addG([[S, AdjL] | R], [S,D], [[S, NewL] | R]) :- addE(AdjL, D, NewL).
addG([H|R], [S,D], [H|NewR]) :- addG(R, [S,D], NewR).

% addE(Adj, D, NewL)
% ------------------
% adds new node, D, to an adjacency list
addE(Adj, D, [D|Adj]) :- \+ member(D,Adj).

% printG(G)
% ---------
% prints graph G
printG([]).
printG([[N,L]|R]):- format("~w: ", [N]), printAdj(L), printG(R).
printAdj([]) :- format("~n").
printAdj([N]) :- format("~w~n", [N]).
printAdj([N|R]) :- format("~w, ", [N]), printAdj(R).

% ------------------------------------------------------------
%     sample graphs
% ------------------------------------------------------------
pickGraph(v0, []).
pickGraph(v1, [[start, [1]], [1, [1, 2]], [2, [1, 2, end]], [end, []]]).
pickGraph(v2, [[start, [1]], [1, [2]], [2, [3, end]], [3, []], [end, []]]).
pickGraph(e0, 3).
pickGraph(e1, [[start, [1]], [1, [1, 2]], [2, [1, 2, start]], [start, []]]).
pickGraph(e2, [[start, 3]]).
pickGraph(e3, [[start, [1]]]).

