1/* 2% =============================================================================================================== 3 % File 'common_logic_sanity.pl' 4 % Purpose: Emulation of OpenCyc for SWI-Prolog 5 % Maintainer: Douglas Miles 6 % Contact: $Author: dmiles $@users.sourceforge.net ; 7 % Version: 'interface.pl' 1.0.0 8 % Revision: $Revision: 1.9 $ 9 % Revised At: $Date: 2002/06/27 14:13:20 $ 10% =============================================================================================================== 11 % File used as storage place for all predicates which make us more like Cyc 12 % special module hooks into the logicmoo engine allow 13 % syntax to be recocogized via our CycL/KIF handlers 14 % 15 % Dec 13, 2035 16 % Douglas Miles 17*/ 18 19% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/plarkc/common_logic_sanity.pl 20:- module(common_logic_sanity,[kif_test/1,test_boxlog/1,test_boxlog/2,test_defunctionalize/1]). 21 22 23:- system:(( 24 op(1199,fx,('==>')), 25 op(1190,xfx,('::::')), 26 op(1180,xfx,('==>')), 27 op(1170,xfx,'<==>'), 28 op(1160,xfx,('<-')), 29 op(1150,xfx,'=>'), 30 op(1140,xfx,'<='), 31 op(1130,xfx,'<=>'), 32 op(600,yfx,'&'), 33 op(600,yfx,'v'), 34 op(350,xfx,'xor'), 35 op(300,fx,'~'), 36 op(300,fx,'-'))). 37 38:- ensure_loaded(library(logicmoo_clif)). 39 40%:- use_module(library(script_files)). 41 42fst:- set_prolog_flag(write_attributes,ignore),freeze(X,(\+ is_ftVar(X),X==[]->(dumpST,break);true)),rtrace((trace,test_boxlog(~ &(human(X), male(X))))). 43 44:- export(fst/0). 45 46 47zebra :- make,load_clif(pack(logicmoo_base/t/examples/fol/'exactly.clif')). 48 49zebra5 :- make,load_clif(pack(logicmoo_base/t/examples/fol/'zebra5.clif')). 50zebra1 :- make,load_clif(pack(logicmoo_base/t/examples/fol/'zebra1.clif')). 51zebra0 :- make,load_clif(pack(logicmoo_base/t/examples/fol/'zebra0.clif')). 52 53rzebra5 :- rtrace(load_clif(pack(logicmoo_base/t/examples/fol/'exactly.clif'))). 54 55z:- cls,zebra5,!. 56z:- rzebra5,!. 57 58boxlog :- ensure_loaded(pack(logicmoo_base/t/examples/fol/'fol_sanity.pl')). 59 60kif_uncompile:- pfclog_uncompile,boxlog_uncompile,clif_uncompile. 61kif_compile:- clif_compile,boxlog_compile,pfclog_compile. 62kif_recompile:- kif_uncompile,kif_compile. 63kif_show:- baseKB:listing(clif/1),baseKB:listing(boxlog/1),baseKB:listing(pfclog/1). 64:- export(kif_recompile/0). 65:- export(kif_compile/0). 66:- export(kif_uncompile/0). 67:- export(kif_show/0). 68 69 70:- kb_shared(compile_clif/0). 71clif_uncompile:- ain(==>( \+ compile_clif)),clif_show. 72clif_recompile:- ain(==>( \+ compile_clif)), ain(==> compile_clif),clif_show. 73clif_compile:- ain(==> compile_clif). % clif_show. 74clif_show:- baseKB:listing(clif/1),baseKB:listing(boxlog/1). 75:- export(clif_recompile/0). 76:- export(clif_compile/0). 77:- export(clif_uncompile/0). 78:- export(clif_show/0). 79 80:- kb_shared(compile_boxlog/0). 81:- export(boxlog_recompile/0). 82:- export(boxlog_compile/0). 83:- export(boxlog_uncompile/0). 84:- export(boxlog_show/0). 85boxlog_uncompile:- ain(==>( \+ compile_boxlog)),boxlog_show. 86boxlog_recompile:- ain(==>( \+ compile_boxlog)), ain(==> compile_boxlog),boxlog_show. 87boxlog_compile:- ain(==> compile_boxlog). % boxlog_show. 88boxlog_show:- baseKB:listing(boxlog/1),baseKB:listing(pfclog/1). 89 90:- kb_shared(compile_pfclog/0). 91:- export(pfclog_recompile/0). 92:- export(pfclog_compile/0). 93:- export(pfclog_uncompile/0). 94:- export(pfclog_show/0). 95 96pfclog_uncompile:- ain(==>( \+ compile_pfclog)),pfclog_show. 97pfclog_recompile:- ain(==>( \+ compile_pfclog)), ain(==> compile_pfclog),pfclog_show. 98pfclog_compile:- ain(==> compile_pfclog). %pfclog_show. 99pfclog_show:- baseKB:listing(pfclog/1). 100 101 102show_kif_to_boxlog(P):- dmsg(test_boxlog(P)),ain(P). 103 104 105test_defunctionalize(I):-defunctionalize(I,O),sdmsg(O). 106 107sdmsg(Form):- 108 if_defined(demodal_sents(_KB,Form,Out),Form=Out), 109 % if_defined(local_pterm_to_sterm(OutM,Out),OutM=Out), 110 must(wdmsgl(wdmsg,Out)). 111 112sdmsgf(Form):- 113 if_defined(demodal_sents(_KB,Form,Out),Form=Out), 114 % if_defined(local_pterm_to_sterm(OutM,Out),OutM=Out), 115 must(wdmsgl(Out)). 116 117/* 118test_boxlog(P):- source_location(_,_),!,nl,nl,b_implode_varnames(P),test_boxlog(P,O),nl,nl, 119 % b_implode_varnames(O), 120 (is_list(O)->maplist(portray_one_line,O);dmsg(O)),flush_output. 121*/ 122 123 124add_boxlog_history(P0):- 125 (nb_current('$variable_names', Vs0)->true;Vs0=[]), 126 copy_term(P0+Vs0,P+Vs), 127 \+ \+ 128 ((b_setval('$variable_names',Vs), 129 b_implode_varnames0(Vs), 130 b_implode_varnames(P), 131 guess_varnames(P), 132 with_output_to(string(S), 133 write_term(P,[numbervars(true),variable_names(Vs),character_escapes(true),ignore_ops(false),quoted(true),fullstop(true)])), 134 stream_property(In,file_no(0)), 135 prolog:history(In, add(S)))),!. 136 137:- export(test_boxlog/1). 138test_boxlog(P):- test_boxlog([],P). 139 140 141test_boxlogq(P):- test_boxlog([+qualify],P),!. 142 143:- export(test_boxlog/2). 144% test_boxlog_m(P,BoxLog):-logicmoo_motel:kif_to_motelog(P,BoxLog),!. 145test_boxlog(KV,P):- 146 locally_tl(kif_option_list(KV),( 147 mmake, 148 % ignore(source_location(_,_) -> add_boxlog_history(test_boxlog(KV,P)) ; true), 149 \+ \+ 150 must_det_l(( 151 (nb_current('$variable_names', Vs)->b_implode_varnames0(Vs);true), 152 wdmsg(:- test_boxlog(P)), 153 b_implode_varnames(P), 154 guess_varnames(P), 155 kif_optionally_e(never,ain,clif(P)), 156 kif_to_boxlog(P,O), 157 guess_varnames(O),flush_output, 158 kif_optionally_e(true,sdmsgf,O),flush_output, 159 kif_optionally(false,assert_to_boxlog,O), 160 kif_optionally(false,print_boxlog_to_pfc,O))))),!. 161 162assert_to_boxlog(G):- ain(boxlog(G)),!. 163 164print_boxlog_to_pfc(O):- 165 boxlog_to_pfc(O,PFC), 166 sdmsgf(pfc=PFC), 167 flush_output. 168 169 170 171 172assert_boxlog(G):- ain(boxlog(G)). 173 174test_boxlog_88(P):- 175 \+ \+ 176 must_det_l(( 177 (nb_current('$variable_names', Vs)->b_implode_varnames0(Vs);true), 178 b_implode_varnames(P),flush_output, 179 wdmsg(:- test_boxlog(P)), 180 with_assert_buffer(with_chaining(ain(P)),Buffer), 181 undo_buffer(Buffer), 182 sdmsgf(Buffer),flush_output)). 183 184 185 186:- export(test_pfc/1). 187test_pfc(P):- mmake, must_det(test_pfc0(P)),!. 188test_pfcq(P):- mmake, locally_tl(qualify_modally,must_det(test_pfc0(P))),!. 189 190test_pfc0(P):- 191 \+ \+ 192 must_det_l(( 193 (nb_current('$variable_names', Vs)->b_implode_varnames0(Vs);true), 194 b_implode_varnames(P),flush_output, 195 wdmsg(:- test_pfc(P)), 196 kif_to_pfc(P,O), 197 sdmsgf(O),flush_output)). 198 199 200 201invert_op_call(OP,What,dmsg(undo(OP,What))). 202 203undo_tell(call(OP,What)):-!, invert_op_call(OP,What,Invert),call(Invert). 204undo_tell(Tell):- ignore(show_call(mpred_retract(Tell))). 205 206undo_buffer(Buffer):- must_maplist(undo_tell,Buffer),!. 207 208 209% invert_op_call(OP,What,Invert):-!.
tsn:- with_all_dmsg(forall(clause(kif,C),must(C)))
.
219/* 220%% regression_test is det. 221% 222% Hook To [baseKB:regression_test/0] For Module Common_logic_snark. 223% Regression Test. 224% 225 226% baseKB:regression_test:- tsn. 227*/ 228 229:- op(0,fy,(kif_test)).
234kif_test(TODO):-atomic(TODO),kif_io(string(TODO),current_output). 235kif_test(X):- kif_add(X). 236:- op(1200,fy,(kif_test)). 237 238 239kif_result(_). 240 241 242baseKBsanity_test:- kif_test(all(R,'=>'(room(R) , exists(D, '&'(door(D) , has(R,D)))))). 243 244baseKBsanity_test:- kif_to_boxlog(not((a , b , c , d)),S),!,disjuncts_to_list(S,L), 245 list_to_set(L,SET),forall(member(P,SET),writeln(P)),!. 246 247 248kif_sanity_tests:- forall(clause(kif_sanity_test_0,B),must(B)). 249 250default_logic_uses:- must(call(call,uses_logic(logicmoo_kb_refution))). 251 252%:- initialization(default_logic_uses). 253%:- default_logic_uses. 254 255 256% :- if_startup_script(reexport(kif_sanity_tests)). 257 258% = % :- reexport(plarkc/mpred_clif). 259 260% = % :- reexport(logicmoo_plarkc). 261 262%:- autoload. 263 264 265 266subtest_assert(I) :- kif_assert(I). 267 268 :- nl,nl,dmsg('%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%'),nl,nl. 270 271test_assert(A):- 272 nop(kif_assert(A)), 273 test_boxlog([+assert],A), 274 nop(forall(subtest(T),do_subtest(T))). 275 276 277do_subtest(List):- must_maplist(call,List). 278 279add_test(Name,Assert):- 280 b_implode_varnames(Name+Assert), 281 assert(is_test(Name)), 282 dbanner,dmsg(test_boxlog(Name)),dbanner, 283 test_boxlog(Assert), 284 dbanner,dmsg(completed_test_boxlog(Name)),dbanner, 285 assert(( :- mmake, dbanner,dmsg(running_test(Name)),dbanner, 286 test_assert(Assert), 287 dbanner,dmsg(completed_running_test(Name)),dbanner)). 288 289show_test(G):- defaultAssertMt(KB),must(show_call(KB:G)). 290show_call_test(G):- defaultAssertMt(KB),must(show_call(KB:G)). 291 292 293 294 :- meta_predicate example_known_is_success( ). 295 :- meta_predicate example_known_is_failure( ). 296 :- meta_predicate example_proven_true( ). 297 :- meta_predicate example_proven_false( ). 298 :- meta_predicate example_inconsistent( ). 299 :- meta_predicate example_unknown( ). 300 301 302 303%= define the example language 304% :- fully_expand_real(change(assert,ain),(example_known_is_success(_30487686):-_30487686),O),writeln(O). 305example_known_is_success(G):- call_u(G). 306example_impossible_is_success(G):- call_u(~(G)). 307example_known_is_failure(G):- \+ call_u(G). 308example_impossible_is_failure(G):- \+ call_u(~(G)). 309 310%= define the four truth values 311example_proven_true(G):- example_known_is_success(G),example_impossible_is_failure(G). 312example_proven_false(G):- example_impossible_is_success(G),example_known_is_failure(G). 313example_inconsistent(G):- example_known_is_success(G),example_impossible_is_success(G). 314example_unknown(G):- example_known_is_failure(G),example_impossible_is_failure(G). 315 316% :-multifile lmconf:shared_hide_data/1. 317%= lmconf:shared_hide_data(hideMeta):-is_main_thread. 318%= lmconf:shared_hide_data(hideTriggers):-is_main_thread. 319 320% = clear the screen 321% :- shell(cls). 322 323%= save compiled clauses using forward chaining storage (by default) 324%= we are using forward chaining just so any logical errors, performance and program bugs manefest 325%= immediately 326% :- set_clause_compile(fwc). 327 328 329 330:- fixup_exports. 331 332:- if(false). 333:- set_prolog_flag(gc,true). 334:- trim_stacks. 335:- garbage_collect_atoms. 336:- garbage_collect_clauses. 337:- garbage_collect. 338:- statistics. 339%:- set_prolog_flag(gc,false). 340:- endif. 341 342 343add_axiom(AX):- ain(baseKB:axiom(AX)). 344 345:- add_axiom(( ~fallacy_t(PROP) => unknown_t(PROP) v false_t(PROP) v true_t(PROP) )). 346:- add_axiom(( ~unknown_t(PROP) => true_t(PROP) v false_t(PROP) )). 347:- add_axiom(( ~false_t(PROP) => fallacy_t(PROP) v unknown_t(PROP) v true_t(PROP) )). 348:- add_axiom(( answerable_t(PROP) <=> askable_t(PROP) & ~unknown_t(PROP) )). 349:- add_axiom(( answerable_t(PROP) => true_t(PROP) v false_t(PROP) )). 350:- add_axiom(( askable_t(PROP) <=> ~fallacy_t(PROP) )). 351:- add_axiom(( askable_t(PROP) => true_t(PROP) v unknown_t(PROP) v false_t(PROP) )). 352:- add_axiom(( askable_t(PROP) v fallacy_t(PROP) )). 353:- add_axiom(( asserted_t(PROP) => true_t(PROP) )). 354:- add_axiom(( fallacy_t(PROP) => false_t(PROP) & true_t(PROP) & ~unknown_t(PROP) & ~possible_t(PROP) )). 355:- add_axiom(( true_t(PROP) & false_t(PROP) => fallacy_t(PROP) )). 356:- add_axiom(( true_t(PROP) v unknown_t(PROP) v false_t(PROP) )). 357 358:- add_axiom(( true_t(PROP) => possible_t(PROP) )). 359:- add_axiom(( possible_t(PROP) => ~false_t(PROP) & ~fallacy_t(PROP) )). 360 361:- add_axiom(( ~true_t(PROP) => false_t(PROP) v fallacy_t(PROP) v possible_t(PROP) )). 362:- add_axiom(( false_t(PROP) <=> ~true_t(PROP) & ~possible_t(PROP) & ~unknown_t(PROP) )). 363:- add_axiom(( true_t(PROP) => ~false_t(PROP) & possible_t(PROP) & ~unknown_t(PROP) )). 364:- add_axiom(( ~asserted_t(PROP) => possible_t(PROP) v false_t(PROP) v fallacy_t(PROP) )). 365:- add_axiom(( ~possible_t(PROP) => false_t(PROP) v fallacy_t(PROP) )). 366:- add_axiom(( possible_t(PROP) => ~false_t(PROP) & ~fallacy_t(PROP) )). 367:- add_axiom(( unknown_t(PROP) => ~true_t(PROP) & possible_t(PROP) & ~asserted_t(PROP) & ~false_t(PROP) )). 368%:- add_axiom(( ist(MT1,askable_t(PROP)) & genlMt(MT1,MT2) => ist(MT2, (true_t(PROP) v unknown_t(PROP) v false_t(PROP) )))). 369% :- add_axiom(( ist(MT1,asserted_t(PROP)) & genlMt(MT1,MT2) => ist(MT2,true_t(PROP)) )). 370 371 372e0 :- any_to_pfc((( 373 (tHeart(skIsHeartInArg2ofHasorgan_Fn(Human)) 374 :- tHuman(Human))),(hasOrgan(Human, skIsHeartInArg2ofHasorgan_Fn(Human)) :- tHuman(Human))),O),wdmsg(O). 375% O = tHuman(Heart)==> if_missing(hasOrgan(Human,_),hasOrgan(Human,skIsHeartInArg2ofHasorgan_Fn(Human))) & tHeart(skIsHeartInArg2ofHasorgan_Fn(Human)). 376 377 378e1:- % ['$VAR'('Room'),'$VAR'('Door')]= [Room,Door], 379 test_boxlog(exists([[Door, tDoor]], isa(Room,tRoom) => hasExit(Room,Door))). 380 381e2:- % ['$VAR'('Room'),'$VAR'('Door')]= [Room,Door], 382 test_boxlog((all([[Room, tRoom]],exists([[Door, tDoor]], hasExit(Room,Door))))). 383 384e3:- % ['$VAR'('Room'),'$VAR'('Door')]= [Room,Door], 385 test_boxlog(exists([[Door, tDoor]], isa(Room,tRoom) => hasExit3(Room,Door))). 386 387e4:- ['$VAR'('Room'),'$VAR'('Door')]= [Room,Door], 388 make,(test_boxlog((isa(Room,tRoom) => exists(Door, isa(Door,tDoor) & hasExit4(Room,Door))))). 389 390 391e5:- ['$VAR'('Human'),'$VAR'('Heart')]= [Human,Heart], 392 (test_boxlog( 393 all([[Human,tHuman]], 394 exists([Heart], 395 % isa(Human,tHuman) => 396 (isa(Heart,tHeart) & hasOrgan(Human,Heart)))))). 397 398e6:- ['$VAR'('Human'),'$VAR'('Heart')]= [Human,Heart], 399 (test_boxlog(all([Human],exists([Heart],isa(Human,tHuman) => (isa(Heart,tHeart) & hasOrgan(Human,Heart)))))). 400 401 402e7:- ['$VAR'('Human'),'$VAR'('Heart')]= [Human,Heart], 403 (kif_to_boxlog(all([Human],exists([Heart],isa(Human,tHuman) 404 => (isa(Heart,tHeart) 405