1 | % (c) 2009-2022 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 | :- module(kodkod_process, [register_problem/7, kodkod_request_intern/5, | |
6 | get_original_problem/2, | |
7 | clear_java_comp_time/0, | |
8 | get_java_comp_time/1, | |
9 | stop_kodkod/0 | |
10 | ]). | |
11 | ||
12 | :- use_module(library(avl)). | |
13 | :- use_module(library(lists)). | |
14 | :- use_module(library(process)). | |
15 | :- use_module(library(file_systems)). | |
16 | ||
17 | :- use_module(probsrc(module_information),[module_info/2]). | |
18 | :- use_module(probsrc(store), [lookup_value_for_existing_id/4]). | |
19 | :- use_module(probsrc(bsyntaxtree)). | |
20 | :- use_module(probsrc(kernel_objects), [equal_object/2]). | |
21 | :- use_module(probsrc(custom_explicit_sets), [expand_custom_set_to_list/2]). | |
22 | :- use_module(probsrc(error_manager)). | |
23 | :- use_module(probsrc(system_call)). | |
24 | :- use_module(probsrc(preferences), [get_preference/2]). | |
25 | :- use_module(probsrc(debug), [debug_format/3, formatsilent/2]). | |
26 | ||
27 | :- use_module(kodkodsrc(kodkod_printer)). | |
28 | ||
29 | ||
30 | :- module_info(group,kodkod). | |
31 | :- module_info(description,'This is the inter-process communication with the Java process that contains the Kodkod engine.'). | |
32 | ||
33 | :- set_prolog_flag(double_quotes, codes). | |
34 | ||
35 | :- dynamic known_problem/7, next_problem_id/1. | |
36 | ||
37 | next_problem_id(0). | |
38 | ||
39 | register_problem(Ids,KExpr,Idmap,Typemap,Valuemap,Predicate,ProblemId) :- | |
40 | startup_kodkod, | |
41 | get_new_problem_id(ProblemId), | |
42 | extract_all_types(Typemap,Types), | |
43 | extract_all_relations(Idmap,Relations), | |
44 | prepare_value_mapping(Valuemap,ProbToKodkodVal,KodkodToProbVal), | |
45 | prepare_id_mapping(Ids,Idmap,ProbToKodkodId,KodkodToProbId), | |
46 | assertz( known_problem(ProblemId,Types,Relations,KExpr, | |
47 | probkodkod(ProbToKodkodVal,ProbToKodkodId), | |
48 | kodkodprob(KodkodToProbVal,KodkodToProbId), | |
49 | Predicate) ), | |
50 | catch( send_problem(ProblemId), | |
51 | error(_,Err), % usually error(system_error,system_error('SPIO_E_NET_CONNRESET')) | |
52 | (format('Restarting Kodkod process due to: ~w~n',[Err]), | |
53 | reset_kodkod_process, | |
54 | startup_kodkod, | |
55 | send_problem(ProblemId))). | |
56 | ||
57 | get_original_problem(Id,OrigPredicate) :- | |
58 | known_problem(Id,_,_,_,_,_,OrigPredicate). | |
59 | ||
60 | extract_all_types(Typemap,Types) :- | |
61 | avl_range(Typemap,Relations), | |
62 | include(is_base_relation,Relations,BaseRelations), | |
63 | %print(extract_int_types(Relations)),nl, | |
64 | extract_int_types(Relations,IntTypes), | |
65 | %print('Result : '), print(IntTypes),nl, | |
66 | append(IntTypes,BaseTypes,Types), | |
67 | maplist(extract_type, BaseRelations, BaseTypes). | |
68 | ||
69 | is_base_relation(relation(_,_,reldef(_,_,_,_,_))). | |
70 | extract_type(relation(Id,Size,_Relspec),type(Id,Size)). | |
71 | ||
72 | :- use_module(kodkod_tools,[pow2integer_relation_kodkod_name/1]). | |
73 | extract_int_types(Relations,IntTypes) :- | |
74 | exclude(is_base_relation,Relations,IntRelations), | |
75 | extract_int_types2(IntRelations,IntTypes). | |
76 | extract_int_types2([],[]) :- !. | |
77 | extract_int_types2(IntRelations,[inttype(PowName,PowMin,PowMax,IntsetName,Min,Max)]) :- | |
78 | selectchk(relation(IntsetName,_,intsetrel(_Id,RMin,Max)),IntRelations,Rest),!, | |
79 | Min is min(RMin,0), | |
80 | extract_int_types2(Rest,RestResult), | |
81 | (RestResult = [inttype(PowName,PowMin,PowMax)] -> true | |
82 | ; RestResult = [] -> pow2integer_relation_kodkod_name(PowName), | |
83 | PowMin=Min, PowMax=Max % I have no idea if this is correct; TO DO: Daniel check this | |
84 | ). % What if RestResult is something else ??? | |
85 | extract_int_types2(IntRelations,[inttype(PowName,PowMin,PowMax)]) :- | |
86 | memberchk(relation(PowName,_,pow2rel(_Id,RPowMin,PowMax)),IntRelations),!, | |
87 | PowMin is min(RPowMin,0). | |
88 | ||
89 | prepare_id_mapping(Ids,Idmap,ProbToKodkod,KodkodToProb) :- | |
90 | prepare_id_mapping2(Ids,Idmap,ProbToKodkod,KodkodToProbList), | |
91 | list_to_avl(KodkodToProbList, KodkodToProb). | |
92 | prepare_id_mapping2([],_,[],[]). | |
93 | prepare_id_mapping2([TId|Rest],Idmap,[PK|ProbToKodkod],[KP|KodkodToProb]) :- | |
94 | prepare_id_mapping3(TId,Idmap,PK,KP), | |
95 | prepare_id_mapping2(Rest,Idmap,ProbToKodkod,KodkodToProb). | |
96 | prepare_id_mapping3(TId,Idmap,bid(BType,P)-K,K-bid(BType,P)) :- | |
97 | get_texpr_id(TId,P), | |
98 | get_texpr_type(TId,BType1), | |
99 | adapt_seq_type(BType1,BType), | |
100 | avl_fetch(P,Idmap,reldef(K,_Types,_SetOrSingle,_ExactOrSubset,_Set)). | |
101 | ||
102 | adapt_seq_type(seq(T),S) :- !,S=set(couple(integer,T)). | |
103 | adapt_seq_type(T,T). | |
104 | ||
105 | prepare_value_mapping(Valuemap,ProbToKodkod,KodkodToProb) :- | |
106 | avl_to_list(Valuemap,ProbKodkodList), | |
107 | maplist(reverse_key_value, ProbKodkodList, KodkodProbList), | |
108 | list_to_avl(KodkodProbList,KodkodToProb), | |
109 | maplist(remove_type_info,ProbKodkodList, L1), | |
110 | list_to_avl(L1,ProbToKodkod). | |
111 | reverse_key_value((T:P)-K, (T:K)-P). | |
112 | remove_type_info((_T:P)-K, P-K). | |
113 | ||
114 | get_new_problem_id(ProblemId) :- | |
115 | retract(next_problem_id(Id)), | |
116 | NextId is Id+1, | |
117 | assertz(next_problem_id(NextId)), | |
118 | ProblemId = Id. | |
119 | ||
120 | extract_all_relations(Idmap,Relations) :- avl_range(Idmap,Relations). | |
121 | ||
122 | send_problem(Id) :- | |
123 | get_kodkod_process(_,KOut,_), | |
124 | known_problem(Id,Types,Relations,Formula,_ToKodkod,_ToProB,_OrigPredicate), | |
125 | get_preference(time_out,TO), | |
126 | get_preference(kodkod_symmetry_level,Symmetry), | |
127 | get_preference(kodkod_sat_solver,Solver), | |
128 | kodkod_printer:kkp_problem(KOut,TO,Symmetry,Solver,Id,problem(Types,Relations,Formula,xxx,none)). | |
129 | ||
130 | get_kodkod_process(A,B,C) :- kodkod_process(A,B,C),!. | |
131 | get_kodkod_process(_,_,_) :- add_error(kodkod_process,'No Kodkod process running'),fail. | |
132 | ||
133 | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | |
134 | % communication with external java process | |
135 | :- dynamic kodkod_process/3. | |
136 | ||
137 | reset_kodkod_process :- retractall(kodkod_process(_,_,_)). | |
138 | ||
139 | startup_kodkod :- kodkod_process(_,_,_), !. | |
140 | startup_kodkod :- | |
141 | absolute_file_name(prob_lib('.'), KodkodDir), | |
142 | kodkod_jar(KodkodJar), | |
143 | ||
144 | atom_concat('-Djava.library.path=', KodkodDir, JLibpath), | |
145 | ||
146 | get_command_path('java',CmdPath), | |
147 | ||
148 | %format('Starting Kodkod JAR ~w using ~w~n',[KodkodJar,JLibpath]), | |
149 | get_preference(kodkod_sat_solver,Solver), | |
150 | ||
151 | process_create(CmdPath, | |
152 | [JLibpath, '-Xmx1024M','-jar', KodkodJar,Solver], | |
153 | [process(KProc),stdout(pipe(KIn)),stdin(pipe(KOut))]), | |
154 | check_correct_startup(KIn), | |
155 | ||
156 | assertz(kodkod_process(KProc,KOut,KIn)). | |
157 | ||
158 | check_correct_startup(S) :- | |
159 | catch( (read_line(S,Line),check_first_line(Line)), | |
160 | E, | |
161 | add_error_and_fail(kodkod_process, 'Exception while connecting to Kodkod process', E)). | |
162 | check_first_line(Line) :- | |
163 | append("ProB-Kodkod started: ",Msg,Line),!, | |
164 | format('Kodkod module started up successfully (SAT solver ~s).~n',[Msg]). | |
165 | check_first_line(_Line) :- | |
166 | add_error_and_fail(kodkod_process,'Unable to start-up Kodkod process.\n'). | |
167 | ||
168 | kodkod_jar(KodkodJar) :- | |
169 | absolute_file_name(prob_lib('probkodkod.jar'), KodkodJar), | |
170 | ( file_exists(KodkodJar,read) -> true | |
171 | ; | |
172 | add_error_and_fail(kodkod_process,'Unable to read Kodkod library. Please check your installation or disable the use of Kodkod')). | |
173 | ||
174 | stop_kodkod :- | |
175 | get_kodkod_process(PId,KOut,KIn), | |
176 | call_cleanup( (write(KOut, 'stop.\n'), flush_output(KOut) ), | |
177 | ( process_wait(PId,_), close(KOut), close(KIn), | |
178 | retractall(kodkod_process(_,_,_)))). | |
179 | ||
180 | %kodkod_problem(Id,Problem) :- | |
181 | % kodkod_process(_,KOut,_), | |
182 | % get_preference(time_out,TO),get_preference(kodkod_symmetry_level,Symmetry),get_preference(kodkod_sat_solver,Solver), | |
183 | % kkp_problem(KOut,TO,Symmetry,Solver,Id,Problem). | |
184 | ||
185 | kodkod_request_intern(ProblemId, Signum, MaxNrOfSols, LocalState, State) :- | |
186 | known_problem(ProblemId,_Size,_Relations,_Formula,ToKodkod,ToProB,_OrigPredicate), | |
187 | extract_known_values(ToKodkod,LocalState,State,Known,UnknownList), | |
188 | copy_term(UnknownList,UnknownListCopy), | |
189 | list_to_avl(UnknownListCopy,Unknown), | |
190 | !, | |
191 | debug_println(19,send_kodkod_request(ProblemId,Signum,MaxNrOfSols,Known)), | |
192 | send_request(ProblemId, ToProB, Signum, MaxNrOfSols, Known, Unknown), | |
193 | %describe_sol(UnknownListCopy), | |
194 | UnknownList=UnknownListCopy. | |
195 | %translate:print_bstate(State). | |
196 | ||
197 | %describe_sol(List) :- | |
198 | % nl,write('Kodkod solution:'),nl,describe_sol2(List). | |
199 | %describe_sol2([]). | |
200 | %describe_sol2([Id-Value|Rest]) :- | |
201 | % describe_sol3(Id,Value), | |
202 | % describe_sol2(Rest). | |
203 | %describe_sol3(Id,Value) :- | |
204 | % write(Id),write(': '),translate:print_bvalue(Value),nl. | |
205 | ||
206 | ||
207 | extract_known_values(probkodkod(ValueMap,Ids),LocalState,State,Out,Unknown) :- | |
208 | extract_known_values2(Ids,ValueMap,LocalState,State,Out,[],Unknown,[]). | |
209 | extract_known_values2([],_ValueMap,_LocalState,_State,Known,Known,Unknown,Unknown). | |
210 | extract_known_values2([bid(Type,Prob)-Kodkod|Rest],ValueMap,LocalState,State, | |
211 | KnownIn,KnownOut,UnknownIn,UnknownOut) :- | |
212 | extract_known_value(Type,Prob,Kodkod,ValueMap,LocalState,State,KnownIn,KnownInter,UnknownIn,UnknownInter), | |
213 | extract_known_values2(Rest,ValueMap,LocalState,State,KnownInter,KnownOut,UnknownInter,UnknownOut). | |
214 | extract_known_value(Type,Prob,Kodkod,ValueMap,LocalState,State,KnownIn,KnownOut,UnknownIn,UnknownOut) :- | |
215 | lookup_value_for_existing_id(Prob,LocalState,State,Value), | |
216 | ( ground(Value) -> | |
217 | map_prob_value_to_kodkod(Type,Value,ValueMap,KValue), | |
218 | KnownIn = [kout(Kodkod,KValue)|KnownOut], | |
219 | UnknownIn = UnknownOut | |
220 | ; | |
221 | KnownIn = KnownOut, | |
222 | UnknownIn = [Kodkod-Value|UnknownOut]),!. | |
223 | extract_known_value(_Type,Prob,_Kodkod,_ValueMap,_LocalState,_State,_KnownIn,_KnownOut,_UnknownIn,_UnknownOut) :- | |
224 | add_error_and_fail(kodkod_process,'mapping ProB value to Kodkod failed', Prob). | |
225 | ||
226 | map_prob_value_to_kodkod(set(_),Prob,ValueMap,Kodkod) :- | |
227 | !, expand_custom_set_to_list(Prob,List), | |
228 | map_prob_values_to_kodkod(List,ValueMap,Kodkod). | |
229 | map_prob_value_to_kodkod(_Type,Prob,ValueMap,Kodkod) :- | |
230 | map_prob_values_to_kodkod([Prob],ValueMap,Kodkod). | |
231 | map_prob_values_to_kodkod([],_,[]). | |
232 | map_prob_values_to_kodkod([P|Prest],ValueMap,[tuple(K)|Krest]) :- | |
233 | map_prob_value_to_kodkod2(P,ValueMap,K,[]), | |
234 | map_prob_values_to_kodkod(Prest,ValueMap,Krest). | |
235 | map_prob_value_to_kodkod2((A,B),ValueMap) --> | |
236 | !,map_prob_value_to_kodkod2(A,ValueMap), | |
237 | map_prob_value_to_kodkod2(B,ValueMap). | |
238 | map_prob_value_to_kodkod2(int(I),_ValueMap) --> !,[I]. | |
239 | map_prob_value_to_kodkod2(Prob,ValueMap) --> [Kodkod], | |
240 | {avl_fetch(Prob,ValueMap,Kodkod)}. | |
241 | ||
242 | ||
243 | :- use_module(probsrc(debug),[debug_println/2]). | |
244 | send_request(ProblemId, ToProb, Signum, MaxNrOfSols,OutValues, In) :- | |
245 | get_kodkod_process(_,OStream,IStream), | |
246 | debug:debug_println(19,sending_kodkod_request(ProblemId,Signum,MaxNrOfSols)), | |
247 | kkp_request(ProblemId, Signum, MaxNrOfSols, OutValues, OStream), | |
248 | get_solutions_from_stream(OStream,IStream,ProblemId,MaxNrOfSols,ToProb,In). | |
249 | ||
250 | read_rest(ProblemId,MaxNrOfSols,ToProb,In) :- | |
251 | get_kodkod_process(_,OStream,IStream), | |
252 | kkp_list(ProblemId,MaxNrOfSols,OStream), | |
253 | get_solutions_from_stream(OStream,IStream,ProblemId,MaxNrOfSols,ToProb,In). | |
254 | ||
255 | get_solutions_from_stream(OStream,IStream,ProblemId,MaxNrOfSols,ToProB,In) :- | |
256 | flush_output(OStream), | |
257 | read_answer_from_kodkod(IStream,Answer), | |
258 | !, | |
259 | process_answer(Answer,ProblemId,MaxNrOfSols,ToProB,In). | |
260 | get_solutions_from_stream(_,_,ProblemId,MaxNrOfSols,ToProB,In) :- | |
261 | process_answer(end_of_file,ProblemId,MaxNrOfSols,ToProB,In). | |
262 | ||
263 | % read an answer but skip over statistics infos: | |
264 | read_answer_from_kodkod(IStream,Answer) :- | |
265 | read(IStream,Answer1), | |
266 | (Answer1=stats(T,S,C,V,P) % special statistics info fact | |
267 | -> debug_format(20,'Kodkod Statistics: ~w ms translation, ~w ms solving, ~w clauses, ~w variables, ~w primary variables~n',[T,S,C,V,P]), | |
268 | read_answer_from_kodkod(IStream,Answer) | |
269 | ; Answer=Answer1). | |
270 | ||
271 | process_answer(solutions(Sols,More,Times),ProblemId,MaxNrOfSols,ToProb,In) :- | |
272 | formatsilent('Times for computing solutions: ~w~n',[Times]), | |
273 | save_java_comp_time(Times), | |
274 | get_solutions(Sols,More,ProblemId,MaxNrOfSols,ToProb,In). | |
275 | process_answer(sat_timeout,ProblemId,_,_ToProb,_In) :- | |
276 | add_warning(kodkod_process,'Kodkod SAT Solver Timeout for Problem Id: ',ProblemId), | |
277 | %throw(time_out). % can only be caught by time_out not by catch ! | |
278 | throw(enumeration_warning(kodkod_timeout,ProblemId,'','',critical)). | |
279 | process_answer(sat_non_incremental,ProblemId,_,_ToProb,_In) :- | |
280 | add_warning(kodkod_process,'Kodkod SAT Solver is non incremental and cannot compute all solutions for Problem Id: ',ProblemId), | |
281 | throw(enumeration_warning(kodkod_timeout,ProblemId,'','',critical)). | |
282 | process_answer(unknown(_),ProblemId,_,_ToProb,_In) :- | |
283 | add_warning(kodkod_process,'Kodkod SAT Solver error occured for Problem Id: ',ProblemId), | |
284 | throw(enumeration_warning(kodkod_error,ProblemId,'','',critical)). | |
285 | process_answer(end_of_file,ProblemId,_,_ToProb,_In) :- | |
286 | add_warning(kodkod_process,'Kodkod SAT Solver aborted for Problem Id: ',ProblemId), | |
287 | throw(enumeration_warning(kodkod_error,ProblemId,'','',critical)). | |
288 | ||
289 | ||
290 | get_solutions(Sols,_More,_ProblemId,_,ToProb,In) :- | |
291 | member(Sol,Sols), get_solution(Sol,ToProb,In). | |
292 | get_solutions(_Sols,more,ProblemId,MaxNrOfSols,ToProb,In) :- | |
293 | read_rest(ProblemId,MaxNrOfSols,ToProb,In). | |
294 | ||
295 | get_solution([],_,_). | |
296 | get_solution([Binding|BRest],kodkodprob(VMap,IdMap),BValues) :- | |
297 | ( Binding = b(Name,KValues) -> true | |
298 | ; Binding = s(Name,KValues) -> Type = set(_)), | |
299 | avl_fetch(Name,BValues,BValue), | |
300 | avl_fetch(Name,IdMap,bid(Type,_BName)), | |
301 | map_kodkod_prob(Type,KValues,VMap,Result),!, | |
302 | equal_object(BValue,Result), | |
303 | get_solution(BRest,kodkodprob(VMap,IdMap),BValues). | |
304 | ||
305 | map_kodkod_prob(set(Type),Tuples,Map,Value) :- | |
306 | !,map_kodkod_prob2(Tuples,Type,Map,Value). | |
307 | map_kodkod_prob(Type,KValue,Map,BValue) :- | |
308 | map_kodkod_prob2([KValue],Type,Map,[BValue]). | |
309 | map_kodkod_prob2([],_,_,[]). | |
310 | map_kodkod_prob2([Values|TRest],Type,Map,[BValue|BRest]) :- | |
311 | map_kodkod_prob3(Type,Map,BValue,Values,[]), | |
312 | map_kodkod_prob2(TRest,Type,Map,BRest). | |
313 | map_kodkod_prob3(couple(TA,TB),Map,(BA,BB)) --> | |
314 | map_kodkod_prob3(TA,Map,BA), | |
315 | map_kodkod_prob3(TB,Map,BB). | |
316 | map_kodkod_prob3(integer,_,int(Value)) --> !,[Value]. | |
317 | map_kodkod_prob3(Type,Map,BValue) --> | |
318 | [K],{avl_fetch(Type:K,Map,BValue),!}. | |
319 | ||
320 | :- dynamic java_comp_time/1. | |
321 | clear_java_comp_time :- | |
322 | retractall(java_comp_time(_)). | |
323 | get_java_comp_time(Time) :- | |
324 | findall( T, (java_comp_time(Ts),member(T,Ts)), Times), | |
325 | sumlist(Times,Time). | |
326 | save_java_comp_time(Times) :- | |
327 | assertz(java_comp_time(Times)). |