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