1:- module(common_logic_loader,
    2	  [load_clif/1,
    3           kif_process/1,
    4           kif_io/2,          
    5           kif_process/2,
    6           kif_read/3]).

common_logic_loader

% Provides interface for loading/interpretation of CLIF/KIF Files % % t/N % hybridRule/2 % % % Logicmoo Project PrologMUD: A MUD server written in Prolog % Maintainer: Douglas Miles % Dec 13, 2035 % */

   20:- meta_predicate
   21   % common_logic_snark
   22   kif_process(*,*),
   23   % common_logic_snark
   24   kif_process(*).   25   % common_logic_snark
   26
   27:- meta_predicate with_ext_translation(+,*,:).   28
   29
   30:- thread_local(t_l:kif_action_mode/1).   31:- asserta_if_new(t_l:kif_action_mode(tell)).   32
   33:- thread_local(t_l:kif_reader_mode/1).   34:- asserta_if_new(t_l:kif_reader_mode(lisp)).   35
   36:- if(exists_source(library(wam_cl/sreader))).   37:- use_module(library(wam_cl/sreader)).   38:- endif.   39
   40:- public(kif_io/0).
 kif_io is det
Knowledge Interchange Format.
   45kif_io:- current_input(In),current_output(Out),!,kif_io(In,Out).
   46
   47
   48load_clif(File):- 
   49  zotrace(absolute_file_name(File,Found,[extensions(['','.clif','.ikl','.kif','.lisp','.lbase','.pfc','.pl']),access(read),expand(true),solutions(all)])),
   50  exists_file(Found),!,
   51  % with_lisp_translation_cached(Found, = , nop).
   52  file_name_extension(_,Ext,Found), 
   53  with_ext_translation(Found, Ext, kif_process_ignore).
   54load_clif(File):- trace_or_throw(missing(load_clif(File))).
   55
   56with_ext_translation(Found,pl, Process):- !,process_script_file(Found,Process).
   57with_ext_translation(Found,pfc, Process):- !,process_script_file(Found,Process).
   58with_ext_translation(Found,_, Process):- with_lisp_translation(Found, Process).
   59
   60kif_process_ignore(P):-must(once(kif_process(P))).
   61must_kif_process(P):-must(once(kif_process(P))).
   62must_kif_process_after_rename(Sent):-  if_defined(sumo_to_pdkb(Sent,SentM),=(Sent,SentM)),must_kif_process(SentM).
   63
   64:- public(kif_process/1).   65
   66get_atom_or_kw(ModeIn,Mode):- trim_off_cll(':',ModeIn,Mode).
   67   trim_off_cll(Left,ModeIn,Mode):-atom_concat(Left,Mode,ModeIn),!.
   68   trim_off_cll(_,ModeIn,ModeIn).
 kif_process(:GoalAssert) is det
Knowledge Interchange Format Process.
   74kif_process(Var):- is_ftVar(Var),!,wdmsg(warn(var_kif_process(Var))).
   75% kif_process(Mode):- atom(Mode),set_kif_mode(Mode).
   76kif_process(List):- is_list(List),must(sexpr_sterm_to_pterm(List,Wff)),t_l:kif_action_mode(Mode),!,ignore(show_failure(kif_process(Mode,Wff))),!.
   77kif_process(Wff):- t_l:kif_action_mode(Mode),!,ignore(show_failure(kif_process(Mode,Wff))),!.
   78kif_process(Wff):- ignore(show_failure(kif_process(tell,Wff))),!.
   79
   80set_kif_mode(ModeIn):- ignore((atom(ModeIn),
   81  get_atom_or_kw(ModeIn,Mode),
   82  retractall(t_l:kif_action_mode(_)),
   83  asserta(t_l:kif_action_mode(Mode)),
   84  fmtl(t_l:kif_action_mode(Mode)))),!.
 kif_process(?Other, :GoalWff) is det
