1% ===================================================================
    2% File 'logicmoo_module_aiml_cxt_path.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_cxt_path.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% get / set  Coversational Variables
   24% ===============================================================================================
   25
   26getAliceMemOrSetDefault(CtxIn,ConvThread,SYM,Name,ValueO,OrDefault):-
   27   checkSym(SYM),
   28   getAliceMemOrSetDefault0(CtxIn,ConvThread,Name,Value,OrDefault),!,
   29   (Value=[]-> ValueO=OrDefault ; ValueO=Value).
   30
   31%%getAliceMemOrSetDefault0(CtxIn,ConvThread,Name,Value,_OrDefault):- hotrace(current_value(CtxIn,ConvThread:Name,Value)),!.
   32getAliceMemOrSetDefault0(CtxIn,ConvThread,Name,Value,_OrDefault):-
   33   aiml_notrace(getIndexedValue(CtxIn,ConvThread,Name,[],Value)),!.
   34getAliceMemOrSetDefault0(CtxIn,ConvThread,Name,Value,OrDefault):-
   35   setAliceMem(CtxIn,ConvThread,Name,OrDefault),!,OrDefault=Value.
   36
   37% ===============================================================================================
   38% get / set  Global Variables
   39% ===============================================================================================
   40:-dynamic(dict/3).
   41:-multifile(dict/3).
   42
   43getAliceMemElse(Ctx,Dict,Name,ValueO):-getAliceMemComplete(Ctx,Dict,Name,ValueO),!.
   44getAliceMemElse(_Ctx,Dict,Name,[Dict,(s),unknown,Name]):-atrace.
   45
   46getAliceMem(Ctx,Dict,DEFAULT,ValueOut):- compound(DEFAULT),DEFAULT=default(Name,Default),!, 
   47     (getAliceMemComplete(Ctx,Dict,Name,ValueO) -> xformOutput(ValueO, ValueOut)  ; xformOutput(Default, ValueOut)). 
   48
   49getAliceMem(Ctx,IDict,NameI,ValueO):-
   50     dictNameDictNameC(Ctx,IDict,NameI,Dict,Name),!,
   51     getAliceMem(Ctx,Dict,Name,ValueO).
   52getAliceMem(Ctx,Dict,Name,ValueO):- var(ValueO), !, getAliceMemElse(Ctx,Dict,Name,ValueO),!.
   53
   54getAliceMem(Ctx,Dict,Name,'OM'):- !, \+((getAliceMemComplete(Ctx,Dict,Name,ValueO),ValueO\=='OM')).
   55%%getAliceMem(Ctx,Dict,Name,ValueI):- %%unresultifyC(ValueI,ValueM),!,getAliceMem(Ctx,Dict,Name,ValueO),!,sameBinding(ValueI,ValueO).%%prolog_must(nonvar(ValueI)),!.
   56getAliceMem(Ctx,Dict,Name,ValueI):- getAliceMemComplete(Ctx,Dict,Name,ValueO),!,sameBinding(ValueI,ValueO).
   57
   58getAliceMemComplete(Ctx,Dict,Name,ValueO):-getInheritedStoredValue(Ctx,Dict,Name,ValueO),!.
   59
   60dictNameKey(Dict,Name,Key):-dictNameKey0(Dict,Name,Key).
   61
   62dictNameKey0([Dict],Name,Key):-nonvar(Dict),!,dictNameKey0(Dict,Name,Key).
   63dictNameKey0(Dict,[Name],Key):-nonvar(Name),!,dictNameKey0(Dict,Name,Key).
   64dictNameKey0(Dict,Name,Name):-nonvar(Dict),neverDictName(Dict),!.
   65dictNameKey0(Dict,Name,Dict:Name):-nonvar(Dict),!.
   66dictNameKey0(_Dict,DictName,Key):- nonvar(DictName),DictName=Dict:Name,!,dictNameKey0(Dict,Name,Key).
   67dictNameKey0(_Dict,NameKey,NameKey).
   68dictNameKey0(Dict,Name,Key):-var(Dict),nonvar(Name),!,Key=Name.
   69
   70neverDictName(Var):-var(Var),!.
   71neverDictName([_=_|_]).
   72neverDictName([]).
   73neverDictName(_=_).
   74
   75
   76getStoredValue(Ctx,Dict,Name,Value):-prolog_must(var(Value)),getContextStoredValue(Ctx,Dict,Name,Value).
   77
   78% ===============================================================================================
   79% named context via inheritance
   80% ===============================================================================================
   81getInheritedStoredValueOrDefault(Ctx,Scope,Name,ValueOut,_Default):- getInheritedStoredValue(Ctx,Scope,Name,ValueO) , xformOutput(ValueO, ValueOut).
   82getInheritedStoredValueOrDefault(_Ctx,_Scope,_Name,ValueOut,Default):- xformOutput(Default, ValueOut). 
   83
   84getInheritedStoredValue(Ctx,Scope,DEFAULT,ValueOut):- compound(DEFAULT),DEFAULT=default(Name,Default),!,getInheritedStoredValueOrDefault(Ctx,Scope,Name,ValueOut,Default).
   85getInheritedStoredValue(Ctx,IScope,NameI,Value):-dictNameDictNameC(Ctx,IScope,NameI,Scope,Name),!,getInheritedStoredValue(Ctx,Scope,Name,Value).
   86getInheritedStoredValue(Ctx,Scope,Name,Value):- getStoredValue(Ctx,Scope,Name,Value).
   87getInheritedStoredValue(Ctx,Scope,Name,Value):- inheritedDictsOrdered(Scope,InHerit),getStoredValue(Ctx,InHerit,Name,Value).
   88
   89
   90% ===============================================================================================
   91% inheritance control
   92% ===============================================================================================
   93addInherit( SYM0,SYMPREV0):-ifChanged(convert_dictname(_Ctx),[SYM0,SYMPREV0],[SYM,SYMPREV]),!,addInherit( SYM,SYMPREV).
   94
   95addInherit(_SYM,SYMPREV):-autoInheritDict(SYMPREV),!.
   96addInherit( SYM,SYMPREV):-dict(SYM,inheritdict,SYMPREV),!.
   97addInherit( SYM,SYMPREV):- asserta_dict(SYM,inheritdict,SYMPREV).
   98
   99% asserta_dict(catefallback, template, ['[]']):- !,trace.
  100asserta_dict(Ctx,N,V):-  asserta(dict(Ctx,N,V)).
  101
  102ifChanged(Pred,List,ListO):-maplist_safe(Pred,List,ListMid),ListMid\=List,prolog_must(ListMid=ListO),!.
  103
  104remInherit(_SYM,SYMPREV):-autoInheritDict(SYMPREV),!.
  105remInherit( SYM,SYMPREV):-retractall(dict(SYM,inheritdict,SYMPREV)),!.
  106
  107inheritedDictsOrdered(Scope,InHerit):-inheritedFrom2(Scope,InHerit), \+(Scope=InHerit).
  108
  109inheritedFrom2(Scope,InHerit):-inheritedFrom(Scope,InHerit).
  110inheritedFrom2(Scope,InHerit):-inheritedFrom(Scope,InHeritMid),inheritedFrom(InHeritMid,InHerit).
  111
  112inheritedFrom([],_):-!,fail.
  113inheritedFrom([Scope],To):-!,inheritedFrom(Scope,To).
  114inheritedFrom([D|LIST],To):-!,member(Scope,[D|LIST]),inheritedFrom(Scope,To).
  115%inheritedFrom(Compound,_):-compound(Compound),!,fail.
  116inheritedFrom(Scope,Dict):-dict(Scope,inheritdict,Dict), \+(autoInheritDict(Dict)).
  117inheritedFrom(Auto,_):-autoInheritDict(Auto),!,fail.
  118inheritedFrom(Atom,_):- \+(atom(Atom)),!,fail.
  119inheritedFrom(Scope,defaultValue(Scope)).
  120inheritedFrom(_Scope,Dict):-autoInheritDict(Dict).
  121
  122autoInheritDict(user).
  123autoInheritDict(default).
  124
  125% ===============================================================================================
  126% getIndexedValue
  127% ===============================================================================================
  128
  129getIndexedValue(Ctx,IDict,Name,MajorMinor,Value):-unresultifyC(IDict,Dict),!,
  130    getIndexedValue(Ctx,Dict,Name,MajorMinor,Value),!.
  131
  132getIndexedValue(Ctx,Dict,Name,[],Value):-!,
  133    getIndexedValue(Ctx,Dict,Name,[1],Value).
  134
  135getIndexedValue(Ctx,Dict,Name,Major,Value):-atomic(Major),!,
  136    getIndexedValue(Ctx,Dict,Name,[Major],Value).
  137
  138getIndexedValue(Ctx,Dict,Name,[Minor],Value):-atomic(Minor),!,
  139    getIndexedValue(Ctx,Dict,Name,[1,Minor],Value).
  140
  141getIndexedValue(Ctx,Dict,Name,[Major,'\b',SEP,'\b'|Minor],Value):-!,
  142    getIndexedValue(Ctx,Dict,Name,[Major,SEP|Minor],Value).
  143
  144getIndexedValue(Ctx,Dict,Name,[Major,SEP|Minor],Value):- member(SEP,[',',':']),!,
  145    getIndexedValue(Ctx,Dict,Name,[Major|Minor],Value).
  146
  147getIndexedValue(Ctx,Dict,Name,MajorMinor,ValueO):- numberFyList(MajorMinor,MajorMinorM),MajorMinor\==MajorMinorM,!,
  148   getIndexedValue(Ctx,Dict,Name,MajorMinorM,ValueO).
  149
  150getIndexedValue(Ctx,Dict,DEFAULT,MajorMinor,ValueOut):- compound(DEFAULT),DEFAULT=default(Name,Default),!,
  151    (getIndexedValue(Ctx,Dict,Name,MajorMinor,ValueO)  -> xformOutput(ValueO, ValueOut)  ; xformOutput(Default, ValueOut)). 
  152
  153getIndexedValue(Ctx,Dict,Name,MajorMinor,ValueO):-
  154    hotrace(getIndexedValue0(Ctx,Dict,Name,MajorMinor,Value)),
  155    xformOutput(Value,ValueO).
  156   
  157getIndexedValue(Ctx,Dict,Name,MajorMinor,ValueO):- fail,   
  158    unify_listing(getContextStoredValue(Ctx,Dict,_N,_V)),
  159    %%unify_listing(getContextStoredValue(Ctx,_,Name,_)),
  160    getIndexedValue0(Ctx,Dict,Name,MajorMinor,Value),
  161    xformOutput(Value,ValueO).
  162
  163
  164% ===============================================================================================
  165% getMajorIndexedValue
  166% ===============================================================================================
  167getMajorIndexedValue(Ctx,Dict,Name,Major,ValueS):- isLinearMemStore,!,
  168   getMajorIndexedValueLinear(Ctx,Dict,Name,Major,ValueS),!.
  169
  170getMajorIndexedValue(Ctx,Dict,Name,Major,ValueS):-
  171   indexOntoKey(Name,Major,Item),
  172   getInheritedStoredValue(Ctx,Dict,Item,ValueS),!.
  173
  174
  175
  176% ===============================================================================================
  177% getMajorIndexedValueLinear
  178% ===============================================================================================
  179getMajorIndexedValueLinear(Ctx,[D|List],Name,Major,ValueS):-
  180   member(Dict,[D|List]),
  181   aiml_notrace(getMajorIndexedValueLinear0(Ctx,Dict,Name,Major,ValueS)),!.
  182
  183getMajorIndexedValueLinear(Ctx,[D|List],Name,Major,ValueS):-!,fail,
  184   unify_listing(dict(_,Name,_)),
  185   member(Dict,[D|List]),
  186   atrace,
  187   getMajorIndexedValueLinear0(Ctx,Dict,Name,Major,ValueS),!.
  188
  189getMajorIndexedValueLinear(Ctx,Dict,Name,Major,ValueS):-
  190   getMajorIndexedValueLinear(Ctx,[Dict],Name,Major,ValueS),!.
  191
  192
  193getMajorIndexedValueLinear0(Ctx,Dict,Name,Major,ValueS):-
  194   subscriptZeroOrOne(Major),!,
  195   getInheritedStoredValue(Ctx,Dict,Name,ValueS),!.
  196
  197getMajorIndexedValueLinear0(Ctx,Dict,Name,Major,ValueS):-
  198   nthResult(Major,getInheritedStoredValue(Ctx,Dict,Name,ValueS)),!.
  199
  200getMajorIndexedValueLinear0(_Ctx,Dict,Name,Major,ValueS):-
  201   nthResult(Major,dict(Dict,Name,ValueS)),!,atrace.
  202
  203nthResult(N,Call):-flag(nthResult,_,N),nthResult0(Call,Rs),!,Rs=1.
  204nthResult0(Call,N):-Call,flag(nthResult,N,N-1),N=1.
  205nthResult0(_,0):-flag(nthResult,_,0),!.
  206
  207% ===============================================================================================
  208% getIndexedValue0
  209% ===============================================================================================
  210getIndexedValue0(Ctx,Dict,Name,[Major|Minor],Value):-
  211   getMajorMinorIndexedValue(Ctx,Dict,Name,Major,Minor,Value),!.
  212
  213getMajorMinorIndexedValue(Ctx,Dict,Name,Major,Minor,Value):-
  214   getMajorIndexedValue(Ctx,Dict,Name,Major,ValueS),!,
  215   getMajorMinorIndexedValue0(Ctx,Dict,Name,Major,Minor,ValueS,Value).
  216
  217getMajorMinorIndexedValue0(_Ctx,_Dict,_Name,_Major,Minor,ValueS,Value):-
  218   getMinorSubscript(ValueS,Minor,Value),!.
  219
  220getMajorMinorIndexedValue0(Ctx,Dict,Name,Major,[M|Minor],ValueS,Value):-
  221   prolog_must(is_list(ValueS)),
  222   length(ValueS,ValueSLen),
  223   MajorN is Major + 1,
  224   N is M - ValueSLen,
  225   getMajorMinorIndexedValue(Ctx,Dict,Name,MajorN,[N|Minor],Value),!.
  226
  227
  228numberFyList([],[]).
  229numberFyList([A|MajorMinor],[B|MajorMinorM]):-
  230  atom(A),atom_number(A,B),
  231  numberFyList(MajorMinor,MajorMinorM),!.
  232numberFyList([A|MajorMinor],[A|MajorMinorM]):-numberFyList(MajorMinor,MajorMinorM).
  233
  234isStarValue(Value):-ground(Value), \+([_,_|_]=Value),member(Value,[[ValueM],ValueM]),!,member(ValueM,['*','_']),!.
  235isEmptyValue([]):-atrace.
  236
  237xformOutput(Value,ValueO):-isStarValue(Value),!,atrace,Value=ValueO.
  238xformOutput(Value,ValueO):-listify(Value,ValueL),Value\==ValueL,!,xformOutput(ValueL,ValueO).
  239xformOutput(Value,Value).
  240
  241subscriptZeroOrOne(Major):-nonvar(Major),member(Major,[0,1,'0','1']).
 getMinorSubscript(Items, Minor, Value)
  246getMinorSubscript(ItemsO,Index,Value):-  \+(is_list(ItemsO)),answerOutput(ItemsO,Items),prolog_must(is_list(Items)),getMinorSubscript(Items,Index,Value),!.
  247getMinorSubscript(Items,'*',Value):- !,prolog_must(flatten(Items,Value)),!.
  248getMinorSubscript(Items,',',Value):- throw_safe(getMinorSubscript(Items,',',Value)), !,prolog_must(=(Items,Value)),!.
  249getMinorSubscript(Items,[A|B],Value):-!,getMinorSubscript(Items,A,ValueS),!,getMinorSubscript(ValueS,B,Value),!.
  250getMinorSubscript(Items,[],Value):-!,xformOutput(Items,Value),!.
  251getMinorSubscript(Items,ANum,Value):- \+ number(ANum),!,prolog_must(atom_number(ANum,Num)),!,getMinorSubscript(Items,Num,Value).
  252%%%
  253getMinorSubscript(Items,Num,Value):- prolog_must(is_list(Items)),length(Items,Len),Index is Len-Num,nth0(Index,Items,Value),is_list(Value),!.
  254getMinorSubscript([],1,[]):-!.
  255getMinorSubscript(Items,1,Value):- last(Items,Last), (is_list(Last)->Value=Last;Value=Items),!.
  256getMinorSubscript(Items,1,Value):- xformOutput(Items,Value),!,atrace.
  257getMinorSubscript(Items,Num,Value):-debugFmt(getMinorSubscriptFailed(Items,Num,Value)),fail.
  258
  259getUserDicts(User,Name,Value):-isPersonaUser(User),isPersonaPred(Name),once(getInheritedStoredValue(_Ctx,User,Name,Value)).
  260
  261isPersonaUser(User):-findall(User0,getContextStoredValue(_Ctx,User0,'is_type','agent'),Users),Users\==[],!,sort(Users,UsersS),!,member(User,UsersS).
  262isPersonaUser(_).
  263isPersonaPred(Name):-findall(Pred,(getContextStoredValue(_Ctx,_Dict,Pred,_Value),atom(Pred)),Preds),sort(Preds,PredsS),!,member(Name,PredsS).
  264
  265
  266
  267% ===============================================================================================
  268% substs dictionaries
  269% ===============================================================================================
  270addReplacement(Ctx,IDict,Find,Replace):-dictNameDictNameC(Ctx,IDict,before,Dict,before),!,addReplacement(Ctx,Dict,Find,Replace).
  271addReplacement(Ctx,SubstsNameI,Find,Replace):-
  272      convert_dictname(Ctx,SubstsNameI,SubstsName),SubstsNameI \== SubstsName,
  273      addReplacement(Ctx,SubstsName,Find,Replace).
  274addReplacement(Ctx,SubstsName,Find,Replace):-
  275      convert_substs(Find,FindM),
  276      convert_replacement(Ctx,Replace,ReplaceM),
  277      (Replace\==ReplaceM;Find\==FindM),!,
  278      addReplacement(Ctx,SubstsName,FindM,ReplaceM).
  279addReplacement(Ctx,Dict,Find,Replace):- immediateCall(Ctx,addReplacement(Dict,Find,Replace)),fail.
  280addReplacement(_Ctx,Dict,Find,Replace):- assertz(dict(substitutions(Dict),Find,Replace)),!.
  281
  282addReplacement(Dict,Find,Replace):-currentContext(addReplacement(Dict,Find,Replace),Ctx), addReplacement(Ctx,Dict,Find,Replace).
  283
  284
  285% ===============================================================================================
  286% context/name cleanups
  287% ===============================================================================================
  288dictNameDictNameC(Ctx,IDict,NameI,Dict,Name):-dictNameDictName(Ctx,IDict,NameI,Dict,Name),!, IDict+NameI \==Dict+Name, nop(debugFmt(IDict+NameI is Dict+Name)).
  289
  290dictNameDictName(Ctx,IDict,NameI,Dict,Name):- traceIf(IDict=[_,_,_]),hotrace(dictNameDictName0(Ctx,IDict,NameI,Dict,Name)).
  291dictNameDictName0(Ctx,_Dict,D:NameI,Dict,Name):- nonvar(D),!,dictNameDictName(Ctx,D,NameI,Dict,Name).
  292dictNameDictName0(Ctx,IDict,NameI,Dict,Name):- convert_dictname(Ctx,IDict,Dict),unresultifyL(Ctx,NameI,Name).
  293
  294unresultifyL(Ctx,NameI,Name):-unresultifyLL(Ctx,NameI,NameU),toLowerIfAtom(NameU,Name),!.
  295
  296unresultifyLL(Ctx,NameI,NameO):-unresultify(NameI,Name),NameI \== Name,!,unresultifyLL(Ctx,Name,NameO).
  297unresultifyLL(Ctx,NameI,NameO):-is_list(NameI),lastMember(Name,NameI),!,unresultifyLL(Ctx,Name,NameO).
  298unresultifyLL(_Ctx,Name,Name).
  299toLowerIfAtom(Dict,Down):-atom(Dict),downcase_atom(Dict,Down),!.
  300toLowerIfAtom(Dict,Dict).
  301
  302
  303
  304ensureValue(ValueO,ValueO):-!. %%TODO: remove this line
  305ensureValue(ValueO,['$value'(ValueO)]).
  306
  307% ===============================================================================================
  308% Add/Setting globals
  309% ===============================================================================================
  310withValueAdd(Ctx,Pred,IDict,NameI,Value):- dictNameDictNameC(Ctx,IDict,NameI,Dict,Name),!,withValueAdd(Ctx,Pred,Dict,Name,Value),!.
  311withValueAdd(Ctx,Pred,IDict,Name,Value):-is_list(IDict),!,trace,foreach(member(Dict,IDict),withValueAdd(Ctx,Pred,Dict,Name,Value)),!.
  312withValueAdd(Ctx,_Pred:Print,Dict,Name,Var):- neverActuallyAdd(Ctx,Print,Dict,Name,Var),!.
  313
  314withValueAdd(Ctx,Pred,Dict,Name,Var):-var(Var),!,withValueAdd(Ctx,Pred,Dict,Name,['$var'(Var)]).
  315withValueAdd(Ctx,Pred,Dict,Name,Atomic):-atomic(Atomic),Atomic\==[],!,withValueAdd(Ctx,Pred,Dict,Name,[Atomic]).
  316
  317withValueAdd(_Ctx,_Pred:_Print,Dict,Name,Value):-uselessNameValue(Dict,Name,Value),!.
  318withValueAdd(Ctx,_Pred:Print,Dict,Name,Value):-immediateCall(Ctx,call(Print,Ctx,Dict,Name,Value)),fail.
  319
  320withValueAdd(Ctx,Pred,Dict,Name,Value):-isStarValue(Value),!,nop(debugFmt(withValueAdd(Ctx,Pred,Dict,Name,Value))),traceIf(nonStarDict(Dict)).
  321%%withValueAdd(Ctx,Pred,Dict,default(Name),DefaultValue):-getAliceMem(Ctx,Pred,Dict,Name,'OM')->setAliceMem(Ctx,Dict,Name,DefaultValue);true.
  322withValueAdd(Ctx,Pred,Dict,Name,NonList):-( \+(is_list(NonList))),!,withValueAdd(Ctx,Pred,Dict,Name,[NonList]).
  323withValueAdd(Ctx,Pred:_Print,Dict,Name,Value):-checkDictIn(Value,ValueO),call(Pred,Ctx,Dict,Name,ValueO).
  324
  325nonStarDict(catefallback):-!,fail.
  326neverActuallyAdd(Ctx,Pred,Dict,Name,Var):-var(Var),debugFmt(x(neverActuallyAdd(Ctx,Pred,Dict,Name,Var))),!.
  327neverActuallyAdd(Ctx,Pred,Dict,topic,[TooGeneral]):-member(TooGeneral,[general]),debugFmt(x(neverActuallyAdd(Ctx,Pred,Dict,topic,TooGeneral))),!.
  328neverActuallyAdd(Ctx,Pred,Dict,Name,Var):- \+(ground(var(Var))),debugFmt(x(maybeNeverActuallyAdd(Ctx,Pred,Dict,Name,Var))),!.
  329
  330
  331uselessNameValue(_Dict,srcfile,_):-!.
  332uselessNameValue(_Dict,srcinfo,[nosrc]):-!.
  333
  334
  335
  336% ===============================================================================================
  337% Setting globals
  338% ===============================================================================================
  339setAliceMem(Dict,X,E):-currentContext(setAliceMem(Dict,X,E),Ctx), prolog_must(setAliceMem(Ctx,Dict,X,E)).
  340
  341% OLD VERSION OF NEXT STATMENT 
  342setAliceMem(Ctx,Dict,Name,Value):-withValueAdd(Ctx,setAliceMem0:setAliceMem,Dict,Name,Value),!.
  343setAliceMem(Ctx,Dict,default(Name),DefaultValue):- (getAliceMem(Ctx,Dict,Name,'OM')->setAliceMem(Ctx,Dict,Name,DefaultValue);true),!.
  344setAliceMem(Ctx,Dict,Name,Value):- prolog_must(setAliceMem_fallback(Ctx,Dict,Name,Value)),!.
  345
  346setAliceMem_fallback(Ctx,Dict,Name,Value):- setAliceMem0(Ctx,Dict,Name,Value),!.
  347setAliceMem_fallback([[fctx]],Dict,Name,Value):- asserta_dict(Dict,Name,Value),!.
  348
  349setAliceMem0(Ctx,Dict,Name,Value):- prolog_must((resetAliceMem0(Ctx,Dict,Name,Value))),!.
  350
  351% ===============================================================================================
  352% Inserting globals
  353% ===============================================================================================
  354insert1StValue(Ctx,IDict,Name,Value):-withValueAdd(Ctx,insert1StValue0:insert1StValue,IDict,Name,Value).
  355insert1StValue0(_Ctx,Dict,Name,Value):- asserta_dict(Dict,Name,Value),!.
  356
  357% ===============================================================================================
  358%    AIML Runtime Database
  359% ===============================================================================================
  360%%checkDictValue(_Value):-!.
  361checkDictValue(Value):-prolog_must(nonvar(Value)),atomic(Value),Value==[],!.
  362checkDictValue(Value):-prolog_must(dictValue(Value)),!.
  363
  364checkDictIn(Value,Value):-var(Value),!.
  365checkDictIn(Value,Value):-prolog_must(ground(Value)),(Value=['ERROR'|_];Value=[['ERROR'|_]|_]),!.
  366
  367checkDictIn(Value,Value):-warnIf( \+(checkDictValue(Value))).
  368
  369dictValue(V):-ground(V),dictValue0k(V),!.
  370dictValue(Value):-valuePresent(Value).
  371dictValue0k(['ERROR',understanding|_]):-!.
  372dictValue0k([X|_]):-dictValue0k(X).
  373
  374
  375resetAliceMem0(Ctx,IDict,NameI,ValueIn):- dictNameDictName(Ctx,IDict,NameI,Dict,Name),
  376   % for printing
  377   checkDictIn(ValueIn,Value),
  378   %%%traceIf(Dict==filelevel),
  379   currentContextValue(Ctx,Dict,Name,B),   
  380   debugFmt('/* ~q. */',[dict(Dict,Name,B->Value)]),
  381   % for cleaning
  382   clearContextValues(Ctx,Dict,Name),
  383   % for setting
  384   addNewContextValue(Ctx,Dict,Name,Value),!.
  385
  386%%getContextStoredValue(Ctx,Dict,Name,Value):-dictNameKey(Dict,Name,Key),debugOnError(current_value(Ctx,Key,Value)),dictValue(Value).
  387currentContextValue(Ctx,Scope,Name,Value):- dictNameKey(Scope,Name,Key),getCtxValueND(Ctx,Key,Value).
  388currentContextValue(Ctx,Dict,Name,Value):- debugOnError((getContextStoredValue(Ctx,Dict,Name,Value))),!.
  389currentContextValue(_Ctx,_Dict,_Name,OMValue):- omOrNil(OMValue).
  390
  391omOrNil([]):-!.
  392omOrNil('OM').
  393omOrNil(['Nothing']).
  394
  395
  396expire1Cache:-dict(N,_,_),number(N),retractall(dict(N,_,_)),fail.
  397expire1Cache:-dict(_,_,E),atom(E),atom_concat(evalsrai,_,E),retractall(dict(_,_,E)),fail.
  398expire1Cache:-dict(E,_,_),atom(E),atom_concat(evalsrai,_,E),retractall(dict(E,_,_)),fail.
  399
  400getContextStoredValue(Ctx,IDict,NameI,Value):-dictNameDictNameC(Ctx,IDict,NameI,Dict,Name),!,getContextStoredValue(Ctx,Dict,Name,Value).
  401getContextStoredValue(_Ctx,Dict,Name,ValueO):- copy_term(ValueO,ValueI),dict(Dict,Name,ValueI),
  402   checkDictValue(ValueI),
  403   ValueI=ValueO.
  404   %%prolog_must(unwrapValue(ValueI,ValueO)).
  405
  406removeContextValue(Ctx,IDict,NameI,Value):-dictNameDictName(Ctx,IDict,NameI,Dict,Name),checkDictValue(Value),copy_term(Value,Kill),ignore(retract(dict(Dict,Name,Kill))).
  407clearContextValues(Ctx,IDict,NameI):-dictNameDictName(Ctx,IDict,NameI,Dict,Name),retractall(dict(Dict,Name,_Value)).
  408
  409addNewContextValue(Ctx,IDict,NameI,Value):-dictNameDictNameC(Ctx,IDict,NameI,Dict,Name),!,addNewContextValue(Ctx,Dict,Name,Value).
  410addNewContextValue(Ctx,Dict,Name,OM):- OM=='OM',!,clearContextValues(Ctx,Dict,Name),!.
  411addNewContextValue(Ctx,Dict,Name,Value):- 
  412   prolog_must((dictNameKey(Dict,Name,Key), addNewContextValue(Ctx,Dict,Key,Name,Value))),!.
  413
  414addNewContextValue(Ctx,Dict,Key,Name,ValueIn):- 
  415   checkDictIn(ValueIn,Value),
  416   ifThen(nonvar(Key),addCtxValue(Ctx,Key,Value)),   
  417   ifThen(nonvar(Dict),ifThen(nonvar(Value),asserta_dict(Dict,Name,Value))),
  418   ifThen( \+(ground(Value)),debugFmt(addCtxValue(Ctx,Key,Value))).
  419
  420%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  421%%%%% pushInto1DAnd2DArray(Ctx,Tall,Wide,Ten,MultiSent,ConvThread)
  422%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  423isLinearMemStore:-true.
  424
  425pushInto1DAnd2DArray(Ctx,Tall,Wide,_Ten,MultiSent,ConvThread):- isLinearMemStore,!,
  426   %%atrace,
  427   splitSentences(MultiSent,Elements),
  428   maplist_safe(insert1StValue(Ctx,ConvThread,Tall),Elements),!,
  429   insert1StValue(Ctx,ConvThread,Wide,Elements),!.
  430
  431pushInto1DAnd2DArray(Ctx,Tall,Wide,Ten,MultiSent,ConvThread):-
  432   %%atrace,
  433   splitSentences(MultiSent,Elements),
  434   previousVars(Tall,TallPrevVars,Ten),
  435   maplist_safe(setEachSentenceThat(Ctx,ConvThread,Tall,TallPrevVars),Elements),!,
  436   
  437   previousVars(Wide,WidePrevVars,Ten),
  438   setEachSentenceThat(Ctx,ConvThread,Wide,WidePrevVars,Elements),
  439   !.
  440
  441setEachSentenceThat(Ctx,User,VarName,Vars,SR0):- cleanSentence(SR0,SR3),setEachSentenceThat0(Ctx,User,VarName,Vars,SR3),!.
  442
  443setEachSentenceThat0(_Ctx,_User,_VarName,_Vars,[]):-!.
  444setEachSentenceThat0(Ctx,User,_VarName,[Var],SR0):- 
  445   setAliceMem(Ctx,User,Var,SR0),!.
  446setEachSentenceThat0(Ctx,User,VarName,[PrevVar,Var|MORE],SR0):-
  447   getAliceMem(Ctx,User,default(Var,'Nothing'),Prev),
  448   setAliceMem(Ctx,User,PrevVar,Prev),
  449   setEachSentenceThat0(Ctx,User,VarName,[Var|MORE],SR0).
  450
  451
  452previousVars(That,[That],0):-!.
  453previousVars(That,[That],1):-!.
  454previousVars(That,[Item|Prevs],N):-indexOntoKey(That,N,Item), NN is N-1,previousVars(That,Prevs,NN).
  455
  456indexOntoKey(That,N,That):-subscriptZeroOrOne(N),!.
  457indexOntoKey(That,N,Item):-prolog_must(atomic(That)),atomic_list_concat_aiml([That,'(',N,')'],Item)