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