1:- module(swi_dicts,
    2          [   % +Key, +Dict0:dict, +OnNotEmpty:callable, +Value, -Dict:dict
    3              put_dict/5,
    4
    5              merge_dict/3,             % +Dict0:dict, +Dict1:dict, -Dict:dict
    6              merge_pair/3,             % +Dict0:dict, +Pair, -Dict:dict
    7              merge_dicts/2,            % +Dicts:list(dict), -Dict:dict
    8
    9              dict_member/2,            % ?Dict:dict, ?Member
   10              dict_leaf/2,              % ?Dict, ?Pair
   11              dict_pair/2,              % ?Dict, ?Pair
   12
   13              % ?Tag, ?Template, :Goal, -Dicts:list(dict)
   14              findall_dict/4,
   15
   16              dict_tag/2,               % +Dict, ?Tag
   17              create_dict/3,            % ?Tag, +Dict0, -Dict
   18              is_key/1,                 % +Key
   19              dict_compound/2,          % +Dict, -Compound
   20              list_dict/3               % ?List, ?Tag, ?Dict
   21          ]).   22
   23:- use_module(compounds).   24:- use_module(atoms).   25:- use_module(lists).   26
   27:- meta_predicate
   28    put_dict(+, +, 3, +, -),
   29    findall_dict(?, ?, 0, -).
 put_dict(+Key, +Dict0:dict, +OnNotEmpty:callable, +Value, -Dict:dict) is det
Updates dictionary pair calling for merge if not empty. Updates Dict0 to Dict with Key-Value, combining Value with any existing value by calling OnNotEmpty/3. The callable can merge its first two arguments in some way, or replace the first with the second, or even reject the second.

The implementation puts Key and Value in Dict0, unifying the result at Dict. However, if the dictionary Dict0 already contains another value for the indicated Key then it invokes OnNotEmpty with the original Value0 and the replacement Value, finally putting the combined or selected Value_ in the dictionary for the Key.

   46put_dict(Key, Dict0, OnNotEmpty, Value, Dict) :-
   47    get_dict(Key, Dict0, Value0),
   48    !,
   49    call(OnNotEmpty, Value0, Value, Value_),
   50    put_dict(Key, Dict0, Value_, Dict).
   51put_dict(Key, Dict0, _, Value, Dict) :-
   52    put_dict(Key, Dict0, Value, Dict).
 merge_dict(+Dict0:dict, +Dict1:dict, -Dict:dict) is semidet
Merges multiple pairs from a dictionary Dict1, into dictionary Dict0, unifying the results at Dict. Iterates the pairs for the Dict1 dictionary, using them to recursively update Dict0 key-by-key. Discards the tag from Dict1; Dict carries the same tag as Dict0.

Merges non-dictionaries according to type. Appends lists when the value in a key-value pair has list type. Only replaces existing values with incoming values when the leaf is not a dictionary, and neither existing nor incoming is a list.

Note the argument order. The first argument specifies the base dictionary starting point. The second argument merges into the first. The resulting merge unifies at the third argument. The order only matters if keys collide. Pairs from Dict1 replace key-matching pairs in Dict0.

Merging does not replace the original dictionary tag. This includes an unbound tag. The tag of Dict0 remains unchanged after merge.

   75merge_dict(Dict0, Dict1, Dict) :-
   76    is_dict(Dict1),
   77    dict_pairs(Dict1, _, Pairs),
   78    foldl(merge_pair_, Pairs, Dict0, Dict).
 merge_pair(+Dict0:dict, +Pair:pair, -Dict:dict) is det
Merges Pair with dictionary. Merges a key-value Pair into dictionary Dict0, unifying the results at Dict.

Private predicate merge_dict_/3 is the value merging predicate; given the original Value0 and the incoming Value, it merges the two values at Value_.

   89merge_pair(Dict0, Key-Value, Dict) :-
   90    merge_pair_(Key-Value, Dict0, Dict).
   91
   92merge_pair_(Key-Value, Dict0, Dict) :-
   93    put_dict(Key, Dict0, merge_dict_, Value, Dict).
 merge_dict_(+Value0, +Value, -Value_) is semidet
