1% ===================================================================
    2% File 'logicmoo_module_aiml_xpath.pl'
    3% Purpose: An Implementation in SWI-Prolog of AIML
    4% Maintainer: Douglas Miles
    5% Contact: $Author: dmiles $@users.sourceforge.net ;
    6% Version: 'logicmoo_module_aiml_xpath.pl' 1.0.0
    7% Revision:  $Revision: 1.7 $
    8% Revised At:   $Date: 2002/07/11 21:57:28 $
    9% ===================================================================
   10
   11%:-module()
   12%:-include('logicmoo_utils_header.pl'). %<?
   13%:- style_check(-singleton).
   14%%:- style_check(-discontiguous).
   15/*
   16:- if((current_prolog_flag(version,MMmmPP),MMmmPP<70000)).
   17:- style_check(-atom).
   18:- style_check(-string).
   19:- endif.
   20*/

   21
   22
   23:- nop(module(xpath_ctx,
   24 [addCtxValue/3,
   25 addScopeParent/2,
   26 attributeValue/5,
   27 checkNameValue/6,
   28 current_value/3,
   29 currentContext/2,
   30          pushAttributes/3,
   31
   32         /*get_ctx_frame_holder/4,
   33         get_ctx_holder/2,
   34         get_o_value/4,
   35                  */

   36 getCtxValueND/3,
   37 get_ctx_frame_holder/4,
   38 isValid/1,
   39 makeAllParams/4,
   40 
   41 peekAttributes/4,
   42 peekNameValue/5,
   43 popNameValue/4,
   44 replaceAttribute/5,
   45 setCtxValue/3,
   46 valuePresent/1,
   47 valuesMatch/3,
   48 withAttributes/3,
   49 withCurrentContext/1,
   50 withNamedContext/2])).
   51
   52% :-ensure_loaded(library('programk/logicmoo_module_aiml_memory.pl')).
   53
   54% ===============================================================================================
   55%    Context values API
   56% ===============================================================================================
   57pushAttributes(Ctx,Scope,List):-prolog_mustEach((prolog_mostly_ground(List),pushCtxFrame(Ctx,Scope,List),pushAttributes1(Ctx,Scope,List))),!.
   58
   59pushAttributes1(Ctx,Scope,[N=V|L]):-pushNameValue(Ctx,Scope,N,V),!,pushAttributes1(Ctx,Scope,L).
   60pushAttributes1(_Ctx,_Scope,[]).
   61pushAttributes1(_Ctx,_Scope,_AnyPushed):-!.
   62
   63peekAttributes(Ctx,SList,Scope,Results):-prolog_must(peekAttributes0(Ctx,SList,Scope,Results)).
   64peekAttributes0(Ctx,[Name|SList],Scope,[Name=Value|Results]):- peekNameValue(Ctx,Scope,Name,Value,'$error'),peekAttributes0(Ctx,SList,Scope,Results),!.
   65peekAttributes0(_Ctx,[],_Scope,[]):-!.
   66
   67%%%%TODO: use?%%%%%%% current_value(Ctx,Scope:Name,Value):-!,attributeValue(Ctx,Scope,Name,Value,'$error').
   68%%%%TODO: use?%%%%%%% current_value(Ctx,Name,Value):-attributeValue(Ctx,_,Name,Value,'$error').
   69current_value(Ctx,Name,Value):-current_value(Ctx,Name,Value,'$global_value').
   70current_value(Ctx,Name,Value,ElseVar):-peekNameValue(Ctx,_Scope,Name,Value,ElseVar).
   71
   72checkNameValue(Pred,Ctx,Scope,[Name],Value,Else):- nonvar(Name),!,checkNameValue(Pred,Ctx,Scope,Name,Value,Else).
   73checkNameValue(Pred,Ctx,Scope,Name,Value,Else):-aiml_notrace(( call(Pred,Ctx,Scope,Name,ValueVar,Else),!,checkValue(ValueVar),valuesMatch(Ctx,ValueVar,Value))),!. %%,atrace.
   74
   75peekNameValue(Ctx,Scope,Name,Value,Else):-nonvar(Value),!,checkNameValue(peekNameValue,Ctx,Scope,Name,Value,Else).
   76peekNameValue(Ctx,Scope,Name,Value,ElseVar):- locateNameValue(Ctx,Scope,Name,Value,'$first'(['$local_value','$global_value','$attribute_value',ElseVar])),!.
   77
   78/*
   79peekNameValue0(Ctx,Scope,Name,Value):-contextScopeTerm(Ctx,Scope,Term),arg_value(Term,Name,Value),!.
   80%%%peekNameValue0(Ctx,List,Name,Value):- nonvar(List),not(atom(List)),attributeValue(Ctx,List,Name,Value,'$failure'),!.
   81%%%%peekNameValue0(CtxI,_Scope,Name,Value):-getCtxValueND(CtxI,Name,Value).
   82peekNameValue0(Ctx,Scope,Name,Value):-is_list(Name),member(N0,Name),peekNameValue(Ctx,Scope,N0,Value,'$failure'),!.
   83peekNameValue0(CtxI,Scope,Name,Value):-dictNameKey(Scope,Name,Key),getCtxValueND(CtxI,Key,Value).
   84peekNameValue0(Ctx,Scope,Name,Value):-peekGlobalMem(Ctx,Scope,Name,Value).
   85peekNameValue0(CtxI,Scope,Name,Value):-var(Scope),!,peekAnyNameValue(CtxI,Scope,Name,Value).
   86peekNameValue0(CtxI,Scope,Name,Value):-getCtxValueND(CtxI,Scope:Name,Value).
   87peekNameValue0(Ctx,ATTRIBS,NameS,ValueO):- aiml_notrace((findAttributeValue(Ctx,ATTRIBS,NameS,ValueO,'$failure'))).
   88peekNameValue0(Ctx,XML,NameS,ValueO):- aiml_notrace((findTagValue(Ctx,XML,NameS,ValueO,'$failure'))).
   89peekNameValue0(_Ctx,CtxI,Name,Value):- getCtxValueND(CtxI,Name,Value).
   90peekNameValue0(Ctx,Scope,Name,Value):-lotrace((getIndexedValue(Ctx,Scope,Name,[],Value),checkAttribute(Scope,Name,Value))).
   91peekNameValue0(Ctx,Scope,Name,Value):-getInheritedStoredValue(Ctx,Scope,Name,Value),checkAttribute(Scope,Name,Value),atrace.
   92peekNameValue0(Ctx,ATTRIBS,NameS,ValueO):- compound(ATTRIBS),compound_or_list(ATTRIBS,LIST),member(E,LIST),prolog_must(nonvar(E)),attributeValue(Ctx,E,NameS,ValueO,'$failure').
   93
   94%%%peekAnyNameValue(Ctx,_Scope,Name,Value):-arg_value(Ctx,Name,Value),!.
   95%%peekAnyNameValue(CtxI,Scope,Name,Value):-prolog_extra_checks, member(Name,[withCategory]),!,dictNameKey(Scope,Name,Key),trace,prolog_must(getCtxValueND(CtxI,Key,Value)),dictNameKey(Scope,Name,Key).
   96%%peekAnyNameValue(Ctx,Scope,Name,Value):-atom(Name),getCtxValueND(Ctx,Scope,Name,Value).
   97peekNameValue0(CtxI,Scope,Name,Value):-nop(debugFmt(not(peekNameValue0(CtxI,Scope,Name,Value)))),!,fail.
   98*/

   99
  100local_value(Ctx,Scope,Name,Value):-contextScopeTerm(Ctx,Scope,Term),arg_value(Term,Name,Value).
  101local_value(CtxI,Scope,Name,Value):-dictNameKey(Scope,Name,Key),getCtxValueND(CtxI,Key,Value).
  102local_value(Ctx,Scope,Name,Value):-is_list(Name),!,member(N0,Name),local_value(Ctx,Scope,N0,Value).
  103local_value(Ctx,List,Name,Value):- nonvar(List),not(atom(List)),attributeValue(Ctx,List,Name,Value,'$failure').
  104%%local_value(Ctx,Scope,Name,Value):-attributeValue(Ctx,Scope,Name,ValueO,'$failure')
  105
  106
  107
  108arg_value(Ctx,Name,Value):-atomic(Name),!,Name==lastArg,!,arg_value_lastArg(Ctx,Value).
  109arg_value(Ctx,arg(N),Value):-integer(N),arg_value_ArgN(Ctx,N,Value).
  110arg_value_lastArg(Ctx,Value):-compound(Ctx),functor(Ctx,_F,A),arg(A,Ctx,Value),!.
  111arg_value_ArgN(Ctx,-1,Value):- !,current_value(Ctx,lastArg,Value),!.
  112arg_value_ArgN(Ctx,N,Value):-prolog_must(compound(Ctx)),arg(N,Ctx,Value),!.
  113
  114contextScopeTerm(Ctx,Scope,Term):- (Scope=Term;Ctx=Term),nonvar(Term).
  115
  116peekGlobalMem(Ctx,[],Name,Value):- !,peekGlobalMem(Ctx,user,Name,Value).
  117peekGlobalMem(_Ctx,[_=_|_],_Name,_Value):-!,fail.
  118peekGlobalMem(Ctx,Scope,Name,Value):- getInheritedStoredValue(Ctx,Scope,Name,Value),checkAttribute(Scope,Name,Value).
  119peekGlobalMem(Ctx,Scope,Name,Value):-ignore(Scope=user),getIndexedValue(Ctx,Scope,Name,[],Value),checkAttribute(Scope,Name,Value),!.%%trace.
  120
  121compound_or_list([ATT|RIBS],[ATT|RIBS]):-!.
  122compound_or_list(ATTRIBS,LIST):-ATTRIBS=..[_|LIST].
  123
  124
  125% ===============================================================================================
  126%    Value verification
  127% ===============================================================================================
  128
  129illegalValue(ValueVar):- ValueVar=['YourBot'],!.
  130
  131valuesMatch(_Ctx,V,V):-!.
  132valuesMatch(Ctx,V,A):-convertToMatchableCS(A,AA),convertToMatchableCS(V,VV),valuesMatch10(Ctx,VV,AA).
  133
  134
  135valuesMatch10(Ctx,V,A):-aiml_notrace(valuesMatch11(Ctx,V,A)),!.
  136valuesMatch10(Ctx,V,A):-ignorecase_literal(A,AA),ignorecase_literal(V,VV),!,valuesMatch11(Ctx,VV,AA),!.
  137
  138valuesMatch1(_Ctx,V,V).
  139valuesMatch1(_Ctx,V,A):- isStar0(V);isStar0(A).
  140valuesMatch1(Ctx,[V],A):-!,valuesMatch1(Ctx,V,A).
  141valuesMatch1(Ctx,V,[A]):-!,valuesMatch1(Ctx,V,A).
  142valuesMatch1(Ctx,V,A):-number(V),atom_number(VA,V),!,valuesMatch1(Ctx,A,VA).
  143valuesMatch1(_Ctx,V,A):-sameBinding(V,A).
  144
  145valuesMatch11(_Ctx,A,A).
  146valuesMatch11(Ctx,[V|VV],[A|AA]):-valuesMatch1(Ctx,V,A),!,valuesMatch11(Ctx,VV,AA).
  147
  148
  149valueMP(Var,M):- member(M, [var(Var), Var=missing, Var=[], Var=(*) ,  Var=('_') , Var=('OM') , (Var=(-(_))) ]),M,!.
  150%valueMP(Var,'$deleted'):-functor(Var,ยท'$deleted',_),!.
  151%valueMP(V,(V='ERROR')):-prolog_must(ground(V)),term_to_atom(V,A), concat_atom([_,_|_],'ERROR',A),trace,!.
  152
  153
  154checkValue(Value):- valueMP(Value,M),throw_safe(M),!.
  155checkValue(_):-!.
  156
  157valuePresent(Value):- var(Value),!,fail.
  158valuePresent(result(_)):- !.
  159valuePresent('$first'(_)):- !,atrace,fail.
  160valuePresent(Value):- valueMP(Value,_M),!,fail.
  161valuePresent(_):-!.
  162
  163isValid(Value):- var(Value),!,fail.
  164isValid([X]):-!,isValid(X).
  165isValid(result(_)):- !.
  166isValid([]):-!.
  167isValid(Value):- valueMP(Value,_M),!,fail.
  168isValid(_):-!.
  169
  170% ===============================================================================================
  171%    push/pop values API group operations
  172% ===============================================================================================
  173%%WIERD popAttributes(Ctx,Scope,OldVals):- popCtxFrame(Ctx,Scope,PrevValues),ignore(PrevValues=OldVals),!,ignore(popAttributes0(Ctx,Scope,OldVals)),!.
  174popAttributes(Ctx,Scope,OldVals):-prolog_must(atom(Scope)),ignore(popAttributes0(Ctx,Scope,OldVals)),popCtxFrame(Ctx,Scope,PrevValues),ignore(PrevValues=OldVals),!.
  175%%popAttributes(Ctx,Scope,List):- prolog_must(ground(Scope)),popAttributes0(Ctx,Scope,OldVals),!.
  176
  177
  178popNameValueOnce(Ctx,Scope,N,V):-nonvar(N),!,checkAttribute(Scope,N,V),popNameValue(Ctx,Scope,N,V),!.
  179
  180popAttributes0(Ctx,Scope,[N=V|L]):- prolog_must(popNameValueOnce(Ctx,Scope,N,V)),popAttributes0(Ctx,Scope,L),!.
  181popAttributes0(_Ctx,_Scope,VA):-var(VA),!.
  182popAttributes0(_Ctx,_Scope,[]):-!.
  183popAttributes0(Ctx,Scope,What):-debugFmt(popAttributes0(Ctx,Scope,What)),unify_listing(retract(dict(Scope,_,_))),!. %%,atrace.
  184
  185withAttributes(_Ctx,ATTRIBS,Call):-ATTRIBS==[],!,call(Call),!.
  186
  187/*
  188withAttributes(CtxIn,ATTRIBS,Call):- fail,
  189 %%gensym(withAttribs,SYM),
  190  ensureScope(NewCtx,ATTRIBS,Scope),
  191  makeContextBase(Scope,NewCtx),
  192  subst(Call,CtxIn,Ctx,ReCall),!,
  193  Ctx = l2r(NewCtx,CtxIn),
  194  aiml_notrace((
  195   ensureScope(NewCtx,ATTRIBS,Scope),
  196   checkAttributes(Scope,ATTRIBS))),
  197   call_cleanup((
  198    once(aiml_notrace(pushAttributes(NewCtx,Scope,ATTRIBS))),
  199    prolog_must(ReCall)),
  200    once((aiml_notrace(popAttributes(NewCtx,Scope,ATTRIBS))))),!.
  201*/

  202
  203 /*
  204 ju:unitTestResult(unit_failed,f(testIt([teststarrecursion],[retention,of,star,values,during,srai,'(','46',')'],['Verifies',that,values,assigned,to,star,elements,from,pattern,matching,are,retained,after,a,srai,'(',i,'.',e,'.',',',that,the,srai,does,not,improperly,cause,the,reassignment,of,a,new,value,to,the,star,',',based,on,the,srai,'\'',ed,pattern,match,'.'],sameBinding(1.2100000000000002-['Test',case,#,'46','.','Test',failed,'.'],['Test',case,#,'46','.','Test',passed,'.'])),sameBinding(1.2100000000000002-['Test',case,#,'46','.','Test',failed,'.'],['Test',case,#,'46','.','Test',passed,'.']))).
  205withAttributes(Ctx,ATTRIBS,Call):- 
  206  aiml_notrace((
  207   ensureScope(Ctx,ATTRIBS,Scope),
  208   checkAttributes(Scope,ATTRIBS))),
  209   call_cleanup((
  210    once(aiml_notrace(pushAttributes(Ctx,Scope,ATTRIBS))),
  211      Call),
  212    once(aiml_notrace(popAttributes(Ctx,Scope,ATTRIBS)))),!.
  213 */

  214% required for testcase 14 teststarrecursion
  215withAttributes(CtxIn,ATTRIBS,Call):-
  216 duplicate_term(CtxIn,Ctx),!,
  217  aiml_notrace((
  218   ensureScope(Ctx,ATTRIBS,Scope),
  219   checkAttributes(Scope,ATTRIBS),
  220   pushAttributes(Ctx,Scope,ATTRIBS))),!,
  221    fr_subst(CtxIn,Ctx,Call,ReCall),!,
  222  call(ReCall),!.
  223
  224
  225fr_subst(F,R,I,O):- F==I,!,O=R.
  226fr_subst(_,_,I,O):- \+ compound(I),!,I=O.
  227fr_subst(_,_,element(C,Call,E),element(C,Call,E)):-!.
  228%fr_subst(F,R,I,O):- is_list(I),maplist(fr_subst(F,R),I,O).
  229fr_subst(F,R,[H|T],[HH|TT]):- !, fr_subst(F,R,H,HH),fr_subst(F,R,T,TT).
  230fr_subst(F,R,I,O):- compound_name_arguments(I,A,II),fr_subst(F,R,II,OO),compound_name_arguments(O,A,OO).
  231
  232addScopeParent(Child,Parent):-addInherit(Child,Parent).
  233
  234checkAttributes(Scope,ATTRIBS):-prolog_must(nonvar(ATTRIBS)),maplist(checkAttribute(Scope),ATTRIBS).
  235checkAttribute(Scope,N=V):-checkAttribute(Scope,N,V).
  236checkAttribute(Scope,N,_V):-N==proof,!,prolog_must(nonvar(Scope)).
  237checkAttribute(Scope,N,V):-prolog_must(nonvar(Scope)),prolog_must(nonvar(N)),!,prolog_must(nonvar(V)).
  238
  239pushNameValue(Ctx,Scope,N,V):-
  240   checkAttribute(Scope,N,V),
  241   insert1StValue(Ctx,Scope,N,V),!.
  242   %%asserta(dict(Scope,N,V)),!.
  243
  244popNameValue(Ctx,Scope,N,Expect):-
  245   prolog_mustEach((
  246   currentContextValue(Ctx,Scope,N,V),
  247   ifThen(Expect\==V,debugFmt(popNameValue(Ctx,Scope,N,Expect,V))),
  248   checkAttribute(Scope,N,V),
  249   removeContextValue(Ctx,Scope,N,V),
  250   checkAttribute(Scope,N,V))),!.
  251
  252%dyn_retract(dict(Scope,N,V)):-(retract(dict(Scope,N,V))),!.
  253
  254ensureScope(Ctx,Attribs,ScopeName):-prolog_must(ensureScope0(Ctx,Attribs,ScopeName)),!.
  255ensureScope0(_Ctx,_ATTRIBS,Scope):-nonvar(Scope).
  256ensureScope0(_Ctx,_ATTRIBS,Scope):-flag(scope,Scope,Scope+1).
  257ensureScope0(_Ctx,_ATTRIBS,Scope):-gensym(scope,Scope).
  258
  259
  260% ===================================================================
  261%  Tagged/Attribute Contexts
  262% ===================================================================
  263replaceAttribute(Ctx,Before,After,ALIST,ATTRIBS):- replaceAttribute0(Ctx,Before,After,ALIST,AA),list_to_set_safe(AA,ATTRIBS),!.%%,traceIf((ALIST\==ATTRIBS,atrace)).
  264% the endcase
  265replaceAttribute0(_Ctx,_Before,_After,[],[]):-!.
  266% only do the first found?
  267replaceAttribute0(_Ctx,Before,After,[Before=Value|ATTRIBS],[After=Value|ATTRIBS]):-prolog_must(ground(Before+After+Value+ATTRIBS)),!.
  268% comment out the line above to do all
  269replaceAttribute0(Ctx,Before,After,[Before=Value|ALIST],[After=Value|ATTRIBS]):-
  270   replaceAttribute0(Ctx,Before,After,ALIST,ATTRIBS),!.
  271% skip over BeforeValue
  272replaceAttribute0(Ctx,Before,After,[BeforeValue|ALIST],[BeforeValue|ATTRIBS]):-
  273   replaceAttribute0(Ctx,Before,After,ALIST,ATTRIBS),!.
  274% the last resort
  275replaceAttribute0(_Ctx,_Before,_After,B,B):-!.
  276
  277
  278
  279makeAllParams(Ctx,[O|Order],Assert,[Tag=RR|Result]):-
  280   UnboundDefault = '$first'(['$attribute_value','$error'(makeAllParams(O))]),
  281   makeSingleTag(Ctx,O,Assert,UnboundDefault,Tag,RR),prolog_must(O\==RR),
  282   makeAllParams(Ctx,Order,Assert,Result),!.
  283makeAllParams(_Ctx,[],_,[]).
  284
  285
  286makeSingleTag(Ctx,Name,ATTRIBS,Default,Tag,Result):-atom(Name),!,makeSingleTag(Ctx,[Name],ATTRIBS,Default,Tag,Result),!.
  287makeSingleTag(Ctx,NameS,ATTRIBS,Default,Tag,ValueO):-makeAimlSingleParam0(Ctx,NameS,ATTRIBS,Default,Tag,ValueI),
  288      transformTagData(Ctx,Tag,Default,ValueI,ValueO),!.
  289
  290makeAimlSingleParam0(_Ctx,[N|NameS],ATTRIBS,_D,N,Value):-member(O,[N|NameS]),lastMember(OI=Value,ATTRIBS),atomsSameCI(O,OI),!,prolog_must(N\==Value).
  291makeAimlSingleParam0(Ctx,[N|NameS],ATTRIBS,ElseVar,N,Value):- aiml_notrace((locateNameValue(Ctx,ATTRIBS,[N|NameS],Value,
  292          '$first'(['$local_value','$call_name'(prolog_must(cateFallback(N,Value)),N),
  293                    '$global_value','$call_name'(prolog_must(defaultPredicates(N,Value)),N),
  294                       ElseVar,'$error'])))),!,
  295           prolog_must(N\==Value).
  296
  297
  298% ===============================================================================================
  299%  Fallback
  300% ===============================================================================================
  301
  302valuePresentOrStar(Var):-var(Var),!,throw_safe(valuePresentOrStar(Var)).
  303valuePresentOrStar(*):-!.
  304valuePresentOrStar([]):-!,trace.
  305valuePresentOrStar(Var):-valuePresent(Var),!.
  306
  307checkElseValue(_ElseVar):-!. 
  308checkElseValue(ElseVar):-var(ElseVar),!,throw_safe(checkElseValue(ElseVar)).
  309checkElseValue(ElseVar):-prolog_must((functor(ElseVar,F,_),!,atom_concat('$',_,F))).
  310
  311
  312%%% arity 5 version
  313locateNameValue(Ctx,Scope,NameS,ValueO,ElseVar):-makeParamFallback(Ctx,Scope,NameS,ValueO,ElseVar),!. %%,prolog_must(valuePresentOrStar(ValueO)).
  314
  315makeParamFallback(Ctx,Scope,NameS,Value,ElseVar):-checkElseValue(ElseVar),var(ElseVar),!,throw_safe(makeParamFallback(Ctx,Scope,NameS,Value,ElseVar)).
  316makeParamFallback(_Ctx,_Scope,_NameS,_Value,'$aiml_error'(E)):-!,aiml_error(E),throw_safe(E).
  317makeParamFallback(_Ctx,_Scope,_NameS,_Value,'$error'(E)):-!,aiml_error(E),throw_safe(E).
  318makeParamFallback(Ctx,Scope,NameS,Value,    '$error'):-!, E=fallbackValue(Ctx,Scope,NameS,Value,'$error'),aiml_error(E),throw_safe(E).
  319makeParamFallback(_Ctx,_Scope,_NameS,_Value,'$failure'):-!,fail.
  320makeParamFallback(_Ctx,_Scope,_NameS,_Value,'$succeed'):-!.
  321
  322makeParamFallback(Ctx,Scope,NameS,ValueO,   '$first'(List)):-!,anyOrEachOf(E,List),locateNameValue(Ctx,Scope,NameS,ValueO,E),!.
  323makeParamFallback(Ctx,Scope,NameS,ValueO,   '$current_value'):-!, locateNameValue(Ctx,Scope,NameS,ValueO,'$first'(['$local_value','$global_value','$attribute_value','$failure'])).
  324
  325makeParamFallback(Ctx,Scope,NameS,ValueO,   '$local_value'):-!,local_value(Ctx,Scope,NameS,ValueO).
  326makeParamFallback(Ctx,Scope,NameS,ValueO,   '$global_value'):-!, peekGlobalMem(Ctx,Scope,NameS,ValueO),valuePresent(ValueO).
  327makeParamFallback(Ctx,Scope,NameS,ValueO,   '$attribute_value'):-!, attributeValue(Ctx,Scope,NameS,ValueO,'$failure').
  328
  329makeParamFallback(_Ctx,_Scope,_NameS,_Value,'$call'(Prolog)):-!,call(Prolog).
  330makeParamFallback(_Ctx,_Scope,NameS,_Value, '$call_name'(Prolog,NameS)):-!,prolog_must(Prolog).
  331makeParamFallback(Ctx,Scope,NameS,ValueO,   '$call_value'(Pred)):-!, call(Pred,Ctx,Scope,NameS,ValueO,'$failure').
  332
  333makeParamFallback(_Ctx,_Scope,_NameS,ValueO,'$value'(Else)):-!,ValueO=Else,!.
  334
  335makeParamFallback(Ctx,Scope,NameS,Value,ElseVar):-not(atom(NameS)),!,anyOrEachOf(Name,NameS),makeParamFallback(Ctx,Scope,Name,Value,ElseVar).
  336makeParamFallback(_Ctx,_Scope,_NameS,ValueO,Else):-ValueO=Else,!.
  337makeParamFallback(_Ctx,_Scope,_NameS,ValueO,Else):-atrace,debugFmt(ignore(ValueO=Else)),!.
  338
  339anyOrEachOf(Name,NameL):-prolog_must(nonvar(NameL)),is_list(NameL),!,member(Name,NameL).
  340anyOrEachOf(Name,NameA):-atom(NameA),!,prolog_must(NameA=Name).
  341anyOrEachOf(Name,NameA):-atrace,!,prolog_must(NameA=Name).
  342
  343% ===================================================================
  344%  AimlContexts
  345%   They hold name-values in
  346%     -- assoc/1 lists
  347%     -- open tailed lists
  348%     -- frame/1 contains one or more of the above
