View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker and Jon Jagger
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2001-2021, 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(ordsets,
   38          [ is_ordset/1,                % @Term
   39            list_to_ord_set/2,          % +List, -OrdSet
   40            ord_add_element/3,          % +Set, +Element, -NewSet
   41            ord_del_element/3,          % +Set, +Element, -NewSet
   42            ord_selectchk/3,            % +Item, ?Set1, ?Set2
   43            ord_intersect/2,            % +Set1, +Set2 (test non-empty)
   44            ord_intersect/3,            % +Set1, +Set2, -Intersection
   45            ord_intersection/3,         % +Set1, +Set2, -Intersection
   46            ord_intersection/4,         % +Set1, +Set2, -Intersection, -Diff
   47            ord_disjoint/2,             % +Set1, +Set2
   48            ord_subtract/3,             % +Set, +Delete, -Remaining
   49            ord_union/2,                % +SetOfOrdSets, -Set
   50            ord_union/3,                % +Set1, +Set2, -Union
   51            ord_union/4,                % +Set1, +Set2, -Union, -New
   52            ord_subset/2,               % +Sub, +Super (test Sub is in Super)
   53                                        % Non-Quintus extensions
   54            ord_empty/1,                % ?Set
   55            ord_memberchk/2,            % +Element, +Set,
   56            ord_symdiff/3,              % +Set1, +Set2, ?Diff
   57                                        % SICSTus extensions
   58            ord_seteq/2,                % +Set1, +Set2
   59            ord_intersection/2          % +PowerSet, -Intersection
   60          ]).   61:- use_module(library(error)).   62
   63:- set_prolog_flag(generate_debug_info, false).

Ordered set manipulation

Ordered sets are lists with unique elements sorted to the standard order of terms (see sort/2). Exploiting ordering, many of the set operations can be expressed in order N rather than N^2 when dealing with unordered sets that may contain duplicates. The library(ordsets) is available in a number of Prolog implementations. Our predicates are designed to be compatible with common practice in the Prolog community. The implementation is incomplete and relies partly on library(oset), an older ordered set library distributed with SWI-Prolog. New applications are advised to use library(ordsets).

Some of these predicates match directly to corresponding list operations. It is advised to use the versions from this library to make clear you are operating on ordered sets. An exception is member/2. See ord_memberchk/2.

