diff --git a/library/pairs.pl b/library/pairs.pl index c751c08578..2d41ba4e98 100644 --- a/library/pairs.pl +++ b/library/pairs.pl @@ -3,8 +3,9 @@ Author: Jan Wielemaker E-mail: J.Wielemaker@vu.nl WWW: http://www.swi-prolog.org - Copyright (c) 2006-2015, University of Amsterdam + Copyright (c) 2006-2024, University of Amsterdam VU University Amsterdam + SWI-Prolog Solutions b.v. All rights reserved. Redistribution and use in source and binary forms, with or without @@ -42,18 +43,20 @@ map_list_to_pairs/3 ]). +:- meta_predicate + map_list_to_pairs(2, +, -). + /** Operations on key-value lists 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. +keysort/2 and the library(assoc). This library is based on discussion in the SWI-Prolog mailinglist, including specifications from Quintus and a library proposal by Richard O'Keefe. @see keysort/2, library(assoc) -@author Jan Wielemaker */ %! pairs_keys_values(?Pairs, ?Keys, ?Values) is det. @@ -67,10 +70,10 @@ % @see pairs_values/2 and pairs_keys/2. pairs_keys_values(Pairs, Keys, Values) :- - ( nonvar(Pairs) -> - pairs_keys_values_(Pairs, Keys, Values) - ; nonvar(Keys) -> - keys_values_pairs(Keys, Values, Pairs) + ( nonvar(Pairs) + -> pairs_keys_values_(Pairs, Keys, Values) + ; nonvar(Keys) + -> keys_values_pairs(Keys, Values, Pairs) ; values_keys_pairs(Values, Keys, Pairs) ). @@ -111,32 +114,32 @@ % Group values with equivalent (==/2) consecutive keys. For % example: % -% == -% ?- group_pairs_by_key([a-2, a-1, b-4, a-3], X). +% ``` +% ?- group_pairs_by_key([a-2, a-1, b-4, a-3], X). % -% X = [a-[2,1], b-[4], a-[3]] -% == +% X = [a-[2,1], b-[4], a-[3]] +% ``` % % Sorting the list of pairs before grouping can be used to group % _all_ values associated with a key. For example, finding all % values associated with the largest key: % -% == -% ?- sort(1, @>=, [a-1, b-2, c-3, a-4, a-5, c-6], Ps), -% group_pairs_by_key(Ps, [K-Vs|_]). -% K = c, -% Vs = [3, 6]. -% == +% ``` +% ?- sort(1, @>=, [a-1, b-2, c-3, a-4, a-5, c-6], Ps), +% group_pairs_by_key(Ps, [K-Vs|_]). +% K = c, +% Vs = [3, 6]. +% ``` % % In this example, sorting by key only (first argument of sort/4 % is 1) ensures that the order of the values in the original list % of pairs is maintained. % -% @param Pairs Key-Value list -% @param Joined List of Key-Group, where Group is the -% list of Values associated with equivalent -% consecutive Keys in the same order as they -% appear in Pairs. +% @arg Pairs Key-Value list +% @arg Joined List of Key-Group, where Group is the +% list of Values associated with equivalent +% consecutive Keys in the same order as they +% appear in Pairs. group_pairs_by_key([], []). group_pairs_by_key([M-N|T0], [M-[N|TN]|T]) :- @@ -164,18 +167,15 @@ flip_pairs(Pairs, Flipped). -%! map_list_to_pairs(:Function, +List, -Keyed) +%! map_list_to_pairs(:Function, +List, -Keyed) is det. % % 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), -% == - -:- meta_predicate - map_list_to_pairs(2, +, -). +% ``` +% map_list_to_pairs(length, ListOfLists, Pairs), +% ``` map_list_to_pairs(Function, List, Pairs) :- map_list_to_pairs2(List, Function, Pairs).