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_keys/2, % +Dict, -Keys 38 dicts_same_keys/2, % +DictList, -Keys 39 dicts_to_same_keys/3, % +DictsIn, :OnEmpty, -DictsOut 40 dict_fill/4, % +Value, +Key, +Dict, -Value 41 dict_no_fill/3, % +Key, +Dict, -Value 42 dicts_join/3, % +Key, +DictsIn, -Dicts 43 dicts_join/4, % +Key, +Dicts1, +Dicts2, -Dicts 44 dicts_slice/3, % +Keys, +DictsIn, -DictsOut 45 dicts_to_compounds/4 % ?Dicts, +Keys, :OnEmpty, ?Compounds 46 ]). 47:- autoload(library(apply),[maplist/2,maplist/3]). 48:- autoload(library(lists),[append/2,append/3]). 49:- autoload(library(ordsets),[ord_subtract/3]). 50:- autoload(library(pairs),[pairs_keys/2,pairs_keys_values/3]). 51 52 53:- meta_predicate 54 dicts_to_same_keys( , , ), 55 dicts_to_compounds( , , , ).
69dicts_same_tag(List, Tag) :- 70 maplist(keys_tag(Tag), List). 71 72keys_tag(Tag, Dict) :- 73 is_dict(Dict, Tag).
79dict_keys(Dict, Keys) :-
80 dict_pairs(Dict, _Tag, Pairs),
81 pairs_keys(Pairs, Keys).
89dicts_same_keys(List, Keys) :- 90 maplist(keys_dict(Keys), List). 91 92keys_dict(Keys, Dict) :- 93 dict_keys(Dict, Keys).
call(:OnEmpty, +Key, +Dict, -Value)
107dicts_to_same_keys(Dicts, _, Table) :- 108 dicts_same_keys(Dicts, _), 109 !, 110 Table = Dicts. 111dicts_to_same_keys(Dicts, OnEmpty, Table) :- 112 maplist(dict_keys, Dicts, KeysList), 113 append(KeysList, Keys0), 114 sort(Keys0, Keys), 115 maplist(extend_dict(Keys, OnEmpty), Dicts, Table). 116 117extend_dict(Keys, OnEmpty, Dict0, Dict) :- 118 dict_pairs(Dict0, Tag, Pairs), 119 pairs_keys(Pairs, DictKeys), 120 ord_subtract(Keys, DictKeys, Missing), 121 ( Missing == [] 122 -> Dict = Dict0 123 ; maplist(key_value_pair(Dict0, OnEmpty), Missing, NewPairs), 124 append(NewPairs, Pairs, AllPairs), 125 dict_pairs(Dict, Tag, AllPairs) 126 ). 127 128key_value_pair(Dict, OnEmpty, Key, Key-Value) :- 129 call(OnEmpty, Key, Dict, Value).
?- dicts_to_same_keys([r{x:1}, r{y:2}], dict_fill(null), L). L = [r{x:1, y:null}, r{x:null, y:2}]. ?- dicts_to_same_keys([r{x:1}, r{y:2}], dict_fill(_), L). L = [r{x:1, y:_G2005}, r{x:_G2036, y:2}].
Use dict_no_fill/3 to raise an error if a dict is missing a key.
148dict_fill(ValueIn, _, _, Value) :-
149 copy_term(ValueIn, Value).
156dict_no_fill(Key, Dict, Value) :-
157 Value = Dict.Key.
?- dicts_join(x, [r{x:1, y:2}, r{x:1, z:3}, r{x:2,y:4}], L). L = [r{x:1, y:2, z:3}, r{x:2, y:4}].
172dicts_join(Join, Dicts0, Dicts) :- 173 sort(Join, @=<, Dicts0, Dicts1), 174 join(Dicts1, Join, Dicts). 175 176join([], _, []) :- !. 177join([H0|T0], Key, [H|T]) :- 178 !, 179 get_dict(Key, H0, V0), 180 join_same(T0, Key, V0, H0, H, T1), 181 join(T1, Key, T). 182join([One], _, [One]) :- !. 183 184join_same([H|T0], Key, V0, D0, D, T) :- 185 get_dict(Key, H, V), 186 V == V0, 187 !, 188 D0 >:< H, 189 put_dict(H, D0, D1), 190 join_same(T0, Key, V0, D1, D, T). 191join_same(DL, _, _, D, D, DL).
?- DL1 = [r{x:1,y:1},r{x:2,y:4}], DL2 = [r{x:1,z:2},r{x:3,z:4}], dicts_join(x, DL1, DL2, DL). DL = [r{x:1, y:1, z:2}, r{x:2, y:4}, r{x:3, z:4}].
211dicts_join(Join, Dicts1, Dicts2, Dicts) :- 212 sort(Join, @=<, Dicts1, Dicts11), 213 sort(Join, @=<, Dicts2, Dicts21), 214 join(Dicts11, Dicts21, Join, Dicts). 215 216join([], [], _, []) :- !. 217join([D1|T1], [D2|T2], Join, [DNew|MoreDicts]) :- 218 !, 219 get_dict(Join, D1, K1), 220 get_dict(Join, D2, K2), 221 compare(Diff, K1, K2), 222 ( Diff == (=) 223 -> D1 >:< D2, 224 put_dict(D1, D2, DNew), 225 join(T1, T2, Join, MoreDicts) 226 ; Diff == (<) 227 -> DNew = D1, 228 join(T1, [D2|T2], Join, MoreDicts) 229 ; DNew = D2, 230 join([D1|T1], T2, Join, MoreDicts) 231 ). 232join([], Dicts, _, Dicts) :- !. 233join(Dicts, [], _, Dicts).
240dicts_slice(Keys, DictsIn, DictsOut) :- 241 sort(Keys, SortedKeys), 242 maplist(dict_slice(SortedKeys), DictsIn, DictsOut). 243 244dict_slice(Keys, DictIn, DictOut) :- 245 dict_pairs(DictIn, Tag, PairsIn), 246 slice_pairs(Keys, PairsIn, PairsOut), 247 dict_pairs(DictOut, Tag, PairsOut). 248 249slice_pairs([], _, []) :- !. 250slice_pairs(_, [], []) :- !. 251slice_pairs([H|T0], [P|PL], Pairs) :- 252 P = K-_, 253 compare(D, H, K), 254 ( D == (=) 255 -> Pairs = [P|More], 256 slice_pairs(T0, PL, More) 257 ; D == (<) 258 -> slice_pairs(T0, [P|PL], Pairs) 259 ; slice_pairs([H|T0], PL, Pairs) 260 ).
row
is used. For example:
?- Dicts = [_{x:1}, _{x:2, y:3}], dicts_to_compounds(Dicts, [x], dict_fill(null), Compounds). Compounds = [row(1), row(2)]. ?- Dicts = [_{x:1}, _{x:2, y:3}], dicts_to_compounds(Dicts, [x,y], dict_fill(null), Compounds). Compounds = [row(1, null), row(2, 3)]. ?- Compounds = [point(1,1), point(2,4)], dicts_to_compounds(Dicts, [x,y], dict_fill(null), Compounds). Dicts = [point{x:1, y:1}, point{x:2, y:4}].
When converting from Dicts to Compounds Keys may be computed by dicts_same_keys/2.
287dicts_to_compounds(Dicts, Keys, OnEmpty, Compounds) :- 288 maplist(dict_to_compound(Keys, OnEmpty), Dicts, Compounds). 289 290dict_to_compound(Keys, OnEmpty, Dict, Row) :- 291 is_dict(Dict, Tag), 292 !, 293 default_tag(Tag, row), 294 maplist(key_value(Dict, OnEmpty), Keys, Values), 295 compound_name_arguments(Row, Tag, Values). 296dict_to_compound(Keys, _, Dict, Row) :- 297 compound(Row), 298 compound_name_arguments(Row, Tag, Values), 299 pairs_keys_values(Pairs, Keys, Values), 300 dict_pairs(Dict, Tag, Pairs). 301 302default_tag(Tag, Tag) :- !. 303default_tag(_, _). 304 305key_value(Dict, OnEmpty, Key, Value) :- 306 ( get_dict(Key, Dict, Value0) 307 -> Value = Value0 308 ; call(OnEmpty, Key, Dict, Value) 309 )
Dict utilities
This library defines utilities that operate on lists of dicts, notably to make lists of dicts consistent by adding missing keys, converting between lists of compounds and lists of dicts, joining and slicing lists of dicts. */