Note, the first argument is the original one. The second is the new value, and the final is an unbound variable waiting for a consolidated binding.
  101merge_dict_(Value0, Value, Dict) :-
  102    is_dict(Value),
  103    !,
  104    merge_dict(Value0, Value, Dict).
  105merge_dict_(Value0, Value, Values) :-
  106    is_list(Value),
  107    !,
  108    merge_list_(Value0, Value, Values).
  109merge_dict_(Value0, Value, [Value0|Value]) :-
  110    is_list(Value0),
  111    !.
  112merge_dict_(_, Value, Value).
  113
  114merge_list_(Value0, Values0, Values) :-
  115    is_list(Value0),
  116    !,
  117    append(Value0, Values0, Values).
  118merge_list_(Value0, Values0, Values) :-
  119    append([Value0], Values0, Values).
 merge_dicts(+Dicts:list(dict), -Dict:dict) is semidet
Merges one or more dictionaries. You cannot merge an empty list of dictionaries. Fails in such cases. It does not unify Dict with a tagless empty dictionary. The implementation merges two consecutive dictionaries before tail recursion until eventually one remains.

Merging ignores tags.

  130merge_dicts([Dict], Dict) :-
  131    !.
  132merge_dicts([Dict0, Dict1|Dicts], Dict) :-
  133    merge_dict(Dict0, Dict1, Dict_),
  134    merge_dicts([Dict_|Dicts], Dict).
 dict_member(?Dict:dict, ?Member) is nondet
Unifies with members of dictionary. Unifies Member with all dictionary members, where Member is any non-dictionary leaf, including list elements, or empty leaf dictionary.

Keys become tagged keys of the form Tag^Key. The caret operator neatly fits by operator precedence in-between the pair operator (-) and the sub-key slash delimiter (/). Nested keys become nested slash-functor binary compounds of the form TaggedKeys/TaggedKey. So for example, the compound Tag^Key-Value translates to Tag{Key:Value} in dictionary form. Tag^Key-Value decomposes term-wise as [-, Tag^Key, Value]. Note that tagged keys, including super-sub tagged keys, take precedence within the term.

This is a non-standard approach to dictionary unification. It turns nested sub-dictionary hierarchies into flatten pair-lists of tagged-key paths and their leaf values.

  156dict_member(Dict, Member) :-
  157    var(Dict),
  158    !,
  159    member_dict_(Member, Dict).
  160dict_member(Dict, Member) :-
  161    dict_pairs(Dict, Tag, Pairs),
  162    member(Key-Value0, Pairs),
  163    dict_member_(Tag^Key-Value0, Member).
  164
  165dict_member_(Tag0^Key0-Tag{}, Tag0^Key0-Tag{}) :-
  166    !.
  167dict_member_(Tag0^Key0-Dict, TaggedKeys-Value) :-
  168    is_dict(Dict),
  169    !,
  170    dict_member(Dict, TaggedKeys0-Value),
  171    flatten_slashes(Tag0^Key0/TaggedKeys0, TaggedKeys).
  172dict_member_(Member, Member).
 member_dict_(+Member, -Dict:dict) is semidet
Should value-free members unite? Yes, allow dictionaries and nested dictionaries using just a Tag without Key or Value, i.e. just Tag rather than Tag^Key-Value.
  180member_dict_(TaggedKeys/Tag^Key-Value, Dict) :-
  181    !,
  182    member_dict_(Tag^Key-Value, Dict0),
  183    member_dict_(TaggedKeys-Dict0, Dict).
  184member_dict_(Tag^Key-Value, Tag{}.put(Key, Value)) :-
  185    !.
  186member_dict_(Tag0^Key/Tag, Tag0{}.put(Key, Dict)) :-
  187    !,
  188    member_dict_(Tag, Dict).
  189member_dict_(Tag, Tag{}) :-
  190    atom(Tag).
 dict_leaf(-Dict, +Pair) is semidet
dict_leaf(+Dict, -Pair) is nondet
Unifies Dict with its leaf nodes non-deterministically. Each Pair is either an atom for root-level keys, or a compound for nested-dictionary keys. Pair thereby represents a nested key path Leaf with its corresponding Value.

