4
5:- module_interface(translate_modal). /*%--------------------------------------
6
7Written by Zoltan Rigo.\bigskip
8
9This module implements The translation of modal formulae into
10first order formulae with terms representing the paths.
11This has been done according to the translation proposed in
12
13Francoise Clerin-Debart
14Theories equationelles et de contraintes pour la demonstration
15automatique en logique multi-modale
16PhD Thesis
17Caen University, France,
181992
19
20\PL*/
21:- export translate_modal/2.
22
23:- begin_module(translate_modal). 29
30:- get_flag(library_path,OldPath),
31 union(["/u/home/procom/System"],OldPath,FullPath),
32 set_flag(library_path,FullPath). 33
34:- lib(lists),
35 lib(options). 36
37
46
47:- op(1100, xfy, 'implies'). 48:- op(1000, xfy, 'and'). 49:- op(1050, xfy, 'or'). 50:- op( 400, fy, 'not'). 51
52:- op( 600, fy, 'forall'). 53:- op( 600, fy, 'exists'). 54
55:- op( 600, fy, 'box'). 56:- op( 600, fy, 'diamond'). % (precedence of : is 600)
57
58
59/*PL%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
60
61Firstly, we define an output option. This is not yet set into power (25/8/94)
62but this is supposed to become a kind of default.
63Then we set a global variable for the identification of the Skolem functions.
64
65\PL*/
66
67:- define_option 'translate_modal:output_file' = '...translated_modals.ppp'.
68
69:-setval(skolemCounter,1). 70
71
84
85translate_modal(Stream,OutStream) :-
86 is_option('translate_modal:output_file',File),
87 open(File,write,CSTStream),
88 repeat,
89 read(Stream,Clause),
90 ( Clause = end_of_file ->
91 true
92
96
97 ; make_nnf(Clause,0,NormalClause),
98 transform(NormalClause,TranslatedClause),
99 normalize_path(TranslatedClause,NormalizedClause),
100 printf(OutStream,"%vQDMw.\n",[NormalizedClause]),
101 fail
102 ),
103 close(CSTStream),
104 ( current_module('modal logic') ->
105 true
106 ; create_module('modal logic')
107 ),
108 call(compile(File),'modal logic'),
109 !.
119
120
121transform(Formula, TranslatedFormula):-
122 transform(0,Formula,[],[],TranslatedFormula).
123
124
148
149transform(PathTerm,Formula,ClassVars,PathVars,Result):-
150 (
151
153
154 var(Formula) ->
155 Result = Formula
156
157
160
161 ; Formula =.. [implies, Formula1, Formula2] ->
162 make_nnf(not Formula1, 0, NewFormula),
163 transform(PathTerm,NewFormula,ClassVars,PathVars,Intermediate1),
164 transform(PathTerm,Formula2,ClassVars,PathVars,Intermediate2),
165 Result =.. ['or', Intermediate1, Intermediate2]
166
167 ; Formula =.. [and, Formula1, Formula2] ->
168 transform(PathTerm,Formula1,ClassVars,PathVars,Intermediate1),
169 transform(PathTerm,Formula2,ClassVars,PathVars,Intermediate2),
170 Result =.. ['and', Intermediate1, Intermediate2]
171
172 ; Formula =.. [or, Formula1, Formula2] ->
173 transform(PathTerm,Formula1,ClassVars,PathVars,Intermediate1),
174 transform(PathTerm,Formula2,ClassVars,PathVars,Intermediate2),
175 Result =.. ['or', Intermediate1, Intermediate2]
176
180
181 ; Formula =.. [not, Formula] ->
182 transform(PathTerm,Formula,ClassVars,PathVars,Intermediate),
183 Result =.. ['not', Intermediate]
184
185
195
196 ; Formula =.. [forall, :(Var, Formula1)] ->
197 term_variables(Formula1,VarList),
198 copy_term(Formula1 + VarList, NewFormula1 + CopyVarList),
199 drei(VarList,CopyVarList,Var),
200
202
203 NewClassVars = [Var | ClassVars],
204
208
209 transform(PathTerm,NewFormula1,NewClassVars,PathVars,Intermediate),
210 Result = Intermediate
211
225
226 ; Formula =.. [exists, :(Var, Formula1)] ->
227 term_variables(Formula1,VarList),
228 copy_term(Formula1 + VarList + Var,NewFormula1 + CopyVarList + NewVar),
229 drei(VarList,CopyVarList,Var),
230 getval(skolemCounter,Value),
231 incval(skolemCounter),
232 concat_atom(['$kolem',Value],NewFunctionSymbol),
233 append([PathTerm], ClassVars, Arguments),
234 transform(PathTerm,NewFormula1,ClassVars,PathVars,Intermediate),
235 NewVar =.. [NewFunctionSymbol | Arguments ],
236 Result = Intermediate
237
243
244 ; Formula =.. [box, Formula1] ->
245 NewPath =.. ['+', PathTerm, X ],
246 NewPathVars = [ X | PathVars ],
247 transform(NewPath,Formula1,ClassVars,NewPathVars,Intermediate),
248 Result = Intermediate
249
255
256 ; Formula =.. [diamond, Formula1] ->
257 getval(skolemCounter,Value),
258 incval(skolemCounter),
259 concat_atom(['$kolemPath',Value],NewPathFunctionSymbol),
260 append([PathTerm], ClassVars, Arguments),
261 NewFunction =.. [NewPathFunctionSymbol | Arguments],
262 NewPath =.. ['+', PathTerm, NewFunction ],
263 transform(NewPath,Formula1,ClassVars,PathVars,Intermediate),
264 Result = Intermediate
265
269
270 ; Formula =.. [OtherFunctor | ArgList] ->
271 transform_a_list(PathTerm,ArgList,ClassVars,PathVars,
272 IntermediateArgList),
273 Result =.. [OtherFunctor , PathTerm | IntermediateArgList]
274
275
276 ).
277
295
296transform_a_list(_,[],_,_,[]).
297
298transform_a_list(PathTerm,[H|T],ClassVars,PathVars,Result):-
299 transform(PathTerm,H,ClassVars,PathVars,I1),
300 transform_a_list(PathTerm,T,ClassVars,PathVars,I2),
301 Result = [I1 | I2].
302
313
314make_nnf(Formula,Polarity,NormalFormula):-
315 ( var(Formula) ->
316 ( Polarity = 0 ->
317 NormalFormula = Formula
318 ; Polarity = 1 ->
319 NormalFormula =.. [not, Formula])
320
321 ; Formula =.. [implies, Formula1, Formula2] ->
322 make_nnf(not Formula1, Polarity, NormalFormula1),
323 make_nnf(Formula2, Polarity, NormalFormula2),
324 NormalFormula =.. [or, NormalFormula1, NormalFormula2]
325
326 ; Formula =.. [and, Formula1, Formula2] ->
327 make_nnf(Formula1, Polarity, NormalFormula1),
328 make_nnf(Formula2, Polarity, NormalFormula2),
329 NormalFormula =.. [and, NormalFormula1, NormalFormula2]
330
331 ; Formula =.. [or, Formula1, Formula2] ->
332 make_nnf(Formula1, Polarity, NormalFormula1),
333 make_nnf(Formula2, Polarity, NormalFormula2),
334 NormalFormula =.. [or, NormalFormula1, NormalFormula2]
335
336 ; Formula =.. [not, Formula1] ->
337 ( Formula1 =.. [not, NewFormula] ->
338 make_nnf(NewFormula, Polarity, NormalFormula)
339 ; NewPolarity is (Polarity + 1) mod 2,
340 make_nnf(Formula1, NewPolarity, NormalFormula))
341
342 ; Formula =.. [forall, :(Var, Formula1)] ->
343 ( Polarity = 0 ->
344 make_nnf(Formula1, Polarity, NewFormula1),
345 NormalFormula =.. [forall, :(Var, NewFormula1)]
346 ; Polarity = 1 ->
347 make_nnf(Formula1, Polarity, NewFormula1),
348 NormalFormula =.. [exists, :(Var, NewFormula1)])
349
350 ; Formula =.. [exists, :(Var, Formula1)] ->
351 ( Polarity = 0 ->
352 make_nnf(Formula1, Polarity, NewFormula1),
353 NormalFormula =.. [exists, :(Var, NewFormula1)]
354 ; Polarity = 1 ->
355 make_nnf(Formula1, Polarity, NewFormula1),
356 NormalFormula =.. [forall, :(Var, NewFormula1)])
357
358 ; Formula =.. [box, Formula1] ->
359 ( Polarity = 0 ->
360 make_nnf(Formula1, Polarity, NewFormula1),
361 NormalFormula =.. [box, NewFormula1]
362 ; Polarity = 1 ->
363 make_nnf(Formula1, Polarity, NewFormula1),
364 NormalFormula =.. [diamond, NewFormula1])
365
366 ; Formula =.. [diamond, Formula1] ->
367 ( Polarity = 0 ->
368 make_nnf(Formula1, Polarity, NewFormula1),
369 NormalFormula =.. [diamond, NewFormula1]
370 ; Polarity = 1 ->
371 make_nnf(Formula1, Polarity, NewFormula1),
372 NormalFormula =.. [box, NewFormula1])
373
374 ; Formula = _Anything_else ->
375 ( Polarity = 0 ->
376 NormalFormula = Formula
377 ; Polarity = 1 ->
378 NormalFormula =.. [not, Formula])
379 ).
380
381
393normalize_path(Var,Var2) :-
394 var(Var),
395 !,
396 Var = Var2.
397normalize_path(Atom,Atom2) :-
398 atomic(Atom),
399 !,
400 Atom = Atom2.
401normalize_path(+(A1,Arg),
402 NormalArg) :-
403 A1 == 0,
404 !,
405 normalize_path(Arg,NormalArg).
406normalize_path(+(Arg,A2),
407 NormalArg) :-
408 A2 == 0,
409 !,
410 normalize_path(Arg,NormalArg).
411normalize_path(+(A1,C),
412 Normal) :-
413 nonvar(A1),
414 A1 = +(A,B),
415 !,
416 normalize_path(+(A,+(B,C)),
417 Normal).
418normalize_path(+(A,B),
419 +(NormalA,NormalB)) :-
420 !,
421 normalize_path(A,NormalA),
422 normalize_path(B,NormalB).
423
424normalize_path(Term,NormalTerm) :-
425 Term =.. [F|Args],
426 normalize_path_list(Args,NormalArgs),
427 NormalTerm =.. [F|NormalArgs].
428
429normalize_path_list([],[]).
430normalize_path_list([H|T],[NormalH|NormalT]) :-
431 !,
432 normalize_path(H,NormalH),
433 normalize_path_list(T,NormalT).
434
448
449drei([],[],_).
450
451drei([H|T],[H1|T1],Var):-
452 (H == Var ->
453 true
454 ; H = H1
455 ),
456 drei(T,T1,Var).
457
465
466tm_file_to_file(Infile,Outfile) :-
467 open(Infile,read,Stream),
468 ( Outfile = '' ->
469 translate_modal(Stream,output)
470 ; open(Outfile,write,OutStream),
471 translate_modal(Stream,OutStream),
472 close(OutStream)
473 ),
474 close(Stream).
475