The ordsets library is based on the standard order of terms. This implies it can handle all Prolog terms, including variables. Note however, that the ordering is not stable if a term inside the set is further instantiated. Also note that variable ordering changes if variables in the set are unified with each other or a variable in the set is unified with a variable that is `older' than the newest variable in the set. In practice, this implies that it is allowed to use member(X, OrdSet) on an ordered set that holds variables only if X is a fresh variable. In other cases one should cease using it as an ordset because the order it relies on may have been changed. */

 is_ordset(@Term) is semidet
True if Term is an ordered set. All predicates in this library expect ordered sets as input arguments. Failing to fullfil this assumption results in undefined behaviour. Typically, ordered sets are created by predicates from this library, sort/2 or setof/3.
  102is_ordset(Term) :-
  103    is_list(Term),
  104    is_ordset2(Term).
  105
  106is_ordset2([]).
  107is_ordset2([H|T]) :-
  108    is_ordset3(T, H).
  109
  110is_ordset3([], _).
  111is_ordset3([H2|T], H) :-
  112    H2 @> H,
  113    is_ordset3(T, H2).
 ord_empty(?List) is semidet
True when List is the empty ordered set. Simply unifies list with the empty list. Not part of Quintus.
  121ord_empty([]).
 ord_seteq(+Set1, +Set2) is semidet
True if Set1 and Set2 have the same elements. As both are canonical sorted lists, this is the same as ==/2.
Compatibility
- sicstus
  131ord_seteq(Set1, Set2) :-
  132    Set1 == Set2.
 list_to_ord_set(+List, -OrdSet) is det
Transform a list into an ordered set. This is the same as sorting the list.
  140list_to_ord_set(List, Set) :-
  141    sort(List, Set).
 ord_intersect(+Set1, +Set2) is semidet
True if both ordered sets have a non-empty intersection.
  148ord_intersect([H1|T1], L2) :-
  149    ord_intersect_(L2, H1, T1).
  150
  151ord_intersect_([H2|T2], H1, T1) :-
  152    compare(Order, H1, H2),
  153    ord_intersect__(Order, H1, T1, H2, T2).
  154
  155ord_intersect__(<, _H1, T1,  H2, T2) :-
  156    ord_intersect_(T1, H2, T2).
  157ord_intersect__(=, _H1, _T1, _H2, _T2).
  158ord_intersect__(>, H1, T1,  _H2, T2) :-
  159    ord_intersect_(T2, H1, T1).
 ord_disjoint(+Set1, +Set2) is semidet
True if Set1 and Set2 have no common elements. This is the negation of ord_intersect/2.
  167ord_disjoint(Set1, Set2) :-
  168    \+ ord_intersect(Set1, Set2).
 ord_intersect(+Set1, +Set2, -Intersection)
Intersection holds the common elements of Set1 and Set2.
deprecated
- Use ord_intersection/3
  177ord_intersect(Set1, Set2, Intersection) :-
  178    ord_intersection(Set1, Set2, Intersection).
 ord_intersection(+PowerSet, -Intersection)
Intersection of a powerset. True when Intersection is an ordered set holding all elements common to all sets in PowerSet.
Compatibility
- sicstus
  188ord_intersection(PowerSet, Intersection) :-
  189    must_be(list, PowerSet),
  190    key_by_length(PowerSet, Pairs),
  191    keysort(Pairs, [_-S|Sorted]),
  192    l_int(Sorted, S, Intersection).
  193
  194key_by_length([], []).
  195key_by_length([H|T0], [L-H|T]) :-
  196    '$skip_list'(L, H, Tail),
  197    (   Tail == []
  198    ->  key_by_length(T0, T)
  199    ;   type_error(list, H)
  200    ).
  201
  202l_int(_, [], I) =>
  203    I = [].
  204l_int([], S, I) =>
  205    I = S.
  206l_int([_-H|T], S0, S) =>
  207    ord_intersection(S0, H, S1),
  208    l_int(T, S1, S).
 ord_intersection(+Set1, +Set2, -Intersection) is det
Intersection holds the common elements of Set1 and Set2. Uses ord_disjoint/2 if Intersection is bound to [] on entry.
  216ord_intersection(Set1, Set2, Intersection) :-
  217    (   Intersection == []
  218    ->  ord_disjoint(Set1, Set2)
  219    ;   ord_intersection_(Set1, Set2, Intersection)
  220    ).
  221
  222ord_intersection_([], _Int, []).
  223ord_intersection_([H1|T1], L2, Int) :-
  224    isect2(L2, H1, T1, Int).
  225
  226isect2([], _H1, _T1, []).
  227isect2([H2|T2], H1, T1, Int) :-
  228    compare(Order, H1, H2),
  229    isect3(Order, H1, T1, H2, T2, Int).
  230
  231isect3(<, _H1, T1,  H2, T2, Int) :-
  232    isect2(T1, H2, T2, Int).
  233isect3(=, H1, T1, _H2, T2, [H1|Int]) :-
  234    ord_intersection_(T1, T2, Int).
  235isect3(>, H1, T1,  _H2, T2, Int) :-
  236    isect2(T2, H1, T1, Int).
 ord_intersection(+Set1, +Set2, ?Intersection, ?Difference) is det
Intersection and difference between two ordered sets. Intersection is the intersection between Set1 and Set2, while Difference is defined by ord_subtract(Set2, Set1, Difference).
See also
- ord_intersection/3 and ord_subtract/3.
  247ord_intersection([], L, [], L) :- !.
  248ord_intersection([_|_], [], [], []) :- !.
  249ord_intersection([H1|T1], [H2|T2], Intersection, Difference) :-
  250    compare(Diff, H1, H2),
  251    ord_intersection2(Diff, H1, T1, H2, T2, Intersection, Difference).
  252
  253ord_intersection2(=, H1, T1, _H2, T2, [H1|T], Difference) :-
  254    ord_intersection(T1, T2, T, Difference).
  255ord_intersection2(<, _, T1, H2, T2, Intersection, Difference) :-
  256    ord_intersection(T1, [H2|T2], Intersection, Difference).
  257ord_intersection2(>, H1, T1, H2, T2, Intersection, [H2|HDiff]) :-
  258    ord_intersection([H1|T1], T2, Intersection, HDiff).
 ord_add_element(+Set1, +Element, ?Set2) is det
Insert an element into the set. This is the same as ord_union(Set1, [Element], Set2).
  266ord_add_element([], El, [El]).
  267ord_add_element([H|T], El, Add) :-
  268    compare(Order, H, El),
  269    addel(Order, H, T, El, Add).
  270
  271addel(<, H, T,  El, [H|Add]) :-
  272    ord_add_element(T, El, Add).
  273addel(=, H, T, _El, [H|T]).
  274addel(>, H, T,  El, [El,H|T]).
 ord_del_element(+Set, +Element, -NewSet) is det
Delete an element from an ordered set. This is the same as ord_subtract(Set, [Element], NewSet).
  283ord_del_element([], _El, []).
  284ord_del_element([H|T], El, Del) :-
  285    compare(Order, H, El),
  286    delel(Order, H, T, El, Del).
  287
  288delel(<,  H, T,  El, [H|Del]) :-
  289    ord_del_element(T, El, Del).
  290delel(=, _H, T, _El, T).
  291delel(>,  H, T, _El, [H|T]).
 ord_selectchk(+Item, ?Set1, ?Set2) is semidet
Selectchk/3, specialised for ordered sets. Is true when select(Item, Set1, Set2) and Set1, Set2 are both sorted lists without duplicates. This implementation is only expected to work for Item ground and either Set1 or Set2 ground. The "chk" suffix is meant to remind you of memberchk/2, which also expects its first argument to be ground. ord_selectchk(X, S, T) => ord_memberchk(X, S) & \+ ord_memberchk(X, T).
author
- Richard O'Keefe
  306ord_selectchk(Item, [X|Set1], [X|Set2]) :-
  307    X @< Item,
  308    !,
  309    ord_selectchk(Item, Set1, Set2).
  310ord_selectchk(Item, [Item|Set1], Set1) :-
  311    (   Set1 == []
  312    ->  true
  313    ;   Set1 = [Y|_]
  314    ->  Item @< Y
  315    ).
 ord_memberchk(+Element, +OrdSet) is semidet
True if Element is a member of OrdSet, compared using ==. Note that enumerating elements of an ordered set can be done using member/2.

Some Prolog implementations also provide ord_member/2, with the same semantics as ord_memberchk/2. We believe that having a semidet ord_member/2 is unacceptably inconsistent with the *_chk convention. Portable code should use ord_memberchk/2 or member/2.

author
- Richard O'Keefe
  332ord_memberchk(Item, [X1,X2,X3,X4|Xs]) :-
  333    !,
  334    compare(R4, Item, X4),
  335    (   R4 = (>) -> ord_memberchk(Item, Xs)
  336    ;   R4 = (<) ->
  337        compare(R2, Item, X2),
  338        (   R2 = (>) -> Item == X3
  339        ;   R2 = (<) -> Item == X1
  340        ;/* R2 = (=),   Item == X2 */ true
  341        )
  342    ;/* R4 = (=) */ true
  343    ).
  344ord_memberchk(Item, [X1,X2|Xs]) :-
  345    !,
  346    compare(R2, Item, X2),
  347    (   R2 = (>) -> ord_memberchk(Item, Xs)
  348    ;   R2 = (<) -> Item == X1
  349    ;/* R2 = (=) */ true
  350    ).
  351ord_memberchk(Item, [X1]) :-
  352    Item == X1.
 ord_subset(+Sub, +Super) is semidet
Is true if all elements of Sub are in Super
  359ord_subset([], _).
  360ord_subset([H1|T1], [H2|T2]) :-
  361    compare(Order, H1, H2),
  362    ord_subset_(Order, H1, T1, T2).
  363
  364ord_subset_(>, H1, T1, [H2|T2]) :-
  365    compare(Order, H1, H2),
  366    ord_subset_(Order, H1, T1, T2).
  367ord_subset_(=, _, T1, T2) :-
  368    ord_subset(T1, T2).
 ord_subtract(+InOSet, +NotInOSet, -Diff) is det
Diff is the set holding all elements of InOSet that are not in NotInOSet.
  376ord_subtract([], _Not, []).
  377ord_subtract([H1|T1], L2, Diff) :-
  378    diff21(L2, H1, T1, Diff).
  379
  380diff21([], H1, T1, [H1|T1]).
  381diff21([H2|T2], H1, T1, Diff) :-
  382    compare(Order, H1, H2),
  383    diff3(Order, H1, T1, H2, T2, Diff).
  384
  385diff12([], _H2, _T2, []).
  386diff12([H1|T1], H2, T2, Diff) :-
  387    compare(Order, H1, H2),
  388    diff3(Order, H1, T1, H2, T2, Diff).
  389
  390diff3(<,  H1, T1,  H2, T2, [H1|Diff]) :-
  391    diff12(T1, H2, T2, Diff).
  392diff3(=, _H1, T1, _H2, T2, Diff) :-
  393    ord_subtract(T1, T2, Diff).
  394diff3(>,  H1, T1, _H2, T2, Diff) :-
  395    diff21(T2, H1, T1, Diff).
 ord_union(+SetOfSets, -Union) is det
True if Union is the union of all elements in the superset SetOfSets. Each member of SetOfSets must be an ordered set, the sets need not be ordered in any way.
author
- Copied from YAP, probably originally by Richard O'Keefe.
  406ord_union([], Union) =>
  407    Union = [].
  408ord_union([Set|Sets], Union) =>
  409    length([Set|Sets], NumberOfSets),
  410    ord_union_all(NumberOfSets, [Set|Sets], Union, []).
  411
  412ord_union_all(N, Sets0, Union, Sets) =>
  413    (   N =:= 1
  414    ->  Sets0 = [Union|Sets]
  415    ;   N =:= 2
  416    ->  Sets0 = [Set1,Set2|Sets],
  417        ord_union(Set1,Set2,Union)
  418    ;   A is N>>1,
  419        Z is N-A,
  420        ord_union_all(A, Sets0, X, Sets1),
  421        ord_union_all(Z, Sets1, Y, Sets),
  422        ord_union(X, Y, Union)
  423    ).
 ord_union(+Set1, +Set2, -Union) is det
Union is the union of Set1 and Set2
  430ord_union([], Set2, Union) =>
  431    Union = Set2.
  432ord_union([H1|T1], L2, Union) =>
  433    union2(L2, H1, T1, Union).
  434
  435union2([], H1, T1, Union) =>
  436    Union = [H1|T1].
  437union2([H2|T2], H1, T1, Union) =>
  438    compare(Order, H1, H2),
  439    union3(Order, H1, T1, H2, T2, Union).
  440
  441union3(<, H1, T1,  H2, T2, Union) =>
  442    Union = [H1|Union0],
  443    union2(T1, H2, T2, Union0).
  444union3(=, H1, T1, _H2, T2, Union) =>
  445    Union = [H1|Union0],
  446    ord_union(T1, T2, Union0).
  447union3(>, H1, T1,  H2, T2, Union) =>
  448    Union = [H2|Union0],
  449    union2(T2, H1, T1, Union0).
 ord_union(+Set1, +Set2, -Union, -New) is det
True iff ord_union(Set1, Set2, Union) and ord_subtract(Set2, Set1, New).
  456ord_union([], Set2, Set2, Set2).
  457ord_union([H|T], Set2, Union, New) :-
  458    ord_union_1(Set2, H, T, Union, New).
  459
  460ord_union_1([], H, T, [H|T], []).
  461ord_union_1([H2|T2], H, T, Union, New) :-
  462    compare(Order, H, H2),
  463    ord_union(Order, H, T, H2, T2, Union, New).
  464
  465ord_union(<, H, T, H2, T2, [H|Union], New) :-
  466    ord_union_2(T, H2, T2, Union, New).
  467ord_union(>, H, T, H2, T2, [H2|Union], [H2|New]) :-
  468    ord_union_1(T2, H, T, Union, New).
  469ord_union(=, H, T, _, T2, [H|Union], New) :-
  470    ord_union(T, T2, Union, New).
  471
  472ord_union_2([], H2, T2, [H2|T2], [H2|T2]).
  473ord_union_2([H|T], H2, T2, Union, New) :-
  474    compare(Order, H, H2),
  475    ord_union(Order, H, T, H2, T2, Union, New).
 ord_symdiff(+Set1, +Set2, ?Difference) is det
Is true when Difference is the symmetric difference of Set1 and Set2. I.e., Difference contains all elements that are not in the intersection of Set1 and Set2. The semantics is the same as the sequence below (but the actual implementation requires only a single scan).
      ord_union(Set1, Set2, Union),
      ord_intersection(Set1, Set2, Intersection),
      ord_subtract(Union, Intersection, Difference).

For example:

?- ord_symdiff([1,2], [2,3], X).
X = [1,3].
  499ord_symdiff([], Set2, Set2).
  500ord_symdiff([H1|T1], Set2, Difference) :-
  501    ord_symdiff(Set2, H1, T1, Difference).
  502
  503ord_symdiff([], H1, T1, [H1|T1]).
  504ord_symdiff([H2|T2], H1, T1, Difference) :-
  505    compare(Order, H1, H2),
  506    ord_symdiff(Order, H1, T1, H2, T2, Difference).
  507
  508ord_symdiff(<, H1, Set1, H2, T2, [H1|Difference]) :-
  509    ord_symdiff(Set1, H2, T2, Difference).
  510ord_symdiff(=, _, T1, _, T2, Difference) :-
  511    ord_symdiff(T1, T2, Difference).
  512ord_symdiff(>, H1, T1, H2, Set2, [H2|Difference]) :-
  513    ord_symdiff(Set2, H1, T1, Difference)