A.16 pairs.pl -- Operations on key-value lists

author
Jan Wielemaker
See also
keysort/2, library(assoc)

This module implements common operations on Key-Value lists, also known as Pairs. Pairs have great practical value, especially due to keysort/2 and the library assoc.pl.

This library is based on disussion in the SWI-Prolog mailinglist, including specifications from Quintus and a library proposal by Richard O'Keefe.

[det]pairs_keys_values(?Pairs, ?Keys, ?Values)
True if Keys holds the keys of Pairs and Values the values.

Deterministic if any argument is instantiated to a finite list and the others are either free or finite lists.

[det]pairs_values(+Pairs, -Values)
Remove the keys from a list of Key-Value pairs. Same as pairs_keys_values(Pairs, _, Values)
[det]pairs_keys(+Pairs, -Keys)
Remove the values from a list of Key-Value pairs. Same as pairs_keys_values(Pairs, Keys, _)
[det]group_pairs_by_key(+Pairs, -Joined:list(Key-Values))
Group values with the same key. For example:
?- group_pairs_by_key([a-2, a-1, b-4], X).

X = [a-[2,1], b-[4]]
Pairs Key-Value list, sorted to the standard order of terms (as keysort/2 does)
Joined List of Key-Group, where Group is the list of Values associated with Key.
[det]transpose_pairs(+Pairs, -Transposed)
Swap Key-Value to Value-Key and sort the result on Value (the new key) using keysort/2.
map_list_to_pairs(:Function, +List, -Keyed)
Create a key-value list by mapping each element of List. For example, if we have a list of lists we can create a list of Length-List using
        map_list_to_pairs(length, ListOfLists, Pairs),