Fails for integer keys because integers cannot serve as functors. Does not attempt to map integer keys to an atom, since this will create a reverse conversion disambiguation issue. This does work for nested integer leaf keys, e.g. a(1), provided that the integer key does not translate to a functor.

Arguments:
Dict- is either a dictionary or a list of key-value pairs whose syntax conforms to valid dictionary data.
  209dict_leaf(Dict, Leaf-Value) :- var(Dict), !, leaf_dict_(Dict, Leaf-Value).
  210dict_leaf(Dict, Leaf-Value) :-
  211    dict_pairs(Dict, _Tag, Pairs),
  212    member(Key-Value0, Pairs),
  213    dict_leaf_(Key-Value0, Leaf-Value).
  214
  215dict_leaf_(Key-Value0, Leaf-Value) :- is_dict(Value0), !,
  216    dict_leaf(Value0, Leaf0-Value),
  217    atom(Key),
  218    Leaf =.. [Key, Leaf0].
  219dict_leaf_(Key-Value, Key-Value).
  220
  221leaf_dict_(Dict, Leaf-Value) :- is_key(Leaf), !,
  222    dict_create(Dict, _, [Leaf-Value]).
  223leaf_dict_(Dict, Leaf-Value) :-
  224    compound(Leaf),
  225    compound_name_arguments(Leaf, Key, [Leaf_]),
  226    leaf_dict_(Dict0, Leaf_-Value),
  227    dict_create(Dict, _, [Key-Dict0]).
 dict_pair(+Dict, -Pair) is nondet
dict_pair(-Dict, +Pair) is det
Finds all dictionary pairs non-deterministically and recursively where each pair is a Path-Value. Path is a slash-delimited dictionary key path. Note, the search fails for dictionary leaves; succeeds only for non-dictionaries. Fails therefore for empty dictionaries or dictionaries of empty sub-dictionaries.
  238dict_pair(Dict, Path-Value) :-
  239    is_dict(Dict),
  240    !,
  241    dict_pairs(Dict, _, Pairs),
  242    member(Key-Value0, Pairs),
  243    dict_pair_(Key-Value0, Path-Value).
  244dict_pair(_{}.put(Path, Value), Path-Value).
  245
  246dict_pair_(Key-Value0, Path-Value) :-
  247    is_dict(Value0),
  248    !,
  249    dict_pair(Value0, Path0-Value),
  250    append_path(Key, Path0, Path).
  251dict_pair_(Key-Value, Key-Value).
 findall_dict(?Tag, ?Template, :Goal, -Dicts:list(dict)) is det
Finds all dictionary-only solutions to Template within Goal. Tag selects which tags to select. What happens when Tag is variable? In such cases, unites with the first bound tag then all subsequent matching tags.
  260findall_dict(Tag, Template, Goal, Dicts) :-
  261    findall(Template, Goal, Bag),
  262    convlist(findall_dict_(Tag), Bag, Dicts).
  263
  264:- public
  265    findall_dict_/3.  266
  267findall_dict_(Tag, Dict, Dict) :-
  268    is_dict(Dict, Tag).
 dict_tag(+Dict, ?Tag) is semidet
Tags Dict with Tag if currently untagged. Fails if already tagged but not matching Tag, just like is_dict/2 with a ground tag. Never mutates ground tags as a result. Additionally Tags all nested sub-dictionaries using Tag and the sub-key for the sub-dictionary. An underscore delimiter concatenates the tag and key.

The implementation uses atomic concatenation to merge Tag and the dictionary sub-keys. Note that atomic_list_concat/3 works for non-atomic keys, including numbers and strings. Does not traverse sub-lists. Ignores sub-dictionaries where a dictionary value is a list containing dictionaries. Perhaps future versions will.

  284dict_tag(Dict, Tag) :-
  285    is_dict(Dict, Tag),
  286    dict_pairs(Dict, Tag, Pairs),
  287    pairs_tag(Pairs, Tag).
  288
  289pairs_tag([], _).
  290pairs_tag([Key-Value|T], Tag) :-
  291    (   is_dict(Value)
  292    ->  atomic_list_concat([Tag, Key], '_', Tag_),
  293        dict_tag(Value, Tag_)
  294    ;   true
  295    ),
  296    pairs_tag(T, Tag).
 create_dict(?Tag, +Dict0, -Dict) is semidet
