1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker and Richard O'Keefe 4 E-mail: J.Wielemaker@cs.vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2002-2022, University of Amsterdam 7 VU University Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(lists, 38 [ member/2, % ?X, ?List 39 memberchk/2, % ?X, ?List 40 append/2, % +ListOfLists, -List 41 append/3, % ?A, ?B, ?AB 42 prefix/2, % ?Part, ?Whole 43 select/3, % ?X, ?List, ?Rest 44 selectchk/3, % ?X, ?List, ?Rest 45 select/4, % ?X, ?XList, ?Y, ?YList 46 selectchk/4, % ?X, ?XList, ?Y, ?YList 47 nextto/3, % ?X, ?Y, ?List 48 delete/3, % ?List, ?X, ?Rest 49 nth0/3, % ?N, ?List, ?Elem 50 nth1/3, % ?N, ?List, ?Elem 51 nth0/4, % ?N, ?List, ?Elem, ?Rest 52 nth1/4, % ?N, ?List, ?Elem, ?Rest 53 last/2, % +List, -Element 54 proper_length/2, % @List, -Length 55 same_length/2, % ?List1, ?List2 56 reverse/2, % +List, -Reversed 57 permutation/2, % ?List, ?Permutation 58 flatten/2, % +Nested, -Flat 59 clumped/2, % +Items,-Pairs 60 61 % Ordered operations 62 max_member/2, % -Max, +List 63 min_member/2, % -Min, +List 64 max_member/3, % :Pred, -Max, +List 65 min_member/3, % :Pred, -Min, +List 66 67 % Lists of numbers 68 sum_list/2, % +List, -Sum 69 max_list/2, % +List, -Max 70 min_list/2, % +List, -Min 71 numlist/3, % +Low, +High, -List 72 73 % set manipulation 74 is_set/1, % +List 75 list_to_set/2, % +List, -Set 76 intersection/3, % +List1, +List2, -Intersection 77 union/3, % +List1, +List2, -Union 78 subset/2, % +SubSet, +Set 79 subtract/3 % +Set, +Delete, -Remaining 80 ]). 81:- autoload(library(error),[must_be/2]). 82:- autoload(library(pairs),[pairs_keys/2]). 83 84:- meta_predicate 85 max_member( , , ), 86 min_member( , , ). 87 88:- set_prolog_flag(generate_debug_info, false). 89 90/** <module> List Manipulation 91 92This library provides commonly accepted basic predicates for list 93manipulation in the Prolog community. Some additional list manipulations 94are built-in. See e.g., memberchk/2, length/2. 95 96The implementation of this library is copied from many places. These 97include: "The Craft of Prolog", the DEC-10 Prolog library (LISTRO.PL) 98and the YAP lists library. Some predicates are reimplemented based on 99their specification by Quintus and SICStus. 100 101@compat Virtually every Prolog system has library(lists), but the set 102 of provided predicates is diverse. There is a fair agreement 103 on the semantics of most of these predicates, although error 104 handling may vary. 105*/ 106 107%! member(?Elem, ?List) 108% 109% True if Elem is a member of List. The SWI-Prolog definition 110% differs from the classical one. Our definition avoids unpacking 111% each list element twice and provides determinism on the last 112% element. E.g. this is deterministic: 113% 114% == 115% member(X, [One]). 116% == 117% 118% @author Gertjan van Noord 119 120member(El, [H|T]) :- 121 member_(T, El, H). 122 123member_(_, El, El). 124member_([H|T], El, _) :- 125 member_(T, El, H). 126 127%! append(?List1, ?List2, ?List1AndList2) 128% 129% List1AndList2 is the concatenation of List1 and List2 130 131append([], L, L). 132append([H|T], L, [H|R]) :- 133 append(T, L, R). 134 135%! append(+ListOfLists, ?List) 136% 137% Concatenate a list of lists. Is true if ListOfLists is a list of 138% lists, and List is the concatenation of these lists. 139% 140% @param ListOfLists must be a list of _possibly_ partial lists 141 142append(ListOfLists, List) :- 143 must_be(list, ListOfLists), 144 append_(ListOfLists, List). 145 146append_([], []). 147append_([L|Ls], As) :- 148 append(L, Ws, As), 149 append_(Ls, Ws). 150 151 152%! prefix(?Part, ?Whole) 153% 154% True iff Part is a leading substring of Whole. This is the same 155% as append(Part, _, Whole). 156 157prefix([], _). 158prefix([E|T0], [E|T]) :- 159 prefix(T0, T). 160 161 162%! select(?Elem, ?List1, ?List2) 163% 164% Is true when List1, with Elem removed, results in List2. This 165% implementation is determinsitic if the last element of List1 has 166% been selected. 167 168select(X, [Head|Tail], Rest) :- 169 select3_(Tail, Head, X, Rest). 170 171select3_(Tail, Head, Head, Tail). 172select3_([Head2|Tail], Head, X, [Head|Rest]) :- 173 select3_(Tail, Head2, X, Rest). 174 175 176%! selectchk(+Elem, +List, -Rest) is semidet. 177% 178% Semi-deterministic removal of first element in List that unifies 179% with Elem. 180 181selectchk(Elem, List, Rest) :- 182 select(Elem, List, Rest0), 183 !, 184 Rest = Rest0. 185 186 187%! select(?X, ?XList, ?Y, ?YList) is nondet. 188% 189% Select from two lists at the same position. True if XList is 190% unifiable with YList apart a single element at the same position 191% that is unified with X in XList and with Y in YList. A typical use 192% for this predicate is to _replace_ an element, as shown in the 193% example below. All possible substitutions are performed on 194% backtracking. 195% 196% == 197% ?- select(b, [a,b,c,b], 2, X). 198% X = [a, 2, c, b] ; 199% X = [a, b, c, 2] ; 200% false. 201% == 202% 203% @see selectchk/4 provides a semidet version. 204 205select(X, XList, Y, YList) :- 206 select4_(XList, X, Y, YList). 207 208select4_([X|List], X, Y, [Y|List]). 209select4_([X0|XList], X, Y, [X0|YList]) :- 210 select4_(XList, X, Y, YList). 211 212%! selectchk(?X, ?XList, ?Y, ?YList) is semidet. 213% 214% Semi-deterministic version of select/4. 215 216selectchk(X, XList, Y, YList) :- 217 select(X, XList, Y, YList), 218 !. 219 220%! nextto(?X, ?Y, ?List) 221% 222% True if Y directly follows X in List. 223 224nextto(X, Y, [X,Y|_]). 225nextto(X, Y, [_|Zs]) :- 226 nextto(X, Y, Zs). 227 228%! delete(+List1, @Elem, -List2) is det. 229% 230% Delete matching elements from a list. True when List2 is a list 231% with all elements from List1 except for those that unify with 232% Elem. Matching Elem with elements of List1 is uses =|\+ Elem \= 233% H|=, which implies that Elem is not changed. 234% 235% @deprecated There are too many ways in which one might want to 236% delete elements from a list to justify the name. 237% Think of matching (= vs. ==), delete first/all, 238% be deterministic or not. 239% @see select/3, subtract/3. 240 241delete([], _, []). 242delete([Elem|Tail], Del, Result) :- 243 ( \+ Elem \= Del 244 -> delete(Tail, Del, Result) 245 ; Result = [Elem|Rest], 246 delete(Tail, Del, Rest) 247 ). 248 249 250/* nth0/3, nth1/3 are improved versions from 251 Martin Jansche <martin@pc03.idf.uni-heidelberg.de> 252*/ 253 254%! nth0(?Index, ?List, ?Elem) 255% 256% True when Elem is the Index'th element of List. Counting starts 257% at 0. 258% 259% @error type_error(integer, Index) if Index is not an integer or 260% unbound. 261% @see nth1/3. 262 263nth0(Index, List, Elem) :- 264 ( integer(Index) 265 -> '$seek_list'(Index, List, RestIndex, RestList), 266 nth0_det(RestIndex, RestList, Elem) % take nth det 267 ; var(Index) 268 -> List = [H|T], 269 nth_gen(T, Elem, H, 0, Index) % match 270 ; must_be(integer, Index) 271 ). 272 273nth0_det(0, [Elem|_], Elem) :- !. 274nth0_det(N, [_|Tail], Elem) :- 275 M is N - 1, 276 M >= 0, 277 nth0_det(M, Tail, Elem). 278 279nth_gen(_, Elem, Elem, Base, Base). 280nth_gen([H|Tail], Elem, _, N, Base) :- 281 succ(N, M), 282 nth_gen(Tail, Elem, H, M, Base). 283 284 285%! nth1(?Index, ?List, ?Elem) 286% 287% Is true when Elem is the Index'th element of List. Counting 288% starts at 1. 289% 290% @see nth0/3. 291 292nth1(Index, List, Elem) :- 293 ( integer(Index) 294 -> Index0 is Index - 1, 295 '$seek_list'(Index0, List, RestIndex, RestList), 296 nth0_det(RestIndex, RestList, Elem) % take nth det 297 ; var(Index) 298 -> List = [H|T], 299 nth_gen(T, Elem, H, 1, Index) % match 300 ; must_be(integer, Index) 301 ). 302 303%! nth0(?N, ?List, ?Elem, ?Rest) is det. 304% 305% Select/insert element at index. True when Elem is the N'th 306% (0-based) element of List and Rest is the remainder (as in by 307% select/3) of List. For example: 308% 309% == 310% ?- nth0(I, [a,b,c], E, R). 311% I = 0, E = a, R = [b, c] ; 312% I = 1, E = b, R = [a, c] ; 313% I = 2, E = c, R = [a, b] ; 314% false. 315% == 316% 317% == 318% ?- nth0(1, L, a1, [a,b]). 319% L = [a, a1, b]. 320% == 321 322nth0(V, In, Element, Rest) :- 323 var(V), 324 !, 325 generate_nth(0, V, In, Element, Rest). 326nth0(V, In, Element, Rest) :- 327 must_be(nonneg, V), 328 find_nth0(V, In, Element, Rest). 329 330%! nth1(?N, ?List, ?Elem, ?Rest) is det. 331% 332% As nth0/4, but counting starts at 1. 333 334nth1(V, In, Element, Rest) :- 335 var(V), 336 !, 337 generate_nth(1, V, In, Element, Rest). 338nth1(V, In, Element, Rest) :- 339 must_be(positive_integer, V), 340 succ(V0, V), 341 find_nth0(V0, In, Element, Rest). 342 343generate_nth(I, I, [Head|Rest], Head, Rest). 344generate_nth(I, IN, [H|List], El, [H|Rest]) :- 345 I1 is I+1, 346 generate_nth(I1, IN, List, El, Rest). 347 348find_nth0(0, [Head|Rest], Head, Rest) :- !. 349find_nth0(N, [Head|Rest0], Elem, [Head|Rest]) :- 350 M is N-1, 351 find_nth0(M, Rest0, Elem, Rest). 352 353 354%! last(?List, ?Last) 355% 356% Succeeds when Last is the last element of List. This 357% predicate is =semidet= if List is a list and =multi= if List is 358% a partial list. 359% 360% @compat There is no de-facto standard for the argument order of 361% last/2. Be careful when porting code or use 362% append(_, [Last], List) as a portable alternative. 363 364last([X|Xs], Last) :- 365 last_(Xs, X, Last). 366 367last_([], Last, Last). 368last_([X|Xs], _, Last) :- 369 last_(Xs, X, Last). 370 371 372%! proper_length(@List, -Length) is semidet. 373% 374% True when Length is the number of elements in the proper list 375% List. This is equivalent to 376% 377% == 378% proper_length(List, Length) :- 379% is_list(List), 380% length(List, Length). 381% == 382 383proper_length(List, Length) :- 384 '$skip_list'(Length0, List, Tail), 385 Tail == [], 386 Length = Length0. 387 388 389%! same_length(?List1, ?List2) 390% 391% Is true when List1 and List2 are lists with the same number of 392% elements. The predicate is deterministic if at least one of the 393% arguments is a proper list. It is non-deterministic if both 394% arguments are partial lists. 395% 396% @see length/2 397 398same_length([], []). 399same_length([_|T1], [_|T2]) :- 400 same_length(T1, T2). 401 402 403%! reverse(?List1, ?List2) 404% 405% Is true when the elements of List2 are in reverse order compared to 406% List1. This predicate is deterministic if either list is a proper 407% list. If both lists are _partial lists_ backtracking generates 408% increasingly long lists. 409 410reverse(Xs, Ys) :- 411 reverse(Xs, Ys, [], Ys). 412 413reverse([], [], Ys, Ys). 414reverse([X|Xs], [_|Bound], Rs, Ys) :- 415 reverse(Xs, Bound, [X|Rs], Ys). 416 417 418%! permutation(?Xs, ?Ys) is nondet. 419% 420% True when Xs is a permutation of Ys. This can solve for Ys given 421% Xs or Xs given Ys, or even enumerate Xs and Ys together. The 422% predicate permutation/2 is primarily intended to generate 423% permutations. Note that a list of length N has N! permutations, 424% and unbounded permutation generation becomes prohibitively 425% expensive, even for rather short lists (10! = 3,628,800). 426% 427% If both Xs and Ys are provided and both lists have equal length 428% the order is |Xs|^2. Simply testing whether Xs is a permutation 429% of Ys can be achieved in order log(|Xs|) using msort/2 as 430% illustrated below with the =semidet= predicate is_permutation/2: 431% 432% == 433% is_permutation(Xs, Ys) :- 434% msort(Xs, Sorted), 435% msort(Ys, Sorted). 436% == 437% 438% The example below illustrates that Xs and Ys being proper lists 439% is not a sufficient condition to use the above replacement. 440% 441% == 442% ?- permutation([1,2], [X,Y]). 443% X = 1, Y = 2 ; 444% X = 2, Y = 1 ; 445% false. 446% == 447% 448% @error type_error(list, Arg) if either argument is not a proper 449% or partial list. 450 451permutation(Xs, Ys) :- 452 '$skip_list'(Xlen, Xs, XTail), 453 '$skip_list'(Ylen, Ys, YTail), 454 ( XTail == [], YTail == [] % both proper lists 455 -> Xlen == Ylen 456 ; var(XTail), YTail == [] % partial, proper 457 -> length(Xs, Ylen) 458 ; XTail == [], var(YTail) % proper, partial 459 -> length(Ys, Xlen) 460 ; var(XTail), var(YTail) % partial, partial 461 -> length(Xs, Len), 462 length(Ys, Len) 463 ; must_be(list, Xs), % either is not a list 464 must_be(list, Ys) 465 ), 466 perm(Xs, Ys). 467 468perm([], []). 469perm(List, [First|Perm]) :- 470 select(First, List, Rest), 471 perm(Rest, Perm). 472 473%! flatten(+NestedList, -FlatList) is det. 474% 475% Is true if FlatList is a non-nested version of NestedList. Note 476% that empty lists are removed. In standard Prolog, this implies 477% that the atom '[]' is removed too. In SWI7, `[]` is distinct 478% from '[]'. 479% 480% Ending up needing flatten/2 often indicates, like append/3 for 481% appending two lists, a bad design. Efficient code that generates 482% lists from generated small lists must use difference lists, 483% often possible through grammar rules for optimal readability. 484% 485% @see append/2 486 487flatten(List, FlatList) :- 488 flatten(List, [], FlatList0), 489 !, 490 FlatList = FlatList0. 491 492flatten(Var, Tl, [Var|Tl]) :- 493 var(Var), 494 !. 495flatten([], Tl, Tl) :- !. 496flatten([Hd|Tl], Tail, List) :- 497 !, 498 flatten(Hd, FlatHeadTail, List), 499 flatten(Tl, Tail, FlatHeadTail). 500flatten(NonList, Tl, [NonList|Tl]). 501 502 503 /******************************* 504 * CLUMPS * 505 *******************************/ 506 507%! clumped(+Items, -Pairs) 508% 509% Pairs is a list of `Item-Count` pairs that represents the _run 510% length encoding_ of Items. For example: 511% 512% ``` 513% ?- clumped([a,a,b,a,a,a,a,c,c,c], R). 514% R = [a-2, b-1, a-4, c-3]. 515% ``` 516% 517% @compat SICStus 518 519clumped(Items, Counts) :- 520 clump(Items, Counts). 521 522clump([], []). 523clump([H|T0], [H-C|T]) :- 524 ccount(T0, H, T1, 1, C), 525 clump(T1, T). 526 527ccount([H|T0], E, T, C0, C) :- 528 E == H, 529 !, 530 C1 is C0+1, 531 ccount(T0, E, T, C1, C). 532ccount(List, _, List, C, C). 533 534 535 /******************************* 536 * ORDER OPERATIONS * 537 *******************************/ 538 539%! max_member(-Max, +List) is semidet. 540% 541% True when Max is the largest member in the standard order of 542% terms. Fails if List is empty. 543% 544% @see compare/3 545% @see max_list/2 for the maximum of a list of numbers. 546 547max_member(Max, [H|T]) => 548 max_member_(T, H, Max). 549max_member(_, []) => 550 fail. 551 552max_member_([], Max0, Max) => 553 Max = Max0. 554max_member_([H|T], Max0, Max) => 555 ( H @=< Max0 556 -> max_member_(T, Max0, Max) 557 ; max_member_(T, H, Max) 558 ). 559 560 561%! min_member(-Min, +List) is semidet. 562% 563% True when Min is the smallest member in the standard order of 564% terms. Fails if List is empty. 565% 566% @see compare/3 567% @see min_list/2 for the minimum of a list of numbers. 568 569min_member(Min, [H|T]) => 570 min_member_(T, H, Min). 571min_member(_, []) => 572 fail. 573 574min_member_([], Min0, Min) => 575 Min = Min0. 576min_member_([H|T], Min0, Min) => 577 ( H @>= Min0 578 -> min_member_(T, Min0, Min) 579 ; min_member_(T, H, Min) 580 ). 581 582 583%! max_member(:Pred, -Max, +List) is semidet. 584% 585% True when Max is the largest member according to Pred, which must be 586% a 2-argument callable that behaves like (@=<)/2. Fails if List is 587% empty. The following call is equivalent to max_member/2: 588% 589% ?- max_member(@=<, X, [6,1,8,4]). 590% X = 8. 591% 592% @see max_list/2 for the maximum of a list of numbers. 593 594max_member(Pred, Max, [H|T]) => 595 max_member_(T, Pred, H, Max). 596max_member(_, _, []) => 597 fail. 598 599max_member_([], _, Max0, Max) => 600 Max = Max0. 601max_member_([H|T], Pred, Max0, Max) => 602 ( call(Pred, H, Max0) 603 -> max_member_(T, Pred, Max0, Max) 604 ; max_member_(T, Pred, H, Max) 605 ). 606 607 608%! min_member(:Pred, -Min, +List) is semidet. 609% 610% True when Min is the smallest member according to Pred, which must 611% be a 2-argument callable that behaves like (@=<)/2. Fails if List is 612% empty. The following call is equivalent to max_member/2: 613% 614% ?- min_member(@=<, X, [6,1,8,4]). 615% X = 1. 616% 617% @see min_list/2 for the minimum of a list of numbers. 618 619min_member(Pred, Min, [H|T]) => 620 min_member_(T, Pred, H, Min). 621min_member(_, _, []) => 622 fail. 623 624min_member_([], _, Min0, Min) => 625 Min = Min0. 626min_member_([H|T], Pred, Min0, Min) => 627 ( call(Pred, Min0, H) 628 -> min_member_(T, Pred, Min0, Min) 629 ; min_member_(T, Pred, H, Min) 630 ). 631 632 633 /******************************* 634 * LISTS OF NUMBERS * 635 *******************************/ 636 637%! sum_list(+List, -Sum) is det. 638% 639% Sum is the result of adding all numbers in List. 640 641sum_list(Xs, Sum) :- 642 sum_list(Xs, 0, Sum). 643 644sum_list([], Sum0, Sum) => 645 Sum = Sum0. 646sum_list([X|Xs], Sum0, Sum) => 647 Sum1 is Sum0 + X, 648 sum_list(Xs, Sum1, Sum). 649 650%! max_list(+List:list(number), -Max:number) is semidet. 651% 652% True if Max is the largest number in List. Fails if List is 653% empty. 654% 655% @see max_member/2. 656 657max_list([H|T], Max) => 658 max_list(T, H, Max). 659max_list([], _) => fail. 660 661max_list([], Max0, Max) => 662 Max = Max0. 663max_list([H|T], Max0, Max) => 664 Max1 is max(H, Max0), 665 max_list(T, Max1, Max). 666 667 668%! min_list(+List:list(number), -Min:number) is semidet. 669% 670% True if Min is the smallest number in List. Fails if List is 671% empty. 672% 673% @see min_member/2. 674 675min_list([H|T], Min) => 676 min_list(T, H, Min). 677min_list([], _) => fail. 678 679min_list([], Min0, Min) => 680 Min = Min0. 681min_list([H|T], Min0, Min) => 682 Min1 is min(H, Min0), 683 min_list(T, Min1, Min). 684 685 686%! numlist(+Low, +High, -List) is semidet. 687% 688% List is a list [Low, Low+1, ... High]. Fails if High < Low. 689% 690% @error type_error(integer, Low) 691% @error type_error(integer, High) 692 693numlist(L, U, Ns) :- 694 must_be(integer, L), 695 must_be(integer, U), 696 L =< U, 697 numlist_(L, U, Ns). 698 699numlist_(U, U, List) :- 700 !, 701 List = [U]. 702numlist_(L, U, [L|Ns]) :- 703 L2 is L+1, 704 numlist_(L2, U, Ns). 705 706 707 /******************************** 708 * SET MANIPULATION * 709 *********************************/ 710 711%! is_set(@Set) is semidet. 712% 713% True if Set is a proper list without duplicates. Equivalence is 714% based on ==/2. The implementation uses sort/2, which implies 715% that the complexity is N*log(N) and the predicate may cause a 716% resource-error. There are no other error conditions. 717 718is_set(Set) :- 719 '$skip_list'(Len, Set, Tail), 720 Tail == [], % Proper list 721 sort(Set, Sorted), 722 length(Sorted, Len). 723 724 725%! list_to_set(+List, ?Set) is det. 726% 727% True when Set has the same elements as List in the same order. 728% The left-most copy of duplicate elements is retained. List may 729% contain variables. Elements _E1_ and _E2_ are considered 730% duplicates iff _E1_ == _E2_ holds. The complexity of the 731% implementation is N*log(N). 732% 733% @see sort/2 can be used to create an ordered set. Many 734% set operations on ordered sets are order N rather than 735% order N**2. The list_to_set/2 predicate is more 736% expensive than sort/2 because it involves, two sorts 737% and a linear scan. 738% @compat Up to version 6.3.11, list_to_set/2 had complexity 739% N**2 and equality was tested using =/2. 740% @error List is type-checked. 741 742list_to_set(List, Set) :- 743 must_be(list, List), 744 number_list(List, 1, Numbered), 745 sort(1, @=<, Numbered, ONum), 746 remove_dup_keys(ONum, NumSet), 747 sort(2, @=<, NumSet, ONumSet), 748 pairs_keys(ONumSet, Set). 749 750number_list([], _, []). 751number_list([H|T0], N, [H-N|T]) :- 752 N1 is N+1, 753 number_list(T0, N1, T). 754 755remove_dup_keys([], []). 756remove_dup_keys([H|T0], [H|T]) :- 757 H = V-_, 758 remove_same_key(T0, V, T1), 759 remove_dup_keys(T1, T). 760 761remove_same_key([V1-_|T0], V, T) :- 762 V1 == V, 763 !, 764 remove_same_key(T0, V, T). 765remove_same_key(L, _, L). 766 767 768%! intersection(+Set1, +Set2, -Set3) is det. 769% 770% True if Set3 unifies with the intersection of Set1 and Set2. The 771% complexity of this predicate is |Set1|*|Set2|. A _set_ is defined to 772% be an unordered list without duplicates. Elements are considered 773% duplicates if they can be unified. 774% 775% @see ord_intersection/3. 776 777intersection([], _, Set) => 778 Set = []. 779intersection([X|T], L, Intersect) => 780 ( memberchk(X, L) 781 -> Intersect = [X|R], 782 intersection(T, L, R) 783 ; intersection(T, L, Intersect) 784 ). 785 786%! union(+Set1, +Set2, -Set3) is det. 787% 788% True if Set3 unifies with the union of the lists Set1 and Set2. The 789% complexity of this predicate is |Set1|*|Set2|. A _set_ is defined to 790% be an unordered list without duplicates. Elements are considered 791% duplicates if they can be unified. 792% 793% @see ord_union/3 794 795union([], L0, L) => 796 L = L0. 797union([H|T], L, Union) => 798 ( memberchk(H, L) 799 -> union(T, L, Union) 800 ; Union = [H|R], 801 union(T, L, R) 802 ). 803 804%! subset(+SubSet, +Set) is semidet. 805% 806% True if all elements of SubSet belong to Set as well. Membership 807% test is based on memberchk/2. The complexity is |SubSet|*|Set|. A 808% _set_ is defined to be an unordered list without duplicates. 809% Elements are considered duplicates if they can be unified. 810% 811% @see ord_subset/2. 812 813subset([], _) => true. 814subset([E|R], Set) => 815 memberchk(E, Set), 816 subset(R, Set). 817 818 819%! subtract(+Set, +Delete, -Result) is det. 820% 821% Delete all elements in Delete from Set. Deletion is based on 822% unification using memberchk/2. The complexity is |Delete|*|Set|. A 823% _set_ is defined to be an unordered list without duplicates. 824% Elements are considered duplicates if they can be unified. 825% 826% @see ord_subtract/3. 827 828subtract([], _, R) => 829 R = []. 830subtract([E|T], D, R) => 831 ( memberchk(E, D) 832 -> subtract(T, D, R) 833 ; R = [E|R1], 834 subtract(T, D, R1) 835 )