View source with formatted comments or as raw
    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)  2001-2014, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(ordsets,
   37          [ is_ordset/1,                % @Term
   38            list_to_ord_set/2,          % +List, -OrdSet
   39            ord_add_element/3,          % +Set, +Element, -NewSet
   40            ord_del_element/3,          % +Set, +Element, -NewSet
   41            ord_selectchk/3,            % +Item, ?Set1, ?Set2
   42            ord_intersect/2,            % +Set1, +Set2 (test non-empty)
   43            ord_intersect/3,            % +Set1, +Set2, -Intersection
   44            ord_intersection/3,         % +Set1, +Set2, -Intersection
   45            ord_intersection/4,         % +Set1, +Set2, -Intersection, -Diff
   46            ord_disjoint/2,             % +Set1, +Set2
   47            ord_subtract/3,             % +Set, +Delete, -Remaining
   48            ord_union/2,                % +SetOfOrdSets, -Set
   49            ord_union/3,                % +Set1, +Set2, -Union
   50            ord_union/4,                % +Set1, +Set2, -Union, -New
   51            ord_subset/2,               % +Sub, +Super (test Sub is in Super)
   52                                        % Non-Quintus extensions
   53            ord_empty/1,                % ?Set
   54            ord_memberchk/2,            % +Element, +Set,
   55            ord_symdiff/3,              % +Set1, +Set2, ?Diff
   56                                        % SICSTus extensions
   57            ord_seteq/2,                % +Set1, +Set2
   58            ord_intersection/2          % +PowerSet, -Intersection
   59          ]).   60:- autoload(library(oset),
   61	    [ oset_int/3,
   62	      oset_addel/3,
   63	      oset_delel/3,
   64	      oset_diff/3,
   65	      oset_union/3
   66	    ]).   67
   68
   69:- set_prolog_flag(generate_debug_info, false).   70
   71/** <module> Ordered set manipulation
   72
   73Ordered sets are lists with unique elements sorted to the standard order
   74of terms (see sort/2). Exploiting ordering,   many of the set operations
   75can be expressed in order N rather  than N^2 when dealing with unordered
   76sets that may contain duplicates. The library(ordsets) is available in a
   77number of Prolog implementations. Our  predicates   are  designed  to be
   78compatible  with  common  practice   in    the   Prolog  community.  The
   79implementation is incomplete and  relies   partly  on  library(oset), an
   80older ordered set library distributed  with SWI-Prolog. New applications
   81are advised to use library(ordsets).
   82
   83Some  of  these  predicates  match    directly   to  corresponding  list
   84operations. It is advised to use the  versions from this library to make
   85clear you are operating on ordered sets.   An exception is member/2. See
   86ord_memberchk/2.
   87
   88The ordsets library is based  on  the   standard  order  of  terms. This
   89implies it can handle  all  Prolog   terms,  including  variables.  Note
   90however, that the ordering is not stable  if   a  term inside the set is
   91further instantiated. Also  note  that   variable  ordering  changes  if
   92variables in the set are unified with each   other  or a variable in the
   93set is unified with a variable that  is `older' than the newest variable
   94in the set. In  practice,  this  implies   that  it  is  allowed  to use
   95member(X, OrdSet) on an ordered set that holds  variables only if X is a
   96fresh variable. In other cases one should   cease  using it as an ordset
   97because the order it relies on may have been changed.
   98*/
   99
  100%!  is_ordset(@Term) is semidet.
  101%
  102%   True if Term is an ordered set.   All predicates in this library
  103%   expect ordered sets as input arguments.  Failing to fullfil this
  104%   assumption results in undefined   behaviour.  Typically, ordered
  105%   sets are created by predicates  from   this  library,  sort/2 or
  106%   setof/3.
  107
  108is_ordset(Term) :-
  109    is_list(Term),
  110    is_ordset2(Term).
  111
  112is_ordset2([]).
  113is_ordset2([H|T]) :-
  114    is_ordset3(T, H).
  115
  116is_ordset3([], _).
  117is_ordset3([H2|T], H) :-
  118    H2 @> H,
  119    is_ordset3(T, H2).
  120
  121
  122%!  ord_empty(?List) is semidet.
  123%
  124%   True when List is the  empty   ordered  set. Simply unifies list
  125%   with the empty list. Not part of Quintus.
  126
  127ord_empty([]).
  128
  129
  130%!  ord_seteq(+Set1, +Set2) is semidet.
  131%
  132%   True if Set1 and Set2  have  the   same  elements.  As  both are
  133%   canonical sorted lists, this is the same as ==/2.
  134%
  135%   @compat sicstus
  136
  137ord_seteq(Set1, Set2) :-
  138    Set1 == Set2.
  139
  140
  141%!  list_to_ord_set(+List, -OrdSet) is det.
  142%
  143%   Transform a list into an ordered set.  This is the same as
  144%   sorting the list.
  145
  146list_to_ord_set(List, Set) :-
  147    sort(List, Set).
  148
  149
  150%!  ord_intersect(+Set1, +Set2) is semidet.
  151%
  152%   True if both ordered sets have a non-empty intersection.
  153
  154ord_intersect([H1|T1], L2) :-
  155    ord_intersect_(L2, H1, T1).
  156
  157ord_intersect_([H2|T2], H1, T1) :-
  158    compare(Order, H1, H2),
  159    ord_intersect__(Order, H1, T1, H2, T2).
  160
  161ord_intersect__(<, _H1, T1,  H2, T2) :-
  162    ord_intersect_(T1, H2, T2).
  163ord_intersect__(=, _H1, _T1, _H2, _T2).
  164ord_intersect__(>, H1, T1,  _H2, T2) :-
  165    ord_intersect_(T2, H1, T1).
  166
  167
  168%!  ord_disjoint(+Set1, +Set2) is semidet.
  169%
  170%   True if Set1 and Set2  have  no   common  elements.  This is the
  171%   negation of ord_intersect/2.
  172
  173ord_disjoint(Set1, Set2) :-
  174    \+ ord_intersect(Set1, Set2).
  175
  176
  177%!  ord_intersect(+Set1, +Set2, -Intersection)
  178%
  179%   Intersection  holds  the  common  elements  of  Set1  and  Set2.
  180%
  181%   @deprecated Use ord_intersection/3
  182
  183ord_intersect(Set1, Set2, Intersection) :-
  184    oset_int(Set1, Set2, Intersection).
  185
  186
  187%!  ord_intersection(+PowerSet, -Intersection)
  188%
  189%   Intersection of a powerset. True when Intersection is an ordered
  190%   set holding all elements common to all sets in PowerSet.
  191%
  192%   @compat sicstus
  193
  194ord_intersection(PowerSet, Intersection) :-
  195    key_by_length(PowerSet, Pairs),
  196    keysort(Pairs, [_-S|Sorted]),
  197    l_int(Sorted, S, Intersection).
  198
  199key_by_length([], []).
  200key_by_length([H|T0], [L-H|T]) :-
  201    length(H, L),
  202    key_by_length(T0, T).
  203
  204l_int([], S, S).
  205l_int([_-H|T], S0, S) :-
  206    ord_intersection(S0, H, S1),
  207    l_int(T, S1, S).
  208
  209
  210%!  ord_intersection(+Set1, +Set2, -Intersection) is det.
  211%
  212%   Intersection holds the common elements of Set1 and Set2.  Uses
  213%   ord_disjoint/2 if Intersection is bound to `[]` on entry.
  214
  215ord_intersection(Set1, Set2, Intersection) :-
  216    (   Intersection == []
  217    ->  ord_disjoint(Set1, Set2)
  218    ;   oset_int(Set1, Set2, Intersection)
  219    ).
  220
  221
  222%!  ord_intersection(+Set1, +Set2, ?Intersection, ?Difference) is det.
  223%
  224%   Intersection  and  difference   between    two   ordered   sets.
  225%   Intersection is the intersection between   Set1  and Set2, while
  226%   Difference is defined by ord_subtract(Set2, Set1, Difference).
  227%
  228%   @see ord_intersection/3 and ord_subtract/3.
  229
  230ord_intersection([], L, [], L) :- !.
  231ord_intersection([_|_], [], [], []) :- !.
  232ord_intersection([H1|T1], [H2|T2], Intersection, Difference) :-
  233    compare(Diff, H1, H2),
  234    ord_intersection2(Diff, H1, T1, H2, T2, Intersection, Difference).
  235
  236ord_intersection2(=, H1, T1, _H2, T2, [H1|T], Difference) :-
  237    ord_intersection(T1, T2, T, Difference).
  238ord_intersection2(<, _, T1, H2, T2, Intersection, Difference) :-
  239    ord_intersection(T1, [H2|T2], Intersection, Difference).
  240ord_intersection2(>, H1, T1, H2, T2, Intersection, [H2|HDiff]) :-
  241    ord_intersection([H1|T1], T2, Intersection, HDiff).
  242
  243
  244%!  ord_add_element(+Set1, +Element, ?Set2) is det.
  245%
  246%   Insert  an  element  into  the  set.    This   is  the  same  as
  247%   ord_union(Set1, [Element], Set2).
  248
  249ord_add_element(Set1, Element, Set2) :-
  250    oset_addel(Set1, Element, Set2).
  251
  252
  253%!  ord_del_element(+Set, +Element, -NewSet) is det.
  254%
  255%   Delete an element from an  ordered  set.   This  is  the same as
  256%   ord_subtract(Set, [Element], NewSet).
  257
  258ord_del_element(Set, Element, NewSet) :-
  259    oset_delel(Set, Element, NewSet).
  260
  261
  262%!  ord_selectchk(+Item, ?Set1, ?Set2) is semidet.
  263%
  264%   Selectchk/3,  specialised  for  ordered  sets.    Is  true  when
  265%   select(Item, Set1, Set2) and Set1, Set2   are  both sorted lists
  266%   without duplicates. This implementation is only expected to work
  267%   for Item ground and either Set1 or Set2 ground. The "chk" suffix
  268%   is meant to remind you of   memberchk/2,  which also expects its
  269%   first  argument  to  be  ground.    ord_selectchk(X,  S,  T)  =>
  270%   ord_memberchk(X, S) & \+ ord_memberchk(X, T).
  271%
  272%   @author Richard O'Keefe
  273
  274ord_selectchk(Item, [X|Set1], [X|Set2]) :-
  275    X @< Item,
  276    !,
  277    ord_selectchk(Item, Set1, Set2).
  278ord_selectchk(Item, [Item|Set1], Set1) :-
  279    (   Set1 == []
  280    ->  true
  281    ;   Set1 = [Y|_]
  282    ->  Item @< Y
  283    ).
  284
  285
  286%!  ord_memberchk(+Element, +OrdSet) is semidet.
  287%
  288%   True if Element is a member of   OrdSet, compared using ==. Note
  289%   that _enumerating_ elements of an ordered  set can be done using
  290%   member/2.
  291%
  292%   Some Prolog implementations also provide  ord_member/2, with the
  293%   same semantics as ord_memberchk/2.  We   believe  that  having a
  294%   semidet ord_member/2 is unacceptably inconsistent with the *_chk
  295%   convention.  Portable  code  should    use   ord_memberchk/2  or
  296%   member/2.
  297%
  298%   @author Richard O'Keefe
  299
  300ord_memberchk(Item, [X1,X2,X3,X4|Xs]) :-
  301    !,
  302    compare(R4, Item, X4),
  303    (   R4 = (>) -> ord_memberchk(Item, Xs)
  304    ;   R4 = (<) ->
  305        compare(R2, Item, X2),
  306        (   R2 = (>) -> Item == X3
  307        ;   R2 = (<) -> Item == X1
  308        ;/* R2 = (=),   Item == X2 */ true
  309        )
  310    ;/* R4 = (=) */ true
  311    ).
  312ord_memberchk(Item, [X1,X2|Xs]) :-
  313    !,
  314    compare(R2, Item, X2),
  315    (   R2 = (>) -> ord_memberchk(Item, Xs)
  316    ;   R2 = (<) -> Item == X1
  317    ;/* R2 = (=) */ true
  318    ).
  319ord_memberchk(Item, [X1]) :-
  320    Item == X1.
  321
  322
  323%!  ord_subset(+Sub, +Super) is semidet.
  324%
  325%   Is true if all elements of Sub are in Super
  326
  327ord_subset([], _).
  328ord_subset([H1|T1], [H2|T2]) :-
  329    compare(Order, H1, H2),
  330    ord_subset_(Order, H1, T1, T2).
  331
  332ord_subset_(>, H1, T1, [H2|T2]) :-
  333    compare(Order, H1, H2),
  334    ord_subset_(Order, H1, T1, T2).
  335ord_subset_(=, _, T1, T2) :-
  336    ord_subset(T1, T2).
  337
  338
  339%!  ord_subtract(+InOSet, +NotInOSet, -Diff) is det.
  340%
  341%   Diff is the set holding all elements of InOSet that are not in
  342%   NotInOSet.
  343
  344ord_subtract(InOSet, NotInOSet, Diff) :-
  345    oset_diff(InOSet, NotInOSet, Diff).
  346
  347
  348%!  ord_union(+SetOfSets, -Union) is det.
  349%
  350%   True if Union is the  union  of   all  elements  in the superset
  351%   SetOfSets. Each member of SetOfSets must  be an ordered set, the
  352%   sets need not be ordered in any way.
  353%
  354%   @author Copied from YAP, probably originally by Richard O'Keefe.
  355
  356ord_union([], []).
  357ord_union([Set|Sets], Union) :-
  358    length([Set|Sets], NumberOfSets),
  359    ord_union_all(NumberOfSets, [Set|Sets], Union, []).
  360
  361ord_union_all(N, Sets0, Union, Sets) :-
  362    (   N =:= 1
  363    ->  Sets0 = [Union|Sets]
  364    ;   N =:= 2
  365    ->  Sets0 = [Set1,Set2|Sets],
  366        ord_union(Set1,Set2,Union)
  367    ;   A is N>>1,
  368        Z is N-A,
  369        ord_union_all(A, Sets0, X, Sets1),
  370        ord_union_all(Z, Sets1, Y, Sets),
  371        ord_union(X, Y, Union)
  372    ).
  373
  374
  375%!  ord_union(+Set1, +Set2, ?Union) is det.
  376%
  377%   Union is the union of Set1 and Set2
  378
  379ord_union(Set1, Set2, Union) :-
  380    oset_union(Set1, Set2, Union).
  381
  382
  383%!  ord_union(+Set1, +Set2, -Union, -New) is det.
  384%
  385%   True iff ord_union(Set1, Set2, Union) and
  386%   ord_subtract(Set2, Set1, New).
  387
  388ord_union([], Set2, Set2, Set2).
  389ord_union([H|T], Set2, Union, New) :-
  390    ord_union_1(Set2, H, T, Union, New).
  391
  392ord_union_1([], H, T, [H|T], []).
  393ord_union_1([H2|T2], H, T, Union, New) :-
  394    compare(Order, H, H2),
  395    ord_union(Order, H, T, H2, T2, Union, New).
  396
  397ord_union(<, H, T, H2, T2, [H|Union], New) :-
  398    ord_union_2(T, H2, T2, Union, New).
  399ord_union(>, H, T, H2, T2, [H2|Union], [H2|New]) :-
  400    ord_union_1(T2, H, T, Union, New).
  401ord_union(=, H, T, _, T2, [H|Union], New) :-
  402    ord_union(T, T2, Union, New).
  403
  404ord_union_2([], H2, T2, [H2|T2], [H2|T2]).
  405ord_union_2([H|T], H2, T2, Union, New) :-
  406    compare(Order, H, H2),
  407    ord_union(Order, H, T, H2, T2, Union, New).
  408
  409
  410%!  ord_symdiff(+Set1, +Set2, ?Difference) is det.
  411%
  412%   Is true when Difference is the  symmetric difference of Set1 and
  413%   Set2. I.e., Difference contains all elements that are not in the
  414%   intersection of Set1 and Set2. The semantics  is the same as the
  415%   sequence below (but the actual   implementation  requires only a
  416%   single scan).
  417%
  418%     ==
  419%           ord_union(Set1, Set2, Union),
  420%           ord_intersection(Set1, Set2, Intersection),
  421%           ord_subtract(Union, Intersection, Difference).
  422%     ==
  423%
  424%   For example:
  425%
  426%     ==
  427%     ?- ord_symdiff([1,2], [2,3], X).
  428%     X = [1,3].
  429%     ==
  430
  431ord_symdiff([], Set2, Set2).
  432ord_symdiff([H1|T1], Set2, Difference) :-
  433    ord_symdiff(Set2, H1, T1, Difference).
  434
  435ord_symdiff([], H1, T1, [H1|T1]).
  436ord_symdiff([H2|T2], H1, T1, Difference) :-
  437    compare(Order, H1, H2),
  438    ord_symdiff(Order, H1, T1, H2, T2, Difference).
  439
  440ord_symdiff(<, H1, Set1, H2, T2, [H1|Difference]) :-
  441    ord_symdiff(Set1, H2, T2, Difference).
  442ord_symdiff(=, _, T1, _, T2, Difference) :-
  443    ord_symdiff(T1, T2, Difference).
  444ord_symdiff(>, H1, T1, H2, Set2, [H2|Difference]) :-
  445    ord_symdiff(Set2, H1, T1, Difference)