1% ===================================================================
    2% File 'logicmoo_util_ctx_frame.pl'
    3% Purpose: An Implementation in SWI-Prolog of Unwindable context frames
    4% Maintainer: Douglas Miles
    5% Contact: $Author: dmiles $@users.sourceforge.net ;
    6% Version: 'logicmoo_util_ctx_frame.pl' 1.0.0
    7% Revision:  $Revision: 1.1 $
    8% Revised At:   $Date: 2002/07/11 21:57:28 $
    9% ===================================================================
   10% ===================================================================
   11%  LocalContexts
   12%   They hold name-values in
   13%     -- assoc/1 lists
   14%     -- open tailed lists
   15%     -- frame/1 contains one or more of the above
= v(Value,Setter,KeyDestructor)
= frame(Named,Destructor,Ctx)
   23% well i played with a couple few differnt environment impls.. they have their pros cons.. one impl.. 
   24% that was unique is that an array of "binding pairs" live in an arraylist.. to be "in" an environment 
   25% it meant that you held an "index" into the arry list that as you went backwards you'd find your bindings.. each symbol had a java int field "lastBindingIndex" 
   26% .. that was a "hint" to where you could fastforward the backwards search .. end named binding context also had a "index" to when you leave a named block.. 
   27% you could quickly reset the top of an index.
   28
   29:-module(ctx_frame,[ctxHideIfNeeded/3,
   30         lastMember/2,
   31         lastMember/3,
   32         pushCtxFrame/3,
   33         getCtxValue/3,
   34         makeLocalContext/2,
   35         appendAttributes/4,
   36         currentContext/2]).   37
   38:-ensure_loaded('../logicmoo/logicmoo_util_library.pl').   39:-use_module(library('logicmoo/logicmoo_util_library.pl')).   40:-ensure_loaded(library('logicmoo/logicmoo_util_bugger.pl')).   41
   42:-ensure_loaded('../logicmoo/logicmoo_util_library.pl').   43:-use_module(library('logicmoo/logicmoo_util_library.pl')).   44:-use_module(library('logicmoo/logicmoo_util_ctx_frame.pl')).   45
   46
   47
   48currentContext(Name,X):-hotrace(makeLocalContext(Name,X)),!.
   49
   50% ===================================================================
   51:-dynamic(no_cyclic_terms/0).   52
   53no_cyclic_terms.
   54
   55makeLocalContext(Name,Ctx):-makeLocalContext1(Name,Ctx),!,setCtxValue(ctx,Ctx,Name),!.
   56
   57makeLocalContext1(Gensym_Key, [frame(Gensym_Key,no_destructor,[assoc(AL)|_])|_]):-    
   58   list_to_assoc([
   59    a-v(is_a,set_assoc,no_destructor(a)),
   60    a-v(is_a2,set_assoc,no_destructor(a)),
   61    b-v(is_b,set_assoc,no_destructor(b))],AL).
   62
   63
   64unwrapValue(HValue,TValue):-TValue==deleted,!,not(unwrapValue1(HValue,_)),!.
   65unwrapValue(HValue,TValue):-unwrapValue1(HValue,Value),!,TValue=Value.
   66
   67unwrapValue1(v(ValueHolder,_SetterFun,_KeyDestroyer),Value):-!,unwrapValue1(ValueHolder,Value).
   68unwrapValue1(deleted,_):-!,fail.
   69unwrapValue1(Value,Value):-!.
   70
   71bestSetterFn(v(_,Setter,_),_OuterSetter,Setter):-!.
   72bestSetterFn(_Value,OuterSetter,OuterSetter).
   73
   74getCtxValue(Name,Ctx,Value):-checkCtx(Ctx), hotrace(( get_ctx_holder(Ctx,Holder),get_o_value(Name,Holder,HValue,_Setter),!, unwrapValue(HValue,Value))),!.
   75getCtxValue(Name,CtxI,Value):-checkCtx(CtxI),lastMember(Ctx,CtxI),hotrace(( get_ctx_holder(Ctx,Holder),get_o_value(Name,Holder,HValue,_Setter),!, unwrapValue(HValue,Value))),!.
   76
   77setCtxValue(Name,Ctx,Value):-checkCtx(Ctx),get_ctx_holder(Ctx,Holder),get_o_value(Name,Holder,HValue,Setter),unwrapValue(HValue,CurrentValue),!,(CurrentValue=Value;call(Setter,Value)),!.
   78setCtxValue(Name,Ctx,Value):-checkCtx(Ctx),addCtxValue1(Name,Ctx,Value),!.
   79
   80addCtxValue(Name,Ctx,Value):-checkCtx(Ctx),addCtxValue1(Name,Ctx,Value),!.
   81addCtxValue1(Name,Ctx,Value):-get_ctx_holderFreeSpot(Ctx,Name=v(Value,Setter,Destructor),Destructor),!,ignore(Setter=no_setter(Name)).
   82
   83remCtxValue(Name,Ctx,_Value):-checkCtx(Ctx),setCtxValue(Name,Ctx,deleted),!.
   84
   85
   86pushCtxFrame(Name,Ctx,NewValues):-checkCtx(Ctx),get_ctx_holderFreeSpot(Ctx,Holder,GuestDest),!,Holder=frame(Name,GuestDest,NewValues).
   87
   88popCtxFrame(Name,Ctx,PrevValues):-checkCtx(Ctx),get_ctx_frame_holder(Ctx,Name,Frame),Frame = frame(Name,Destructor,PrevValues),Destructor,!.
   89
   90checkCtx(Ctx):-nonvar(Ctx),!.
   91checkCtx(Ctx):-makeLocalContext(broken,Ctx),!.
   92
   93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   94%%%%% get the frame holder
   95%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   96get_ctx_frame_holder(Ctx,Name,R):-compound(Ctx),get_ctx_frame_holder1(Ctx,Name,R).
   97get_ctx_frame_holder1(v(_,_,_),_Name,_R):-!,fail.
   98get_ctx_frame_holder1(frame(Name,Dest,Ctx),Name,R):- R = frame(Name,Dest,Ctx),!.
   99get_ctx_frame_holder1([H|T],Name,R):- nonvar(H), !, ( get_ctx_frame_holder(T,Name,R);get_ctx_frame_holder1(H,Name,R)) .
  100%%get_ctx_frame_holder1(Ctx,Name,Ctx):-!,get_ctx_frame_holder1(Ctx,Name,R).
  101
  102
  103%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  104%%%%% get the holders areas last in first out %%%%%
  105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  106%%%%% get_ctx_holder(+Ctx, -PlaceToSearch),
  107
  108get_ctx_holder(Ctx,R):-compound(Ctx),get_ctx_holder1(Ctx,R).
  109get_ctx_holder1([H|T],R):- nonvar(H), !, ( get_ctx_holder(T,R);get_ctx_holder1(H,R)) .
  110get_ctx_holder1(v(_,_,_),_R):-!,fail.
 get_ctx_holder(Ctx, R)
  111get_ctx_holder1(frame(_N,_Dest,Ctx),R):-!,get_ctx_holder(Ctx,R).
  112%get_ctx_holder1(Ctx,R):- functor(Ctx,F,A),A<3,!,fail.
  113get_ctx_holder1(assoc(Ctx),assoc(Ctx)):-!.
  114get_ctx_holder1(Ctx,Ctx).
  115
  116
  117%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  118%%%%% find a free area to place a: vv(name,val) %%%%%
  119%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  120%%%%% get_ctx_holderFreeSpot(+Ctx, -Put_NV, -CallToRemoveNV)
  121
  122get_ctx_holderFreeSpot(Ctx,NamedValue,no_destructor(holder)):-no_cyclic_terms,!,get_ctx_holderFreeSpot0(Ctx,NamedValue,_NO_Destruct),!.
  123get_ctx_holderFreeSpot(Ctx,NamedValue,Destruct):-get_ctx_holderFreeSpot0(Ctx,NamedValue,Destruct).
  124
  125get_ctx_holderFreeSpot0(Ctx,NamedValue,Destruct):-compound(Ctx),get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct).
  126
  127get_ctx_holderFreeSpot1(assoc(_Ctx),_,_):-!,fail.
  128get_ctx_holderFreeSpot1(frame(Key,_Inner_Dest,Ctx),NamedValue,Destruct):- nonvar(Key), !, get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct).
  129get_ctx_holderFreeSpot1(Ctx,NamedValue,Destruct):-functor(Ctx,F,A),!,get_ctx_holderFreeSpot1(Ctx,F,A,NamedValue,Destruct).
  130
  131get_ctx_holderFreeSpot1(Ctx,'.',2,NamedValue,nb_setarg(Ctx,2,NEXT)):-arg(2,Ctx,Try1), var(Try1),!, Try1 = [NamedValue|NEXT].
  132get_ctx_holderFreeSpot1(Ctx,'.',2,NamedValue,Destruct):-arg(2,Ctx,Try2),get_ctx_holderFreeSpot0(Try2,NamedValue,Destruct).
  133
  134%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,_):-!,fail.
  135%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,nb_setarg(Ctx,N,NEXT)):-arg(N,Ctx,Try3),var(Try3),!, Try3 = [NamedValue|NEXT].
  136%%get_ctx_holderFreeSpot1(Ctx,_,_,NamedValue,Destruct):-arg(N,Ctx,Try4),get_ctx_holderFreeSpot0(Try4,NamedValue,Destruct).
  137
  138
  139%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  140%%%%% find the value holder associated with a keyname
  141%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  142get_ctx_value(Name,Ctx,Value,Setter):-nonvar(Name),var(Value),get_o_value(Name,Ctx,Value,OuterSetter),bestSetterFn(Value,OuterSetter,Setter).
  143
  144get_o_value(Name,Ctx,Value,no_setter(Name)):-no_cyclic_terms,!,get_o_value0(Name,Ctx,Value,_HIDE_Setter),!.
  145get_o_value(Name,Ctx,Value,Setter):-hotrace(get_o_value0(Name,Ctx,Value,Setter)),!.
  146
  147get_o_value0(Name,Ctx,Value,Setter):-compound(Ctx),get_o_value1(Name,Ctx,Value,Setter).
  148get_o_value1(Name,assoc(Ctx),Value,set_assoc):- get_assoc(Name,Ctx,Value),!.
  149get_o_value1(Name,frame(Key,_Inner_Dest,Ctx),Value,Setter):- nonvar(Key), get_o_value0(Name,Ctx,Value,Setter),!.
  150get_o_value1(Name,[H|T],Value,Setter):- !,(get_o_value0(Name,T,Value,Setter);get_o_value1(Name,H,Value,Setter)).
  151get_o_value1(Name,Pred,Value,Setter):-functor(Pred,F,A),!,get_n_value(Name,Pred,F,A,Value,Setter).
  152
  153get_n_value(Name,Name,_F,_A,_Value,_):-!,fail.
  154get_n_value(Name,Pred,Name,1,Value,nb_setarg(1,Pred)):-arg(1,Pred,Value).
  155get_n_value(Name,Pred,Name,_,Value,Setter):- arg(1,Pred,Value),!,arg(2,Pred,Setter). 
  156get_n_value(Name,Pred,Dash,2,Value,nb_setarg(2,Pred)):-arg(1,Pred,Name),member(Dash,[=,-,vv]),!, arg(2,Pred,Value).
  157%%get_n_value(Name,Pred,'.',2,Value,Setter):-arg(2,Pred,Try1), get_o_value0(Name,Try1,Value,Setter);(arg(1,Pred,Try2),get_o_value0(Name,Try2,Value,Setter)).
  158%%get_n_value(Name,Pred,_,_,Value,Setter):- !, arg(_,Pred,Try2),get_o_value0(Name,Try2,Value,Setter).
  159
  160
  161lastMember(_E,List):-var(List),!,fail.
  162lastMember(E,[H|List]):-lastMember(E,List);E=H.
  163
  164lastMember(E,List,Rest):-lastMember(E,List),!,delete_safe(List,E,Rest),!.
  165
  166delete_safe(List,_E,Rest):-var(List),!,Rest=List.
  167delete_safe(List,E,Rest):-is_list(List),!,delete(List,E,Rest).
  168delete_safe([H|List],E,Rest):- H==E,!,delete_safe(List,E,Rest).
  169delete_safe([H|List],E,[H|Rest]):-delete_safe(List,E,Rest).
  170
  171
  172getKeyValue(FullList,N=V):-lastMember(N=V,FullList),!.
  173%%addKeyValue(FullList,N=V):-nonvar(N),!,append(_Closed,[N=V|_],FullList),!.
  174addKeyValue(FullList,NV):- prolog_must((not(ground(FullList)),nonvar(NV))),append(_Closed,[NV|_],FullList),!.
  175
  176
  177lastMember2(E,List):-to_open_list(_,Closed,_Open,List),reverse(Closed,Rev),member(E,Rev).
  178
  179%lastMember(End,List) :- append(_,[End|_],List).
  180
  181ctxHideIfNeeded(_Ctx,Before,After):-hideIfNeeded(Before,After),!.
  182
  183hideIfNeeded(I,I):- (var(I);atomic(I)),!.
  184hideIfNeeded([I|_],ctx):-nonvar(I),I=frame(_,_,_),!.
  185hideIfNeeded([I|_],ctx):-nonvar(I),functor(I,frame,_),!.
  186hideIfNeeded([I|N],[I0|N0]):-!,hideIfNeeded(I,I0),hideIfNeeded(N,N0),!.
  187hideIfNeeded(Comp,Comp2):-compound(Comp),Comp=..[L,I|ST],hideIfNeeded([I|ST],[OI|OIST]),Comp2=..[L,OI|OIST],!.
  188hideIfNeeded(I,I):-!.
  189
  190
  191to_open_list(FullList,Closed,Open,FullList) :- append(Closed,Open,FullList),var(Open),!.
  192to_open_list(Closed,Closed,Open,FullList) :- append(Closed,Open,FullList),!.
  193
  194
  195revappend([], Ys, Ys).
  196revappend([X|Xs], Ys, Zs) :- revappend(Xs, [X|Ys], Zs).
  197
  198reverseA(Xs,Ys) :- revappend(Xs,[],Ys).
  199
  200appendAttributes(_Ctx,L,R,AA):-hotrace((mergeAppend0(L,R,A),list_to_set_safe(A,AA))),!.
  201
  202mergeAppend0(L,R,R):-var(L),!,var(R),!.
  203mergeAppend0(L,R,A):-var(R),append(L,R,A),!.
  204mergeAppend0(L,R,A):-var(L),append(L,R,A),!.
  205mergeAppend0(L,[R|RR],A):-eqmember(R,L),mergeAppend0(L,RR,A).
  206mergeAppend0([L|LL],R,A):-eqmember(L,R),mergeAppend0(LL,R,A).
  207mergeAppend0(L,R,A):-append(L,R,A).
  208
  209eqmember(E,List):-copy_term_numvars(E:List,E0:List0),member(E0,List0).
  210copy_term_numvars(OLD,NEW):-copy_term(OLD,NEW),numbervars(NEW,0,_)