2:- module(open_dicts, [
    3              open_dict/1,
    4              open_dict/2,
    5              close_dict/1,
    6              close_dict/2,
    7              contains/2,
    8              op(210, yfx, '.^'),
    9              op(200, yf, '+')
   10          ]).

Open Dicts for SWI Prolog

author
- :Eyal Dechter <eyaldechter@gmail.com>

*/

   21:- use_module(library(function_expansion)).   22
   23
   24:- op(210, yfx, '.^').   25:- op(200, yf, '+').   26
   27
   28:- multifile error:has_type/2.   29error:has_type(open_dict, O) :-
   30    var(O), 
   31    get_attr(O, open_dicts, _).
 open_dict(?Dict, ?Open)
   36open_dict(Dict, Open) :-
   37    must_be(dict, Dict),
   38    put_attr(X, open_dicts, Dict),
   39    Open = X.
 open_dict(?Open)
   43open_dict(Open) :-
   44    open_dict(_{}, Open).
 close_dict(+Open, ?Dict) is det
   49close_dict(Open, Closed) :-
   50    must_be(open_dict, Open),
   51    get_attr(Open, open_dicts, Closed).
 close_dict(+Open)
   54close_dict(O) :-
   55    close_dict(O, O). 
 contains(+Open, Data) is nondet
   59contains(Open, Data) :-
   60    dict_create(D, _, Data),
   61    open_dict(D, Open1),
   62    Open = Open1.
 open_dict_get(KeyPath, Open, Value)
   66open_dict_get(KeyPath, Open, Value) :-
   67    must_be(open_dict, Open),
   68    must_be(ground, KeyPath),
   69    
   70    (KeyPath = (K.^KeyPath1) ->
   71         open_dict_get(K, Open, Open1),
   72         open_dict_get(KeyPath1, Open1, Value)
   73    ; % otherwise -> 
   74      Key = KeyPath, 
   75      dict_create(Dict, _, [Key-Value]),
   76      open_dict(Dict, Open1),
   77      Open = Open1
   78    ).
 unify_dicts(+Open1, +Open2, ?Open) is det
   88unify_dicts(Open1, Open2, Unified) :-
   89    Open1 >:< Open2,    
   90    Unified = Open1.put(Open2). 
   91
   92
   93attr_unify_hook(Dict, Other) :-
   94    (get_attr(Other, open_dicts, Dict1) ->
   95         unify_dicts(Dict, Dict1, Unified),
   96         put_attr(Other, open_dicts, Unified)
   97    ;
   98    var(Other) ->
   99         put_attr(Other, open_dicts, Dict)
  100    ;
  101    is_dict(Other) ->
  102         unify_dicts(Dict, Other, Other)
  103    ;
  104    domain_error(unwrapped_open_dict, Other)
  105    ).
  106
  107attribute_goals(Open) -->
  108    {get_attr(Open, open_dicts, Dict)},    
  109    [open_dict(Dict, Open)].
  110
  111
  112:- multifile user:portray/1.  113user:portray(V) :-
  114    get_attr(V, open_dicts, D),
  115    format('~p', [open_dict(D, V)]).
  116    
  117user:portray(V) :-
  118    nonvar(V),
  119    V = open_dict(Dict, Open),
  120    format('~@ = ~p+', [write_term(Open, [attributes(ignore), numbervars(true)]), Dict]).
  121    
  122    
  123    
  124    
  125
  126
  127/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  128     Syntactic sugar
  129- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  130
  131:- multifile user:function_expansion/2.  132
  133user:function_expansion(In, Out, Guard) :-
  134    nonvar(In),
  135    In = D + , 
  136    Guard = open_dict(D, Out).
  137
  138user:function_expansion(In, Out, Guard) :-
  139    nonvar(In),
  140    In = Open .^ KeyPath,    
  141    Guard = (open_dict(Open), open_dicts:open_dict_get(KeyPath, Open, Out))