1:- module(cgp_common_logic_extra,
2 [ 3 convert_clif_to_cg/2]). 4
5:- throw(cgp_common_logic_extra). 6
7:- use_module(library(logicmoo_common)). 8:- use_module(library(logicmoo/dcg_meta)). 9:- use_module(library(logicmoo/util_bb_frame)). 10:- use_module(library(cgp_lib/cgp_swipl)). 11:- use_module(library(logicmoo_clif)). 12
13
14
18do_varaibles(Mode, EoF, Var, Asserts, Fixes):- \+ is_list(Var), !,
19 do_varaibles(Mode, EoF, [Var], Asserts, Fixes).
20
21do_varaibles(Mode, EoF, Vars, Asserts, Fixes):- is_list(Vars), !,
22 maplist(do_one_var(Mode, EoF), _, Vars, Assert, Fix),
23 flatten(Assert, Asserts),
24 flatten(Fix, Fixes),
25 !.
26
27
28do_one_var(Mode, EoF, X, Var, Asserts, Fixes):- \+ is_list(Var), !,
29 do_one_var(Mode, EoF, X, [Var], Asserts, Fixes).
30
31do_one_var(Mode, EoF, X, [VarName| Types], [Grok|Asserts], [Fix|Fixes]):-
32 \+ number(VarName),
33 var(X), cg_var_name(VarName, X, Fix),
34 add_mode(Mode, cg_quantz(EoF, ?(X)), Grok),
35 do_one_var(Mode, EoF, X, Types, Asserts, Fixes).
36do_one_var(Mode, EoF, X, [Number| Types], [Grok|Asserts], Fixes):-
37 number(Number),
38 add_mode(Mode, cg_quantz_num(EoF,Number,?(X)), Grok),
39 do_one_var(Mode, EoF, X, Types, Asserts, Fixes).
40do_one_var(Mode, EoF, X, [Type| Types], [cg_type(?(X),Type)|Asserts], Fixes):-
41 do_one_var(Mode, EoF, X, Types, Asserts, Fixes).
42do_one_var(_Mode, _EoF, _X, [], [], []).
43
44cg_var_name('?'(X), X, []):-!.
45cg_var_name(X, X, [X = '?'(X)]).
46
50unchop(In1, In2, Out):- flatten([In1, In2], Out), !.
51unchop(In1, In2, Out):-
52 listify_h(In1, L1),
53 listify_h(In2, L2),
54 append(L1, L2, Out).
55
56listify_h(L1, L2):- flatten([L1], L2), !.
57listify_h(L1, L2):- listify(L1, L2), !.
58
62chop_up(Stuff, Out):-
63 chop_up(+, Stuff, Out).
64
65
66
70chop_up(Mode, [ExistsOrForall, VarList, Stuff], Out):-
71 member(ExistsOrForall, [exists, forall]),
72 do_varaibles(Mode, ExistsOrForall, VarList, Out1, NewVars),
73 subst_each(Stuff, NewVars, NewStuff),
74 chop_up(Mode, NewStuff, Out2),
75 unchop(Out1, Out2, Out).
76
77chop_up(Mode, ['implies'|Stuff], Out) :- chop_up(Mode, ['=>'|Stuff], Out).
78chop_up(Mode, ['if'|Stuff], Out) :- chop_up(Mode, ['=>'|Stuff], Out).
79
80chop_up(_Mode, ['#'(quote), Mary], '#'(Mary)).
81chop_up(_Mode, '$STRING'(S), S).
82
83
84chop_up(+, [not, Stuff], Out) :- chop_up(-, Stuff, Out).
85chop_up(-, [not, Stuff], Out) :- chop_up(+, Stuff, Out).
86
87chop_up(Mode, [Type, Arg], Out) :- chop_up(Mode, ['Type', Arg, Type], Out).
88
89chop_up(+, [and|Stuff], Out ) :- chop_up_list(+, Stuff, Out).
90chop_up(-, [and|Stuff], or(Out)) :- chop_up_list(-, Stuff, Out).
91chop_up(+, [or|Stuff], or(Out)) :- chop_up_list(+, Stuff, Out).
92chop_up(-, [or|Stuff], Out ) :- chop_up_list(-, Stuff, Out).
93
94
95chop_up(Mode, ['=>', Arg1, Arg2], Out):-
96 chop_up(Mode, Arg1, F1),flatten([F1],Out1),
97 chop_up(Mode, Arg2, F2),flatten([F2],Out2),
98 Out =.. ['cg_implies', Out1, Out2], !.
99
100
101chop_up(Mode, [Name, Arg1, Arg2], Out):- is_cg_pred(Name, Pred), !,
102 chop_up(Mode, Arg1, Out1),
103 chop_up(Mode, Arg2, Out2),
104 Out =.. [Pred, Out1, Out2], !.
105
106chop_up(Mode, [Pred|Args], Out):-
107 chop_up_list(+, Args, ArgsO),
108 (HOLDS =.. [cg_holds, Pred|ArgsO]),
109 add_mode(Mode, HOLDS, Out).
110
111chop_up(_Mode, O, O).
112
113
114is_cg_pred(Name, _):- \+ atom(Name), !, fail.
115is_cg_pred('=>', 'cg_implies'):-!.
116is_cg_pred(Name, Pred):- downcase_atom(Name, NameDC), member(NameDC, [name, type]), atom_concat('cg_', NameDC, Pred), !.
117is_cg_pred(Name, Pred):- downcase_atom(Name, Pred), atom_concat('cg_', _, Pred).
118
119add_mode(-, - A, A).
120add_mode(-, A, -A).
121add_mode(_, A, A).
122
126chop_up_list(Mode, Stuff, Out):- maplist(chop_up(Mode), Stuff, Out).
127
128
133kif_to_term(InS, Clif):-
134 locally(t_l:sreader_options(logicmoo_read_kif, true),
135 parse_sexpr(string(InS), Clif)), !.
136
137
142run_1_test(String):-
143 write('\n\n\n'),
144 dmsg("================================================="),
145 kif_to_term(String, Clif),
146 pprint_ecp(magenta, (?- run_1_test(String))),
147 pprint_ecp(yellow, clif=Clif),
148 convert_clif_to_cg(Clif, CG),
149 pprint_ecp(cyan, cg(CG)),
150 dmsg("================================================="), !.
151
152test_logicmoo_cg_clif:- update_changed_files, forall(cl_example(String), run_1_test(String)).
153
154:- add_history(test_logicmoo_cg_clif). 155
161
162
164qvar_to_vvar(I, O):- \+ compound(I), !, I=O.
165qvar_to_vvar('?'(Name), '$VAR'(UPPER)):- upcase_atom(Name, UPPER), !.
166qvar_to_vvar(I, O):-
167 compound_name_arguments(I, F, ARGS),
168 maplist(qvar_to_vvar, ARGS, ArgsO),
169 compound_name_arguments(O, F, ArgsO).
170
171
176convert_clif_to_cg(In, Out):-
177 chop_up(In, Mid),
178 qvar_to_vvar(Mid, Mid2),
179 unnumbervars(Mid2, Out).
180
181
186compound_name_arguments_sAfe(F, F, []):- !. 187compound_name_arguments_sAfe(LpsM, F, ArgsO):- compound_name_arguments(LpsM, F, ArgsO).
188
189
190
191
198
199cl_example("
200(=>
201 (and
202 (attribute ?P Muslim)
203 (capability Hajj agent ?P))
204
205 (modalAttribute
206 (exists (?H)
207 (and
208 (instance ?H Hajj)
209 (agent ?H ?P)))
210 Obligation)) ").
211cl_example("
212(exists (x y) (and (Red x) (not (Ball x)) (On x y) (not (and (Table y) (not (Blue y))))))").
213
214cl_example('
215(exists ((x Drive) (y Chevy) (z Old))
216 (and (Person Bob) (City "St. Louis")
217 (Agnt x Bob)(Dest x "St. Louis") (Thme x y) (Poss Bob y) (Attr y z) ))').
218
220cl_example("(not (exists ((x Cat) (y Mat)) (and (On x y)(not (exists z) (and (Pet x) (Happy z) (Attr x z))))))").
221
223cl_example("(forall ((x Cat) (y Mat))(if (On x y) (and (Pet x) (exists ((z Happy)) (Attr x z)))))").
224
225cl_example("(exists ((r Relation)) (and (Familial r) (r Bob Sue)))").
226
227cl_example("(exists ( ?y ) (implies (isa ?y Mat) (Pred ?y ?z)))").
228
230cl_example("(exists ((?x Cat) (?y Mat)) (On ?x ?y))").
231
232cl_example("(not (exists ((?x Cat)) (not (exists ((?y Mat)) (On ?x ?y)))))").
233
235cl_example("(forall ((?x Cat)) (exists ((?y Mat)) (On ?x ?y)))").
236
238cl_example("(exists ((?y Mat)(?x Cat)(?z Cat)) (and (On ?x ?y)(On ?z ?y)(different ?x ?z)))").
239
241cl_example("
242(exists ((x Go) (y Bus))
243 (and (Person John) (city Boston)
244 (Agnt x John) (Dest x Boston) (Inst x y)))").
245
246cl_example("
247(exists ((?x Go) (?y Person) (?z City) (?w Bus))
248 (and (Name ?y John) (Name ?z Boston)
249 (Agnt ?x ?y) (Dest ?x ?z) (Inst ?x ?w)))").
250
251
252
253
255cl_example("
256(exists ((?x1 person) (?x2 believe))
257 (and (expr ?x2 ?x1)
258 (thme ?x2
259 (exists ((?x3 person) (?x4 want) (?x8 situation))
260 (and (name ?x3 'Mary) (expr ?x4 ?x3) (thme ?x4 ?x8)
261 (dscr ?x8 (exists ((?x5 marry) (?x6 sailor))
262 (and (Agnt ?x5 ?x3) (Thme ?x5 ?x6)))))))))").
264
265
266skip_cl_example("
267(exists ((?x person) (?y rock) (?z place) (?w hard))
268 (and (betw ?y ?z ?x) (attr ?z ?w)))").
269
270skip_cl_example( "
271(For a number x, a number y is ((x+7) / sqrt(7)))")