1 % (c) 2025-2025 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(clingo_interface,[run_clingo/2, run_clingo/6,
6 reset_clingo_interface/0,
7 clingo_generated_id/4,
8 register_clingo_generated_id/4, register_clause_head/2,
9 write_clingo_show_directive/0,
10 get_string_nr/2, get_nr_of_registered_strings/1]).
11
12 :- use_module(probsrc(module_information),[module_info/2]).
13 :- module_info(group,b2asp).
14 :- module_info(description,'Running clingo on a file and parsing model output.').
15
16 :- use_module(library(lists)).
17 :- use_module(library(file_systems),[file_exists/1]).
18 :- use_module(library(process)).
19
20 :- if(current_module(error_manager)).
21 :- use_module(probsrc(error_manager)).
22 :- use_module(probsrc(tools_strings),[ajoin/2]).
23 :- use_module(probsrc(debug)).
24 :- use_module(probsrc(preferences)).
25 :- use_module(probsrc(system_call),[safe_process_create/3]).
26 get_clingo_path(Path) :- get_preference(path_to_clingo,Path).
27 add_b2asp_error(Msg,Args) :- add_error(b2asp,Msg,Args).
28 add_b2asp_warning(Msg,Args) :- add_warning(b2asp,Msg,Args).
29 :- else.
30 get_clingo_path('C:/Users/hhuri/Desktop/stage/clingo-5.4.0-win64/clingo.exe').
31 get_clingo_path('/opt/homebrew/bin/clingo').
32 add_b2asp_error(Msg,Args) :-
33 write(user_error,Msg), write(user_error,Args), nl(user_error).
34 add_b2asp_warning(Msg,Args) :-
35 add_b2asp_error(Msg,Args).
36 debug_mode(on).
37 debug_format(_,FS,A) :- format(user_output,FS,A).
38 safe_process_create(Cmd,Args,Opts) :- process_create(Cmd,Args,Opts).
39 :- endif.
40
41 :- use_module(probsrc(tools),[start_ms_timer/1, stop_ms_timer_with_msg/2, get_elapsed_walltime/2]).
42 :- use_module(covsrc(hit_profiler),[add_to_profile_stats/2]).
43
44 run_clingo(File,Result) :- run_clingo(File,1,-1,_,Result,_).
45 run_clingo(File,MaxNrModels,TimeoutSecs,WT,Result,Exhaustive) :-
46 statistics(walltime,[Start,_]),
47 (debug_mode(on) -> DOpt=['-V'] ; DOpt=[]),
48 (MaxNrModels<2 -> ModelsOpt='--models=1' % so that code works without ajoin
49 ; ajoin(['--models=',MaxNrModels],ModelsOpt)),
50 (TimeoutSecs >= 0
51 -> ajoin(['--time-limit=',TimeoutSecs],TimeOpt), TOpt = [TimeOpt|DOpt]
52 ; TOpt=DOpt),
53 OtherOptions = [ModelsOpt|TOpt] , % =0 outputs all models
54 debug_format(19,' Running CLINGO on ~w (options=~w)~n',[File,OtherOptions]),flush_output,
55 Options = [process(Process),stdout(pipe(JStdout,[encoding(utf8)])),
56 stderr(pipe(JStderr,[encoding(utf8)]))],
57 (get_clingo_path(Clingo), file_exists(Clingo)-> true
58 ; get_clingo_path(Clingo) -> add_b2asp_error('Cannot find Clingo binary at (be sure to set path_to_clingo preference to point to clingo binary): ',Clingo),fail
59 ; add_b2asp_error('Cannot find Clingo binary (be sure to set path_to_clingo preference to point to clingo binary)',''),fail
60 ),
61 safe_process_create(Clingo, [File|OtherOptions], Options),
62 debug_format(4,' Created process ~w~n',[Options]),flush_output,
63 read_all(JStdout,Clingo,stdout,OutLines), % read before process_wait; avoid blocking clingo
64 read_all(JStderr,Clingo,stderr,ErrLines),
65 debug_format(4,' process_wait ~w~n',[Process]),flush_output,
66 process_wait(Process,Exit),
67 % above almost corresponds to: system_call_with_options(Clingo,[File|OtherOptions],[],OutLines,ErrLines,ExitCode)
68 % except that here we do not call append/2 on OutLines and ErrLines
69 statistics(walltime,[Stop,_]), WT is Stop-Start,
70 format(' CLINGO walltime: ~w ms, ~w~n',[WT,Exit]),flush_output,
71 debug_format(19,'--- CLINGO OUTPUT ----~n',[]),flush_output,
72 start_ms_timer(T1),
73 process_clingo_output(OutLines,Models),
74 get_elapsed_walltime(T1,WT1),add_to_profile_stats(back_translation_time,WT1),
75 stop_ms_timer_with_msg(T1,'translating clingo model back to B'),
76 if((Exit=exit(Code),
77 % ErrLines = [], % clingo write debug info on stderr (parsed program, rewritten program)
78 translate_clingo_exit_code(Code,Models,Result,Exhaustive)
79 ),
80 (debug_format(19,'Clingo exit code = ~w -> ~w (~w)~n',[Code,Result,Exhaustive]),
81 show_stderr(ErrLines)),
82 (format('Unrecognised exit code: ~w~n',[Exit]),
83 show_stderr(ErrLines),
84 Result=no_solution_found(Exit))
85 ).
86
87 show_stderr([]) :- !.
88 show_stderr(ErrLines) :-
89 append(ErrLines,ErrText),
90 (ErrText = [] -> true
91 ; format('--- CLINGO STDERR ----~n~s~n',[ErrText])).
92
93 % see https://github.com/potassco/clasp/issues/42#issuecomment-459981038%3E
94 translate_clingo_exit_code(0,_,no_solution_found('E_UNKNOWN'),non_exhaustive).
95 translate_clingo_exit_code(1,_,no_solution_found('E_INTERRUPT'),non_exhaustive). % can be timeout
96 translate_clingo_exit_code(33,_,no_solution_found('E_MEMORY'),non_exhaustive).
97 translate_clingo_exit_code(65,_,no_solution_found('E_ERROR'),non_exhaustive). % is for syntax error and unsafe vars
98 translate_clingo_exit_code(128,_,no_solution_found('E_NO_RUN'),non_exhaustive).
99 translate_clingo_exit_code(20,_,contradiction_found,exhaustive). % UNSATISFIABLE (E_EXHAUST)
100 translate_clingo_exit_code(10,Sols,solution(Sol),non_exhaustive) :-
101 get_sol(Sols,Sol). % E_SAT = 10, /*!< At least one model was found.
102 translate_clingo_exit_code(30,Sols,solution(Sol),exhaustive) :-
103 get_sol(Sols,Sol). %all_solutions_found (E_EXHAUST)
104
105 get_sol([Sol|T],R) :- !, member(R,[Sol|T]).
106 get_sol(L,R) :- add_b2asp_error('Unexpected clingo solution: ',L), R=[].
107
108 %get_first_sol([Sol|_],R) :- !, R=Sol.
109 %get_first_sol(L,R) :- add_b2asp_error('Unexpected clingo solution: ',L), R=[].
110
111 % process clingo output stream and extract answers (stable models)
112 process_clingo_output([],[]).
113 process_clingo_output([[0'\n]|T],Models) :- !, process_clingo_output(T,Models).
114 process_clingo_output([Line|T],Models) :- debug_format(19,'>>> ~s~n',[Line]),
115 clingo_answer_line(Nr,Line,[]), !,
116 process_clingo_model_line(T,Nr,Models).
117 process_clingo_output([_|T],Models) :- process_clingo_output(T,Models).
118
119 process_clingo_model_line([[0'\n]|T],Nr,Models) :- !, process_clingo_model_line(T,Nr,Models).
120 process_clingo_model_line([ModelLine|T],Nr,[BSolution|TM]) :- clingo_model(Model,ModelLine,[]), !,
121 debug_format(19,'>>> ~s~n',[ModelLine]),
122 add_to_profile_stats(clingo_models,1),
123 length(Model,Len),
124 add_to_profile_stats(clingo_model_atoms,Len),
125 (debug_mode(on)
126 -> length(ModelLine,LenLine),
127 format('Parsed clingo model ~w (length ~w) with ~w relevant atoms~n',[Nr,LenLine,Len])
128 ;
129 format('Parsed clingo model ~w with ~w relevant atoms~n',[Nr,Len])
130 ),
131 sort(Model,SModel), % TODO: extract solution for registered identifiers
132 keyclumped(SModel,Groups),
133 %write(Groups),nl,
134 translate_clingo_model_to_bindings(Groups,BSolution),
135 %write(BSolution),nl,
136 process_clingo_output(T,TM).
137 process_clingo_model_line(T,Nr,Models) :-
138 add_b2asp_error('Could not parse clingo model answer: ',Nr),
139 process_clingo_output(T,Models).
140
141 % TRANSLATING clingo model atoms back to B values
142 % -----------------------------------------------
143
144 translate_clingo_model_to_bindings(Model,Bindings) :-
145 findall(expected(Pred,Kind,BaseType,BID),clingo_generated_id(Pred,Kind,BaseType,BID),ExpectedPreds),
146 sort(ExpectedPreds,SExpectedPreds),
147 translate_clingo_model_to_bindings3(Model,SExpectedPreds,Bindings).
148
149 translate_clingo_model_to_bindings3([],[],Sol) :- !, Sol=[].
150 translate_clingo_model_to_bindings3([Pred-ModelArgs|TM],[expected(Pred,Kind,BaseType,BID)|ET],
151 [bind(BID,BVal)|BT]) :- !,
152 translate_clingo_value(Kind,BaseType,ModelArgs,BVal),
153 translate_clingo_model_to_bindings3(TM,ET,BT).
154 translate_clingo_model_to_bindings3(Model,[expected(Pred,Kind,_BaseType,BID)|ET],
155 [bind(BID,BVal)|BT]) :- !,
156 (Kind=set
157 -> debug_format(19,'Setting set to empty: ~w (~w)~n',[Pred,BID]),
158 BVal=[] % the clingo identifier represents a set, we have no facts meaning the set is empty
159 ; add_b2asp_error('No value for clingo scalar in model: ',Pred),
160 BVal=term(undefined)
161 ),
162 translate_clingo_model_to_bindings3(Model,ET,BT).
163
164 % translate a solution for a clingo identifier back to a B value
165 translate_clingo_value(scalar,BaseType,[[ClingoVal]],BVal) :- !,
166 translate_clingo_scalar(BaseType,ClingoVal,BVal).
167 translate_clingo_value(scalar,BaseType,[Sol1|T],BVal) :- !,
168 add_b2asp_warning('Unexpected multiple solutions for clingo scalar: ',[Sol1|T]),
169 translate_clingo_scalar(BaseType,Sol1,BVal).
170 translate_clingo_value(set,BaseType,Sols,BValSetAsList) :- !,
171 maplist(translate_clingo_arg(BaseType),Sols,BValSetAsList).
172 translate_clingo_value(Kind,_,_,_) :-
173 add_b2asp_error('Unexpected Kind for Clingo ID: ',Kind), fail.
174
175 translate_clingo_arg(BaseType,[ClingoVal],BVal) :- translate_clingo_scalar(BaseType,ClingoVal,BVal).
176 % translate_clingo_arg(BaseType,[ClingoVal1,ClingoVal2],BVal) :- ... convert to B pairs
177
178 % translate a solution for a clingo scalar back to a B value
179 %translate_clingo_scalar(A,ID,FDVAL) :- write(translate_clingo_scalar(A,ID,FDVAL)),nl,trace,fail.
180 translate_clingo_scalar(integer,Nr,BV) :- integer(Nr),!, BV=int(Nr).
181 translate_clingo_scalar(interval(_,_),Nr,BV) :- integer(Nr),!, BV=int(Nr).
182 translate_clingo_scalar(integer_in_range(_,_,Type),Nr,BV) :- integer(Nr),
183 ( Type = integer -> !, BV=int(Nr)
184 ; Type = string, nr2string(Nr,String), !, BV=string(String)).
185 translate_clingo_scalar(boolean,pred_false,BV) :- !, BV=pred_false.
186 translate_clingo_scalar(boolean,pred_true,BV) :- !, BV=pred_true.
187 translate_clingo_scalar(couple(TA,TB),(CA,CB),(BA,BB)) :- !,
188 translate_clingo_scalar(TA,CA,BA),
189 translate_clingo_scalar(TB,CB,BB).
190 translate_clingo_scalar(global(GS),Nr,FDVAL) :- integer(Nr),!, FDVAL=fd(Nr,GS).
191 translate_clingo_scalar(string,Nr,S) :- integer(Nr),nr2string(Nr,String), !, S=string(String).
192 translate_clingo_scalar(T,V,term(V)) :- add_b2asp_warning('Unknown clingo scalar: ',T:V).
193
194 % PARSING CODE for clingo OUTPUT
195 % ---------------------
196 % detect line like Answer: 1 (Time: 0.003s)
197 clingo_answer_line(Nr) --> "Answer: ",clingo_number(Nr), anything.
198
199 clingo_number(Nr) --> digit(X), !, answer_nr_rest(R), {number_codes(Nr,[X|R])}.
200 clingo_number(MinusNr) --> "-", digit(X), !, answer_nr_rest(R), {number_codes(Nr,[X|R]),MinusNr is -Nr}.
201 answer_nr_rest([X|T]) --> digit(X), !, answer_nr_rest(T).
202 answer_nr_rest([]) --> "".
203
204 anything --> [_],!,anything.
205 anything --> "".
206
207 % a clingo identifier (TODO check that this conforms to clingo syntax)
208 clingo_identifier(ID) --> letter(H), !, id2(T), {atom_codes(ID,[H|T])}.
209 id2([H|T]) --> digit_or_letter(H),!, id2(T).
210 id2([95|T]) --> "_",!, id2(T).
211 id2([]) --> "".
212
213 % a single stable model generated by clingo, a list of ground atoms separated by single whitespace
214 clingo_model(M) --> " ", !, clingo_model(M).
215 clingo_model(Model) --> clingo_atom(Pred,Args),!,
216 %{format(user_output,' model atom --> ~w ~w~n',[Pred,Args])},
217 {(clingo_generated_id(Pred,_,_,_) -> Model = [Pred-Args|T] ; Model = T)},
218 clingo_model(T).
219 clingo_model([]) --> "".
220 %clingo_model(In,_Out) :- format(user_error,'Cannot parse: ~s~n',[In]),fail.
221
222 % a single clingo atom either a ground predicate p(2), p((2,3)), or p(2,3) or a proposition p
223 clingo_atom(Pred,Args) --> clingo_identifier(Pred), clingo_opt_args(Args).
224 clingo_opt_args(Args) --> "(", !, clingo_args(Args),")".
225 clingo_opt_args([]) --> "". % for propositions without arguments
226 clingo_args([A|T]) --> clingo_constant(A),!, clingo_args2(T).
227 clingo_args([(A,B)|T]) --> clingo_pair(A,B),!, clingo_args2(T).
228
229 clingo_constant(A) --> clingo_number(A).
230 clingo_constant(A) --> clingo_identifier(A).
231
232 clingo_args2(T) --> ",", clingo_args(T).
233 clingo_args2([]) --> "".
234
235 clingo_pair(A,B) --> "(", clingo_cst_or_pair(A),!, ",", clingo_cst_or_pair(B),")".
236
237 clingo_cst_or_pair(A) --> clingo_constant(A),!.
238 clingo_cst_or_pair((A,B)) --> "(", clingo_cst_or_pair(A),",", clingo_cst_or_pair(B),")".
239
240 digit_or_letter(X) --> [X], {letter(X) ; digit(X)}.
241 letter(X) --> [X], {letter(X)}.
242 digit(X) --> [X], {digit(X)}.
243 letter(X) :- (X >= 97, X =< 122) ; (X >= 65, X=< 90). % underscore = 95, minus = 45
244 digit(X) :- X >= 48, X =< 57.
245
246 % ---------
247
248 % read all characters from a stream
249 read_all(S,Command,Pipe,Lines) :-
250 call_cleanup(read_all1(S,Command,Pipe,Lines),
251 close(S)).
252 read_all1(S,Command,Pipe,Lines) :-
253 catch(read_all2(S,Lines), error(_,E), ( % E could be system_error('SPIO_E_ENCODING_INVALID')
254 ajoin(['Error reading ',Pipe,' for "',Command,'" due to exception: '],Msg),
255 add_error(system_call,Msg,E),
256 fail
257 )).
258 read_all2(S,Text) :-
259 read_line(S,Line),
260 ( Line==end_of_file -> Text=[[]]
261 ;
262 Text = [Line, [0'\n] | Rest],
263 %debug_format(19,'Read line on stream ~w: ~s~n',[S,Line]),
264 read_all2(S,Rest)).
265
266 % ------------
267
268
269 :- dynamic clingo_generated_id/4, clingo_clause_head_info/2.
270
271 % register that Clingo predicate Pred represents a solution for a B variable ID
272 % Kind is set or scalar, BaseType is B type term
273 register_clingo_generated_id(Pred,Kind,BaseType,ID) :-
274 debug_format(5,'~n** Registering clingo predicate ~w for ~w~n',[Pred,ID]),
275 assertz(clingo_generated_id(Pred,Kind,BaseType,ID)).
276
277 % register that a clause has been generated for this clingo predicate
278 register_clause_head(Pred,ArgList) :- %format(user_output,'Registering clause head ~w ~w~n',[Pred,ArgList]),
279 clingo_generated_id(Pred,_Kind,_BaseType,_ID), % comment out for more stringent checking of arities for all preds
280 length(ArgList,Arity),
281 \+ clingo_clause_head_info(Pred,Arity),!,
282 (clingo_clause_head_info(Pred,Other)
283 -> add_b2asp_warning('Multiple arities for clingo predicate: ',Pred/Other) ; true),
284 assert(clingo_clause_head_info(Pred,Arity)).
285 register_clause_head(_,_).
286
287 get_clingo_generated_id_with_arity(Pred,Arity) :-
288 clingo_generated_id(Pred,_Kind,_BaseType,_ID),
289 if(clingo_clause_head_info(Pred,A),Arity=A,
290 (add_b2asp_warning('No clingo clause generated for: ',Pred),fail)).
291
292 % The #show directive allows you to filter what atoms are shown in the output.
293 write_clingo_show_directive :-
294 findall(Pred/Arity,get_clingo_generated_id_with_arity(Pred,Arity),List),
295 maplist(write_show,List).
296
297 write_show(Pred/Arity) :- format('#show ~w/~w.~n',[Pred,Arity]).
298
299
300 :- dynamic string_counter/1, string2nr/2, nr2string/2.
301 string_counter(0).
302 string2nr('dummy_string',0).
303 nr2string(0,'dummy_string').
304
305 get_nr_of_registered_strings(Nr) :- string_counter(Nr).
306
307 get_string_nr(String,Nr) :- var(String),!,
308 add_internal_error('String must be ground: ',get_string_nr(String,Nr)),
309 string2nr(String,Nr).
310 get_string_nr(String,Nr) :-
311 (string2nr(String,R) -> Nr=R
312 ; retract(string_counter(R)), N1 is R+1,
313 assert(string_counter(N1)),
314 assert(string2nr(String,N1)),
315 assert(nr2string(N1,String)),
316 debug_format(19,' Registered string ~w --> ~w~n',[String,N1]),
317 Nr=N1
318 ).
319
320
321
322 reset_clingo_interface :-
323 retractall(string_counter(_)),
324 retractall(string2nr(_,_)),
325 retractall(nr2string(_,_)),
326 debug_format(9,'Reset clingo interface~n',[]),
327 assert(string2nr('dummy_string',0)),
328 assert(nr2string(0,'dummy_string')),
329 assert(string_counter(0)),
330 retractall(clingo_clause_head_info(_,_)),
331 retractall(clingo_generated_id(_,_,_,_)).