1 % (c) 2009-2024 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5
6 :- module(state_space_dijkstra,[find_shortest_path_from_to/4,
7 find_shortest_path_from_to_found_predicate/4,
8 set_target_id/1, set_found_predicate/2, set_longest_trace_target/0
9 ]).
10
11 :- use_module(tools).
12 :- use_module(module_information).
13 :- module_info(group,animator).
14 :- module_info(description,'Tools for finding shortest paths between visited states.').
15
16 % can find the shortest path from a given node to
17 % any node satisfying a genering "found_predicate"
18
19 :- use_module(state_space).
20 :- use_module(library(heaps)).
21 :- use_module(library(lists)).
22
23
24 :- dynamic found_predicate/2. % a predicate that should return true if we have found a target node
25 :- dynamic mark_id/3.
26
27 set_target_id(TargetID) :-
28 retractall(found_predicate(_,_)),
29 assertz(found_predicate(TargetID,_)).
30
31 set_found_predicate(ID,COND) :-
32 retractall(found_predicate(_,_)),
33 assertz((found_predicate(ID,_Heap) :- COND)).
34
35 % use Dijkstra to find longest trace from a node (usually root)
36 set_longest_trace_target :-
37 retractall(found_predicate(_,_)),
38 assertz((found_predicate(ID,Heap) :- heaps:empty_heap(Heap), \+ any_new_transition(ID,_,_))). % last node processed has longest trace
39
40
41
42 % find_shortest_path_from_to(FromStateID,ToStateID,-ResOpIDPath,-ResStateIDL)
43 find_shortest_path_from_to(From,To,ResOpIDPath,ResIDL) :-
44 set_target_id(To),
45 find_shortest_path_from_to_found_predicate(From,ResOpIDPath,ResIDL,_).
46 find_shortest_path_from_to_found_predicate(From,ResPath,ResIDL,TargetID) :-
47 retractall(mark_id(_,_,_)),
48 %tools:start_ms_timer(T1),
49 empty_heap(H),
50 add_to_heap(H,0,node(From,null,null),NH),
51 dijkstra(NH,RP,RI,TargetID,500),
52 %tools:stop_ms_timer_with_msg(T1,'Shortest path'),
53 reverse(RP,ResPath),
54 reverse(RI,ResIDL).
55
56 :- use_module(debug).
57
58 dijkstra(Heap,ResOpIDPath,ResIDList,TargetID,Cnt) :-
59 (Cnt>0 -> C1 is Cnt-1 ; C1=1000, printsilent('.'),flush_output(user)),
60 get_from_heap(Heap,Dist,node(ID,PrevID,TransID),NewHeap),!,
61 %format('Processing: ~w dist: ~w~n',[ID,Dist]),
62 (found_predicate(ID,NewHeap) -> TargetID=ID, %print(extracting_path(ID)),nl,
63 assertz(mark_id(ID,PrevID,TransID)),
64 nls,
65 extract_path(ID,ResIDList,ResOpIDPath) %,print(res(ResIDList)),nl
66 ; treat_node(ID,PrevID,TransID,Dist,NewHeap,NewHeap1),
67 dijkstra(NewHeap1,ResOpIDPath,ResIDList,TargetID,C1)
68 ).
69 dijkstra(_,_,_,_,_) :-
70 print('NO PATH EXISTS TO A NODE WITH found_predicate TRUE ! '),nl,
71 fail.
72
73 extract_path(ID,StateIDL,Path) :-
74 mark_id(ID,PrevID,TransID),
75 (PrevID=null -> StateIDL=[], Path=[]
76 ; % any_transition(PrevID,TransID,ID), % not necessary ?
77 % here we could choose a transition with minimal changes from previous transition
78 StateIDL=[ID|TI],Path=[TransID|TP],
79 extract_path(PrevID,TI,TP)).
80
81 treat_node(ID,_,_,_,H,RH) :- mark_id(ID,_,_),!,RH=H. % node already treated
82 treat_node(ID,PrevID,TransID,Dist,H,RH) :- assertz(mark_id(ID,PrevID,TransID)),
83 findall(node(NewID,ID,NewTransID),
84 any_new_transition(ID,NewTransID,NewID),
85 Succs),
86 D1 is Dist+1,
87 add_nodes(Succs,D1,H,RH).
88
89 any_new_transition(ID,NewTransID,NewID) :-
90 any_transition(ID,NewTransID,NewID),
91 \+ mark_id(NewID,_,_). % as all weights are 1, we do not need to add NewID: is already visited
92
93 add_nodes([],_,H,H).
94 add_nodes([N|T],Prio,H,RH) :-
95 add_to_heap(H,Prio,N,H1),
96 add_nodes(T,Prio,H1,RH).
97
98 % use_module(state_space_dijkstra), find_shortest_path_to(root,22,P,I)
99
100 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
101
102
103