31
32:- module(shortest_paths,
33 [ shortest_paths/3,
34 all_pairs_shortest_paths/2
35 ]). 36
37
38:- ensure_loaded((utils_higher_order)). 40:- ensure_loaded((utils_set)). 41
42
43shortest_paths(From, Adjacency, Paths):-
44 shortest_paths([path(From, From, 0, [From])], Adjacency, [], Paths).
45
52
53shortest_paths([], _, Paths, Paths).
54shortest_paths([path(Start, Current, Cost, Path)|OpenNodes0], Adjacency, ShortestPaths0, ShortestPaths):-
55 one ( setof(EdgeCost - Neighbour, call(Adjacency, Current, Neighbour, EdgeCost), CostedNeighbours0)
56 ; CostedNeighbours0 = [] ),
57 filter(CostedNeighbours0, [_ - X]^(\+ member(path(Start, X, _, _), ShortestPaths0)), CostedNeighbours),
58 relax(CostedNeighbours, Start, Current, Cost, Path, OpenNodes0, OpenNodes),
59 shortest_paths(OpenNodes, Adjacency, [path(Start, Current, Cost, Path)|ShortestPaths0], ShortestPaths).
60
61
62relax([], _, _, _, _, Open, Open).
63relax([Cost - Neighbour | CostedNeighbours], Start, Current, PathCost, Path, OpenNodes0, OpenNodes):-
64 NewPathCost is PathCost + Cost,
65 ( select(path(Start, Neighbour, OtherCost, _OtherPath), OpenNodes0, RemainingOpen)
66 -> ( NewPathCost < OtherCost
67 -> insert_merge(RemainingOpen, path(Start, Neighbour, NewPathCost, [Neighbour|Path]),
68 compare_paths_by_cost, OpenNodes1)
69 ; OpenNodes1 = OpenNodes0 )
70 ; insert_merge(OpenNodes0, path(Start, Neighbour, NewPathCost, [Neighbour|Path]),
71 compare_paths_by_cost, OpenNodes1) ),
72 relax(CostedNeighbours, Start, Current, PathCost, Path, OpenNodes1, OpenNodes).
73
74
75compare_paths_by_cost(Rel, path(_, _, Cost1, _), path(_, _, Cost2, _)):-
76 compare(Rel, Cost1, Cost2).
77
78
79all_pairs_shortest_paths(Adjacency, AllPaths):-
80 setof(Node, Node2^Cost^call(Adjacency, Node, Node2, Cost), Nodes),
81 foldl(Nodes,
82 [ExistingPaths, Node, Paths]^
83 (shortest_paths([path(Node, Node, 0, [Node])], Adjacency, ExistingPaths, Paths)),
84 [],
85 AllPaths)