1 % (c) 2009-2019 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]).
9
10 :- use_module(tools).
11 :- use_module(module_information).
12 :- module_info(group,animator).
13 :- module_info(description,'Tools for finding shortest paths between visited states.').
14
15 % can find the shortest path from a given node to
16 % any node satisfying a genering "found_predicate"
17
18 :- use_module(state_space).
19 :- use_module(library(heaps)).
20 :- use_module(library(lists)).
21
22
23 :- dynamic found_predicate/1. % a predicate that should return true if we have found a target node
24 :- dynamic mark_id/3.
25
26 set_target_id(TargetID) :-
27 retractall(found_predicate(_)),
28 assert(found_predicate(TargetID)).
29
30 set_found_predicate(ID,COND) :-
31 retractall(found_predicate(_)),
32 assert((found_predicate(ID) :- COND)).
33
34 % find_shortest_path_from_to(FromStateID,ToStateID,-ResOpIDPath,-ResStateIDL)
35 find_shortest_path_from_to(From,To,ResOpIDPath,ResIDL) :-
36 set_target_id(To),
37 find_shortest_path_from_to_found_predicate(From,ResOpIDPath,ResIDL,_).
38 find_shortest_path_from_to_found_predicate(From,ResPath,ResIDL,TargetID) :-
39 retractall(mark_id(_,_,_)),
40 empty_heap(H),
41 add_to_heap(H,0,node(From,null,null),NH),
42 dijkstra(NH,RP,RI,TargetID,10),
43 reverse(RP,ResPath), reverse(RI,ResIDL).
44
45 :- use_module(debug).
46
47 dijkstra(Heap,ResOpIDPath,ResIDList,TargetID,Cnt) :-
48 (Cnt>0 -> C1 is Cnt-1 ; C1=1000, printsilent('.'),flush_output(user)),
49 get_from_heap(Heap,Dist,node(ID,PrevID,TransID),NewHeap),!,
50 (found_predicate(ID) -> TargetID=ID, %print(extracting_path(ID)),nl,
51 assert(mark_id(ID,PrevID,TransID)),
52 nls,
53 extract_path(ID,ResIDList,ResOpIDPath) %,print(res(ResIDList)),nl
54 ; treat_node(ID,PrevID,TransID,Dist,NewHeap,NewHeap1),
55 dijkstra(NewHeap1,ResOpIDPath,ResIDList,TargetID,C1)
56 ).
57 dijkstra(_,_,_,_,_) :-
58 print('NO PATH EXISTS TO A NODE WITH found_predicate TRUE ! '),nl,
59 fail.
60
61 extract_path(ID,StateIDL,Path) :-
62 mark_id(ID,PrevID,TransID),
63 (PrevID=null -> StateIDL=[], Path=[]
64 ; % any_transition(PrevID,TransID,ID), % not necessary ?
65 % here we could choose a transition with minimal changes from previous transition
66 StateIDL=[ID|TI],Path=[TransID|TP],
67 extract_path(PrevID,TI,TP)).
68
69 treat_node(ID,_,_,_,H,RH) :- mark_id(ID,_,_),!,RH=H. % node already treated
70 treat_node(ID,PrevID,TransID,Dist,H,RH) :- assert(mark_id(ID,PrevID,TransID)),
71 findall(node(NewID,ID,NewTransID),
72 any_transition(ID,NewTransID,NewID), Succs),
73 D1 is Dist+1,
74 add_nodes(Succs,D1,H,RH).
75
76 add_nodes([],_,H,H).
77 add_nodes([N|T],Prio,H,RH) :- add_to_heap(H,Prio,N,H1),
78 add_nodes(T,Prio,H1,RH).
79
80 % use_module(state_space_dijkstra), find_shortest_path_to(root,22,P,I)