1/* 2% Game loading Utils 3% 4% Logicmoo Project PrologMUD: A MUD server written in Prolog 5% Maintainer: Douglas Miles 6% Dec 13, 2035 7% 8*/ 9 10% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/mpred/mpred_loader.pl 11:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )). 12mpred_loader_module:- fail, nop(module(mpred_loader, 13 [ add_from_file/1, 14 % unused_assertion/1, 15 mpred_ops/0, 16 set_file_lang/1, 17 mpred_te/6, 18 pfc_dcg/0, 19 get_original_term_src/1, 20 21 set_lang/1, 22 simplify_language_name/2, 23 %is_undefaulted/1, 24 current_op_alias/2, 25 show_load_call/1, 26 add_term/2, 27 28 % system:import_module_to_user/1, 29 30 31 make_file_command/3, 32 % import_shared_pred/3, 33 % import_to_user0/3, 34 % import_to_user_mfa0/4, 35 36 %predicate_is_undefined_fa/2, 37 38 same_language/2, 39 call_file_command0/4, 40 is_compiling_clause/0, 41 to_prolog_xform/2, 42 mpred_ain_loaded/0, 43 44 45 begin_pfc/0, 46 call_file_command/4, 47 can_be_dynamic/1, 48 cl_assert/2, 49 clear_predicates/1, 50 collect_expansions/3, 51 compile_clause/1, 52 mpred_term_expansion_by_storage_type/3, 53 convert_side_effect/2, 54 convert_side_effect/3, 55 convert_side_effect_buggy/2, 56 current_context_module/1, 57 % cwc/0, 58 decache_file_type/1, 59 mpred_ops/0, 60 %setup_module_ops/1, 61 %mpred_op_each/1, 62 %mpred_op_unless/4, 63 declare_load_dbase/1, 64 disable_mpred_expansion/0, 65 disable_mpreds_in_current_file/0, 66 67 dyn_begin/0, 68 dyn_end/0, 69 enable_mpred_expansion/0, 70 end_module_type/1, 71 end_module_type/2, 72 ensure_loaded_no_mpreds/1, 73 74 % ensure_prolog_file_consulted/2, ensure_mpred_file_consulted/2, 75 ensure_mpred_file_loaded/1, 76 ensure_mpred_file_loaded/2, 77 78 etrace/0, 79 expand_in_mpred_kb_module/2, 80 expanded_already_functor/1, 81 file_begin/1, 82 file_end/1, 83 finish_processing_world/0, 84 force_reload_mpred_file/1, 85 force_reload_mpred_file/2, 86 force_reload_mpred_file2/2, 87 get_file_type/2, 88 get_lang/1, 89 get_lang0/1, 90 get_last_time_file/3, 91 get_op_alias/2, 92 gload/0, 93 hdr_debug/2, 94 include_mpred_files/1, 95 include_prolog_files/1, 96 get_lang0/1, 97 is_code_body/1, 98 is_compiling/0, 99 is_compiling_sourcecode/0, 100 is_directive_form/1, 101 is_mpred_file/1, 102 lang_op_alias/3, 103 expand_term_to_load_calls/2, 104 mpred_expander_now_physically/3, 105 load_init_world/2, 106 load_language_file/1, 107 load_mpred_files/0, 108 load_mpred_on_file_end/2, 109 loader_side_effect_capture_only/2, 110 loader_side_effect_verify_only/2, 111 must_expand_term_to_command/2, 112 113 make_db_listing/0, 114 make_dynamic/1, 115 (make_dynamic_ilc)/1, 116 module_typed_term_expand/2, 117 module_typed_term_expand/5, 118 mpred_begin/0, 119 mpred_expand_inside_file_anyways/0, 120 mpred_expand_inside_file_anyways/1, 121 mpred_te/6, 122 mpred_file_term_expansion/4, 123 dont_term_expansion/2, 124 mpred_file_term_expansion/4, 125 126 mpred_expand_file_module_clause/4, 127 mpred_expand_file_module_clause/4, 128 mpred_implode_varnames/1, 129 130 mpred_prolog_only_file/1, 131 mpred_may_expand/0, 132 mpred_may_expand_module/1, 133 mpred_maybe_skip/1, 134 135 baseKB:mpred_skipped_module/1, 136 mpred_term_expansion/2, 137 mpred_use_module/1, 138 must_compile_special_clause/1, 139 expand_term_to_load_calls/2, 140 must_locate_file/2, 141 maybe_locate_file/2, 142 myDebugOnError/1, 143 144 op_alias/2, 145 op_lang/1, 146 pl_to_mpred_syntax/2, 147 pl_to_mpred_syntax_h/2, 148 pop_predicates/2, 149 push_predicates/2, 150 read_one_term/2, 151 read_one_term/3, 152 register_module_type/1, 153 register_module_type/2, 154 rsavedb/0, 155 savedb/0, 156 scan_updates/0, 157 show_bool/1, 158 show_interesting_cl/2, 159 show_load_context/0, 160 simplify_why/2, 161 simplify_why_r/4, 162 stream_pos/1, 163 term_expand_local_each/5, 164 165 transform_opers/3, 166 167 use_was_isa/3, 168 was_exported_content/3, 169 with_mpred_expansions/1, 170 % with_delayed_chaining/1, 171 lmcache:mpred_directive_value/3, 172 173 baseKB:loaded_file_world_time/3, 174 baseKB:mpred_provide_clauses/3, 175 baseKB:never_reload_file/1, 176 always_expand_on_thread/1, 177 t_l:current_lang/1, 178 179 baseKB:mpred_skipped_module/1, 180 %prolog_load_file_loop_checked/2, 181% registered_module_type/2, 182 %t_l:into_form_code/0, 183 %t_l:mpred_module_expansion/1, 184 185 user:term_expansion/2, 186 mpred_loader_module_transparent/1, 187 convert_side_effect_0a/2, convert_side_effect_0b/2, 188 convert_side_effect_0c/2, guess_if_mpred_file0/1, expand_term_to_load_calls/2, load_file_term_to_command_1/3, 189 load_file_term_to_command_1b/3, mpred_term_expansion_by_pred_class/3, 190 must_expand_term_to_command/2, pl_to_mpred_syntax0/2, 191 192 transform_opers_0/2, transform_opers_1/2, 193 mpred_loader_file/0, 194 mpred_unload_file/0, 195 mpred_unload_file/1 196 ])). 197 198:- include('mpred_header.pi'). 199:- use_module(library(dictoo_lib)). 200 201:- endif. 202 203%:- user:use_module(library('file_scope')). 204 205:- thread_local(t_l:into_form_code/0). 206 207:- thread_local(t_l:disable_px/0). 208:- multifile(prolog:make_hook/2). 209:- dynamic(prolog:make_hook/2). 210 211% :- asserta_if_new((prolog:make_hook(BA, C):- dmsg_pretty(prolog:make_hook(BA, C)),fail)). 212% prolog:make_hook(before, FileS):- maplist(mpred_loader:mpred_unload_file,FileS). 213 214% Avoid Warning: mpred_loader:prolog_load_context(reload,true), which is called from 215mpred_unload_file:- prolog_load_context(reload,true),!. 216mpred_unload_file:- source_location(File,_),mpred_unload_file(File). 217mpred_unload_file(File):- dmsg(nop(mpred_unload_file(File))),!. 218mpred_unload_file(File):- 219 findall( 220 mpred_withdraw(Data,(mfl4(VarNameZ,Module, File, LineNum),AX)), 221 % clause_u 222 call_u(spft(Data, mfl4(VarNameZ,Module, File, LineNum),AX)), 223 ToDo), 224 length(ToDo,Len), 225 dmsg_pretty(mpred_unload_file(File,Len)), 226 maplist(call,ToDo),!. 227 228 229 :- module_transparent((load_file_term_to_command_1b/3,pfc_dcg/0, mpred_term_expansion_by_pred_class/3, 230 must_expand_term_to_command/2, pl_to_mpred_syntax0/2, 231 232 transform_opers_0/2, transform_opers_1/2)). 233 234 :- meta_predicate 235 % make_reachable(?,?), 236 call_file_command( , , , ), 237 cl_assert( , ), 238 show_bool( ), 239 convert_side_effect( , , ), 240 241 ensure_loaded_no_mpreds( ), 242 ensure_mpred_file_loaded( ), 243 ensure_mpred_file_loaded( , ), 244 force_reload_mpred_file( ), 245 force_reload_mpred_file2( , ), 246 get_last_time_file( , , ), 247 expand_term_to_load_calls( , ), 248 mpred_expander_now_physically( , , ), 249 load_init_world( , ), 250 module_typed_term_expand( , ), 251 mpred_te( , , , , , ), 252 253 mpred_term_expansion( , ), 254 myDebugOnError( ), 255 with_mpred_expansions( ), 256 %with_delayed_chaining(0), 257 mpred_loader_module_transparent( ), 258 baseKB:loaded_file_world_time( , , ). 259:- multifile(( user:term_expansion/2)). 260:- (dynamic user:term_expansion/2). 261% :- (module_transparent add_from_file/1, add_term/2 262% begin_pfc/0, call_file_command/4, 263% call_from_module/2, with_source_module/2, can_be_dynamic/1, cl_assert/2, clear_predicates/1, collect_expansions/3, compile_clause/1, 264% mpred_term_expansion_by_storage_type/3, convert_side_effect/2, convert_side_effect/3, convert_side_effect_0a/2, convert_side_effect_0b/2, convert_side_effect_0c/2, 265% convert_side_effect_buggy/2, current_context_module/1, current_op_alias/2, cwc/0, decache_file_type/1, ensure_abox/1, declare_load_dbase/1, 266% disable_mpred_expansion/0, disable_mpreds_in_current_file/0, dyn_begin/0, dyn_end/0, enable_mpred_expansion/0, end_module_type/1, end_module_type/2, ensure_loaded_no_mpreds/1, ensure_mpred_file_consulted/2, ensure_mpred_file_loaded/1, ensure_mpred_file_loaded/2, ensure_prolog_file_consulted/2, etrace/0, expand_in_mpred_kb_module/2, expanded_already_functor/1, file_begin/1, file_end/1, finish_processing_world/0, force_reload_mpred_file/1, 267% force_reload_mpred_file2/2, force_reload_mpred_file/2, from_kif_string/2, get_file_type/2, get_lang/1, get_last_time_file/3, get_op_alias/2, gload/0, guess_file_type_loader/2, hdr_debug/2, in_include_file/0, in_mpred_kb_module/0, include_mpred_files/1, get_lang/1, is_code_body/1, is_compiling/0, is_compiling_sourcecode/0, is_kif_string/1, is_mpred_file/1, guess_if_mpred_file0/1, lang_op_alias/3, load_file_dir/2, load_file_some_type/2, expand_term_to_load_calls/2, load_file_term_to_command_1/3, load_file_term_to_command_1b/3, mpred_term_expansion_by_pred_class/3, expand_term_to_load_calls/2, expand_term_to_load_calls/4, load_init_world/2, load_language_file/1, load_mpred_files/0, load_mpred_on_file_end/2, loader_side_effect_capture_only/2, loader_side_effect_verify_only/2, expand_term_to_command/2, loading_source_file/1, make_db_listing/0, make_dynamic/1, module_typed_term_expand/2, module_typed_term_expand/5, mpred_begin/0, mpred_expand_inside_file_anyways/0, mpred_expand_inside_file_anyways/1, mpred_te/4, mpred_expander_now/2, mpred_expand_file_module_clause/4, mpred_implode_varnames/1, mpred_loader_file/0, mpred_may_expand/0, mpred_may_expand_module/1, mpred_maybe_skip/1, mpred_process_input/2, mpred_process_input_1/1, baseKB:mpred_skipped_module/1, mpred_term_expansion/2, mpred_use_module/1, must_compile_special_clause/1, expand_term_to_load_calls/2, must_locate_file/2, must_expand_term_to_command/2, myDebugOnError/1, op_alias/2, op_lang/1, pl_to_mpred_syntax/2, pl_to_mpred_syntax0/2, pl_to_mpred_syntax_h/2, pop_predicates/2, process_this_script/0, process_this_script/1, process_this_script0/1, prolog_load_file_loop_checked/2, prolog_load_file_loop_checked_0/2, prolog_load_file_nlc/2, prolog_load_file_nlc_0/2, push_predicates/2, read_one_term/2, read_one_term/3, register_module_type/1, register_module_type/2, rsavedb/0, savedb/0, scan_updates/0, show_bool/1, show_interesting_cl/2, show_load_context/0, simplify_why/2, simplify_why_r/4, stream_pos/1, term_expand_local_each/5, transform_opers/3, transform_opers_0/2, transform_opers_1/2, use_file_type_loader/2, use_was_isa/3, was_exported_content/3, with_mpred_expansions/1, with_delayed_chaining/1, with_source_module/2, xfile_module_term_expansion_pass_3/7, 268% (~)/1, baseKB:cl_assert/2, baseKB:cwc/0, baseKB:mpred_provide_clauses/3, always_expand_on_thread/1, t_l:current_lang/1, current_op_alias/2, defaultAssertMt/1, baseKB:loaded_file_world_time/3, mpred_directive_value/3, baseKB:mpred_skipped_module/1, 269% never_reload_file/1, prolog_load_file_loop_checked/2, registered_module_type/2). 270:- module_transparent 271 mpred_ops/0. 272 %setup_module_ops/1. 273 274:- thread_local(t_l:into_form_code/0). 275:- thread_local(t_l:mpred_module_expansion/1). 276 277%:- (volatile t_l:into_form_code/0, t_l:mpred_module_expansion/1). 278%:- /**/ export((convert_side_effect_0a/2, convert_side_effect_0b/2, convert_side_effect_0c/2, guess_if_mpred_file0/1, expand_term_to_load_calls/2, load_file_term_to_command_1/3, load_file_term_to_command_1b/3, mpred_term_expansion_by_pred_class/3, mpred_process_input_1/1, must_expand_term_to_command/2, pl_to_mpred_syntax0/2, process_this_script0/1, prolog_load_file_loop_checked_0/2, prolog_load_file_nlc_0/2, transform_opers_0/2, transform_opers_1/2, xfile_module_term_expansion_pass_3/7)). 279%:- dynamic((registered_module_type/2, current_op_alias/2, baseKB:mpred_skipped_module/1, prolog_load_file_loop_checked/2, lmcache:mpred_directive_value/3, defaultAssertMt/1, baseKB:loaded_file_world_time/3, baseKB:never_reload_file/1, always_expand_on_thread/1, t_l:current_lang/1, current_op_alias/2, defaultAssertMt/1, baseKB:loaded_file_world_time/3, mpred_directive_value/3, baseKB:mpred_skipped_module/1, never_reload_file/1, prolog_load_file_loop_checked/2, registered_module_type/2, user:prolog_load_file/2, user:term_expansion/2)). 280%:- dynamic(registered_module_type/2). 281 282 283:- multifile((baseKB:registered_module_type/2)). 284:- dynamic((baseKB:registered_module_type/2)). 285 286 287 288mpred_load(In):- is_stream(In),!, 289 repeat, 290 line_count(In,_Lineno), 291 % double_quotes(_DQBool) 292 Options = [variables(_Vars),variable_names(VarNames),singletons(_Singletons),comment(_Comment)], 293 catchv((read_term(In,Term,[syntax_errors(error)|Options])),E,(dmsg_pretty(E),fail)), 294 set_varname_list(VarNames),expand_term(Term,TermO),mpred_load_term(TermO), 295 Term==end_of_file, 296 close(In). 297 298mpred_load(PLNAME):- % unload_file(PLNAME), 299 open(PLNAME, read, In, []), 300 absolute_file_name(PLNAME,Disk), 301 set_how_virtualize_file(heads,Disk), 302 mpred_load(In). 303 304mpred_reload(PLNAME):- mpred_unload_file(PLNAME),mpred_load(PLNAME). 305 306 307 308% TODO uncomment the next line without breaking it all! 309% baseKB:use_cyc_database.
318mpred_loader_module_transparent(F/A):-!,mpred_loader_module_transparent(F/A). 319mpred_loader_module_transparent(M:F/A):-!, M:module_transparent(M:F/A),dtrace, system:import(M:F/A). 320mpred_loader_module_transparent(F/A):-!, module_transparent(F/A). 321 322% :- module_property(mpred_loader, exports(List)),maplist(mpred_loader_module_transparent,List). 323 324:- thread_local(t_l:mpred_already_in_file_expansion/1).
333mpred_prolog_only_file(File):- var(File),!,fail. 334mpred_prolog_only_file(File):- get_how_virtualize_file(false,File),!. 335mpred_prolog_only_file(File):- lmcache:mpred_directive_value(File,language,pl),!. 336mpred_prolog_only_file(File):- file_name_extension(File,_,pfc),!,fail. 337mpred_prolog_only_file(File):- lmcache:mpred_directive_value(File,language,pfc),!,fail. 338mpred_prolog_only_file(_). 339 340 341% mpred_te(_,_,I,OO):-thread_self(X),X\==main,!,I=OO. 342% not actual function
351:- prolog_load_context(directory,Dir),asserta(baseKB:mpred_loader_dir(Dir)). 352 353mpred_te(Type,_,I,_,_,_):- !,fail,quietly(dont_term_expansion(Type,I)),!,fail. 354mpred_te(Type,Module,I,PosI,O,PosO):- 355 \+ current_prolog_flag(mpred_te,false), 356 % prolog_load_context(file,S),prolog_load_context(source,S), 357 mpred_file_term_expansion(Type,Module,I,O)->PosO=PosI. 358 359dont_term_expansion(Type,I):- 360 current_prolog_flag(subclause_expansion,false); 361 var(I); 362 I=(_ --> _) ; 363 current_prolog_flag(xref,true); 364 (prolog_load_context(directory,Dir), baseKB:mpred_loader_dir(Dir)); 365 I= '$si$':'$was_imported_kb_content$'(_,_); 366 (Type \== term , Type \= _:term ) ; 367 (t_l:disable_px, false ).
376:- meta_predicate mpred_file_term_expansion( , , , ). 377% mpred_file_term_expansion(_,_,_,_):- \+ current_predicate(_,_:mpred_loader_file),!,fail. 378mpred_file_term_expansion(_,_,I,_):- is_directive_form(I),!,fail. 379mpred_file_term_expansion(_,_,I,_):- is_ftVar(I),!,fail. 380% mpred_file_term_expansion(_,_,_,_):- get_lang(pl),!,fail. 381% mpred_file_term_expansion(Type,LoaderMod,(I:-B),OO):-B==true,!,mpred_file_term_expansion(Type,LoaderMod,I,OO). 382% mpred_file_term_expansion(_Type,_LoaderMod,I,( :- must(ain(I)))):-!. 383 384mpred_file_term_expansion(Type,LoaderMod,I,OO):- !,fail, 385 no_loop_check(mpred_file_term_expansion0(Type,LoaderMod,I,OO)). 386 387% Ensure rule macro predicates are being used checked just before assert/query time 388mpred_file_term_expansion0(Type,LoaderMod,I,O):- 389 sanity((ground(Type:LoaderMod),nonvar(I),var(O))), 390 quietly_must(get_source_mfl(mfl4(VarNameZ,MF,F,L))),!, 391 % \+ mpred_prolog_only_file(F), 392 call_u(baseKB:mtHybrid(MT1)), 393 must((proper_source_mod([LoaderMod,MF,MT1],AM))), 394 (((nb_current('$source_term',TermWas), TermWas == I); 395 (b_getval('$term',TermWas), TermWas == I))), 396 call_cleanup( 397 locally(t_l:current_why_source(mfl4(VarNameZ,AM,F,L)), 398 (( get_original_term_src(Orig), 399 b_setval('$orig_term',Orig), 400 b_setval('$term',[]), 401 (O= (:- must(mpred_ain(I,(mfl4(VarNameZ,AM,F,L),ax)))))))), 402 b_setval('$term',TermWas)),!, dmsg_pretty(I-->O). 403 404 405proper_source_mod(List,AM):- member(AM,List),call_u(mtHybrid(AM)),!. 406proper_source_mod(List,AM):- member(AM,List),call_u(mtCanAssert(AM)),!.
mpred_expand_file_module_clause(_,_,I,O)
:- var(I)
,!,quietly_must(I=O)
.
414%mpred_expand_file_module_clause(_,_,(?-(G0)),(?-(G1))):-!,quietly_must(fully_expand_goal(change(assert,ain),G0,G1)). 415%mpred_expand_file_module_clause(F,M,I,O):- is_directive_form(I),!,quietly_must(fully_expand(change(assert,load(F,M)),I,O)). 416%mpred_expand_file_module_clause(F,M,(H:-B),O):- get_lang(pl),!,quietly_must(fully_expand(change(assert,load(F,M)),(H:-B),O)). 417%mpred_expand_file_module_clause(_,_,I,O):- t_l:verify_side_effect_buffer,!,loader_side_effect_verify_only(I,O). 418%mpred_expand_file_module_clause(_,_,I,O):- t_l:use_side_effect_buffer,!,loader_side_effect_capture_only(I,O). 419mpred_expand_file_module_clause(_,M,I,O):- mpred_expander_now_physically(M,I,O).
427mpred_expander_now_physically(M,I,OO):-
428 '$set_source_module'(Old,M),
429 call_cleanup(M:((
430 quietly_must((source_context_module(CM),CM\==pfc_lib,CM\==mpred_loader)),
431 quietly_must(loop_check(expand_term_to_load_calls(I,O),trace_or_throw_ex(in_loop(expand_term_to_load_calls(I,O))))),!,
432 quietly_must(I\=@=O),
433 (((t_l:mpred_term_expansion_ok;mpred_expand_inside_file_anyways)-> true ;
434 ((show_load_context,dmsg_pretty(warning,wanted_mpred_term_expansion(I,O))),fail)),
435 ((O=(:-(CALL))) -> quietly_must((M:call_file_command(I,CALL,OO,O)));
436 (OO = O))))),'$set_source_module'(Old)).
447show_bool(G):- must(forall((G*->dmsg_pretty(true=G);dmsg_pretty(false=G)),true)).
456show_load_context:-
457 must((
458 %listing(baseKB:registered_mpred_file),
459 show_bool(mpred_may_expand),
460 show_bool(in_mpred_kb_module),
461 show_bool(mpred_expand_inside_file_anyways),
462 show_bool(t_l:mpred_term_expansion_ok),
463 show_bool(loading_source_file(_)),
464 show_bool(nb_current('$source_term',_)),
465 show_bool(nb_current('$goal_term',_)),
466 show_bool(nb_current('$term',_)),
467 show_bool(nb_current('$orig_term',_)),
468 show_bool(get_lang(_)))).
478add_term(end_of_file,_):-!. 479add_term(Term,Vs):- 480 put_variable_names( Vs), 481 add_from_file(Term).
491add_from_file(Term):-
492 locally(t_l:mpred_already_in_file_expansion(Term),quietly_must(ain(Term))).
501myDebugOnError(Term):-catch(once(quietly_must((Term))),E,(dmsg_pretty(error(E,start_myDebugOnError(Term))),dumpST,dtrace,rtrace((Term)),dmsginfo(stop_myDebugOnError(E=Term)),dtrace,Term)).
510read_one_term(Term,Vs):- catch(once(( read_term(Term,[double_quotes(string),variable_names(Vs)]))),E,(Term=error(E),dmsg_pretty(error(E,read_one_term(Term))))).
518read_one_term(Stream,Term,Vs):- catch(once(( read_term(Stream,Term,[double_quotes(string),variable_names(Vs)]))),E,(Term=error(E),dmsg_pretty(error(E,read_one_term(Term))))). 519 520% rescan_mpred_stubs:- doall((mpred_prop(M,F,A,prologHybrid),arity(F,A),A>0,warnOnError(declare_mpred_local_dynamic(moo,F,A)))). 521 522 523 524:- /**/ export(etrace/0).
532etrace:-leash(+all),leash(+exception),dtrace. 533 534 535% el(X):- cwc,sanity(nonvar(X)),logicmoo_util_filesystem:filematch(X,Y),sanity(atom(Y)),ensure_loaded(Y),!. 536 537 538:- style_check(+singleton). 539:- style_check(-discontiguous). 540% :- style_check(-atom). 541 542% gload:- ensure_mpred_file_loaded(savedb),!.
550gload:- baseKB:ensure_mpred_file_loaded(logicmoo('rooms/startrek.all.pfc.pl')). 551 552%:-meta_predicate(savedb/0).
560savedb:-!. 561savedb:- on_x_debug(rsavedb),!. 562%:-meta_predicate(rsavedb/0).
570rsavedb:-
571 nop(on_x_debug(agenda_mpred_repropigate)),
572 catch((
573 ignore(catch(make_directory('/tmp/lm/'),_,true)),
574 ignore(catch(delete_file('/tmp/lm/savedb'),E,(dmsginfo(E:delete_file('/tmp/lm/savedb'))))),
575 tell('/tmp/lm/savedb'),make_db_listing,told),E,dmsginfo(savedb(E))),!.
585make_db_listing:-
586 % defaultAssertMt(DBM),
587% listing(t),
588 % listing(mpred_f),
589 listing(_),
590 listing(baseKB:_),
591 listing(dbase:_),
592 listing(dyn:_),
593 listing(moo_loader:_),
594 listing(world :_),
595 listing(_),!.
607hdr_debug(_,_):-!. 608hdr_debug(F,A):-'format'(F,A). 609:- meta_predicate module_typed_term_expand( , ).
619module_typed_term_expand(X,_):-not(compound(X)),!,fail. 620module_typed_term_expand( ((':-'(_))) , _ ):-!,fail. 621module_typed_term_expand(_:B1,B2):-!,module_typed_term_expand(B1,B2),!. 622module_typed_term_expand(X,CvtO):- compound(X),loading_module(CM),functor_catch(X,F,A),module_typed_term_expand(CM,X,F,A,CvtO).
631module_typed_term_expand(CM,X,F,A,CvtO):-findall(CvtO,term_expand_local_each(CM,X,F,A,CvtO),Ys), Ys == [],!,fail.
640term_expand_local_each(_,_,F,A,_):- member(F / A,[never_expand]),!,fail. 641term_expand_local_each(CM,X,F,A,X):-baseKB:registered_module_type(CM,utility),export(F/A). 642term_expand_local_each(CM,X,F,A,X):-baseKB:registered_module_type(CM,dynamic),dynamic(F/A). 643 644 645 646 647 648% ======================================== 649% include_mpred_file(MASK) 650% ========================================
659include_mpred_files(Mask):- 660 forall(maybe_locate_file(Mask,E),ensure_mpred_file_loaded(E)). 661 662:- module_transparent(include_prolog_files/1). 663 664include_prolog_files(Mask):- 665 forall(maybe_locate_file(Mask,E),ensure_loaded(E)). 666 667/* 668module(M,Preds):- 669 'format'(user_output /*e*/,'% visting module ~w.~n',[M]), 670 forall(member(P,Preds),export(P)). 671*/
679scan_updates:-thread_property(X,alias(loading_code)),thread_property(X,status(running)),!. 680scan_updates:-!. 681scan_updates:-ignore(catch(make,_,true)). 682 683/* 684do_term_expansions:- source_context_module(CM), (do_term_expansions(CM)). 685 686do_term_expansions(_):- thread_self(ID),baseKB:always_expand_on_thread(ID),!. 687%do_term_expansions(_):- always_transform_heads,not(prevent_transform_mpreds),!. 688do_term_expansions(_):- is_compiling_clause. 689do_term_expansions(CM):- check_how_virtualize_file(heads,CM),!, not(ended_transform_mpreds), not(prevent_transform_mpreds). 690 691check_term_expansions:- not(do_term_expansions). 692*/ 693 694% :- (do_term_expansions(_)->true;throw(not_term_expansions)). 695 696 697:- op(1120,fx,export),op(1120,fx,export). 698 699:- /**/ export(((current_context_module/1, 700 module_typed_term_expand/2, 701 register_module_type/1, 702 end_module_type/1))). 703 704 705 706 707 708 709 710 711 712 713% :- user:use_module(library(base32)). 714 715% :-autoload. 716 717% https://docs.google.com/document/u/0/export?format=txt&id=1yyGne4g8vXKxNPKIKVLOtt0OxIM2kxyfmvjqR1lgbcY 718% http_get 719:- asserta_if_new(t_l:infForward). 720 721:- dynamic(baseKB:mpred_skipped_module/1).
:-show_call(why,loading_module(X))
,retractall(X)
.
732%:-listing(baseKB:mpred_skipped_module/1). 733 734 735%fwc:-true. 736%bwc:-true. 737 738%is_fc_body(P):- quietly(fwc==P ; (compound(P),arg(1,P,E),is_fc_body(E))),!. 739%is_bc_body(P):- quietly(bwc==P ; (compound(P),arg(1,P,E),is_bc_body(E))),!.
747is_code_body(P):- quietly(cwc==P ; (compound(P),arg(1,P,E),is_code_body(E))),!. 748 749 750% :- meta_predicate(with_source_module(:,(*))).
758get_file_type(File,Type):-var(File),!,quietly_must(loading_source_file(File)),get_file_type(File,Type). 759get_file_type(File,Type):-lmcache:mpred_directive_value(File,language,Type). 760get_file_type(File,pfc):-file_name_extension(_,'.pfc.pl',File). 761get_file_type(File,Type):-file_name_extension(_,Type,File).
770is_mpred_file(F):- var(F),!,quietly_must(loading_source_file(F)),F\==user,!, baseKB:how_virtualize_file(heads,F,0),!. 771is_mpred_file(F):- guess_if_mpred_file0(F),!,guess_if_mpred_file0(F),(set_how_virtualize_file(heads,F,0)),!.
777guess_if_mpred_file0(F):- file_name_extension(_,pfc,F),!. 778guess_if_mpred_file0(F):- atom_concat(_,'.pfc.pl',F),!. 779guess_if_mpred_file0(F):- file_name_extension(_,plmoo,F),!. 780% guess_if_mpred_file0(F):- filematch(prologmud(**/*),F0),F0=F. 781guess_if_mpred_file0(F):- loop_check(get_lang(pfc)),!,loop_check(loading_source_file(F0)),F0=F. 782guess_if_mpred_file0(F):- atom(F),exists_file(F), file_name_extension(_,WAS,F),WAS\=pl,WAS\= '',WAS\=chr,!.
790decache_file_type(F):-
791 forall(clause(baseKB:how_virtualize_file(_,F,_),true,Ref),erase(Ref)).
799must_compile_special_clause(:- (_) ):-!,fail. 800%must_compile_special_clause(CL):- sanity(nonvar(CL)),not(t_l:into_form_code),not(t_l:mpred_already_in_file_expansion(CL)),not((get_functor(CL,F),expanded_already_functor(F))). 801must_compile_special_clause(CL):- \+ t_l:disable_px, 802 sanity(nonvar(CL)), \+(t_l:into_form_code), 803 \+(t_l:mpred_already_in_file_expansion(CL)), 804 \+((get_functor(CL,F),expanded_already_functor(F))), 805 mpred_db_type(CL,_),!. 806 807:- thread_local(t_l:mpred_module_expansion/1).
816mpred_use_module(M):- \+ atom(M),!. 817mpred_use_module(M):- atom(M),quietly_must(atom(M)),retractall(baseKB:mpred_skipped_module(M)),show_call(why,asserta_if_new(t_l:mpred_module_expansion(M))). 818 819% ================================================================================ 820% DETECT PREDS THAT NEED SPECIAL STORAGE 821% ================================================================================
828mpred_may_expand:-loading_source_file(_F),get_lang(pfc). 829mpred_may_expand:-loading_source_file(_F),get_lang(mpred). 830mpred_may_expand:-quietly_must(loading_module(M)),mpred_may_expand_module(M),!,mpred_expand_inside_file_anyways.
839mpred_may_expand_module(M):-baseKB:mpred_skipped_module(M),!,fail. 840mpred_may_expand_module(M):-module_property(M,file(F)),check_how_virtualize_file(heads,F). 841mpred_may_expand_module(M):- t_l:mpred_module_expansion(M),!. 842mpred_may_expand_module(_):- t_l:mpred_module_expansion(*),!.
851mpred_expand_inside_file_anyways:- loading_source_file(F),!,mpred_expand_inside_file_anyways(F).
860mpred_expand_inside_file_anyways(F):- var(F),!,loading_source_file(F),nonvar(F),mpred_expand_inside_file_anyways(F). 861mpred_expand_inside_file_anyways(F):- check_how_virtualize_file(heads,F), !. 862mpred_expand_inside_file_anyways(F):- t_l:loading_mpred_file(_,F),!. 863mpred_expand_inside_file_anyways(F):- check_how_virtualize_file(heads,F),quietly_must(loading_module(M);source_module(M)), 864 (M=user; \+ baseKB:mpred_skipped_module(M)),!.
873was_exported_content(I,CALL,'$si$':'$was_imported_kb_content$'(I,CALL)). 874 875:- thread_local(t_l:mpred_term_expansion_ok/0). 876:- thread_local(t_l:mpred_already_inside_file_expansion/1). 877 878:- assert_if_new(t_l:mpred_term_expansion_ok).
889baseKBmpred_provide_clauses(_H,_B,_What):- fail.
898show_interesting_cl(_Dir,_). 899show_interesting_cl(Dir,P):- loading_source_file(File),get_file_type(File,Type), 900 ((nonvar(Dir),functor(Dir,Type,_))->true;dmsg_pretty(Type:cl_assert(Dir,P))). 901 902:- meta_predicate(cl_assert( , )).
910cl_assert(kif(Dir),P):- show_if_debug(must_det_l(( show_interesting_cl(kif(Dir),P),call(call,kif_process,P)))),!. 911cl_assert(Dir,P):- show_interesting_cl(Dir,P),ain(P),!. 912cl_assert(pl,P):- !, show_if_debug(must_det_l((source_location(F,_L), '$compile_aux_clauses'(P,F)))). 913cl_assert(_Code,P):- !, show_if_debug(ain(P)). 914 915:- meta_predicate(call_file_command( , , , )). 916%call_file_command(_,cl_assert(pl,OO),OO,_):-!,show_interesting_cl(pl,OO). 917 918 919get_original_term_src(Orig):- nb_current('$orig_term',Orig),!. 920get_original_term_src(Orig):- nb_current('$term',Orig),Orig\==[],!. 921get_original_term_src(true). 922 923make_file_command(IN,(:- CALL),OUT):- nonvar(CALL),!, must(make_file_command(IN,CALL,OUT)). 924 925make_file_command(_IN,cl_assert(pfc(WHY),PFC),(NEWSOURCE:-true)):- 926 current_why(CY), 927 CMD = mpred_ain(PFC,(CY,ax)), 928 get_original_term_src(Orig), 929 was_exported_content(Orig,WHY,NEWSOURCE),!, 930 show_call(quietly_must((CMD))). 931 932 933make_file_command(_IN,cl_assert(pfc(WHY),PFC),[(:- CMD), NEWSOURCE]):- 934 current_why(CY), 935 CMD = ain(PFC,CY), 936 get_original_term_src(Orig), 937 was_exported_content(Orig,WHY,NEWSOURCE),!. 938 939 940make_file_command(IN,cl_assert(WHY,NEWISH),OUT):- get_lang(kif),if_defined(is_kif_clause(NEWISH)),!,must(make_file_command(IN,cl_assert(kif(WHY),NEWISH),OUT)). 941make_file_command(_IN,cl_assert(WHY,CMD2),SET):- 942 get_original_term_src(Orig), 943 was_exported_content(Orig,WHY,NEWSOURCE),list_to_set([(:- cl_assert(WHY,CMD2)), NEWSOURCE],SET). 944 945make_file_command(IN,cl_assert(WHY,CMD2),[CMD2, (:- cl_assert(WHY,CMD2)), NEWSOURCE ]):- was_exported_content(WHY,IN,NEWSOURCE),!. 946 947make_file_command(_IN,'$si$':'$was_imported_kb_content$'(IN2,WHY),'$si$':'$was_imported_kb_content$'(IN2,WHY)).
954call_file_command(I,CALL,OO,O):- call_file_command0(I,CALL,OO,O),dmsg_pretty(call_file_command(I,CALL,OO,O)). 955 956call_file_command0(I,cl_assert(OTHER,OO),OO,I):- get_lang(kif),if_defined(is_kif_clause(OO)),!,call_file_command(I,cl_assert(kif(OTHER),OO),OO,I). 957call_file_command0(I,CALL,[(:- quietly_must(CALL2)),(:- quietly_must(CALL)),OO],(:-CALL2)):- CALL2\=@=CALL, 958 was_exported_content(I,CALL,OO),!. 959call_file_command0(I,CALL,[(:- quietly_must(CALL)),OO],(:-CALL)):- was_exported_content(I,CALL,OO),!. 960% call_file_command(I,CALL,OO,O):- (current_predicate(_,CALL) -> ((quietly_must(call(CALL)),was_exported_content(I,CALL,OO))); OO=[O,:-CALL]).
968mpred_implode_varnames([]):-!. 969mpred_implode_varnames([N=V|Vs]):-V='$VAR'(N),mpred_implode_varnames(Vs),!. 970 971% mudKeyword("happy","happy") -> mudKeyword(vHappy,"happy"). 972 973% quietly_must skip already loaded modules (we remember these so make/0 doesnt dbreak)
981mpred_maybe_skip(M):- t_l:mpred_module_expansion(N),N==M,!. 982mpred_maybe_skip(M):- asserta_if_new(baseKB:mpred_skipped_module(M)),!. 983% :- forall(current_module(M),mpred_maybe_skip(M)). 984 985 986:- dynamic(lmcache:mpred_directive_value/3).
996expanded_already_functor('$si$':'$was_imported_kb_content$'). 997expanded_already_functor(was_enabled). 998expanded_already_functor(_:NV):-nonvar(NV),!,expanded_already_functor(NV). 999 1000% expanded_already_functor(F):-mpred_prop(M,F,A,pl). 1001 1002 1003%:- thread_local is_compiling_clause/0. 1004%is_compiling:-is_compiling_clause;compiling. 1005 1006%:- kb_local(user:term_expansion/2). 1007%:- kb_local(system:goal_expansion/2). 1008% system:goal_expansion(A,_B):-fail,quietly((source_module(M),(M=mpred_sanity;M=user;M=system),if_defined(pmsg(M:goal_expansion(A)),format(user_output /*e*/,'~N% ~q~n',M:goal_expansion(A))))),fail. 1009% user:term_expansion(A,_B):-fail,quietly((source_module(M),(M=mpred_sanity;M=user;M=system),if_defined(pmsg(M:term_expansion(A)),format(user_output /*e*/,'~N% ~q~n',M:term_expansion(A))))),fail. 1010 1011% system:goal_expansion(N,mpred_prove_neg(P)):-fail,mpred_from_negation_plus_holder(N,P),show_failure(why,mpred_isa(P,pfcControlled)).
1020mpred_ops:- prolog_load_context(module,M),setup_module_ops(M).
1027pfc_dcg:- file_begin(pfc), op(400,yfx,('\\\\')),op(1200,xfx,('-->>')),op(1200,xfx,('--*>>')), op(1200,xfx,('<<--')). 1028 1029:- thread_local(mpred_ain_loaded/0). 1030 1031 1032 1033 1034 1035 1036% ======================================== 1037% begin/end_transform_mpreds 1038% ======================================== 1039:- dynamic(t_l:current_lang/1). 1040 1041 1042:- dynamic(always_expand_on_thread/1). 1043:- thread_local is_compiling_clause/0.
1049is_compiling:-is_compiling_clause;compiling. 1050 1051:- style_check(+discontiguous). 1052:- style_check(-discontiguous). 1053 1054 1055unload_this_file(File):- 1056 ignore(( 1057 source_file(M:P,File), 1058 copy_term(P,PP), 1059 clause(M:,_,Ref), 1060 clause_property(Ref,file(File)), 1061 erase(Ref), 1062 \+ clause(M:,_,_), 1063 abolish(M:PP),fail)), 1064 unload_file(File). 1065 1066 1067:- export(clause_count/2). 1068:- module_transparent(clause_count/2). 1069 1070clause_count(Mask,N):- arg(_,Mask,Var),nonvar(Var),!, 1071 flag(clause_count,_,0), 1072 ignore((current_module(M),clause(M:,_,Ref), 1073 (clause_property(Ref,module(MW))->must(ignore((M==MW)));true), 1074 flag(clause_count,X,X+1),fail)),flag(clause_count,N,0),!. 1075clause_count(Mask,N):- 1076 flag(clause_count,_,0), 1077 ignore((current_module(M), M\==rdf_rewrite, 1078 \+ predicate_property(M:Mask,imported_from(_)), 1079 predicate_property(M:Mask,number_of_clauses(Count)), 1080 flag(clause_count,X,X), must(ignore(sanity((X=0,nop(clause_count(Mask,M,Count)))))), 1081 flag(clause_count,X,X+Count),fail)),flag(clause_count,N,0),!. 1082 1083 1084:- dynamic(checked_clause_count/1). 1085 1086checked_clause_count(isa(_,_)). 1087checked_clause_count(~(_)). 1088checked_clause_count(prologBuiltin(_)). 1089checked_clause_count(prologHybrid(_)). 1090checked_clause_count(hybrid_support(_)). 1091checked_clause_count(pfcControlled(_)). 1092checked_clause_count(t(_,_)). 1093checked_clause_count(t(_,_,_)). 1094checked_clause_count(arity(_,_)). 1095checked_clause_count(argIsa(_,_,_)). 1096checked_clause_count(argQuotedIsa(_,_,_)). 1097checked_clause_count(tCol(_)). 1098checked_clause_count(resultIsa(_,_)). 1099checked_clause_count(genls(_,_)). 1100checked_clause_count((_ <- _)). 1101checked_clause_count((_ ==> _)). 1102checked_clause_count((_ <==> _)). 1103%checked_clause_count(spft(_,_,ax)). 1104checked_clause_count(agent_command(_,_)). 1105checked_clause_count(how_virtualize_file(_,_,_)). 1106 1107 1108:- dynamic(lmcache:last_clause_count/2). 1109 1110check_clause_count(MMask):- swc, 1111 strip_module(MMask,_,Mask), 1112 clause_count(Mask,N), 1113 (retract(lmcache:last_clause_count(Mask,Was)) -> true ; Was=0), 1114 (assert(lmcache:last_clause_count(Mask,N)), 1115 Diff is N - Was), 1116 (Diff ==0 -> true; 1117 (Diff == -1 -> true; 1118 ((Diff<0 ,Change is N/abs(Diff ), Change>0.20) 1119 -> trace_or_throw_ex(bad_count(Mask,(Was --> N))) ; dmsg_pretty(good_count(Mask,(Was --> N)))))). 1120 1121check_clause_counts:-!. 1122check_clause_counts:- flag_call(runtime_speed==true),!. 1123check_clause_counts:- current_prolog_flag(unsafe_speedups , true) ,!. 1124check_clause_counts:- ((forall(checked_clause_count(Mask),sanity(check_clause_count(Mask))))),fail. 1125check_clause_counts. 1126:- sexport(check_clause_counts/0).
1134mpred_begin:-file_begin(pfc).
1142dyn_begin:-file_begin(dyn).
1150dyn_end:-file_end(dyn).
1159enable_mpred_expansion :-
1160 set_prolog_flag(mpred_te,true),
1161 (( \+ (t_l:disable_px, false )) -> true ;
1162 (retractall(t_l:disable_px),
1163 call_on_eof(asserta_if_new(t_l:disable_px)))).
1172disable_mpred_expansion:- 1173 set_prolog_flag(mpred_te,false), 1174 (( t_l:disable_px) -> true ; 1175 assert_until_eof(t_l:disable_px)). 1176 1177 1178 1179predicate_is_undefined_fa(F,A):- 1180 call(( 1181 ( \+ current_predicate(_:F/A)), 1182 functor(P,F,A), 1183 (( 1184 \+ predicate_property(_:P,exported), 1185 \+ predicate_property(_:P,static), 1186 \+ predicate_property(_:P,dynamic))))). 1187 1188 1189:-multifile(baseKB:locked_baseKB/0). 1190:-dynamic(baseKB:locked_baseKB/0). 1191 1192simplify_language_name(W,W2):-var(W),!,W2=W. 1193simplify_language_name(mpred,pfc). 1194simplify_language_name(plmoo,pfc). 1195simplify_language_name(prolog,pl). 1196simplify_language_name(code,pl). 1197simplify_language_name(W,W).
1204file_begin(WIn):- simplify_language_name(WIn,pfc), !, begin_pfc,op_lang(WIn). 1205file_begin(WIn):- 1206 simplify_language_name(WIn,Else), 1207 must_det_l(( 1208 op_lang(WIn), 1209 set_file_lang(Else), 1210 disable_mpred_expansion)),!, 1211 sanity(get_lang(Else)).
1218begin_pfc:- 1219 must_det_l(( 1220 mpred_ops, 1221 op_lang(pfc), 1222 set_file_lang(pfc), 1223 fileAssertMt(Mt), 1224 set_fileAssertMt(Mt), 1225 enable_mpred_expansion)),!, 1226 sanity(get_lang(pfc)). 1227 1228:- nodebug(logicmoo(loader)). 1229 1230set_file_lang(W):- 1231 source_location(File,_Line), 1232 assert_if_new(lmcache:mpred_directive_value(File,language,W)), 1233 (W==pfc-> (set_how_virtualize_file(heads,File)) ; true),!, 1234 set_lang(W). 1235set_file_lang(W):- 1236 forall((prolog_load_context(file,Source);which_file(Source);prolog_load_context(source,Source)), 1237 ignore(( % \+ lmcache:mpred_directive_value(Source,language,W), 1238 source_location(File,Line), 1239 (W==pfc-> (set_how_virtualize_file(heads,File)) ; true), 1240 prolog_load_context(module,Module), 1241 INFO = source_location_lang(Module,File,Line,Source,W), 1242 asserta(lmconf:), 1243 decache_file_type(Source), 1244 debug(logicmoo(loader),'~N~p~n',[INFO]), 1245 % (Source = '/root/lib/swipl/pack/logicmoo_base/prolog/logicmoo/pfc/system_common.pfc.pl'-> must(W=pfc);true), 1246 assert(lmcache:mpred_directive_value(Source,language,W))))), 1247 sanity(get_lang(W)), 1248 asserta_until_eof(t_l:current_lang(W)),!. 1249 1250 1251set_lang(WIn):- simplify_language_name(WIn,W),!, 1252 set_prolog_flag_until_eof(dialect_pfc,W), 1253 asserta_until_eof(t_l:current_lang(W)).
1260file_end(WIn):-
1261 must_det((
1262 simplify_language_name(WIn,W),
1263 loading_source_file(ISource),decache_file_type(ISource),
1264 ignore(show_failure(retract(lmcache:mpred_directive_value(ISource,language,W)))))),!.
1272get_lang(LANG):- ((get_lang0(LANGVAR)->same_language(LANG,LANGVAR))). 1273 1274same_language(LANG,LANGVAR):- 1275 simplify_language_name(LANGVAR,LANGVARS), 1276 simplify_language_name(LANG,LANGS),!, 1277 LANGS=LANGVARS. 1278 1279:-thread_local( t_l:current_lang/1). 1280 1281get_lang0(W) :- t_l:current_lang(W),!. 1282get_lang0(W) :- prolog_load_context(file,Source)->lmcache:mpred_directive_value(Source,language,W). 1283get_lang0(W) :- prolog_load_context(source,Source)->lmcache:mpred_directive_value(Source,language,W). 1284get_lang0(W) :- loading_source_file(Source)->lmcache:mpred_directive_value(Source,language,W). 1285get_lang0(W):- current_prolog_flag(dialect_pfc,W). 1286get_lang0(pfc):- loading_source_file(F)->check_how_virtualize_file(heads,F),!. 1287get_lang0(pl). 1288 1289 1290 1291 1292 1293:- meta_predicate(expand_term_to_load_calls( , )). 1294:- meta_predicate(mpred_term_expansion( , )). 1295 1296% Specific "*SYNTAX*" based default 1297 1298% :- ensure_loaded(logicmoo(snark/common_logic_sexpr)).
1307op_alias(OP,OTHER):-retractall(current_op_alias(OP,_)),asserta(current_op_alias(OP,OTHER)).
1315op_lang(_LANG):- !.
1324get_op_alias(OP,ALIAS):-current_op_alias(OP,ALIAS). 1325get_op_alias(OP,ALIAS):-get_lang(LANG),lang_op_alias(LANG,OP,ALIAS). 1326 1327% current_op_alias((<==>),dup(impliesF,(','))). 1328% current_op_alias((=>),==>). 1329% current_op_alias((not),(~)).
1337:- dynamic(current_op_alias/2). 1338current_op_alias( not(:-),~(:-)). 1339current_op_alias( (:-),(:-)).
1347lang_op_alias(pfc,(<==>),(<==>)). 1348lang_op_alias(pfc,(==>),==>). 1349% lang_op_alias(pfc,(<=>),(<==>)). 1350lang_op_alias(pfc,(<=),(<-)). 1351lang_op_alias(pfc,(<-),(<-)). 1352lang_op_alias(pfc,(not),(~)). 1353lang_op_alias(pfc,not(:-),~(:-)). 1354lang_op_alias(pfc,(:-),(:-)). 1355% lang_op_alias(pfc,(A=B),{(A=B)}). 1356% kif 1357lang_op_alias(kif,(<==>),(<==>)). 1358lang_op_alias(kif,(==>),==>). 1359lang_op_alias(kif,(not),(~)). 1360lang_op_alias(kif,(~),(~)). 1361lang_op_alias(kif,(=>),(if)). 1362lang_op_alias(kif,(<=>),(iff)). 1363lang_op_alias(kif, not(':-'),~('<-')). 1364lang_op_alias(kif,(:-),rev(==>)). 1365% cyc 1366lang_op_alias(cyc,(<==>),(<==>)). 1367lang_op_alias(cyc,(==>),==>). 1368lang_op_alias(cyc,(implies),(if)). 1369lang_op_alias(cyc,(equiv),(iff)). 1370lang_op_alias(cyc, not(':-'),~('<-')). 1371lang_op_alias(cyc,(:-),rev(==>)). 1372% prolog - pl 1373lang_op_alias(pl,(<==>),(<==>)). 1374lang_op_alias(pl,(==>),==>). 1375lang_op_alias(pl, not(':-'),~('<-')). 1376lang_op_alias(pl,(:-),(:-)). 1377lang_op_alias(pl,(<=),(<=)). 1378lang_op_alias(pl,(<-),(<-)).
1387transform_opers(LANG,PFCM,PFCO):- quietly((locally(t_l:current_lang(LANG),((transitive_lc(transform_opers_0,PFCM,PFC),!, subst(PFC,(not),(~),PFCO)))))). 1388 1389:- op(1199,fx,('==>')). 1390:- op(1190,xfx,('::::')). 1391:- op(1180,xfx,('==>')). 1392:- op(1170,xfx,'<==>'). 1393:- op(1160,xfx,('<-')). 1394:- op(1150,xfx,'=>'). 1395:- op(1140,xfx,'<='). 1396:- op(1130,xfx,'<=>'). 1397:- op(1100,fx,('nesc')). 1398:- op(300,fx,'-'). 1399:- op(300,fx,'~'). 1400:- op(600,yfx,'&'). 1401:- op(600,yfx,'v'). 1402:- op(1075,xfx,'<-'). 1403:- op(350,xfx,'xor').
1412transform_opers_0(AIS,AIS):- if_defined(leave_as_is(AIS)),!. 1413transform_opers_0((A/B),C):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]),conjoin_op((/),AA,BB,C). 1414transform_opers_0(PFCM,PFC):- transform_opers_1(PFCM,PFC),!. 1415transform_opers_0(=>(A),=>(C)):- !, transform_opers_0(A,C). 1416transform_opers_0(==>(A),==>(C)):- !, transform_opers_0(A,C). 1417transform_opers_0(~(A),~(C)):- !, transform_opers_0(A,C). 1418transform_opers_0(nesc(A),nesc(C)):- !, transform_opers_0(A,C). 1419transform_opers_0({A},{A}):-!. 1420transform_opers_0((A;B),C):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]),conjoin_op((;),AA,BB,C). 1421transform_opers_0((B=>A),(BB=>AA)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1422transform_opers_0((B==>A),(BB==>AA)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1423transform_opers_0(<=(A,B),<=(AA,BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1424transform_opers_0((A<-B),(AA<-BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1425transform_opers_0((A<=>B),(AA<=>BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1426transform_opers_0((A<==>B),(AA<==>BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1427transform_opers_0((A<==>B),(AA<==>BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1428transform_opers_0(if(A,B),if(AA,BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1429transform_opers_0(iff(A,B),iff(AA,BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1430transform_opers_0(implies(A,B),implies(AA,BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1431transform_opers_0(equiv(A,B),equiv(AA,BB)):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]). 1432transform_opers_0((B:-A),OUTPUT):- !, must_maplist(transform_opers_0,[A,B],[AA,BB]),=((BB:-AA),OUTPUT). 1433transform_opers_0(not(A),OUTPUT):- !, must_maplist(transform_opers_0,[A],[AA]),=(not(AA),OUTPUT). 1434transform_opers_0(not(A),C):- !, transform_opers_0(~(A),C). 1435%transform_opers_0((A),OUTPUT):- !, must_maplist(transform_opers_0,[A],[AA]),=((AA),OUTPUT). 1436transform_opers_0(O,O).
1445transform_opers_1(not(AB),(BBAA)):- get_op_alias(not(OP),rev(OTHER)), atom(OP),atom(OTHER),AB=..[OP,A,B],!, must_maplist(transform_opers_0,[A,B],[AA,BB]),BBAA=..[OTHER,BB,AA]. 1446transform_opers_1(not(AB),(BOTH)):- get_op_alias(not(OP),dup(OTHER,AND)),atom(OTHER), atom(OP),AB=..[OP,A,B],!, must_maplist(transform_opers_0,[A,B],[AA,BB]),AABB=..[OTHER,AA,BB],BBAA=..[OTHER,BB,AA],BOTH=..[AND,AABB,BBAA]. 1447transform_opers_1(not(AB),~(NEG)):- get_op_alias(not(OP),~(OTHER)),atom(OTHER), atom(OP),AB=..[OP|ABL],!, must_maplist(transform_opers_0,ABL,AABB),NEG=..[OTHER|AABB]. 1448transform_opers_1(not(AB),(RESULT)):- get_op_alias(not(OP),(OTHER)), atom(OP),atom(OTHER),AB=..[OP|ABL],!, must_maplist(transform_opers_0,ABL,AABB),RESULT=..[OTHER|AABB]. 1449transform_opers_1((AB),(BBAA)):- get_op_alias(OP,rev(OTHER)), atom(OP),atom(OTHER),AB=..[OP,A,B],!, must_maplist(transform_opers_0,[A,B],[AA,BB]),BBAA=..[OTHER,BB,AA]. 1450transform_opers_1((AB),(BOTH)):- get_op_alias(OP,dup(OTHER,AND)), atom(OP),atom(OTHER),AB=..[OP,A,B],!, must_maplist(transform_opers_0,[A,B],[AA,BB]),AABB=..[OTHER,AA,BB],BBAA=..[OTHER,BB,AA],BOTH=..[AND,AABB,BBAA]. 1451transform_opers_1((AB),(RESULT)):- get_op_alias(OP,(OTHER)),atom(OP), atom(OTHER),AB=..[OP|ABL],!, must_maplist(transform_opers_0,ABL,AABB),RESULT=..[OTHER|AABB]. 1452transform_opers_1(OP,OTHER):- get_op_alias(OPO,OTHER),OPO=OP,!.
1462to_prolog_xform(O,OO):-
1463 ( is_directive_form(O) -> (OO = O); OO= (:- cl_assert(pfc(to_prolog_xform),O))),!.
1471is_directive_form((:-(V))):-!,nonvar(V). 1472is_directive_form((?-(V))):-!,nonvar(V). 1473is_directive_form(List):-is_list(List),!,member(E,List),is_directive_form(E). 1474%is_directive_form((:-(V,_))):-!,nonvar(V). 1475%is_directive_form(_:(:-(V,_))):-!,nonvar(V).
1485expand_in_mpred_kb_module(I,O):- is_directive_form(I),quietly_must(I=O),!. 1486expand_in_mpred_kb_module(I,OO):- quietly_must(expand_term_to_load_calls(I,O)),!,quietly_must(to_prolog_xform(O,OO)).
1493expand_term_to_load_calls(I,OO):- if_defined(convert_if_kif_string(I,O)),!, 1494 quietly_must(expand_term_to_load_calls(O,OO)). 1495 1496expand_term_to_load_calls(PI,OO):- PI=..[P,I], if_defined(convert_if_kif_string(I,O)),!, 1497 quietly_must((PO=..[P,O], expand_term_to_load_calls(PO,OO))). 1498 1499expand_term_to_load_calls((H:-B),O):- B==true,!,quietly_must(expand_term_to_load_calls(H,O)). 1500 1501expand_term_to_load_calls(HB,O):- strip_module(HB,M,(H:-B)),B==true,(H:-B)\=@=HB,!,quietly_must(expand_term_to_load_calls(M:H,O)). 1502 1503expand_term_to_load_calls(C,O):- fail, quietly((get_lang(LANG),show_success(transform_opers,(quietly_must(transform_opers(LANG,C,M)),C\=@=M)))),!, 1504 quietly_must(expand_term_to_load_calls(M,O)). 1505 1506expand_term_to_load_calls(C,O):- fail,quietly(show_success(load_calls,(compound(C), get_op_alias(OP,ALIAS), 1507 atom(OP),atom(ALIAS),C=..[OP|ARGS]))),CC=..[ALIAS|ARGS],quietly_must(loop_check(must_expand_term_to_command(CC,O))),!. 1508 1509expand_term_to_load_calls(C,O):- must_expand_term_to_command(C,O)->quietly_must(is_directive_form(O)). 1510expand_term_to_load_calls(O,(:-compile_clause(O))):- get_lang(pl),!.
1517must_expand_term_to_command(C,O):- mpred_term_expansion(C,O),C\=@=O,quietly_must(is_directive_form(O)),!. 1518must_expand_term_to_command(O,(:-compile_clause(O))):- get_lang(pl),!.
1525mpred_term_expansion(((P==>Q)),(:- cl_assert(pfc(fwc),(P==>Q)))). 1526mpred_term_expansion((('=>'(Q))),(:- cl_assert(pfc(fwc),('=>'(Q))))). 1527mpred_term_expansion((('==>'(Q))),(:- cl_assert(pfc(fwc),('=>'(Q))))). 1528mpred_term_expansion(((nesc(Q))),(:- cl_assert(pfc(fwc),nesc(Q)))). 1529mpred_term_expansion(~(Q),(:- cl_assert(pfc(fwc),~(Q)))). 1530mpred_term_expansion(('<-'(P,Q)),(:- cl_assert(pfc(bwc),('<-'(P,Q))))). 1531mpred_term_expansion(('<==>'(P,Q)),(:- cl_assert(pfc(bwc),(P<==>Q)))). 1532mpred_term_expansion((<=(Q,P)),(:- cl_assert(pfc(bwc),(Q<-P)))). 1533 1534 1535 1536mpred_term_expansion(if(P,Q),(:- cl_assert(kif(fwc),if(P,Q)))). 1537mpred_term_expansion(iff(P,Q),(:- cl_assert(kif(fwc),iff(P,Q)))). 1538mpred_term_expansion(not(Q),(:- cl_assert(kif(fwc),not(Q)))). 1539mpred_term_expansion(exists(V,PQ),(:- cl_assert(kif(fwc),exists(V,PQ)))). 1540mpred_term_expansion(forall(V,PQ),(:- cl_assert(kif(fwc),forall(V,PQ)))). 1541mpred_term_expansion(all(V,PQ),(:- cl_assert(kif(fwc),all(V,PQ)))). 1542 1543 1544% maybe reverse some rules? 1545%mpred_term_expansion((P==>Q),(:- cl_assert(pfc(fwc),('<-'(Q,P))))). % speed-up attempt 1546mpred_term_expansion((RuleName :::: Rule),(:- cl_assert(named_rule,(RuleName :::: Rule)))). 1547mpred_term_expansion((==>(P)),(:- cl_assert(pfc(fwc),(==>(P))))). 1548mpred_term_expansion(Fact,(:- cl_assert(pl,Fact))):- get_functor(Fact,F,_A),(a(prologDynamic,F)). 1549mpred_term_expansion(Fact,Output):- load_file_term_to_command_1(_Dir,Fact,C),quietly_must(mpred_term_expansion(C,Output)),!.
1556 load_file_term_to_command_1(pfc(act),(H:-(Chain,B)),(PFC==>PH)):-cwc, is_action_body(Chain),pl_to_mpred_syntax((Chain,B),PFC),pl_to_mpred_syntax_h(H,PH). 1557 load_file_term_to_command_1(pfc(fwc),(H:-(Chain,B)),(PFC==>PH)):-cwc, is_fc_body(Chain),pl_to_mpred_syntax((Chain,B),PFC),pl_to_mpred_syntax_h(H,PH),can_be_dynamic(PH),make_dynamic(PH). 1558 load_file_term_to_command_1(pfc(bwc),(H:-(Chain,B)),(PH<-PFC)):-cwc, is_bc_body(Chain),pl_to_mpred_syntax((Chain,B),PFC),pl_to_mpred_syntax_h(H,PH),can_be_dynamic(PH),make_dynamic(PH). 1559 load_file_term_to_command_1(pfc(awc),(H:-(Chain,B)),(H:-(Chain,B))):-cwc, has_body_atom(awc,Chain),!. 1560 load_file_term_to_command_1(pfc(zwc),(H:-(Chain,B)),(H:-(Chain,B))):-cwc, has_body_atom(zwc,Chain),!. 1561 1562 1563mpred_term_expansion(Fact,Output):- load_file_term_to_command_1b(_Dir,Fact,C),!,quietly_must(mpred_term_expansion(C,Output)),!.
1569 load_file_term_to_command_1b(pfc(act),(H:-Chain,B),(H==>{(Chain,B)})):-cwc, is_action_body(Chain),make_dynamic(H). 1570 load_file_term_to_command_1b(pfc(fwc),(H:-Chain,B),((Chain,B)==>H)):-cwc, is_fc_body(Chain),make_dynamic(H). 1571 load_file_term_to_command_1b(pfc(bwc),(H:-Chain,B),(H<-(Chain,B))):-cwc, is_bc_body(Chain),make_dynamic(H). 1572 1573 1574% mpred_term_expansion((H:-Chain,B),(H:-(B))):- atom(Chain),is_code_body(Chain),!,quietly_must(atom(Chain)),make_dynamic(H). 1575 1576 1577 1578 1579mpred_term_expansion_by_storage_type(_M,'$si$':'$was_imported_kb_content$'(_,_),pl):-!. 1580mpred_term_expansion_by_storage_type(M,( \+ C ),HOW):- nonvar(C), !,mpred_term_expansion_by_storage_type(M,C,HOW). 1581mpred_term_expansion_by_storage_type(_M,C,compile_clause(static)):- is_static_predicate(C). 1582%mpred_term_expansion_by_storage_type(_M,C,requires_storage(WHY)):- requires_storage(C,WHY),!. 1583mpred_term_expansion_by_storage_type(_M,C,must_compile_special):- must_compile_special_clause(C),t_l:mpred_already_inside_file_expansion(C). 1584 1585 1586mpred_term_expansion(Fact,Fact):- get_functor(Fact,F,_A),(a(prologDynamic,F)),!. 1587mpred_term_expansion(Fact,(:- ((cl_assert(Dir,Fact))))):- show_success(mpred_term_expansion_by_pred_class(Dir,Fact,_Output)),!. 1588 1589mpred_term_expansion(MC,(:- cl_assert(ct(How),MC))):- fail, strip_module(MC,M,C),quietly(mpred_rule_hb(C,H,_B)), 1590 (mpred_term_expansion_by_storage_type(M,H,How)->true;(C \= (_:-_),mpred_term_expansion_by_storage_type(M,C,How))),!. 1591 1592 1593mpred_term_expansion((Fact:- BODY),(:- ((cl_assert(Dir,Fact:- BODY))))):- nonvar(Fact), 1594 mpred_term_expansion_by_pred_class(Dir,Fact,_Output),!. 1595 1596mpred_term_expansion((M:Fact:- BODY),(:- ((cl_assert(Dir,M:Fact:- BODY))))):- nonvar(Fact), 1597 mpred_term_expansion_by_pred_class(Dir,Fact,_Output),!.
1604 mpred_term_expansion_by_pred_class(_,Fact,Output):- get_functor(Fact,F,_A),lookup_u(prologOnly(F)),Output='$si$':'$was_imported_kb_content$'(Fact,pfcControlled(F)),!,fail. 1605 mpred_term_expansion_by_pred_class(pfc(pred_type),Fact,Output):- get_functor(Fact,F,_A),lookup_u(ttRelationType(F)),Output='$si$':'$was_imported_kb_content$'(Fact,ttRelationType(F)),!. 1606 mpred_term_expansion_by_pred_class(pfc(func_decl),Fact,Output):- get_functor(Fact,F,_A),lookup_u(functorDeclares(F)),Output='$si$':'$was_imported_kb_content$'(Fact,functorDeclares(F)),!. 1607 mpred_term_expansion_by_pred_class(pfc(macro_head),Fact,Output):- get_functor(Fact,F,_A),lookup_u(functorIsMacro(F)),Output='$si$':'$was_imported_kb_content$'(Fact,functorIsMacro(F)),!. 1608 mpred_term_expansion_by_pred_class(pfc(mpred_ctrl),Fact,Output):- get_functor(Fact,F,_A),lookup_u(pfcControlled(F)),Output='$si$':'$was_imported_kb_content$'(Fact,pfcControlled(F)),!. 1609 mpred_term_expansion_by_pred_class(pfc(hybrid),Fact,Output):- get_functor(Fact,F,_A),lookup_u(prologHybrid(F)),Output='$si$':'$was_imported_kb_content$'(Fact,pfcControlled(F)),!. 1610 mpred_term_expansion_by_pred_class(pfc(pl),Fact,Output):- get_functor(Fact,F,_A),(a(prologDynamic,F)),Output='$si$':'$was_imported_kb_content$'(Fact,pfcControlled(F)),!. 1611 % mpred_term_expansion_by_pred_class(pfc(in_mpred_kb_module),Fact,Output):- in_mpred_kb_module,Output=Fact,!. 1612 1613 1614% Specific "*FILE*" based default 1615mpred_term_expansion(Fact,(:- ((cl_assert(dyn(get_lang(dyn)),Fact))))):- get_lang(dyn),!. 1616mpred_term_expansion(Fact,(:- ((cl_assert(kif(get_lang(kif)),Fact))))):- get_lang(kif),!. 1617%mpred_term_expansion(Fact,(:- ((cl_assert(pfc(in_mpred_kb_module),Fact))))):- in_mpred_kb_module,!. 1618%mpred_term_expansion(Fact,(:- ((cl_assert(pfc(get_lang(pl)),Fact))))):- get_lang(pl),!. 1619mpred_term_expansion(Fact,Fact):- get_lang(pl),!. 1620%mpred_term_expansion(Fact,(:- ((cl_assert(pfc(get_lang(pfc)),Fact))))):- get_lang(pfc),!. 1621 1622/* 1623mpred_term_expansion(Fact,(:- ((cl_assert(pfc(expand_file),Fact))))):- 1624 quietly(mpred_expand_inside_file_anyways(F)),!,_Output='$si$':'$was_imported_kb_content$'(Fact,mpred_expand_inside_file_anyways(F)),!. 1625*/
1634can_be_dynamic(H):- predicate_property(H,dynamic),!. 1635can_be_dynamic( \+ H):- nonvar(H), predicate_property(H,dynamic),!. 1636can_be_dynamic(H):- \+ is_static_predicate(H), \+ predicate_property(H,static), \+ predicate_property(H,meta_predicate(_)).
1645pl_to_mpred_syntax_h(A,PFC_A):- quietly_must(pl_to_mpred_syntax0(A,PFC_A)),!, PFC_A \= '{}'(_).
1653pl_to_mpred_syntax(A,PFC_A):- quietly_must(pl_to_mpred_syntax0(A,PFC_A)),!.
1662pl_to_mpred_syntax0(A,A):-is_ftVar(A),!. 1663pl_to_mpred_syntax0((A,B),PFC):-!,pl_to_mpred_syntax(A,PFC_A),pl_to_mpred_syntax(B,PFC_B),conjoin_body(PFC_A,PFC_B,PFC). 1664pl_to_mpred_syntax0(pfc(A),A):-!. 1665pl_to_mpred_syntax0(A,{A}):-!.
1673conjoin_body({H},{BB},{C}):-conjoin_body(H,BB,C). 1674conjoin_body({H},({BB},D),O):-conjoin_body(H,BB,C),conjoin_body({C},D,O). 1675conjoin_body(H,(BB,D),O):-conjoin_body(H,BB,C),conjoin_body(C,D,O). 1676conjoin_body(H,BB,C):-conjoin(H,BB,C).
1683stream_pos(File:LineNo):-loading_source_file(File),current_input(S),stream_property(S, position(Position)), !,stream_position_data(line_count, Position, LineNo),!.
1692compile_clause(CL):- quietly_must((make_dynamic(CL),assertz_if_new(CL),!,clause_asserted(CL))).
1701make_dynamic((H:-_)):- sanity(nonvar(H)),!,must(make_dynamic(H)). 1702make_dynamic(M:(H:-_)):- sanity(nonvar(H)),!,must(make_dynamic(M:H)). 1703make_dynamic(C):- loop_check(make_dynamic_ilc(C),trace_or_throw_ex(looped_make_dynamic(C))). 1704 1705make_dynamic_ilc(baseKB:C):- predicate_property(baseKB:C, dynamic),!. 1706% make_dynamic_ilc(C):- predicate_property(C, dynamic). 1707make_dynamic_ilc(C):- % trace_or_throw_ex(make_dynamic_ilc(C)), 1708 compound(C),strip_module(C,MIn,_),get_functor(C,F,A),quietly_must(F\=='$VAR'), 1709 (\+ a(mtHybrid,MIn) -> must(defaultAssertMt(M)) ; MIn =M), 1710 functor(P,F,A), 1711 1712 ( \+predicate_property(M:P,_) -> kb_local(M:F/A) ; 1713 (predicate_property(M:P,dynamic)->true;dynamic_safe(M:P))),!, 1714 kb_local(M:F/A), 1715 quietly_must((predicate_property(M:P,dynamic))). 1716 1717% once(baseKB:mpred_is_impl_file(F);asserta(baseKB:mpred_is_impl_file(F))). 1718 1719%user:goal_expansion(G,OUT):- \+ t_l:disable_px, G\=isa(_,_),(use_was_isa(G,I,C)),!,to_isa_form(I,C,OUT). 1720%user:term_expansion(G,OUT):- \+ t_l:disable_px, quietly(use_was_isa(G,I,C)),!,to_isa_form(I,C,OUT). 1721%user:term_expansion(I,O):- \+ t_l:disable_px, t_l:consulting_sources, locally_hide(t_l:consulting_sources,ain(I)),O=true. 1722 1723 1724 1725% :-set_prolog_flag(allow_variable_name_as_functor,true). 1726 1727% :- source_location(S,_),forall(loading_source_file(H,S),ignore(( \+predicate_property(M:H,built_in), functor(H,F,A),M:module_transparent(F/A),M:export(F/A)))). 1728 1729 1730 1731%:- user:use_module(library(shlib)). 1732%:- user:use_module(library(operators)). 1733 1734:- source_location(F,_),(set_how_virtualize_file(false,F)). 1735 1736% filetypes 1737% 1738% pfc - all terms are sent to ain/1 (the the execeptions previously defined) 1739% pl - all terms are sent to compile_clause/1 (the the execeptions previously defined) 1740% prolog - all terms are sent to compile_clause/1 (even ones defined conflictingly) 1741% dyn - all terms are sent to ain/1 (even ones defined conflictingly) 1742 1743:- thread_local(t_l:pretend_loading_file/1). 1744 1745 1746:- dynamic(baseKB:never_reload_file/1).
1755load_language_file(Name0):-
1756 forall(filematch_ext('qlf',Name0,Name),
1757 once((dmsg_pretty(load_language_file(Name0->Name)),
1758 locally([set_prolog_flag(subclause_expansion,false),
1759 set_prolog_flag(read_attvars,false),
1760 (t_l:disable_px),
1761 (user:term_expansion(_,_):-!,fail),
1762 (user:term_expansion(_,_,_,_):-!,fail),
1763 (user:goal_expansion(_,_):-!,fail),
1764 (user:goal_expansion(_,_,_,_):-!,fail),
1765 (system:term_expansion(_,_):-!,fail),
1766 (system:term_expansion(_,_,_,_):-!,fail),
1767 (system:goal_expansion(_,_,_,_):-!,fail),
1768 (system:goal_expansion(_,_):-!,fail)],
1769 gripe_time(1,(baseKB:load_files([Name],[qcompile(part),if(not_loaded)])))
1770 ->asserta(baseKB:never_reload_file(Name));retract(baseKB:never_reload_file(Name)))))),!.
1778disable_mpreds_in_current_file:- loading_source_file(F),show_call(why,asserta((t_l:disable_px:-loading_source_file(F),!))). 1779 1780 1781:- /**/ export(with_mpred_expansions/1). 1782:- meta_predicate(with_mpred_expansions( )).
1790with_mpred_expansions(Goal):- 1791 locally_hide(tlbugger:no_buggery_tl, 1792 locally_hide(t_l:disable_px,Goal)). 1793 1794:- /**/ export(ensure_loaded_no_mpreds/1). 1795:- meta_predicate(ensure_loaded_no_mpreds( )).
1803ensure_loaded_no_mpreds(M:F):- 1804 with_delayed_chaining(forall(must_locate_file(F,L),((set_how_virtualize_file(false,L)),M:ensure_loaded(M:L)))). 1805 1806:- meta_predicate(with_delayed_chaining( )).
1811with_delayed_chaining(Goal):- 1812 locally(tlbugger:no_buggery_tl, 1813 locally(t_l:disable_px,Goal)). 1814:- export(with_delayed_chaining/1). 1815:- system:import(with_delayed_chaining/1).
1823use_was_isa(G,I,C):-call((current_predicate(_,_:mpred_types_loaded/0),if_defined(was_isa(G,I,C)))).
1832current_context_module(Ctx):-quietly((loading_module(Ctx))),!. 1833current_context_module(Ctx):-quietly((source_context_module(Ctx))). 1834 1835% ======================================== 1836% register_module_type/end_module_type 1837% ======================================== 1838%:- was_module_transparent(baseKB:register_module_type/1).
1846register_module_type(Type):-current_context_module(CM),register_module_type(CM,Type).
1854:- multifile(baseKB:registered_module_type/2). 1855register_module_type(CM,Types):-is_list(Types),!,forall(member(T,Types),register_module_type(CM,T)). 1856register_module_type(CM,Type):-asserta_new(baseKB:registered_module_type(CM,Type)). 1857 1858:- /**/ export(end_module_type/2).
1866end_module_type(Type):-current_context_module(CM),end_module_type(CM,Type).
1874end_module_type(CM,Type):-retractall(baseKB:registered_module_type(CM,Type)). 1875 1876 1877 1878:- export(declare_load_dbase/1).
1886declare_load_dbase(Spec):- forall(no_repeats(File,must_locate_file(Spec,File)), 1887 show_call(why,(set_how_virtualize_file(heads,File)))). 1888 1889% :- /**/ export((is_compiling_sourcecode/1)).
1897is_compiling_sourcecode:-is_compiling,!. 1898is_compiling_sourcecode:-compiling, current_input(X),not((stream_property(X,file_no(0)))),prolog_load_context(source,F),\+((t_l:loading_mpred_file(_,_))),F=user,!. 1899is_compiling_sourcecode:-compiling,dmsg_pretty(system_compiling),!. 1900 1901:- /**/ export(load_mpred_files/0).
1909load_mpred_files :- 1910 forall((baseKB:how_virtualize_file(Heads,File,_),false\==Heads,bodies\==Heads), 1911 baseKB:ensure_mpred_file_loaded(File)). 1912 1913 1914% ======================================================= 1915:- meta_predicate show_load_call( ). 1916show_load_call(C):- must(on_x_debug(show_call(why,C))). 1917 1918 1919 1920:- dynamic(baseKB:loaded_file_world_time/3). 1921:- meta_predicate(baseKB:loaded_file_world_time( , , )). 1922:- meta_predicate(get_last_time_file( , , )).
1930get_last_time_file(FileIn,World,LastTime):- absolute_file_name(FileIn,File),FileIn\==File,!,get_last_time_file(File,World,LastTime). 1931get_last_time_file(File,World,LastTime):- baseKB:loaded_file_world_time(File,World,LastTime),!. 1932get_last_time_file(File,_, LoadTime):- source_file_property(File, modified(LoadTime)). 1933get_last_time_file(_,_,0.0). 1934 1935:- meta_predicate(load_init_world( , )).
1943load_init_world(World,File):- 1944 locally_hide(baseKB:use_cyc_database, 1945 ( world_clear(World), 1946 retractall(baseKB:loaded_file_world_time(_,_,_)), 1947 time_call(ensure_mpred_file_loaded(File)),!, 1948 time_call(finish_processing_world))). 1949 1950 1951:- meta_predicate(ensure_mpred_file_loaded( )). 1952 1953 1954 1955/****** 1956 1957% :- meta_predicate(ensure_mpred_file_loaded(:)). 1958 1959:- meta_predicate ensure_mpred_file_loaded(:,+). 1960 1961 1962ensure_mpred_file_loaded(M:F0,List):-!, 1963 must_locate_file(M:F0,F), % scope_settings expand(true),register(false), 1964 % 'format'(user_error ,'% ~q + ~q -> ~q.~n',[M,F0,F]), 1965 load_files([F],[if(not_loaded), must_be_module(true)|List]). 1966 %load_files(F,[redefine_module(false),if(not_loaded),silent(false),exported(true),must_be_module(true)|List]). 1967ensure_mpred_file_loaded(M:F0,List):- 1968 must_locate_file(M:F0,F), % scope_settings 1969 'format'(user_error ,'% load_mpred_file_M ~q.~n',[M=must_locate_file(F0,F)]), 1970 load_files([F],[redefine_module(false),module(M),expand(true),if(not_loaded),exported(true),register(false),silent(false),must_be_module(true)|List]). 1971 1972******/
1978:- meta_predicate(ensure_mpred_file_loaded( )). 1979 1980% ensure_mpred_file_loaded(MFileIn):- baseKB:ensure_loaded(MFileIn),!. 1981ensure_mpred_file_loaded(MFileIn):- strip_module(MFileIn,M,_), 1982 forall((must_locate_file(MFileIn,File), 1983 needs_load_or_reload_file(File)), 1984 (set_how_virtualize_file(heads,File), 1985 force_reload_mpred_file(M:File))). 1986 1987needs_load_or_reload_file(File) :- \+ source_file_property(File, _),!. 1988needs_load_or_reload_file(File) :- 1989 source_file_property(Source, modified(Time)), 1990 \+ source_file_property(Source, included_in(_,_)), 1991 Time > 0.0, % See source_file/1 1992 ( source_file_property(Source, derived_from(File, LoadTime)) 1993 -> true 1994 ; File = Source, 1995 LoadTime = Time 1996 ), 1997 ( catch(time_file(File, Modified), _, fail), 1998 Modified - LoadTime > 0.001 % (*) 1999 -> true 2000 ; source_file_property(Source, includes(Included, IncLoadTime)), 2001 catch(time_file(Included, Modified), _, fail), 2002 Modified - IncLoadTime > 0.001 % (*) 2003 -> true 2004 ). 2005 2006old_mpred_ensure_loaded(M,File):- 2007 must_det_l((set_how_virtualize_file(heads,File),time_file(File,FileTime),!, 2008 get_last_time_file(File,_World,LastLoadTime), 2009 (FileTime \== LastLoadTime -> force_reload_mpred_file(M:File); M:ensure_loaded(File)))). 2010 2011:- meta_predicate(force_reload_mpred_file( )). 2012 2013:- meta_predicate(ensure_mpred_file_loaded( , )).
2021ensure_mpred_file_loaded(World,FileIn):-
2022 with_umt(World,ensure_mpred_file_loaded(FileIn)).
2031must_locate_file(FileIn,File):- must(maybe_locate_file(FileIn,File)). 2032 2033maybe_locate_file(FileIn,File):- 2034 no_repeats(File, quietly(filematch_ext(['','mpred','ocl','moo','plmoo','pl','plt','pro','p','pl.in','pfc','pfct'],FileIn,File))).
2046force_reload_mpred_file(MFileIn):-
2047 strip_module(MFileIn,M,FileIn),
2048 (FileIn==MFileIn->defaultAssertMt(World);World=M),
2049 quietly_must(force_reload_mpred_file(World,FileIn)).
2059%force_reload_mpred_file(World,MFileIn):- must(World:consult(MFileIn)),!. 2060force_reload_mpred_file(World,MFileIn):- 2061 without_varname_scan(force_reload_mpred_file2(World,MFileIn)).
2068force_reload_mpred_file2(World,MFileIn):- 2069 time_file(MFileIn,NewTime), 2070 system:retractall(baseKB:loaded_file_world_time(MFileIn,World,_)), 2071 system:assert(baseKB:loaded_file_world_time(MFileIn,World,NewTime)), 2072 must(World:consult(MFileIn)),!. 2073 2074force_reload_mpred_file2(WorldIn,MFileIn):- 2075 sanity(call_u(baseKB:mtHybrid(WorldIn))), 2076 must(call_u(baseKB:mtHybrid(WorldIn)->World=WorldIn;defaultAssertMt(World))), 2077 strip_module(MFileIn,_MaybeNewModule,_), 2078 NewModule = World, 2079 with_source_module(NewModule,(( 2080 % NewModule:ensure_loaded(logicmoo(mpred/mpred_userkb)), 2081 forall(must_locate_file(MFileIn,File), 2082 must_det_l(( 2083 sanity(\+ check_how_virtualize_file(false,File) ), 2084 once(show_success(prolog_load_file,defaultAssertMt(DBASE));DBASE=NewModule), 2085 sanity(exists_file(File)), 2086 sanity((true,defaultAssertMt(World))), 2087 nop(mpred_remove_file_support(File)), 2088 (set_how_virtualize_file(heads,File)), 2089 quietly_must(time_file(File,NewTime)), 2090 retractall(baseKB:loaded_file_world_time(File,World,_)), 2091 system:assert(baseKB:loaded_file_world_time(File,World,NewTime)), DBASE = DBASE, 2092 locally_hide(t_l:disable_px, 2093 locally(set_prolog_flag(subclause_expansion,true), 2094 locally(set_prolog_flag(mpred_te,true), 2095 show_call((with_source_module(NewModule,load_files(NewModule:File, [module(NewModule)]))))))), 2096 must(force_reload_mpred_file3(File,World)) 2097 )))))). 2098 2099force_reload_mpred_file3(File,World):- 2100 catch((locally(t_l:loading_mpred_file(World,File), 2101 load_mpred_on_file_end(World,File))), 2102 Error, 2103 (dmsg_pretty(error(Error,File)),retractall(baseKB:loaded_mpred_file(World,File)), 2104 retractall(baseKB:loaded_file_world_time(File,World,_AnyTime)))). 2105 2106 2107:- dynamic(baseKB:loaded_mpred_file/2).
2113:- export(load_mpred_on_file_end/2). 2114load_mpred_on_file_end(World,File):- 2115 sanity(atom(File)), 2116 asserta_new(baseKB:loaded_mpred_file(World,File)), 2117 must(signal_eof(File)),!.
2124finish_processing_world :-
2125 load_mpred_files,
2126 loop_check(locally(t_l:agenda_slow_op_do_prereqs,doall(finish_processing_dbase)),true).
2135loader_side_effect_verify_only(I,Supposed):-
2136 sanity(var(Supposed)),
2137 push_predicates(t_l:side_effect_buffer/3,STATE),
2138 prolog_load_context(module,M),
2139 mpred_expander_now_physically(M,I,Supposed),
2140 get_source_ref1(Why),
2141 collect_expansions(Why,I,Actual),
2142 convert_side_effect(suppose(Supposed),S),
2143 conjoin(S, Actual,ActualSupposed),
2144 conjuncts_to_list(ActualSupposed,Readable),
2145 system:assert(t_l:actual_side_effect(I,Readable)),
2146 pop_predicates(t_l:side_effect_buffer/3,STATE),!.
2155loader_side_effect_capture_only(I,ActualSupposed):- 2156 sanity(var(ActualSupposed)), 2157 push_predicates(t_l:side_effect_buffer/3,STATE), 2158 prolog_load_context(module,M), 2159 mpred_expander_now_physically(M,I,Supposed), 2160 get_source_ref1(Why), 2161 collect_expansions(Why,I,Actual), 2162 conjoin(Actual,Supposed,ActualSupposed), 2163 pop_predicates(t_l:side_effect_buffer/3,STATE),!. 2164 2165 2166with_assert_buffer(G,List):- 2167 sanity(var(List)), 2168 push_predicates(t_l:side_effect_buffer/3,STATE), 2169 locally(t_l:use_side_effect_buffer,(call_u(G),mpred_run)), 2170 findall(Tell,(retract(t_l:side_effect_buffer(OP, Data, _Why)),convert_as_tell(OP,Data,Tell)),List), 2171 pop_predicates(t_l:side_effect_buffer/3,STATE),!. 2172 2173convert_as_tell(_P,Data,_Tell):- must_be(nonvar,Data),fail. 2174convert_as_tell(OP,M:Data,Tell):-M==baseKB,!,convert_as_tell(OP,Data,Tell). 2175convert_as_tell(OP,Data,Tell):- is_assert_op(OP),!,Tell=Data. 2176convert_as_tell(OP,Data,call(OP,Data)). 2177 2178is_assert_op(OP):-must_be(callable,OP),fail. 2179is_assert_op(call(OP,_)):-!,is_assert_op(OP),!. 2180is_assert_op(db_op_call(OP,_)):-!,is_assert_op(OP),!. 2181is_assert_op(asserta). 2182is_assert_op(assertz). 2183is_assert_op(assert).
2190collect_expansions(_Why,I,I):- \+ t_l:side_effect_buffer(_Op,_Data,_),!. 2191collect_expansions(NWhy,_I, TODO):- findall(ReproduceSWhy, 2192 ( retract(t_l:side_effect_buffer(Op, Data, Why)), 2193 must_det_l(convert_side_effect(Op, Data,Reproduce)), 2194 quietly_must(simplify_why_r(Reproduce,Why,NWhy,ReproduceSWhy))), TODOs), 2195 must_det_l( list_to_conjuncts(TODOs,TODO)).
2204simplify_why_r(Reproduce,Why,NWhy, Reproduce):- Why==NWhy, !. 2205simplify_why_r(Reproduce,Why,_,Reproduce:SWhy):-simplify_why(Why,SWhy),!. 2206 2207% aliases 2208:- meta_predicate(convert_side_effect( , , )).
2217simplify_why(Why,SWhy):-var(Why),!,Why=SWhy. 2218simplify_why(Why:0,SWhy):-!,simplify_why(Why,SWhy). 2219simplify_why(Why:N,SWhy:N):-!,simplify_why(Why,SWhy). 2220simplify_why(Why,SWhy):- atom(Why),!,directory_file_path(_,SWhy,Why). 2221simplify_why(Why,Why).
2230convert_side_effect(M:C,A,SE):- Call=..[C,A],!,convert_side_effect(M:Call,SE). 2231convert_side_effect(C,A,SE):- Call=..[C,A],!,convert_side_effect(Call,SE).
2240convert_side_effect(suppose(OO), suppose(Result)):- convert_side_effect_0a(OO,Result),!. 2241convert_side_effect(I,OO):-convert_side_effect_0c(I,O),((O=(N-_V),number(N))->OO=O;OO=O),!.
2250convert_side_effect_0a(asserta(Data), ( a(DataR))):-convert_side_effect_0a(Data,DataR). 2251convert_side_effect_0a(assertz(Data), ( z(DataR))):-convert_side_effect_0a(Data,DataR). 2252convert_side_effect_0a(retract(Data), ( r(DataR))):-convert_side_effect_0a(Data,DataR). 2253convert_side_effect_0a(cl_assert(Why,Data), ( cl_assert(Why,DataR))):-convert_side_effect_0a(Data,DataR). 2254convert_side_effect_0a(attvar_op(How,Data),Reproduce):-!,convert_side_effect(How,Data,Reproduce),!. 2255convert_side_effect_0a(I,O):-convert_side_effect_0b(I,O),!. 2256convert_side_effect_0a(I,I).
2265convert_side_effect_0b((OpData:-TRUE),Result):- is_true(TRUE),!,convert_side_effect_0a(OpData,Result),!. 2266convert_side_effect_0b(suppose(OpData),Result):-!,convert_side_effect_0a(OpData,Result),!. 2267convert_side_effect_0b(baseKB:OpData,Reproduce):- !,convert_side_effect_0a(OpData,Reproduce),!. 2268convert_side_effect_0b(( :- OpData),( ( (Result)))):-!,convert_side_effect_0a(OpData,Result),!. 2269convert_side_effect_0b('$si$':'$was_imported_kb_content$'(_, OO),Result):-!,convert_side_effect_0a(OO,Result),!. 2270convert_side_effect_0b(asserta_if_new(Data),Result):-!,convert_side_effect_0a(asserta(Data),Result). 2271convert_side_effect_0b(assertz_if_new(Data),Result):-!,convert_side_effect_0a(assertz(Data),Result). 2272convert_side_effect_0b(assert_if_new(Data),Result):-!,convert_side_effect_0a(assertz(Data),Result). 2273convert_side_effect_0b(assert(Data),Result):-!,convert_side_effect_0a(assertz(Data),Result). 2274 2275 2276% unused_assertion('$was_imported_kb_content$'([], A)):-atom(A).
2283convert_side_effect_0c(OpData,Reproduce):- convert_side_effect_0b(OpData,Reproduce),!. 2284convert_side_effect_0c(OpData,Reproduce):- show_success(convert_side_effect,convert_side_effect_buggy(OpData,Reproduce)),!. 2285convert_side_effect_0c(OpData,Reproduce):- trace_or_throw_ex(unknown_convert_side_effect(OpData,Reproduce)),!. 2286 2287% todo
2295convert_side_effect_buggy(erase(clause(H,B,_Ref)), (e(HB))):- convert_side_effect_0a((H:-B),HB). 2296convert_side_effect_buggy(retract(Data), (r(DataR))):-convert_side_effect_0a(Data,DataR). 2297convert_side_effect_buggy(retractall(Data), (c(DataR))):-convert_side_effect_0a(Data,DataR). 2298convert_side_effect_buggy(OpData,( ( error_op(OpData)))):-dmsg_pretty(unknown_convert_side_effect(OpData)).
2308clear_predicates(M:H):- forall(M:clause(H,_,Ref),erase(Ref)).
2316push_predicates(M:F/A,STATE):- functor(H,F,A),findall((H:-B), (M:clause(H,B,Ref),erase(Ref)), STATE).
2324pop_predicates(M:F/A,STATE):- functor(H,F,A),forall(member((H:-B),STATE),M:assert((H:-B))). 2325 2326 2327 2328 2329:- fixup_exports. 2330 2331mpred_loader_file. 2332 2333%system:term_expansion(end_of_file,_):-must(check_clause_counts),fail. 2334%system:term_expansion(EOF,_):-end_of_file==EOF,must(check_clause_counts),fail.