1:- module(
    2  pair_ext,
    3  [
    4    change_keys/3,         % +Pairs1, +Changes, -Pairs2
    5    compound_pair/2,       % ?Compound, ?Pair
    6    group_values_by_key/2, % +Pairs, -Groups
    7    merge_pairs/3,         % +New, +Old, -Merge
    8    sum_value/2            % +Pair1, -Pair2
    9  ]
   10).   11:- reexport(library(pairs)).

Extended support for pairs

Extends the support for pairs in the SWI-Prolog standard library.

*/

   19:- use_module(library(error)).   20:- use_module(library(lists)).   21
   22:- use_module(library(dict)).   23
   24:- multifile
   25    error:has_type/2.   26
   27error:has_type(pair(Type), Pair) :-
   28  error:has_type(pair(Type,Type), Pair).
   29error:has_type(pair(KeyType,ValueType), Key- Value) :-
   30  error:has_type(KeyType, Key),
   31  error:has_type(ValueType, Value).
 change_keys(+Pairs1:list(pair(atom,term)), +Changes:ordset(pair(atom,atom)), -Pairs2:list(pair(atom,term))) is det
   41change_keys(L, [], L) :- !.
   42change_keys([Key1-Value|T1], [Key1-Key2|T2], [Key2-Value|T3]) :- !,
   43  change_keys(T1, T2, T3).
   44change_keys([H|T1], Changes, [H|T2]) :- !,
   45  change_keys(T1, Changes, T2).
   46change_keys([], _, []).
 compound_pair(+Compound:compound, +Pair:pair) is semidet
compound_pair(+Compound:compound, -Pair:pair) is semidet
compound_pair(-Compound:compound, +Pair:pair) is det
   54compound_pair(Compound, Key-Value) :-
   55  compound_name_arguments(Compound, Key, [Value]).
 group_values_by_key(+Pairs:ordset(pair(term,term)), -Groups:ordset(term)) is det
   61group_values_by_key(Pairs, Groups) :-
   62  group_pairs_by_key(Pairs, GroupedPairs),
   63  pairs_values(GroupedPairs, Groups).
 merge_pairs(+New:list(pair), +Old:list(pair), -Merge:list(pair)) is det
   69merge_pairs([], L, L) :- !.
   70merge_pairs(L, [], L) :- !.
   71% Key is only present in new dict: use it in merge.
   72merge_pairs([Key1-Value1|T1], [Key2-Value2|T2], [Key1-Value1|T3]) :-
   73  Key1 @< Key2, !,
   74  merge_pairs(T1, [Key2-Value2|T2], T3).
   75% Key is only present in old dict: use it in merge.
   76merge_pairs([Key1-Value1|T1], [Key2-Value2|T2], [Key2-Value2|T3]) :-
   77  Key2 @< Key1, !,
   78  merge_pairs([Key1-Value1|T1], T2, T3).
   79% Key is present in both dicts: either merge recursively (for dicts),
   80% or take the new value.
   81merge_pairs([Key-New|T1], [Key-Old|T2], [Key-Value|T3]) :-
   82  (   maplist(is_dict, [Old,New])
   83  ->  merge_dicts(New, Old, Value)
   84  ;   Value = New
   85  ),
   86  merge_pairs(T1, T2, T3).
 sum_value(+Pair1:pair(term,number), -Pair2:pair(term,number)) is det
   92sum_value(Key-Vals, Key-Val) :-
   93  sum_list(Vals, Val)