Creates a dictionary just like dict_create/3 does but with two important differences. First, the argument order differs. Tag comes first to make maplist/3 and convlist/3 more convenient where the Goal argument includes the Tag. The new dictionary Dict comes last for the same reason. Secondly, always applies the given Tag to the new Dict, even if the incoming Data supplies one.

Creating a dictionary using standard dict_create/3 overrides the tag argument from its Data dictionary, ignoring the Tag if any. For example, using dict_create/3 for tag xyz and dictionary abc{} gives you abc{} as the outgoing dictionary. This predicate reverses this behaviour; the Tag argument replaces any tag in a Data dictionary.

  313create_dict(Tag, Dict0, Dict) :-
  314    is_dict(Dict0, _),
  315    !,
  316    dict_pairs(Dict0, _, Pairs),
  317    dict_create(Dict, Tag, Pairs).
  318create_dict(Tag, Data, Dict) :-
  319    dict_create(Dict, Tag, Data).
 is_key(+Key:any) is semidet
Succeeds for terms that can serve as keys within a dictionary. Dictionary keys are atoms or tagged integers, otherwise known as constant values. Integers include negatives.
Arguments:
Key- successfully unites for all dictionary-key conforming terms: atomic or integral.
  330is_key(Key) :- atom(Key), !.
  331is_key(Key) :- integer(Key).
 dict_compound(+Dict:dict, ?Compound:compound) is nondet
Finds all compound-folded terms within Dict. Unifies with all pairs within Dict as compounds of the form key(Value) where key matches the dictionary key converted to one-two style and lower-case.

Unfolds lists and sub-dictionaries non-deterministically. For most occasions, the non-deterministic unfolding of sub-lists results in multiple non-deterministic solutions and typically has a plural compound name. This is not a perfect solution for lists of results, since the order of the solutions defines the relations between list elements.

Dictionary keys can be atoms or integers. Converts integers to compound names using integer-to-atom translation. However, compounds for sub-dictionaries re-wrap the sub-compounds by inserting the integer key as the prefix argument of a two or more arity compound.

  351dict_compound(Dict, Compound) :-
  352    dict_pairs(Dict, _, Pairs),
  353    member(Key-Value, Pairs),
  354    dict_compound_(Key-Value, Compound).
  355
  356dict_compound_(Key-Value, Compound) :-
  357    is_dict(Value),
  358    !,
  359    dict_compound__(Key-Value, Compound).
  360dict_compound_(Key-Value, Compound) :-
  361    is_list(Value),
  362    !,
  363    member(Member, Value),
  364    dict_compound_(Key-Member, Compound).
  365dict_compound_(Key0-Value, Compound) :-
  366    dict_compound_key(Key0, Key),
  367    Compound =.. [Key, Value].
  368
  369dict_compound__(Key-Dict, Compound) :-
  370    integer(Key),
  371    !,
  372    dict_compound(Dict, Compound0),
  373    Compound0 =.. [Name|Arguments],
  374    Compound =.. [Name, Key|Arguments].
  375dict_compound__(Key0-Dict, Compound) :-
  376    dict_compound(Dict, Compound0),
  377    dict_compound_key(Key0, Key),
  378    Compound =.. [Key, Compound0].
  379
  380dict_compound_key(Key0, Key) :-
  381    integer(Key0),
  382    !,
  383    atom_number(Key, Key0).
  384dict_compound_key(Key0, Key) :-
  385    restyle_identifier_ex(one_two, Key0, Key_),
  386    downcase_atom(Key_, Key).
 list_dict(?List, ?Tag, ?Dict) is semidet
List to Dict by zipping up items from List with integer indexed keys starting at 1. Finds only the first solution, even if multiple solutions exist.
  394list_dict(List, Tag, Dict) :-
  395    indexed(List, 1, Pairs),
  396    dict_create(Dict, Tag, Pairs),
  397    !