Knowledge Interchange Format Process.
   91kif_process(_,Var):- must_be(nonvar,Var),fail.
   92kif_process(_,'$COMMENT'([])):-!.
   93kif_process(_,'$COMMENT'([String])):-!, dmsg(String).
   94kif_process(_,'$COMMENT'(String)):-!, dmsg(String).
   95kif_process(_,'include'(String)):- !, load_clif(String).
   96kif_process(_,'dmsg'(String)):-!, dmsg(String).
   97kif_process(_,'wdmsg'(String)):-!, wdmsg(String).
   98kif_process(_,'kif-mode'(Mode)):- set_kif_mode(Mode).
   99kif_process(_,'kif_mode'(Mode)):- set_kif_mode(Mode).
  100
  101kif_process(kif_add,Wff):- !, show_failure(kif_add(Wff)).
  102kif_process(kif_ask,Wff):- !, show_failure(kif_ask(Wff)).
  103
  104kif_process(call_u,M:Wff):- !, show_call(call_u(M:Wff)).
  105kif_process(call_u,Wff):- !, show_call(call_u(Wff)).
  106
  107kif_process(_,end_of_file):- !,signal_eof(kif_process),!.
  108kif_process(_,_:EOF):- EOF == end_of_file,!,signal_eof(kif_process),!.
  109kif_process(_,':-'(Call)):- !, kif_process(call,Call).
  110kif_process(_,'?-'(Goal)):- !, kif_process(ask,Goal).
  111kif_process(_,'ask'(Wff)):- !, kif_process(ask,Wff).
  112kif_process(_,'tell'(Wff)):- !, kif_process(tell,Wff).
  113kif_process(OP,'forall'(Vars,Wff)):- !, kif_process(OP,'all'(Vars,Wff)).
  114kif_process(_,'set-kif-option'(ModeIn)):-!,get_atom_or_kw(ModeIn,Mode), dmsg('set-kif-option'(Mode)).
  115
  116kif_process(call,Was):- Was\=(_:_),!,prolog_load_context(module,Prev),kif_process(call,Prev:Was).
  117
  118kif_process(_,From:prolog):- !, with_umt(From,prolog),!.
  119
  120
  121
  122kif_process(call,Into:module(To,Exports)):- !,
  123  prolog_load_context(module,From),
  124  '$set_source_module'(To),
  125  maplist(To:export,Exports),
  126  maplist(From:import,Exports),
  127  maplist(Into:import,Exports),
  128  call_on_eof(kif_process,'$set_source_module'(From)).
  129
  130kif_process(_,Atom):- atom(Atom),current_predicate(Atom/0),!,kif_process(call_u,Atom).
  131kif_process(_,Atom):- atom(Atom),current_predicate(Atom/1),fail,!,set_kif_mode(Atom).
  132kif_process(call,Call):- !,kif_process(call_u,Call).
  133kif_process(tell,Call):- is_static_predicate(Call),!,kif_process(call_u,Call).
  134kif_process(tell,Wff):- !,kif_process(kif_add,Wff).
  135kif_process(ask,Wff):- !,kif_process(kif_ask,Wff).
  136kif_process(Other,Wff):- wdmsg(error(missing_kif_process(Other,Wff))),fail.
  137kif_process(Pred1,Wff):- current_predicate(Pred1/1),!,call(Pred1,Wff).
  138
  139
  140
  141%open_input(InS,InS):- is_stream(InS),!.
  142%open_input(string(InS),In):- text_to_string(InS,Str),string_codes(Str,Codes),open_chars_stream(Codes,In),!.
 kif_read(?InS, ?Wff, ?Vs) is det
Knowledge Interchange Format Read.
  149kif_read(In,Wff,Vs):- !, input_to_forms(In,Wff,Vs).
  150kif_read(In,Wff,Vs):- 
  151  (t_l:kif_reader_mode(lisp) ->
  152  without_must( catch(input_to_forms(In,Wff,Vs),E,(dmsg(E:kif_read_input_to_forms(In,Wff,Vs)),fail)))*-> true ;
  153      (catch(read_term(In,Wff,[module(user),double_quotes(string),variable_names(Vs)]),E,
  154                 (dmsg(E:kif_read_term_to_forms(In,Wff,Vs)),fail)))).
  155
  156%= ===== to test program =====-
  157% :- ensure_loaded(logicmoo(snark/common_logic_sexpr)).
  158
  159:- public(kif_io/2).  160:- assert_until_eof(t_l:canonicalize_types).
 kif_io(?InS, ?Out) is det
Knowledge Interchange Format Input/output.
  168kif_io(In,Out):-
  169   repeat,
  170      on_x_debug((
  171          once((t_l:kif_action_mode(Mode),write(Out,Mode),write(Out,'> '))),
  172          once(on_x_debug(kif_read(In,Wff,Vs))),
  173          once(on_x_debug((put_variable_names( Vs), portray_clause(Out,Wff,[variable_names(Vs),quoted(true)])))),
  174          on_x_debug(kif_process(Wff)),
  175           Wff == end_of_file)),!.
  176
  177
  178:- assert_until_eof(t_l:canonicalize_types).  179
  180
  181:- fixup_exports.