= v(Value,Setter,KeyDestructor)
= frame(Named,Destructor,Ctx)
  356/*
  357
  358 well i played with a couple few differnt environment impls.. they have their pros cons.. one impl..
  359 that was unique is that an array of "binding pairs" live in an arraylist.. to be "in" an environment it meant that you held an "index" 
  360 into the arry list that as you went backwards you would find your bindings.. each symbol had a java int field "lastBindingIndex" .. 
  361 that was a "hint" to where you could fastforward the backwards search .. end named binding context also had a 
  362 "index" to when you leave a named block.. you could quickly reset the top of an index.
  363
  364 */

  365
  366% ===================================================================
  367
  368withCurrentContext(Goal):-prolog_must(atom(Goal)),prolog_must((currentContext(Goal,Ctx),call(Goal,Ctx))).
  369
  370withNamedContext(CtxNameKey,NewCtx):-makeContextBase(CtxNameKey,NewCtx),!,setCtxValue(NewCtx,ctxname,CtxNameKey),!.
  371
  372currentContext(CtxNameKey,CurrentCtx):-ifThen(var(CurrentCtx),withNamedContext(CtxNameKey,CurrentCtx)),!.
  373
  374makeContextBase(CtxNameKey, [frame(CtxNameKey,ndestruct,[assoc(AL)|_])|_]):- list_to_assoc([],AL).
  377makeContextBase__only_ForTesting(Gensym_Key, [frame(Gensym_Key,ndestruct,[assoc(AL)|_])|_]):-    
  378   list_to_assoc([
  379    a-v(error_in_assoc,set_assoc,ndestruct(a)),
  380    a-v(is_a2,set_assoc,ndestruct(a)),
  381    b-v(is_b,set_assoc,ndestruct(b))],AL).
  382
  383
  384% ===================================================================
  385% push/pop frames
  386% ===================================================================
  387pushCtxFrame(Ctx,Name,NewValues):-prolog_mustEach((checkCtx(pushCtxFrame,Ctx),get_ctx_holderFreeSpot(Ctx,Holder,GuestDest),!,Holder=frame(Name,GuestDest,NewValues))).
  388
  389popCtxFrame(Ctx,Name,PrevValuesIn):- aiml_notrace(prolog_mustEach(((
  390      checkCtx(popCtxFrame,Ctx),
  391      get_ctx_frame_holder(Ctx,Name,Frame,_Held),
  392      %%prolog_must(atom(Name)),prolog_must(compound(Frame)),
  393      Frame = frame(Name,Destructor,PrevValues),
  394      call(Destructor,Name,Ctx,Frame),!,
  395      mustMatch(PrevValues,PrevValuesIn))))).
  396
  397%%checkCtx(Fallback,Ctx):-var(Ctx),!,Ctx=[broken(Fallback)|_]. 
  398checkCtx(Fallback,Ctx):-var(Ctx),!,brokenFallback(Fallback,Ctx).
  399checkCtx(_Fallback,_):-!.
  400checkCtx(_Fallback,Ctx):-prolog_must(nonvar(Ctx)).
  401checkCtx(Fallback,Ctx):-brokenFallback(Fallback,Ctx).
  402
  403brokenFallback(Fallback,Ctx):-withNamedContext(broken(Fallback),Ctx),!.
  404
  405mustMatch(PrevValues,PrevValuesIn):-ignore(PrevValues=PrevValuesIn).
  406
  407:-dynamic(no_cyclic_terms/0).
  408
  409no_cyclic_terms.
  410
  411% ===================================================================
  412% value getter/setters
  413% ===================================================================
  414ndestruct:-atrace.
  415ndestruct(Holder):-debugFmt(unImplemented(ndestruct(Holder))).
  416
  417mdestruct(_Why,Name,_Ctx,Frame):-prolog_must(atom(Name)),prolog_must(compound(Frame)),Frame=frame(NameF,_,_),prolog_must(Name==NameF),
  418   Dest = '$deleted'(scope(Name)),prolog_must(atom(Name)),
  419   %%seeing is we can keep it arround setarg(1,Frame,Dest),
  420   setarg(2,Frame,Dest),setarg(3,Frame,Dest),!. %%,Frame=Frame.
  421mdestruct(Why,Name,Ctx,Value):-debugFmt(unImplemented11(mdestruct(Why,Name,Ctx,Value))).
  422no_setter(Why,Name,Ctx,Value):-debugFmt(unImplemented2(no_setter(Why,Name,Ctx,Value))).
  423
  424
  425nb_setarg(N,Term,Name,OldCtx,Value):-var(Term),throw_safe(nb_setarg(N,Term,Name,OldCtx,Value)),!.
  426nb_setarg(N,NameT=Term,Name,_OldCtx,Value):-prolog_must(Name=NameT),!,nb_setarg(N,Term,Value).
  427nb_setarg(N,Term,_Name,_OldCtx,Value):-atrace,nb_setarg(N,Term,Value).
  428
  429% set_assoc as the "setter" means to use the term found in a assoc/1 .. change the calue and resave assoc/1 internal held term
  430set_assoc(ASSOC,Name,_Ctx,Value):- ASSOC = assoc(Assoc), 
  431      assoc_to_list(Assoc, List), !,
  432      append(List,[Name-Value],NewValues),!,
  433      list_to_assoc(NewValues,NewAssoc),nb_setarg(1,ASSOC,NewAssoc),!.
  434
  435% set_v3 as the "setter" means to use the v3 data structure to set the value
  436set_assoc(_OrigName,Name,CtxIn,Value):- prolog_must(setCtxValue(CtxIn,Name,Value)),!.
  437
  438
  439unwrapValue(HValue,TValue):-TValue=='$deleted',!,not(unwrapValue1(HValue,_)),!.
  440unwrapValue(HValue,TValue):-unwrapValue1(HValue,Value),!,TValue=Value.
  441
  442unwrapValue1(Value,ValueOut):-var(Value),!,atrace,throw_safe(unwrapValue1(Value,ValueOut)),Value=ValueOut.
  443unwrapValue1(v(ValueHolder,_SetterFun,_KeyDestroyer),Value):-!,unwrapValue1(ValueHolder,Value),!.
  444unwrapValue1('$deleted',_):-!,fail.
  445%unwrapValue1([Value],[ValueOut]):-!,unwrapValue1(Value,ValueOut),!.
  446%unwrapValue1([V|Value],[VO|ValueOut]):-!,unwrapValue1(V,VO),unwrapValue1(Value,ValueOut),!.
  447unwrapValue1(Value,Value):-not(compound(Value)),!.
  448unwrapValue1(Deleted,_):-functor(Deleted,'$deleted',_),!,fail.
  449%%unwrapValue1(Compound,ArgO):-compound(Compound),arg(_,Compound,Arg),unwrapValue1(Arg,ArgO),!.
  450unwrapValue1(Compound,Compound).
  451
  452
  453bestSetterFn(v(_,Setter,_),_OuterSetter,Setter):-!.
  454bestSetterFn(_Value,OuterSetter,OuterSetter).
  455
  456getCtxValueND(CtxIn,Name,Value):-checkCtx(getCtxValueND,CtxIn), aiml_notrace(( get_ctx_holder(CtxIn,Ctx),get_o_value(Name,Ctx,HValue,_Setter),unwrapValue(HValue,Value))).
  457getCtxValueND(CtxI,Name,Value):-checkCtx(getCtxValueND,CtxI),lastMember(Ctx,CtxI),aiml_notrace(( get_ctx_holder(Ctx,CtxH),get_o_value(Name,CtxH,HValue,_Setter), unwrapValue(HValue,Value))),atrace.
  458
  459/*
  460getCtxValueND(CtxIn,Dict:Name,Value):-var(Dict),!,getCtxValueND(CtxIn,Name,Value).
  461getCtxValueND(CtxIn,Name,Value):-prolog_must(nonvar(Name)),getCtxValueND0(CtxIn,Name,Value).
  462getCtxValueND(CtxIn,Dict:Name,Value):-getNamedCtxValue(CtxIn,Dict,Name,Value).
  463
  464getCtxValueND0(CtxIn,Name,Value):-checkCtx(getCtxValueND,CtxIn), aiml_notrace(( get_ctx_holder(CtxIn,Ctx),get_o_value(Name,Ctx,HValue,_Setter),unwrapValue(HValue,Value))).
  465getCtxValueND0(CtxI,Name,Value):-checkCtx(getCtxValueND,CtxI),lastMember(Ctx,CtxI),aiml_notrace(( get_ctx_holder(Ctx,CtxH),get_o_value(Name,CtxH,HValue,_Setter), unwrapValue(HValue,Value))),atrace.
  466*/

  467
  468getCtxValue_nd(Ctx,Key,Value):- getNamedCtxValue(Ctx,Dict,Name,Value),dictNameKey(Dict,Name,Key).
  469
  470getNamedCtxValue(CtxIn,Dict,Name,Value):-get_ctx_frame_holder(CtxIn,Dict,_Frame,Held),atrace,get_c_value_wrapped(Held,Name,Value).
  471getNamedCtxValue(CtxIn,Dict,Name,Value):-lastMember(Ctx,CtxIn),aiml_notrace((get_ctx_holder(Ctx,CtxHolder),ctxDict(CtxHolder,Dict,Held),get_c_value_wrapped(Held,Name,Value) )).
  472getNamedCtxValue(CtxIn,Dict,Name,'$deleted'(CtxIn,Dict,Name)):-ignore(Dict=nodict),ignore(Name=noname).
  473
  474ctxDict(Ctx,Dict,[]):-var(Ctx),!,Dict=noctx.
  475ctxDict(frame(Named,_,Held),Dict,Held):-!,Named=Dict.
  476ctxDict(Ctx,Dict,Ctx):-!,Dict=unnamedctx.
  477
  478get_c_value_wrapped(Ctx,Name,Value):-get_o_value(Name,Ctx,Value,_Setter).%%,unwrapValue(HValue,Value).
  479get_c_value_wrapped(_Ctx,Name,'$deleted'(Name)):-ignore(Name=noname).
  480
  481setCtxValue(Ctx,Name,Value):-(getCtxValueND(Ctx,Name,PrevValue),!, Value==PrevValue) -> true; addCtxValue1(Ctx,Name,Value).
  482
  483addCtxValue(Ctx,Name,Value):-checkCtx(addCtxValue,Ctx),addCtxValue1(Ctx,Name,Value),!.
  484%%addCtxValue1(Ctx,Name,Value):-get_ctx_holderFreeSpot(Ctx,Name=v(Value,Setter,Destructor),Destructor),!,ignore(Setter=set_v3(Name)).
  485addCtxValue1(CtxIn,Name,Value):-get_ctx_frame_holder(CtxIn,_Dict,Ctx,_Held),get_ctx_holderFreeSpot(Ctx,NameValue,Destructor), NameValue = (Name=v(Value,set_v3(Name),Destructor)).
  486                                                                                             
  487
  488%%remCtxValue(Ctx,Name,_Value):-checkCtx(remCtxValue,Ctx),setCtxValue(Ctx,Name,'$deleted'),!.
  489
  490%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  491%%%%% get the frame holder
  492%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  493get_ctx_frame_holder(R,NameIn,Frame,Held):- prolog_must(get_ctx_frame_holder0(R,NameIn,Frame,Held)).
  494
  495get_ctx_frame_holder0(v(_,_,_),_Name,_R,_Held):-!,fail.
  496get_ctx_frame_holder0(R,NameIn,Frame,Held):- R = frame(Name,_,Inner),!, Name\=destroyed(_),
  497                        (  get_ctx_frame_holder0(Inner,NameIn,Frame,Held); 
  498                           (Name=NameIn,prolog_mustEach((Held=Inner,R=Frame,Name=NameIn,!)))).
  499get_ctx_frame_holder0([H|T],Name,R,Held):- nonvar(H), !, ( get_ctx_frame_holder0(T,Name,R,Held);get_ctx_frame_holder0(H,Name,R,Held)) .
  500%%get_ctx_frame_holder(Ctx,Name,Ctx):-!,get_ctx_frame_holder(Ctx,Name,R).
  501
  502
  503%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  504%%%%% get the holders areas last in first out %%%%%
  505%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  506%%%%% get_ctx_holder(+Ctx, -PlaceToSearch),
  507
  508get_ctx_holder(Ctx,R):-compound(Ctx),get_ctx_holder1(Ctx,R).
  509get_ctx_holder1([H|T],R):- nonvar(H), !, ( get_ctx_holder(T,R);get_ctx_holder1(H,R)) .
  510get_ctx_holder1(v(_,_,_),_R):-!,fail. % get_ctx_holder(Ctx,R).
  511get_ctx_holder1(frame(_N,_Dest,Ctx),R):-!,get_ctx_holder(Ctx,R).
  512get_ctx_holder1(l2r(H,T),R):- !, ( get_ctx_holder1(H,R);get_ctx_holder(T,R)) .
  513get_ctx_holder1(assoc(Ctx),assoc(Ctx)):-!.
  514%get_ctx_holder1(Ctx,R):- functor(Ctx,F,A),A<3,!,fail.
  515get_ctx_holder1(Ctx,Ctx).
  516
  517
  518%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  519%%%%% find a free area to place a: vv(name,val) %%%%%
  520%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  521%%%%% get_ctx_holderFreeSpot(+Ctx, -Put_NV, -CallToRemoveNV)
  522
  523get_ctx_holderFreeSpot(Ctx,NamedValue,mdestruct(no_cyclic_terms)):-no_cyclic_terms,!,get_ctx_holderFreeSpot0(Ctx,NamedValue,_NO_Destruct),!.
  524get_ctx_holderFreeSpot(Ctx,NamedValue,Destruct):-get_ctx_holderFreeSpot0(Ctx,NamedValue,Destruct).
  525
  526get_ctx_holderFreeSpot0(Ctx,NamedValue,Destruct):-compound(Ctx),get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct).
  527
  528get_ctx_holderFreeSpot1(assoc(_Ctx),_,_):-!,fail.
  529get_ctx_holderFreeSpot1(frame(Key,_Inner_Dest,Ctx),NamedValue,Destruct):- nonvar(Key), !, get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct).
  530get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct):-get_ctx_holderFreeSpot2(Ctx,Ctx,NamedValue,Destruct),!.
  531
  532get_ctx_holderFreeSpot2(_,Try1,NamedValue,nb_setarg(1,Try1)):- var(Try1),!, Try1 = [NamedValue|_NEXT],atrace.
  533get_ctx_holderFreeSpot2(_,[_|Try1],NamedValue,nb_setarg(1,Try1)):- var(Try1),!, Try1 = [NamedValue|_NEXT].
  534get_ctx_holderFreeSpot2(_,[_|Try2],NamedValue,Destruct):-get_ctx_holderFreeSpot0(Try2,NamedValue,Destruct).
  535
  536%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,_):-!,fail.
  537%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,nb_setarg(N,NEXT)):-arg(N,Ctx,Try3),var(Try3),!, Try3 = [NamedValue|NEXT].
  538%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,Destruct):-arg(N,Ctx,Try4),get_ctx_holderFreeSpot0(Try4,NamedValue,Destruct).
  539
  540
  541%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  542%%%%% find the value holder associated with a keyname
  543%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  544get_ctx_value(Name,Ctx,Value,Setter):-nonvar(Name),var(Value),get_o_value(Name,Ctx,Value,OuterSetter),bestSetterFn(Value,OuterSetter,Setter).
  545
  546get_o_value00(Name,Ctx,Value,Setter):-get_o_value0(Name,Ctx,Value,HIDE_Setter),((no_cyclic_terms,cyclic_term(HIDE_Setter))-> Setter=no_setter(cyclicOn(Name)) ; Setter =HIDE_Setter).
  547get_o_value(Name,Ctx,Value,Setter):- aiml_notrace(get_o_value00(Name,Ctx,Value,Setter)).
  548
  549get_o_value0(Name,Ctx,Value,Setter):-compound(Ctx),get_o_value1(Name,Ctx,Value,Setter).
  550get_o_value1(Name,[H|T],Value,Setter):- !,(get_o_value0(Name,T,Value,Setter);get_o_value1(Name,H,Value,Setter)).
  551get_o_value1(Name,ASSOC,Value,set_assoc(ASSOC)):- ASSOC = assoc(Ctx),!, get_assoc(Name,Ctx,Value).
  552get_o_value1(Name,frame(Key,_Inner_Dest,Ctx),Value,Setter):- nonvar(Key),!, get_o_value0(Name,Ctx,Value,Setter).
  553get_o_value1(Name,l2r(H,T),Value,Setter):- !,(get_o_value1(Name,H,Value,Setter);get_o_value0(Name,T,Value,Setter)).
  554get_o_value1(Name,Pred,Value,Setter):-functor(Pred,F,A),!,get_n_value(Name,Pred,F,A,Value,Setter),!.
  555
  556get_n_value(Name,Name,_F,_A,_Value,_):-!,fail.
  557get_n_value(Name,Pred,Name,1,Value,nb_setarg(1,Pred)):-arg(1,Pred,Value).
  558get_n_value(Name,Pred,Name,_,Value,Setter):- arg(1,Pred,Value),!,arg(2,Pred,Setter). 
  559get_n_value(Name,Pred,Dash,2,Value,nb_setarg(2,Pred)):-arg(1,Pred,Name),member(Dash,[=,-,vv]),!, arg(2,Pred,Value).
  560%%get_n_value(Name,Pred,'.',2,Value,Setter):-arg(2,Pred,Try1), get_o_value0(Try1,Name,Value,Setter);(arg(1,Pred,Try2),get_o_value0(Try2,Name,Value,Setter)).
  561%%get_n_value(Name,Pred,_,_,Value,Setter):- !, arg(_,Pred,Try2),get_o_value0(Try2,Name,Value,Setter).
  562
  563% ===================================================================
  564% attribute searching (Document contexts)
  565% ===================================================================
  566/*
  567attributeValue(Ctx,Scope,Name,Value,Else):-nonvar(Value),!,checkNameValue(attributeValue,Ctx,Scope,Name,Value,Else).
  568attributeValue(Ctx,Scope,Name,Value,_ElseVar):-peekNameValue0(Ctx,Scope,Name,Value),!.
  569attributeValue(Ctx,_Scope,Name,Value,ElseVar):-makeParamFallback(Ctx,Name,Value,ElseVar),!.
  570*/

  571attributeValue(Ctx,ATTRIBS,NameS,ValueO,_Else):- ((findAttributeValue(Ctx,ATTRIBS,NameS,ValueO,'$failure'))),!.
  572attributeValue(Ctx,XML,NameS,ValueO,_Else):- aiml_notrace((findTagValue(Ctx,XML,NameS,ValueO,'$failure'))),!.
  573attributeValue(Ctx,ATTRIBS,NameS,ValueO,_Else):-compound(ATTRIBS),ATTRIBS=..[_|LIST],member(E,LIST),
  574   attributeValue(Ctx,E,NameS,ValueO,'$failure'),!.
  575attributeValue(Ctx,Scope,NameS,ValueO,ElseVar):-ElseVar\=='$failure',makeParamFallback(Ctx,Scope,NameS,ValueO,ElseVar),!.
  576
  577findAttributeValue(Ctx,ATTRIBS,NameS,ValueO,Else):- ((findAttributeValue0(Ctx,ATTRIBS,NameS,ValueI,Else), aiml_eval_to_unit(Ctx,ValueI,ValueO))),!.
  578findAttributeValue(Ctx,ATTRIBS,NameS,ValueO,Else):-   Else\=='$failure',prolog_must((findAttributeValue0(Ctx,ATTRIBS,NameS,ValueI,Else), aiml_eval_to_unit(Ctx,ValueI,ValueO))),!.
  579
  580findAttributeValue0(_Ctx,ATTRIBS,NameS,ValueO,_Else):- lastMemberTest(NameE=ValueO,ATTRIBS), member(Name,NameS), atomsSameCI(Name,NameE),!.
  581findAttributeValue0(Ctx,ATTRIBS,NameS,Value,ElseVar):- makeParamFallback(Ctx,ATTRIBS,NameS,Value,ElseVar),!.
  582
  583lastMemberTest(E,L):- ground(L),!,reverse(L,R),member(E,R).
  584lastMemberTest(E,L):-lastMember(E,L).
  585
  586findTagValue(_Ctx,XML,_NameS,_ValueO,_Else):-var(XML),!,fail.
  587
  588findTagValue(Ctx,XML,NameS,ValueO,Else):-
  589      member(Name,NameS),
  590      findTagValue(Ctx,XML,Name,ValueO,Else),!.
  591
  592findTagValue(Ctx,XML,NameS,ValueO,Else):-
  593      member(element(NameE,ATTRIBS,ValueI),XML),
  594      findTagValue(Ctx,element(NameE,ATTRIBS,ValueI),NameS,ValueO,Else),!.
  595
  596findTagValue(Ctx,XML,Name,ValueO,Else):-!,
  597      findTagValue0_of_xml_element(Ctx,XML,Name,ValueO,Else).
  598
  599findTagValue(Ctx,XML,[NameE=_|_],ValueO,_Else):-
  600      member(element(NameA,ATTRIBS,ValueI),XML),member(_=NameI,ATTRIBS),
  601     atomsSameCI(NameA,NameE),atomsSameCI(NameA,NameI),
  602     aiml_select_unit(Ctx,NameA,ValueI,ValueO),!.
  603
  604
  605findTagValue0_of_xml_element(Ctx,element(NameE,ATTRIBS,ValueI),Name,ValueO,_Else):- 
  606      atomsSameCI(Name,NameE),!,
  607   aiml_select_unit(Ctx,NameE,element(NameE,ATTRIBS,ValueI),ValueO),!.
  608
  609findTagValue0_of_xml_element(Ctx,element(NameE,ATTRIBS,ValueI),Name,ValueO,_Else):-
  610      lastMember(name=Name,ATTRIBS,Rest),atomsSameCI(Name,NameE),!,
  611   aiml_select_unit(Ctx,Name,element(NameE,Rest,ValueI),ValueO),!.
  612
  613
  614aiml_select_unit(Ctx,NameA,element(NameA,[],ValueI),ValueO):-aiml_eval_to_unit(Ctx,ValueI,ValueO),!.
  615aiml_select_unit(Ctx,_NameA,ValueI,ValueO):-aiml_eval_to_unit(Ctx,ValueI,ValueO),!