3:- module(mpred_terms,
    4          [ 
    5          any_to_number/2,
    6          is_ftText/1,
    7          any_to_value/2,
    8          atom_to_value/2
    9          ]).   10
   11:- include('mpred_header.pi').
   23:- export(any_to_number/2).
   28any_to_value(Var,Var):-var(Var),!.
   29any_to_value(V,Term):-atom(V),!,atom_to_value(V,Term).
   30any_to_value(A,V):-any_to_number(A,V).
   31any_to_value(A,A).
   38any_to_number(N,N):- number(N),!.
   39any_to_number(ftDiceFn(A,B,C),N):- ground(A),if_defined(roll_dice(A,B,C,N)),!.
   40any_to_number(A,N):-atom(A),atom_to_value(A,V),A\=V,any_to_number(V,N).
   41any_to_number(A,N):- catch(number_string(N,A),_,fail).
   47atom_to_value(V,Term):-not(atom(V)),!,any_to_value(V,Term).
   49atom_to_value(V,Term):- catch((read_term_from_atom(V,Term,[variable_names([])])),_,fail),!.
   51atom_to_value(V,ftDiceFn(T1,T2,+T3)):- atomic_list_concat_safe([D1,'d',D2,'+',D3],V), atom_to_value(D1,T1),atom_to_value(D2,T2),atom_to_value(D3,T3),!.
   52atom_to_value(V,ftDiceFn(T1,T2,-T3)):- atomic_list_concat_safe([D1,'d',D2,'-',D3],V), atom_to_value(D1,T1),atom_to_value(D2,T2),atom_to_value(D3,T3),!.
   60is_ftText(Arg):- string(Arg),!.
   61is_ftText(Arg):- \+ compound(Arg),!,fail.
   62is_ftText(Arg):- safe_functor(Arg,s,_),!.
   63is_ftText([Arg|_]):-string(Arg),!.
   64is_ftText(Arg):- is_ftVar(Arg),!,fail.
   65is_ftText(Arg):- text_to_string_safe(Arg,_),!.
   66is_ftText(Arg):- safe_functor(Arg,S,_), ereq(resultIsa(S,ftText)).
   67
   68:- kb_global(baseKB:ftText/1).   69:-ain(baseKB:(ftText(A):- !, if_defined(term_is_ft(A, ftText),is_ftText(A)),!)).   70
   74
   75:- was_export(inverse_args/2).
   83inverse_args([AR,GS],[GS,AR]):-!.
   84inverse_args([AR,G,S],[S,G,AR]):-!.
   85inverse_args([A,R,G,S],[S,R,G,A]):-!.
   86inverse_args([P,A,R,G,S],[S,A,R,G,P]):-!.
   87
   88:- was_export(same_vars/2).
   96same_vars(T1,T2):-term_variables(T1,V1),term_variables(T2,V2),!,V1==V2.
  105replace_arg(C,A,_VAR,_CC):-sanity((is_ftCompound(C),integer(A))),fail.
  106replace_arg((C:-B),A,VAR,(CC:-B)):-!,replace_arg(C,A,VAR,CC).
  107replace_arg(~ (C),A,VAR,~(CC)):-!,replace_arg(C,A,VAR,CC).
  108replace_arg( \+ (C),A,VAR,~(CC)):-!,replace_arg(C,A,VAR,CC).
  109replace_arg(M:(C),A,VAR,M:(CC)):-!,replace_arg(C,A,VAR,CC).
  110replace_arg(C,0,VAR,CC):-!, C=..[_|ARGS],CC=..[VAR|ARGS].
  111replace_arg(C,1,VAR,CC):-!, C=..[F,_|ARGS],CC=..[F,VAR|ARGS].
  112replace_arg(C,2,VAR,CC):-!, C=..[F,A,_|ARGS],CC=..[F,A,VAR|ARGS].
  113replace_arg(C,3,VAR,CC):-!, C=..[F,A,B,_|ARGS],CC=..[F,A,B,VAR|ARGS].
  115replace_arg(C,A,VAR,CC):- C=..FARGS,replace_nth_arglist(FARGS,A,VAR,FARGO),!,CC=..FARGO.
  116
  129replace_nth_arglist([],_,_,[]):- !.
  130replace_nth_arglist([_|ARGO],0,VAR,[VAR|ARGO]):- !.
  131replace_nth_arglist([T|FARGS],A,VAR,[T|FARGO]):- 
  132    A2 is A-1,replace_nth_arglist(FARGS,A2,VAR,FARGO).
  142replace_nth_ref([],_N,_OldVar,_NewVar,[]):- !,trace_or_throw_ex(missed_the_boat).
  143replace_nth_ref([OldVar|ARGS],1,OldVar,NewVar,[NewVar|ARGS]):- !.
  144replace_nth_ref([Carry|ARGS],Which,OldVar,NewVar,[Carry|NEWARGS]):- 
  145 Which1 is Which-1,
  146 replace_nth_ref(ARGS,Which1,OldVar,NewVar,NEWARGS),!.
  147
  148
  157update_value(OLD,NEW,NEXT):- var(NEW),!,trace_or_throw_ex(logicmoo_bug(update_value(OLD,NEW,NEXT))).
  158update_value(OLD,NEW,NEWV):- var(OLD),!,compute_value_no_dice(NEW,NEWV).
  159update_value(OLD,X,NEW):- is_list(OLD),!,list_update_op(OLD,X,NEW),!.
  160update_value(OLDI,+X,NEW):- compute_value(OLDI,OLD),number(OLD),catch(NEW is OLD + X,_,fail),!.
  161update_value(OLDI,-X,NEW):- compute_value(OLDI,OLD),number(OLD),catch(NEW is OLD - X,_,fail),!.
  162update_value(OLDI,X,NEW):- number(X),X<0,compute_value(OLDI,OLD),number(OLD),catch(NEW is OLD + X,_,fail),!.
  163update_value(_,NEW,NEWV):- compute_value_no_dice(NEW,NEWV),!.
  172flatten_append(First,Last,Out):-flatten([First],FirstF),flatten([Last],LastF),append(FirstF,LastF,Out),!.
  181list_update_op(OLDI,+X,NEW):-flatten_append(OLDI,X,NEW),!.
  182list_update_op(OLDI,-X,NEW):-flatten([OLDI],OLD),flatten([X],XX),!,list_difference_eq(OLD,XX,NEW),!.
  191compute_value_no_dice(NEW,NEW):- compound(NEW),functor_catch(NEW,ftDiceFn,_),!.
  192compute_value_no_dice(NEW,NEW):- compound(NEW),functor_catch(NEW,ftDice,_),!.
  193compute_value_no_dice(NEW,NEWV):-compute_value(NEW,NEWV).
  202compute_value(NEW,NEWV):-catch(NEWV is NEW,_,fail),!.
  203compute_value(NEW,NEWV):-catch(any_to_value(NEW,NEWV),_,fail),!.
  204compute_value(NEW,NEW).
  213insert_into(ARGS,0,Insert,[Insert|ARGS]):- !.
  214insert_into([Carry|ARGS],After,Insert,[Carry|NEWARGS]):- 
  215   After1 is After - 1,
  216   insert_into(ARGS,After1,Insert,NEWARGS).
  217
  218
  219
  223
  224
  225:- was_export(into_plist/2).  226
  233into_plist(In,Out):-into_plist_arities(2,12,In,Out).
  234
  235:- was_export(into_plist_arities/4).  236
  243into_plist_arities(Min,Max,PLIST,PLISTO):- var(PLIST),!,between(Min,Max,X),length(PLIST,X),PLISTO=PLIST.
  244into_plist_arities(_,_,[P|LIST],[P|LIST]):-var(P),!.
  245into_plist_arities(_,_,[(t)|PLIST],PLIST):-!.    246into_plist_arities(_,_,plist(P,LIST),[P|LIST]):-!.
  247into_plist_arities(_,_,Call,PLIST):- Call=..PLIST.   248
  249
  250
  258never_mpred_tcall(mpred_prop).
  259never_mpred_tcall(isa).
  260never_mpred_tcall(arity).
  261
  262
  263local_qh_mpred_prop(M,F,A,C):- call_u(mpred_prop(M,F,A,C)).
  264
  265
  267
  268
  269                   
  271
  272:- meta_predicate(if_result(0,0)).  273
  280if_result(TF,Call):-(TF->Call;true).
  281
  282
  283
  284
  292mpred_plist_t(P,LIST):-var(P),!,is_list(LIST),CALL=..[t,P|LIST],on_x_debug((CALL)).
  293mpred_plist_t(t,[P|LIST]):-!, mpred_plist_t(P,LIST).
  295mpred_plist_t(isa,[I,C]):-!,call(call,t,C,I).
  296mpred_plist_t(P,_):-never_mpred_tcall(P),!,fail.
  297mpred_plist_t(P,[L|IST]):-is_holds_true(P),!,mpred_plist_t(L,IST).
  298mpred_plist_t(P,LIST):-is_holds_false(P),!,call_u(mpred_f(LIST)).
  299mpred_plist_t(P,LIST):- CALL=..[t,P|LIST],on_x_debug(CALL).
  300
  301
  302:- meta_predicate(mpred_fa_call(?,?,0)).  303
  304
  305
  312mpred_fa_call(F,A,Call):- var(F),!,
  313 no_repeats(F,(clause_b(support_hilog(F,A));clause_b(arity(F,A)))), 
  314   once((F\==t, 
  315   \+ a(rtNotForUnboundPredicates,F),current_predicate(F,M:_OtherCall))),
  316    on_x_debug(M:Call).
  317mpred_fa_call(M:F,A,Call):- nonvar(M),!,mpred_fa_call(F,A,M:Call).
  318mpred_fa_call(F,_,Call):-F\==t,current_predicate(F,M:_OtherCall),!,M:Call.
  319
  320
  327mpred_fact_arity(F,A):- call_u(arity(F,A)),
  328  suggest_m(M),
  329  once(local_qh_mpred_prop(M,F,A,prologHybrid);
  330     local_qh_mpred_prop(M,F,A,pfcControlled);
  331     local_qh_mpred_prop(M,F,A,prologPTTP);
  332     local_qh_mpred_prop(M,F,A,prologKIF)),!.
  333
  334
  341prologHybridFact(G):- (var(G)->(mpred_fact_arity(F,A),safe_functor(G,F,A));true),into_mpred_form(G,M),!,no_repeats(call_u(M)).
  342
  343
  344
  345
  346
  347:- fixup_exports.
 
mpred_terms
% Provides a common set of operators in translation between the several logical languages % % Logicmoo Project PrologMUD: A MUD server written in Prolog % Maintainer: Douglas Miles % Dec 13, 2035 % */