1/*  Part of SWI-Prolog
    2    Author:        Douglas R. Miles, Jan Wielemaker
    3    E-mail:        logicmoo@gmail.com, jan@swi-prolog.org
    4    WWW:           http://www.swi-prolog.org http://www.logicmoo.org
    5    Copyright (C): 2015, University of Amsterdam
    6                                    VU University Amsterdam
    7    This program is free software; you can redistribute it and/or
    8    modify it under the terms of the GNU General Public License
    9    as published by the Free Software Foundation; either version 2
   10    of the License, or (at your option) any later version.
   11    This program is distributed in the hope that it will be useful,
   12    but WITHOUT ANY WARRANTY; without even the implied warranty of
   13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14    GNU General Public License for more details.
   15    You should have received a copy of the GNU General Public
   16    License along with this library; if not, write to the Free Software
   17    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   18    As a special exception, if you link this library with other files,
   19    compiled with a Free Software compiler, to produce an executable, this
   20    library does not by itself cause the resulting executable to be covered
   21    by the GNU General Public License. This exception does not however
   22    invalidate any other reasons why the executable file might be covered by
   23    the GNU General Public License.
   24*/
   25
   26:- module(multivar,
   27 [
   28   test_case_1/0,
   29   test_case_2/0,
   30   test_case_3/0,
   31   test_case_4/0
   32  /* mdwq/1, 
   33		  plvar/1,
   34          nb_var/1, nb_var/2,
   35          vdict/1, vdict/2,
   36		  un_mv/1, un_mv1/1,
   37		  mv_peek_value/2,mv_peek_value1/2,
   38		  mv_set/2,mv_set1/2,
   39		  mv_add1/2,mv_allow/2,
   40		  ic_text/1,
   41
   42   is_mv/1, multivar/1 % create special varaible that cannot be bound
   43   */
   44   ]).   45
   46:- use_module(logicmoo_common).   47:- meta_predicate user:attvar_variant(0,0).   48:- use_module(library(option),[dict_options/2,option/2]).   49
   50:- export((mdwq/1, 
   51		  plvar/1,
   52          nb_var/1, nb_var/2,
   53          vdict/1, vdict/2,
   54		  un_mv/1, un_mv1/1,
   55		  mv_peek_value/2,mv_peek_value1/2,
   56      mv_set_values/2,
   57		  %mv_set/2,
   58      mv_set1/2,
   59		  mv_add1/2,mv_allow/2,
   60		  ic_text/1, xvarx/1, is_mv/1, multivar/1)).   61
   62%:- set_prolog_flag(access_level,system).
   63%:- set_prolog_flag(gc,false).
   64
   65% use_module(library(multivar)),call(multivar(X)),trace,X=2.
   66
   67mdwq(Q):- format(user_error,'~NMWQ: ~q~n',[Q]).
   68
   69:- meta_predicate(mdwq_call(*)).   70mdwq_call(Q):- !, call(Q).
   71%mdwq_call(Q):- call(Q) *-> mdwq(success:Q); (mdwq(failed:Q),!,fail).
   72
   73:- define_into_module(system,mdwq_call/1).   74
   75:- create_prolog_flag(attr_pre_unify_hook,false,[keep(true)]).   76:- create_prolog_flag(attr_pre_unify_hook,true,[keep(true)]).   77
   78
   79
   80
   81:- if(current_prolog_flag(attr_pre_unify_hook,true)).   82
   83:- module_transparent(user:attr_pre_unify_hook/3).   84:- user:export(user:attr_pre_unify_hook/3).   85
   86:- '$set_source_module'('$attvar').   87
   88:- module_transparent(system : = /2).   89:- module_transparent(wakeup/2).   90:- module_transparent('$wakeup'/1).   91wakeup(wakeup(Attribute, Value, Rest),M) :- !,
   92    begin_call_all_attr_uhooks(Attribute, Value, M),
   93    '$wakeup'(Rest).
   94wakeup(_,_).
   95
   96:- import(user:attr_pre_unify_hook/3).   97:- module_transparent(user:attr_pre_unify_hook/3).   98% replaces call_all_attr_uhooks
   99begin_call_all_attr_uhooks(att('$VAR$', IDVar, Attrs),Value, M) :- !,
  100    M:attr_pre_unify_hook(IDVar, Value, Attrs).
  101
  102begin_call_all_attr_uhooks(Attribute, Value, M) :-
  103    call_all_attr_uhooks(Attribute, Value, M).
  104
  105:- module_transparent(call_all_attr_uhooks/3).  106call_all_attr_uhooks(att(Module, AttVal, Rest), Value, M) :- !,
  107    uhook(Module, AttVal, Value, M),
  108    call_all_attr_uhooks(Rest, Value, M).
  109call_all_attr_uhooks(_, _, _).
  110
  111:- module_transparent(uhook/4).  112uhook(freeze, Goal, Y, M) :-
  113 M:(
  114    !,
  115    (   attvar(Y)
  116    ->  (   get_attr(Y, freeze, G2)
  117        ->  put_attr(Y, freeze, '$and'(G2, Goal))
  118        ;   put_attr(Y, freeze, Goal)
  119        )
  120    ;   '$attvar':unfreeze(Goal)
  121    )).
  122
  123uhook(Module, AttVal, Value, M) :-
  124  M:(
  125    true,
  126    Module:attr_unify_hook(AttVal, Value)).
  127
  128
  129:- ((abolish('$wakeup'/1),'$attvar':asserta('$wakeup'(M:G):-wakeup(G,M)))).  130:- meta_predicate('$wakeup'(:)).  131
  132%:- all_source_file_predicates_are_transparent.
  133:- debug(logicmoo(loader),'~N~p~n',[all_source_file_predicates_are_transparent(File)]),
  134    forall((source_file(ModuleName:P,File),functor(P,F,A)),
  135      ignore(( 
  136        ignore(( \+ atom_concat('$',_,F), ModuleName:export(ModuleName:F/A))),
  137            \+ (predicate_property(ModuleName:P,(transparent))),
  138                   % ( nop(dmsg(todo(module_transparent(ModuleName:F/A))))),
  139                   (module_transparent(ModuleName:F/A))))).  140
  141:- '$set_source_module'('multivar').  142
  143:- module_transparent(attr_pre_unify_hook_m/4).  144:- dynamic(attr_pre_unify_hook_m/4).  145:- export(attr_pre_unify_hook_m/4).  146attr_pre_unify_hook_m(IDVar, Value, _, M):- \+ attvar(IDVar),!, M:(IDVar=Value).
  147attr_pre_unify_hook_m(Var,Value,Rest, M):- 
  148  mdwq_call('$attvar':call_all_attr_uhooks(Rest, Value, M)),
  149  nop(M:mv_add1(Var,Value)).
  150
  151:- module_transparent(attr_pre_unify_hook/3).  152:- dynamic(attr_pre_unify_hook/3).  153:- export(attr_pre_unify_hook/3).  154attr_pre_unify_hook(Var,Value,Rest):- strip_module(Rest,M,_), attr_pre_unify_hook_m(Var,Value,Rest,M).
  155           
  156
  157
  158:- else.  159
  160
  161:- module_transparent(user:meta_unify/3).  162user:meta_unify(Var,Rest,Value):- user:attr_pre_unify_hook(Var,Value,Rest).
  163
  164%-----------------------------------------------------------------
  165% Blugened in version of verify_attributes/3
  166
  167
  168user:attr_pre_unify_hook(IDVar, Value, _):- \+ attvar(IDVar),!, IDVar=Value.
  169/*
  170user:attr_pre_unify_hook(IDVar, Value, Attrs):-
  171  call_verify_attributes(Attrs, Value, IDVar, [], Goals),
  172  nop(attv_bind(IDVar, Value)),
  173  maplist(call,Goals).
  174*/
  175%user:attr_pre_unify_hook(IDVar, Value, Attrs):-  '$attvar':call_all_attr_uhooks(att('$VAR$',IDVar,Attrs),Value).
  176user:attr_pre_unify_hook(Var,Value,Rest):- 
  177  mdwq_call('$attvar':call_all_attr_uhooks(Rest, Value)),
  178  nop(mv_add1(Var,Value)).
  179
  180:- endif.  181
  182
  183
  184call_verify_attributes([], _, _) --> [].
  185call_verify_attributes(att(Module, _, Rest), Value, IDVar) -->
  186    { Module:verify_attributes(IDVar, Value, Goals) }, 
  187    Goals,
  188    call_verify_attributes(Rest, Value, IDVar).
  189
  190% make code us verify_attributes/3 instead of attr_unify_hook/2
  191use_va(Var):-
  192  put_attr(Var,'$VAR$',Var).
  193
  194%-----------------------------------------------------------------
  195
  196verify_attributes(Var, _, Goals) :-
  197   get_attr(Var, '$VAR$', Info), !,
  198   \+ contains_var(Var,Info),
  199  Goals=[].
  200
  201verify_attributes(_, _, []).
  202
  203
  204% Swi-pre-unify Case#1  not able to emulate in SWI  due to "Identity"
  205
  206swiu_case_1 :-
  207 use_va(Y), put_attr(Y,'$VAR$',Y),
  208 Y = 4201.
  209
  210% must fail
  211test_case_1 :-  \+  swiu_case_1.
  212
  213
  214%-----------------------------------------------------------------
  215
  216% Swi-pre-unify Case#2   "Identity"
  217
  218swiu_case_2 :-
  219   use_va(Y), put_attr(Y, '$VAR$', al(Y,a(X))),
  220   X = 420,
  221   Y = 420.
  222
  223% must fail
  224test_case_2 :-  \+  swiu_case_2.
  225
  226
  227% -----------------------------------------------------------------
  228% Swi-pre-unify Case #3   "Identity" (fixed from last email)
  229
  230swiu_case_3 :-
  231  use_va(Y), put_attr(Y,'$VAR$', a(420)),
  232  Y = 420.
  233
  234% must Succeed
  235test_case_3 :-  swiu_case_3.
  236
  237
  238
  239%-----------------------------------------------------------------
  240% Swi-pre-unify Case #4  more "Identity"
  241
  242swiu_case_4 :-
  243 use_va(Y), put_attr(Y,'$VAR$', X),
  244 X = 420,
  245 Y = 420.
  246
  247% must succeed
  248test_case_4 :-  swiu_case_4.
  249
  250
  251% ==========================================
  252%  Unify hook
  253% ==========================================
  254
  255% 'unify':attr_unify_hook(_,_).  % OR tracing with 'unify':attr_unify_hook(N,Var):- mdwq(meta_unify_hook(N,Var)).
  256
  257
  258% multivar(Var):- put_attr(Var,unify,Var).
  259% multivar(Var):- put_attr(Var,'$VAR$',Var).
  260
  261xvarx(Var):- 
  262   get_attr(Var,'$VAR$',_MV)-> true ; 
  263   (get_attrs(Var,Attrs) -> put_attrs(Var,att('$VAR$',Var,Attrs)) ;
  264   (true -> put_attrs(Var,att('$VAR$',Var,[])))).
  265:- export(xvarx/1).  266:- system:import(xvarx/1).  267
  268 
  269
  270% is_mv(Var):- attvar(Var),get_attr(Var,unify,Waz),var(Waz).
  271is_mv(Var):- attvar(Var),get_attr(Var,'$VAR$',_Waz).
  272
  273% ==========================================
  274% ATOM_dvard override TODO
  275% ==========================================
  276
  277'$VAR$':attr_unify_hook(_,_).
  278'$VAR$':attribute_goals(Var) --> {is_implied_xvarx(Var)}->[] ; [xvarx(Var)].
  279
  280is_implied_xvarx(MV):- get_attrs(MV,ATTS),is_implied_xvarx(MV,ATTS).
  281is_implied_xvarx(MV,att(M,Val,ATTS)):- ((Val==MV, \+ atom_concat('$',_,M)) -> true ; is_implied_xvarx(MV,ATTS)).
  282% ==========================================
  283% Variant override TODO
  284% ==========================================
  285
  286'variant':attr_unify_hook(_,_).
  287user:attvar_variant(N,Var):- (N==Var -> true ;  mdwq_call( \+ \+ =(N,Var) )).
  288
  289% ==========================================
  290% reference override TODO
  291% ==========================================
  292
  293'references':attr_unify_hook(_,_).
  294user:attvar_references(N,Var):- (N==Var -> true ;  mdwq_call( \+ \+ =(N,Var) )).
  295
  296
  297% ==========================================
  298% Sets values
  299% ==========================================
  300multivar(Var):- var(Var)->multivar1(Var);(term_variables(Var,Vars),maplist(multivar1,Vars)).
  301multivar1(Var):- xvarx(Var),(get_attr(Var,'$value',some(Var,_))->true; put_attr(Var,'$value',some(Var,[]))).
  302'$value':attr_unify_hook(some(Was,Values),Becoming):- var(Was),attvar(Becoming),!,mv_add_values(Becoming,Values).
  303'$value':attr_unify_hook(some(Var,_Values),Value):- mv_add1(Var,Value).
  304
  305%'$value':attribute_goals(_)-->!.
  306'$value':attribute_goals(Var)--> {get_attr(Var,'$value',some(Var,Values))},[mv_set_values(Var,Values)].
  307
  308
  309mv_set_values(Var,Values):- put_attr(Var,'$value',some(Var,Values)).
  310mv_set1(Var,Value):- put_attr(Var,'$value',some(Var,[Value])).
  311mv_add1(Var,NewValue):- Var==NewValue,!.
  312mv_add1(Var,NewValue):- mv_prepend1(Var,'$value',NewValue).
  313mv_add_values(Becoming,Values):- maplist(mv_add1(Becoming),Values).
  314
  315
  316mv_prepend1(Var,Mod,Value):- get_attr(Var,Mod,some(Var,Was))->(prepend_val(Value,Was,New)->put_attr(Var,Mod,some(Var,New)));put_attr(Var,Mod,some(Var,[Value])).
  317mv_prepend_values(Becoming,Mod,Values):- maplist(mv_prepend1(Becoming,Mod),Values).
  318
  319prepend_val(Value,[],[Value]).
  320prepend_val(Value,Was,[Value|NewList]):- pred_delete_first(call(==,Value),Was,NewList).
  321
  322pred_delete_first(_,[],[]).
  323pred_delete_first(P,[Elem0|NewList],NewList):- call(P,Elem0),!.
  324pred_delete_first(P,[ElemKeep|List],[ElemKeep|NewList]):-pred_delete_first(P,List,NewList).
  325
  326% faster than mv_prepend1 - might use?
  327mv_prepend(Var,Mod,Value):- get_attr(Var,Mod,some(Var,Was))->
  328   put_attr(Var,Mod,some(Var,[Value|Was]));
  329   put_attr(Var,Mod,some(Var,[Value])).
  330
  331% ==========================================
  332% Peeks values
  333% ==========================================
  334
  335mv_peek_value(Var,Value):- mv_members(Var,'$value',Value).
  336mv_peek_value1(Var,Value):- mv_peek_value(Var,Value),!.
  337
  338
  339
  340% ==========================================
  341% Peeks any
  342% ==========================================
  343
  344mv_members(Var,Mod,Value):- get_attr(Var,Mod,some(_,Values)),!,member(Value,Values).
  345% mv_get_attr1(Var,Mod,Value):- mv_members(Var,Mod,Value),!.
  346           
  347
  348bless_plvar(V):- nonvar(V),!.
  349bless_plvar(V):- attvar(V),!.
  350bless_plvar(V):- xvarx(V),!.
  351
  352project_lst_goals_as(Var,Attr,Pred,Res):- 
  353  get_attr(Var,Attr,some(Var,List)),
  354  (List==[] -> Res=[] ;   
  355   List=[V] -> (Call=..[Pred,Var,V], Res=[Call]) ;
  356   (Call=..[Pred,Var], Res=[maplist(Call,List)])).
  357
  358% ==========================================
  359% Allow-only values
  360% ==========================================
  361
  362check_allow(Var,Value):- get_attr(Var,'$allow',some(Var,Allow)), memberchk_variant_mv(Value,Allow).
  363mv_allow(Var,Allow):- bless_plvar(Allow),mv_prepend(Var,'$allow',Allow).
  364'$allow':attr_unify_hook(some(Var,Allow),Value):- \+ ((memberchk_variant_mv(Value,Allow)->true;get_attr(Var,ic_text,_))),!,fail.
  365'$allow':attr_unify_hook(some(Was,Values),Becoming):- 
  366  ignore((var(Was),attvar(Becoming),!,mv_prepend_values(Becoming,'$allow',Values))).
  367'$allow':attribute_goals(Var)--> {project_lst_goals_as(Var,'$allow',mv_allow,Res)},Res.
  368
  369% ==========================================
  370% Disallow-only values
  371% ==========================================
  372
  373check_disallow(Var,Value):- (get_attr(Var,'$disallow',some(Var,Disallow)) -> \+ memberchk_variant_mv(Value,Disallow) ; true).
  374mv_disallow(Var,Disallow):- bless_plvar(Disallow),mv_prepend(Var,'$disallow',Disallow).
  375'$disallow':attr_unify_hook(some(_Var,Disallow),Value):-  memberchk_variant_mv(Value,Disallow),!,fail.
  376'$disallow':attr_unify_hook(some(Was,Values),Becoming):- 
  377   ignore((var(Was),attvar(Becoming),!,mv_prepend_values(Becoming,'$disallow',Values))).
  378'$disallow':attribute_goals(Var)--> {project_lst_goals_as(Var,'$disallow',mv_disallow,Res)},Res.
  379
  380 
  381%'$disallow':attribute_goals(Var)--> {get_attr(Var,'$disallow',some(Var,Disallow))},[mv_disallow(Var,Disallow)].
 memberchk_variant_mv(?X, :TermY0) is semidet
