3% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/common_logic/common_logic_boxlog.pl
    4%:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )).
    5:- module(common_logic_utils,
    6          [ ]).    7
    8:- include(library('logicmoo/common_logic/common_header.pi')).    9%:- endif.
   10%% delistify_last_arg( ?Arg, :PredMiddleArgs, ?Last) is det.
   11%
   12% Delistify Last Argument.
   13%
   14
   15delistify_last_arg(Arg,Pred,Last):- no_repeats(Last,must(delistify_last_arg0(Arg,Pred,Last))).
   16
   17delistify_last_arg0(Arg,Pred,Last):- is_list(Arg),!,member(E,Arg),must(delistify_last_arg0(E,Pred,Last)).
   18delistify_last_arg0(Arg,M:Pred,Last):- Pred=..[F|ARGS],append([Arg|ARGS],[NEW],NARGS),NEWCALL=..[F|NARGS],quietly(M:NEWCALL),!,member_ele(NEW,Last).
   19delistify_last_arg0(Arg,Pred,Last):- Pred=..[F|ARGS],append([Arg|ARGS],[NEW],NARGS),NEWCALL=..[F|NARGS],quietly(NEWCALL),!,member_ele(NEW,Last).
 is_kif_clause(?Var) is det
If Is A Knowledge Interchange Format Rule.
   27is_kif_clause(Var):- is_ftVar(Var),!,fail.
   28is_kif_clause(R):- kif_hook(R),!.
   29is_kif_clause(R):- is_clif(R),!.
 kif_hook(+TermC) is det
Knowledge Interchange Format Hook.
   38kif_hook(C):- not_ftCompound(C),!,fail.
   39kif_hook(_H :- _):-  !,fail.
   40kif_hook(_H <- _):-  !,fail.
   41kif_hook(_H --> _):- !,fail.
   42kif_hook(_ ==> _):-  !,fail.
   43kif_hook(_ <==> _):- !,fail.
   44% uncommenting these next 3 lines may break sanity_birdt test
   45
   46 kif_hook(  ~(H)):- !,nonvar(H),kif_hook(H).
   47 kif_hook(  \+ H):- !,nonvar(H),kif_hook(H).
   48 kif_hook(not(H)):- !,nonvar(H),kif_hook(H).
   49
   50kif_hook( naf(H)):- !,nonvar(H),kif_hook(H).
   51kif_hook(In):- kif_hook_skel(In).
   52kif_hook(C):- callable(C),functor(C,F,A),kif_hook(C,F,A).
   53
   54kif_hook(_,F,_):- atom_concat('sk',_,F),atom_concat(_,'Fn',F),!.
   55kif_hook(C,_,_):- leave_as_is(C),!,fail.
   56kif_hook(C,F,_):- is_sentence_functor(F),!,arg(_,C,E),kif_hook(E).
   57
   58: - fixup_exports.
 kif_hook_skel(+TermC) is det
Knowledge Interchange Format Hook Skelecton.
   65kif_hook_skel(forAll(_,_)).
   66kif_hook_skel(_=>_).
   67kif_hook_skel(_<=_).
   68kif_hook_skel(_<=>_).
   69kif_hook_skel((_ & _)).
   70kif_hook_skel((_ /\ _)).
   71kif_hook_skel((_ \/ _)).
   72kif_hook_skel((_ v _)).
   73kif_hook_skel(nesc(_)).
   74kif_hook_skel(poss(_)).
   75kif_hook_skel(cir(_)).
   76kif_hook_skel(all(_,_)).
   77kif_hook_skel(exactly(_,_,_)).
   78kif_hook_skel(atmost(_,_,_)).
   79kif_hook_skel(atleast(_,_,_)).
   80kif_hook_skel(quant(_,_,_)).
   81kif_hook_skel(exists(_,_)).
   82kif_hook_skel(if(_,_)).
   83kif_hook_skel(iff(_,_)).
   84kif_hook_skel(equiv(_,_)).
   85kif_hook_skel(implies(_,_)).
   86kif_hook_skel(CLIF):- is_clif(CLIF).
   87kif_hook_skel( ~(H)):- loop_check(kif_hook(H)).
   88kif_hook_skel( not(H)):- loop_check(kif_hook(H)).
   89kif_hook_skel( Compound):- arg(_,v(poss,nesc,until,always,release,cir),F),between(2,3,A),functor( Compound,F,A).
   90kif_hook_skel( Compound):- compound( Compound),!,functor(Compound,F,_),arg(_,v(and,or,xor),F).
   91kif_hook_skel( Compound):- var(Compound),!,arg(_,v(and,or,xor),F),between(1,12,A),functor( Compound,F,A).
   92
   93
   94
   95:- fixup_exports.