1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2015-2024, VU University Amsterdam 7 SWI-Prolog Solutions b.v. 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(dicts, 37 [ mapdict/2, % :Goal, +Dict 38 mapdict/3, % :Goal, ?Dict1, ?Dict2 39 mapdict/4, % :Goal, ?Dict1, ?Dict2, ?Dict3 40 dicts_same_tag/2, % +List, -Tag 41 dict_size/2, % +Dict, -KeyCount 42 dict_keys/2, % +Dict, -Keys 43 dicts_same_keys/2, % +DictList, -Keys 44 dicts_to_same_keys/3, % +DictsIn, :OnEmpty, -DictsOut 45 dict_fill/4, % +Value, +Key, +Dict, -Value 46 dict_no_fill/3, % +Key, +Dict, -Value 47 dicts_join/3, % +Key, +DictsIn, -Dicts 48 dicts_join/4, % +Key, +Dicts1, +Dicts2, -Dicts 49 dicts_slice/3, % +Keys, +DictsIn, -DictsOut 50 dicts_to_compounds/4 % ?Dicts, +Keys, :OnEmpty, ?Compounds 51 ]). 52:- autoload(library(apply),[maplist/2,maplist/3]). 53:- autoload(library(lists),[append/2,append/3]). 54:- autoload(library(ordsets),[ord_subtract/3]). 55:- autoload(library(pairs),[pairs_keys/2,pairs_keys_values/3]). 56:- autoload(library(error), [domain_error/2, must_be/2]). 57 58 59:- meta_predicate 60 mapdict( , ), 61 mapdict( , , ), 62 mapdict( , , , ), 63 dicts_to_same_keys( , , ), 64 dicts_to_compounds( , , , ). 65 66/** <module> Dict utilities 67 68This library defines utilities that operate on lists of dicts, notably 69to make lists of dicts consistent by adding missing keys, converting 70between lists of compounds and lists of dicts, joining and slicing lists 71of dicts. 72*/ 73 74%! mapdict(:Goal, +Dict). 75%! mapdict(:Goal, ?Dict, ?Dict2). 76%! mapdict(:Goal, ?Dict, ?Dict2, ?Dict3). 77% 78% True when all dicts have the same set of keys and call(Goal, Key, 79% V1, ...) is true for all keys in the dicts. At least one of the 80% dicts must be instantiated. 81% 82% @error instantiation_error if no dict is bound 83% @error type_error(dict, Culprit) if one of the dict arguments is not 84% a dict. 85% @error domain_error(incompatible_dict, Culprit) if Culprit does not 86% have the same keys as one of the other dicts. 87 88mapdict(Goal, Dict) :- 89 mapdict_(1, Goal, Dict). 90 91mapdict_(I, Goal, D1) :- 92 ( '$get_dict_kv'(I, D1, K, V1) 93 -> call(Goal, K, V1), 94 I2 is I+1, 95 mapdict_(I2, Goal, D1) 96 ; true 97 ). 98 99mapdict(Goal, Dict1, Dict2) :- 100 ( dict_same_keys(Dict1, Dict2) 101 -> mapdict_(1, Goal, Dict1, Dict2) 102 ; domain_error(incompatible_dict, Dict2) 103 ). 104 105mapdict_(I, Goal, D1, D2) :- 106 ( '$get_dict_kv'(I, D1, D2, K, V1, V2) 107 -> call(Goal, K, V1, V2), 108 I2 is I+1, 109 mapdict_(I2, Goal, D1, D2) 110 ; true 111 ). 112 113 114mapdict(Goal, Dict1, Dict2, Dict3) :- 115 ( nonvar(Dict1) 116 -> dict_same_keys(Dict1, Dict2), 117 dict_same_keys(Dict1, Dict3) 118 ; nonvar(Dict2) 119 -> dict_same_keys(Dict1, Dict2), 120 dict_same_keys(Dict1, Dict3) 121 ; dict_same_keys(Dict3, Dict2), 122 dict_same_keys(Dict3, Dict1) 123 ), 124 !, 125 mapdict_(1, Goal, Dict1, Dict2, Dict3). 126mapdict(_Goal, Dict1, Dict2, Dict3) :- 127 ( nonvar(Dict3) 128 -> domain_error(incompatible_dict, Dict3) 129 ; nonvar(Dict2) 130 -> domain_error(incompatible_dict, Dict2) 131 ; domain_error(incompatible_dict, Dict1) 132 ). 133 134mapdict_(I, Goal, D1, D2, D3) :- 135 ( '$get_dict_kv'(I, D1, D2, D3, K, V1, V2, V3) 136 -> call(Goal, K, V1, V2, V3), 137 I2 is I+1, 138 mapdict_(I2, Goal, D1, D2, D3) 139 ; true 140 ). 141 142 143%! dicts_same_tag(+List, -Tag) is semidet. 144% 145% True when List is a list of dicts that all have the tag Tag. 146 147dicts_same_tag(List, Tag) :- 148 maplist(keys_tag(Tag), List). 149 150keys_tag(Tag, Dict) :- 151 is_dict(Dict, Tag). 152 153%! dict_size(+Dict, -KeyCount) is det. 154% 155% True when KeyCount is the number of keys in Dict. 156 157dict_size(Dict, KeyCount) :- 158 must_be(dict,Dict), 159 compound_name_arity(Dict,_,Arity), 160 KeyCount is (Arity-1)//2. 161 162%! dict_keys(+Dict, -Keys) is det. 163% 164% True when Keys is an ordered set of the keys appearing in Dict. 165 166dict_keys(Dict, Keys) :- 167 dict_pairs(Dict, _Tag, Pairs), 168 pairs_keys(Pairs, Keys). 169 170 171%! dicts_same_keys(+List, -Keys) is semidet. 172% 173% True if List is a list of dicts that all have the same keys and 174% Keys is an ordered set of these keys. 175 176dicts_same_keys(List, Keys) :- 177 maplist(keys_dict(Keys), List). 178 179keys_dict(Keys, Dict) :- 180 dict_keys(Dict, Keys). 181 182%! dicts_to_same_keys(+DictsIn, :OnEmpty, -DictsOut) 183% 184% DictsOut is a copy of DictsIn, where each dict contains all keys 185% appearing in all dicts of DictsIn. Values for keys that are 186% added to a dict are produced by calling OnEmpty as below. The 187% predicate dict_fill/4 provides an implementation that fills all 188% new cells with a predefined value. 189% 190% == 191% call(:OnEmpty, +Key, +Dict, -Value) 192% == 193 194dicts_to_same_keys(Dicts, _, Table) :- 195 dicts_same_keys(Dicts, _), 196 !, 197 Table = Dicts. 198dicts_to_same_keys(Dicts, OnEmpty, Table) :- 199 maplist(dict_keys, Dicts, KeysList), 200 append(KeysList, Keys0), 201 sort(Keys0, Keys), 202 maplist(extend_dict(Keys, OnEmpty), Dicts, Table). 203 204extend_dict(Keys, OnEmpty, Dict0, Dict) :- 205 dict_pairs(Dict0, Tag, Pairs), 206 pairs_keys(Pairs, DictKeys), 207 ord_subtract(Keys, DictKeys, Missing), 208 ( Missing == [] 209 -> Dict = Dict0 210 ; maplist(key_value_pair(Dict0, OnEmpty), Missing, NewPairs), 211 append(NewPairs, Pairs, AllPairs), 212 dict_pairs(Dict, Tag, AllPairs) 213 ). 214 215key_value_pair(Dict, OnEmpty, Key, Key-Value) :- 216 call(OnEmpty, Key, Dict, Value). 217 218%! dict_fill(+ValueIn, +Key, +Dict, -Value) is det. 219% 220% Implementation for the dicts_to_same_keys/3 `OnEmpty` closure 221% that fills new cells with a copy of ValueIn. Note that 222% copy_term/2 does not really copy ground terms. Below are two 223% examples. Note that when filling empty cells with a variable, 224% each empty cell is bound to a new variable. 225% 226% == 227% ?- dicts_to_same_keys([r{x:1}, r{y:2}], dict_fill(null), L). 228% L = [r{x:1, y:null}, r{x:null, y:2}]. 229% ?- dicts_to_same_keys([r{x:1}, r{y:2}], dict_fill(_), L). 230% L = [r{x:1, y:_G2005}, r{x:_G2036, y:2}]. 231% == 232% 233% Use dict_no_fill/3 to raise an error if a dict is missing a key. 234 235dict_fill(ValueIn, _, _, Value) :- 236 copy_term(ValueIn, Value). 237 238%! dict_no_fill is det. 239% 240% Can be used instead of dict_fill/4 to raise an exception if some 241% dict is missing a key. 242 243dict_no_fill(Key, Dict, Value) :- 244 Value = Dict.Key. 245 246%! dicts_join(+Key, +DictsIn, -Dicts) is semidet. 247% 248% Join dicts in Dicts that have the same value for Key, provided 249% they do not have conflicting values on other keys. For example: 250% 251% == 252% ?- dicts_join(x, [r{x:1, y:2}, r{x:1, z:3}, r{x:2,y:4}], L). 253% L = [r{x:1, y:2, z:3}, r{x:2, y:4}]. 254% == 255% 256% @error existence_error(key, Key, Dict) if a dict in Dicts1 257% or Dicts2 does not contain Key. 258 259dicts_join(Join, Dicts0, Dicts) :- 260 sort(Join, @=<, Dicts0, Dicts1), 261 join(Dicts1, Join, Dicts). 262 263join([], _, []) :- !. 264join([H0|T0], Key, [H|T]) :- 265 !, 266 get_dict(Key, H0, V0), 267 join_same(T0, Key, V0, H0, H, T1), 268 join(T1, Key, T). 269join([One], _, [One]) :- !. 270 271join_same([H|T0], Key, V0, D0, D, T) :- 272 get_dict(Key, H, V), 273 V == V0, 274 !, 275 D0 >:< H, 276 put_dict(H, D0, D1), 277 join_same(T0, Key, V0, D1, D, T). 278join_same(DL, _, _, D, D, DL). 279 280%! dicts_join(+Key, +Dicts1, +Dicts2, -Dicts) is semidet. 281% 282% Join two lists of dicts (Dicts1 and Dicts2) on Key. Each pair 283% D1-D2 from Dicts1 and Dicts2 that have the same (==) value for 284% Key creates a new dict D with the union of the keys from D1 and 285% D2, provided D1 and D2 to not have conflicting values for some 286% key. For example: 287% 288% == 289% ?- DL1 = [r{x:1,y:1},r{x:2,y:4}], 290% DL2 = [r{x:1,z:2},r{x:3,z:4}], 291% dicts_join(x, DL1, DL2, DL). 292% DL = [r{x:1, y:1, z:2}, r{x:2, y:4}, r{x:3, z:4}]. 293% == 294% 295% @error existence_error(key, Key, Dict) if a dict in Dicts1 296% or Dicts2 does not contain Key. 297 298dicts_join(Join, Dicts1, Dicts2, Dicts) :- 299 sort(Join, @=<, Dicts1, Dicts11), 300 sort(Join, @=<, Dicts2, Dicts21), 301 join(Dicts11, Dicts21, Join, Dicts). 302 303join([], [], _, []) :- !. 304join([D1|T1], [D2|T2], Join, [DNew|MoreDicts]) :- 305 !, 306 get_dict(Join, D1, K1), 307 get_dict(Join, D2, K2), 308 compare(Diff, K1, K2), 309 ( Diff == (=) 310 -> D1 >:< D2, 311 put_dict(D1, D2, DNew), 312 join(T1, T2, Join, MoreDicts) 313 ; Diff == (<) 314 -> DNew = D1, 315 join(T1, [D2|T2], Join, MoreDicts) 316 ; DNew = D2, 317 join([D1|T1], T2, Join, MoreDicts) 318 ). 319join([], Dicts, _, Dicts) :- !. 320join(Dicts, [], _, Dicts). 321 322 323%! dicts_slice(+Keys, +DictsIn, -DictsOut) is det. 324% 325% DictsOut is a list of Dicts only containing values for Keys. 326 327dicts_slice(Keys, DictsIn, DictsOut) :- 328 sort(Keys, SortedKeys), 329 maplist(dict_slice(SortedKeys), DictsIn, DictsOut). 330 331dict_slice(Keys, DictIn, DictOut) :- 332 dict_pairs(DictIn, Tag, PairsIn), 333 slice_pairs(Keys, PairsIn, PairsOut), 334 dict_pairs(DictOut, Tag, PairsOut). 335 336slice_pairs([], _, []) :- !. 337slice_pairs(_, [], []) :- !. 338slice_pairs([H|T0], [P|PL], Pairs) :- 339 P = K-_, 340 compare(D, H, K), 341 ( D == (=) 342 -> Pairs = [P|More], 343 slice_pairs(T0, PL, More) 344 ; D == (<) 345 -> slice_pairs(T0, [P|PL], Pairs) 346 ; slice_pairs([H|T0], PL, Pairs) 347 ). 348 349%! dicts_to_compounds(?Dicts, +Keys, :OnEmpty, ?Compounds) is semidet. 350% 351% True when Dicts and Compounds are lists of the same length and 352% each element of Compounds is a compound term whose arguments 353% represent the values associated with the corresponding keys in 354% Keys. When converting from dict to row, OnEmpty is used to 355% compute missing values. The functor for the compound is the same 356% as the tag of the pair. When converting from dict to row and the 357% dict has no tag, the functor `row` is used. For example: 358% 359% == 360% ?- Dicts = [_{x:1}, _{x:2, y:3}], 361% dicts_to_compounds(Dicts, [x], dict_fill(null), Compounds). 362% Compounds = [row(1), row(2)]. 363% ?- Dicts = [_{x:1}, _{x:2, y:3}], 364% dicts_to_compounds(Dicts, [x,y], dict_fill(null), Compounds). 365% Compounds = [row(1, null), row(2, 3)]. 366% ?- Compounds = [point(1,1), point(2,4)], 367% dicts_to_compounds(Dicts, [x,y], dict_fill(null), Compounds). 368% Dicts = [point{x:1, y:1}, point{x:2, y:4}]. 369% == 370% 371% When converting from Dicts to Compounds Keys may be computed by 372% dicts_same_keys/2. 373 374dicts_to_compounds(Dicts, Keys, OnEmpty, Compounds) :- 375 maplist(dict_to_compound(Keys, OnEmpty), Dicts, Compounds). 376 377dict_to_compound(Keys, OnEmpty, Dict, Row) :- 378 is_dict(Dict, Tag), 379 !, 380 default_tag(Tag, row), 381 maplist(key_value(Dict, OnEmpty), Keys, Values), 382 compound_name_arguments(Row, Tag, Values). 383dict_to_compound(Keys, _, Dict, Row) :- 384 compound(Row), 385 compound_name_arguments(Row, Tag, Values), 386 pairs_keys_values(Pairs, Keys, Values), 387 dict_pairs(Dict, Tag, Pairs). 388 389default_tag(Tag, Tag) :- !. 390default_tag(_, _). 391 392key_value(Dict, OnEmpty, Key, Value) :- 393 ( get_dict(Key, Dict, Value0) 394 -> Value = Value0 395 ; call(OnEmpty, Key, Dict, Value) 396 )