Memberchk based on == for Vars else =@= .
  387memberchk_variant_mv(X, List) :- is_list(List),!, \+ atomic(List), C=..[v|List],(var(X)-> (arg(_,C,YY),X==YY) ; (arg(_,C,YY),X =@= YY)),!.
  388memberchk_variant_mv(X, Ys) :-  nonvar(Ys), var(X)->memberchk_variant0(X, Ys);memberchk_variant1(X,Ys).
  389memberchk_variant0(X, [Y|Ys]) :-  X==Y  ; (nonvar(Ys),memberchk_variant0(X, Ys)).
  390memberchk_variant1(X, [Y|Ys]) :-  X =@= Y ; (nonvar(Ys),memberchk_variant1(X, Ys)).
  391
  392
  393member_predchk_variant_mv(X, Ys) :- each_from(Ys, E), call(E,X).
  394
  395%each_from(List,E):- is_list(List), \+ atomic(List), C=..[v|List], !, arg(_, C, E).
  396each_from(Ys, E) :- nonvar(Ys), Ys=[Y|Ys2], (E=Y ; each_from(Ys2, E)).
  397% each_from(List,E):- member(E,List).
  398
  399
  400% ==========================================
  401% Allow_p-only values
  402% ==========================================
  403
  404% ?- xvarx(X),mv_allow_p(X, writeln),X=1,X=2.
  405
  406check_allow_p(Var,Value):- get_attr(Var,'$allow_p',some(Var,Allow_p)), memberchk_variant_mv(Value,Allow_p).
  407mv_allow_p(Var,Allow_p):- bless_plvar(Allow_p),mv_prepend(Var,'$allow_p',Allow_p).
  408'$allow_p':attr_unify_hook(some(Var,Allow_p),Value):- \+ ((memberchk_variant_mv(Value,Allow_p)->true;get_attr(Var,ic_text,_))),!,fail.
  409'$allow_p':attr_unify_hook(some(Was,Values),Becoming):- 
  410  ignore((var(Was),attvar(Becoming),!,mv_prepend_values(Becoming,'$allow_p',Values))).
  411'$allow_p':attribute_goals(Var)--> {project_lst_goals_as(Var,'$allow_p',mv_allow_p,Res)},Res.
  412
  413% ==========================================
  414% Disallow_p-only values
  415% ==========================================
  416
  417check_disallow_p(Var,Value):- (get_attr(Var,'$disallow_p',some(Var,Disallow_p)) -> \+ memberchk_variant_mv(Value,Disallow_p) ; true).
  418mv_disallow_p(Var,Disallow_p):- bless_plvar(Disallow_p),mv_prepend(Var,'$disallow_p',Disallow_p).
  419'$disallow_p':attr_unify_hook(some(_Var,Disallow_p),Value):-  memberchk_variant_mv(Value,Disallow_p),!,fail.
  420'$disallow_p':attr_unify_hook(some(Was,Values),Becoming):- 
  421   ignore((var(Was),attvar(Becoming),!,mv_prepend_values(Becoming,'$disallow_p',Values))).
  422'$disallow_p':attribute_goals(Var)--> {project_lst_goals_as(Var,'$disallow_p',mv_disallow_p,Res)},Res.
  423
  424% ==========================================
  425% Label values
  426% ==========================================
  427
  428un_mv(Var):-del_attr(Var,'$VAR$')->(mv_peek_value(Var,Value)*->Var=Value;true);true.
  429un_mv1(Var):-del_attr(Var,'$VAR$')->ignore(mv_peek_value1(Var,Var));true.
  430
  431
  432% ==========================================
  433% Examples
  434% ==========================================
  435/*
  436
  437% ?- multivar(X),X=1,X=2,un_mv(X),writeq(X).
  438% ?- multivar(X),X=x(X),mv_allow(X,hello),mv_allow(X,hi), X=hello,X=hi,mv_peek_value(X,V)
  439% ?- multivar(X),mv_allow(X,hello),mv_allow(X,hi), X=hello,X=hi,writeq(X).
  440% ?- multivar(X),mv_allow(X,hello),mv_allow(X,hi),X=hello,X=hi,X=hello,un_mv(X).
  441% ?- multivar(X),mv_allow(X,hello),mv_allow(X,hi),X=hello,X=hi,X=hello,!,un_mv(X)
  442% ?- multivar(X),mv_allow(X,One),X=good,!,un_mv(X).
  443% ?- \+ (multivar(X),mv_allow(X,One),X=good,X=bad,un_mv(X)).
  444
  445
  446% ?- \+ (ic_text(X),X="GOOD",X=good,X=one).
  447% ?- ic_text(X),X=good,X=gooD,un_mv(X).
  448% ?- ic_text(X),X="GOOD",X=good.
  449% ?- ic_text(X),mv_allow(X,"GOOD"),mv_allow(X,"BAD"),X=good,X=baD.
  450% ?- \+ (ic_text(X),mv_allow(X,"GOOD"),mv_allow(X,"BAD"),X=good,X=one).
  451
  452?- multivar(X),mv_disallow(X,1),mv_disallow(X,3).
  453multivar(X),
  454mv_disallow(X, some(X, [3, 1])).
  455
  456*/
  457% ==========================================
  458% Prolog-Like vars
  459% ==========================================
  460plvar(Var):- xvarx(Var),put_attr(Var,plvar,Var),multivar(Var).
  461%plvar(Var):- xvarx(Var), put_attr(Var,plvar,Var).
  462'plvar':attr_unify_hook(Var,Value):- mv_peek_value1(Var,Was)-> Value=Was; mv_set1(Var,Value).
  463'plvar':attribute_goals(Var)--> {get_attr(Var,'plvar',VarWas),Var==VarWas},[plvar(Var)].
  464
  465
  466% Maybe Variables entering the clause database
  467:- meta_predicate multivar_call(1,0).  468multivar_call(Type,Goal):-term_variables(Goal,Vars),maplist(Type,Vars),call(Goal).
  469
  470
  471% ==========================================
  472% Symbol-Like Global vars
  473% ==========================================
  474nb_var(Var):- gensym(nb_var_,Symbol),nb_var(Symbol, Var).
  475nb_var(Symbol, Var):- xvarx(Var), put_attr(Var,nb_var,some(Var,Symbol)), nb_linkval(Symbol,Var).
  476
  477% This should pretend to be be value1 slot instead
  478% so that we extext mv_peek_value1/2 and mv_set1/2
  479% to store things in GVAR in the case of a nb_var
  480'nb_var':attr_unify_hook(some(_Var,Symbol),Value):-
  481       nb_getval(Symbol,Prev),
  482       ( % This is how we produce a binding for +multivar "iterator"
  483          (var(Value),nonvar(Prev)) ->  Value=Prev;
  484         % same binding (effectively)
  485             Value==Prev->true;
  486         % On unification we will update the internal '$value'
  487             Value=Prev->nb_setval(Symbol,Prev)).
  488
  489% ==========================================
  490% Hashmap-Like vars
  491% ==========================================
  492edict(Var):- xvarx(Var),put_attr(Var,'edict',Var),multivar(Var).
  493edict(Value,Var):- edict(Var),Var=Value.
  494
  495'edict':attr_unify_hook(Var,OValue):-
  496 to_dict(OValue,Value),
  497 (mv_peek_value(Var,Prev)
  498   -> (merge_dicts(Prev,Value,Result)-> mv_set1(Var,Result))
  499   ; mv_add1(Var,Value)).
  500
  501vdict(Var):- put_attr(Var,vdict,Var),multivar(Var).
  502vdict(Value,Var):- vdict(Var),Var=Value.
  503'vdict':attr_unify_hook(Var,OValue):-
  504 to_dict(OValue,Value)-> mv_peek_value(Var,Prev), 
  505 merge_dicts(Prev,Value,Result)-> mv_set1(Var,Result).
  506
  507
  508to_dict(Value,Value):- is_dict(Value),!.
  509to_dict(OValue,Value):- is_list(OValue),!,dict_options(Value,OValue).
  510to_dict(OValue,Value):- compound(OValue),!,option(OValue,[MValue]),!,dict_options(Value,[MValue]).
  511to_dict(OValue,Value):- option('$value'=OValue,[MValue]),!,dict_options(Value,[MValue]).
  512                                                              
  513
  514merge_dicts(Value,Value,Value).
  515merge_dicts(Prev,Value,Prev):- Value :< Prev.
  516merge_dicts(Value,Prev,Prev):- Value :< Prev.
  517merge_dicts(Dict1,Dict2,Combined):- dicts_to_same_keys([Dict1,Dict2],dict_fill(_),[Combined,Combined]).
  518
  519% ==========================================
  520% Insensitively cased text
  521% ==========================================
  522
  523ic_text(Var):- put_attr(Var,ic_text,Var),multivar(Var),!.
  524
  525'ic_text':attr_unify_hook(Var,Value):- check_disallow(Var,Value),
  526 ((mv_members(Var,'$allow',One);mv_peek_value1(Var,One))*-> ic_unify(One,Value)).
  527'ic_text':attribute_goals(Var)--> {get_attr(Var,'ic_text',Var)},[ic_text(Var)].
  528/*
  529*/
  530
  531ic_unify(One,Value):- (One=Value -> true ; (term_upcase(One,UC1),term_upcase(Value,UC2),UC1==UC2)).
  532
  533term_upcase(Value,UC2):-catch(string_upper(Value,UC2),_,(format(string(UC1),'~w',Value),string_upper(UC1,UC2))).
  534/*
  535:-
  536 source_location(S,_), prolog_load_context(module,LC),
  537 forall(source_file(M:H,S),
  538 (functor(H,F,A),
  539  ignore(((\+ predicate_property(M:H,transparent), module_transparent(M:F/A), 
  540  \+ atom_concat('__aux',_,F),debug(modules,'~N:- module_transparent((~q)/~q).~n',[F,A])))),
  541    ignore(((\+ atom_concat('$',_,F),\+ atom_concat('__aux',_,F),LC:export(M:F/A), 
  542  (current_predicate('system':F/A)->true; 'system':import(M:F/A))))))).
  543*/
  544
  545:- system:import((mdwq/1, 
  546		  plvar/1,
  547          nb_var/1, nb_var/2,
  548          vdict/1, vdict/2,
  549		  un_mv/1, un_mv1/1,
  550		  mv_peek_value/2,mv_peek_value1/2,
  551      mv_set_values/2,
  552		  %mv_set/2,
  553      mv_set1/2,
  554		  mv_add1/2,mv_allow/2,
  555		  ic_text/1, xvarx/1, is_mv/1, multivar/1)).  556:- fixup_exports.