View source with raw comments or as raw
    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-2016, 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(lists,
   37        [ member/2,                     % ?X, ?List
   38          append/2,                     % +ListOfLists, -List
   39          append/3,                     % ?A, ?B, ?AB
   40          prefix/2,                     % ?Part, ?Whole
   41          select/3,                     % ?X, ?List, ?Rest
   42          selectchk/3,                  % ?X, ?List, ?Rest
   43          select/4,                     % ?X, ?XList, ?Y, ?YList
   44          selectchk/4,                  % ?X, ?XList, ?Y, ?YList
   45          nextto/3,                     % ?X, ?Y, ?List
   46          delete/3,                     % ?List, ?X, ?Rest
   47          nth0/3,                       % ?N, ?List, ?Elem
   48          nth1/3,                       % ?N, ?List, ?Elem
   49          nth0/4,                       % ?N, ?List, ?Elem, ?Rest
   50          nth1/4,                       % ?N, ?List, ?Elem, ?Rest
   51          last/2,                       % +List, -Element
   52          proper_length/2,              % @List, -Length
   53          same_length/2,                % ?List1, ?List2
   54          reverse/2,                    % +List, -Reversed
   55          permutation/2,                % ?List, ?Permutation
   56          flatten/2,                    % +Nested, -Flat
   57
   58                                        % Ordered operations
   59          max_member/2,                 % -Max, +List
   60          min_member/2,                 % -Min, +List
   61
   62                                        % Lists of numbers
   63          sum_list/2,                   % +List, -Sum
   64          max_list/2,                   % +List, -Max
   65          min_list/2,                   % +List, -Min
   66          numlist/3,                    % +Low, +High, -List
   67
   68                                        % set manipulation
   69          is_set/1,                     % +List
   70          list_to_set/2,                % +List, -Set
   71          intersection/3,               % +List1, +List2, -Intersection
   72          union/3,                      % +List1, +List2, -Union
   73          subset/2,                     % +SubSet, +Set
   74          subtract/3                    % +Set, +Delete, -Remaining
   75        ]).   76:- use_module(library(error)).   77:- use_module(library(pairs)).   78
   79:- set_prolog_flag(generate_debug_info, false).

List Manipulation

This library provides commonly accepted basic predicates for list manipulation in the Prolog community. Some additional list manipulations are built-in. See e.g., memberchk/2, length/2.

The implementation of this library is copied from many places. These include: "The Craft of Prolog", the DEC-10 Prolog library (LISTRO.PL) and the YAP lists library. Some predicates are reimplemented based on their specification by Quintus and SICStus.

Compatibility
-
Virtually every Prolog system has library(lists), but the set of provided predicates is diverse. There is a fair agreement on the semantics of most of these predicates, although error handling may vary. */
 member(?Elem, ?List)
True if Elem is a member of List. The SWI-Prolog definition differs from the classical one. Our definition avoids unpacking each list element twice and provides determinism on the last element. E.g. this is deterministic:
    member(X, [One]).
author
- Gertjan van Noord
  111member(El, [H|T]) :-
  112    member_(T, El, H).
  113
  114member_(_, El, El).
  115member_([H|T], El, _) :-
  116    member_(T, El, H).
 append(?List1, ?List2, ?List1AndList2)
List1AndList2 is the concatenation of List1 and List2
  122append([], L, L).
  123append([H|T], L, [H|R]) :-
  124    append(T, L, R).
 append(+ListOfLists, ?List)
Concatenate a list of lists. Is true if ListOfLists is a list of lists, and List is the concatenation of these lists.
Arguments:
ListOfLists- must be a list of possibly partial lists
  133append(ListOfLists, List) :-
  134    must_be(list, ListOfLists),
  135    append_(ListOfLists, List).
  136
  137append_([], []).
  138append_([L|Ls], As) :-
  139    append(L, Ws, As),
  140    append_(Ls, Ws).
 prefix(?Part, ?Whole)
True iff Part is a leading substring of Whole. This is the same as append(Part, _, Whole).
  148prefix([], _).
  149prefix([E|T0], [E|T]) :-
  150    prefix(T0, T).
 select(?Elem, ?List1, ?List2)
Is true when List1, with Elem removed, results in List2.
  157select(X, [X|Tail], Tail).
  158select(Elem, [Head|Tail], [Head|Rest]) :-
  159    select(Elem, Tail, Rest).
 selectchk(+Elem, +List, -Rest) is semidet
Semi-deterministic removal of first element in List that unifies with Elem.
  167selectchk(Elem, List, Rest) :-
  168    select(Elem, List, Rest0),
  169    !,
  170    Rest = Rest0.
 select(?X, ?XList, ?Y, ?YList) is nondet
Select from two lists at the same positon. True if XList is unifiable with YList apart a single element at the same position that is unified with X in XList and with Y in YList. A typical use for this predicate is to replace an element, as shown in the example below. All possible substitutions are performed on backtracking.
?- select(b, [a,b,c,b], 2, X).
X = [a, 2, c, b] ;
X = [a, b, c, 2] ;
false.
See also
- selectchk/4 provides a semidet version.
  191select(X, XList, Y, YList) :-
  192    select_(XList, X, Y, YList).
  193
  194select_([X|List], X, Y, [Y|List]).
  195select_([X0|XList], X, Y, [X0|YList]) :-
  196    select_(XList, X, Y, YList).
 selectchk(?X, ?XList, ?Y, ?YList) is semidet
Semi-deterministic version of select/4.
  202selectchk(X, XList, Y, YList) :-
  203    select(X, XList, Y, YList),
  204    !.
 nextto(?X, ?Y, ?List)
True if Y directly follows X in List.
  210nextto(X, Y, [X,Y|_]).
  211nextto(X, Y, [_|Zs]) :-
  212    nextto(X, Y, Zs).
 delete(+List1, @Elem, -List2) is det
Delete matching elements from a list. True when List2 is a list with all elements from List1 except for those that unify with Elem. Matching Elem with elements of List1 is uses \+ Elem \= H, which implies that Elem is not changed.
See also
- select/3, subtract/3.
deprecated
- There are too many ways in which one might want to delete elements from a list to justify the name. Think of matching (= vs. ==), delete first/all, be deterministic or not.
  227delete([], _, []).
  228delete([Elem|Tail], Del, Result) :-
  229    (   \+ Elem \= Del
  230    ->  delete(Tail, Del, Result)
  231    ;   Result = [Elem|Rest],
  232        delete(Tail, Del, Rest)
  233    ).
  234
  235
  236/*  nth0/3, nth1/3 are improved versions from
  237    Martin Jansche <martin@pc03.idf.uni-heidelberg.de>
  238*/
 nth0(?Index, ?List, ?Elem)
True when Elem is the Index'th element of List. Counting starts at 0.
Errors
- type_error(integer, Index) if Index is not an integer or unbound.
See also
- nth1/3.
  249nth0(Index, List, Elem) :-
  250    (   integer(Index)
  251    ->  nth0_det(Index, List, Elem)         % take nth deterministically
  252    ;   var(Index)
  253    ->  List = [H|T],
  254        nth_gen(T, Elem, H, 0, Index)       % match
  255    ;   must_be(integer, Index)
  256    ).
  257
  258nth0_det(0, [Elem|_], Elem) :- !.
  259nth0_det(1, [_,Elem|_], Elem) :- !.
  260nth0_det(2, [_,_,Elem|_], Elem) :- !.
  261nth0_det(3, [_,_,_,Elem|_], Elem) :- !.
  262nth0_det(4, [_,_,_,_,Elem|_], Elem) :- !.
  263nth0_det(5, [_,_,_,_,_,Elem|_], Elem) :- !.
  264nth0_det(N, [_,_,_,_,_,_   |Tail], Elem) :-
  265    M is N - 6,
  266    M >= 0,
  267    nth0_det(M, Tail, Elem).
  268
  269nth_gen(_, Elem, Elem, Base, Base).
  270nth_gen([H|Tail], Elem, _, N, Base) :-
  271    succ(N, M),
  272    nth_gen(Tail, Elem, H, M, Base).
 nth1(?Index, ?List, ?Elem)
Is true when Elem is the Index'th element of List. Counting starts at 1.
See also
- nth0/3.
  282nth1(Index, List, Elem) :-
  283    (   integer(Index)
  284    ->  Index0 is Index - 1,
  285        nth0_det(Index0, List, Elem)        % take nth deterministically
  286    ;   var(Index)
  287    ->  List = [H|T],
  288        nth_gen(T, Elem, H, 1, Index)       % match
  289    ;   must_be(integer, Index)
  290    ).
 nth0(?N, ?List, ?Elem, ?Rest) is det
Select/insert element at index. True when Elem is the N'th (0-based) element of List and Rest is the remainder (as in by select/3) of List. For example:
?- nth0(I, [a,b,c], E, R).
I = 0, E = a, R = [b, c] ;
I = 1, E = b, R = [a, c] ;
I = 2, E = c, R = [a, b] ;
false.
?- nth0(1, L, a1, [a,b]).
L = [a, a1, b].
  311nth0(V, In, Element, Rest) :-
  312    var(V),
  313    !,
  314    generate_nth(0, V, In, Element, Rest).
  315nth0(V, In, Element, Rest) :-
  316    must_be(nonneg, V),
  317    find_nth0(V, In, Element, Rest).
 nth1(?N, ?List, ?Elem, ?Rest) is det
As nth0/4, but counting starts at 1.
  323nth1(V, In, Element, Rest) :-
  324    var(V),
  325    !,
  326    generate_nth(1, V, In, Element, Rest).
  327nth1(V, In, Element, Rest) :-
  328    must_be(positive_integer, V),
  329    succ(V0, V),
  330    find_nth0(V0, In, Element, Rest).
  331
  332generate_nth(I, I, [Head|Rest], Head, Rest).
  333generate_nth(I, IN, [H|List], El, [H|Rest]) :-
  334    I1 is I+1,
  335    generate_nth(I1, IN, List, El, Rest).
  336
  337find_nth0(0, [Head|Rest], Head, Rest) :- !.
  338find_nth0(N, [Head|Rest0], Elem, [Head|Rest]) :-
  339    M is N-1,
  340    find_nth0(M, Rest0, Elem, Rest).
 last(?List, ?Last)
Succeeds when Last is the last element of List. This predicate is semidet if List is a list and multi if List is a partial list.
Compatibility
- There is no de-facto standard for the argument order of last/2. Be careful when porting code or use append(_, [Last], List) as a portable alternative.
  353last([X|Xs], Last) :-
  354    last_(Xs, X, Last).
  355
  356last_([], Last, Last).
  357last_([X|Xs], _, Last) :-
  358    last_(Xs, X, Last).
 proper_length(@List, -Length) is semidet
True when Length is the number of elements in the proper list List. This is equivalent to
proper_length(List, Length) :-
      is_list(List),
      length(List, Length).
  372proper_length(List, Length) :-
  373    '$skip_list'(Length0, List, Tail),
  374    Tail == [],
  375    Length = Length0.
 same_length(?List1, ?List2)
Is true when List1 and List2 are lists with the same number of elements. The predicate is deterministic if at least one of the arguments is a proper list. It is non-deterministic if both arguments are partial lists.
See also
- length/2
  387same_length([], []).
  388same_length([_|T1], [_|T2]) :-
  389    same_length(T1, T2).
 reverse(?List1, ?List2)
Is true when the elements of List2 are in reverse order compared to List1.
  397reverse(Xs, Ys) :-
  398    reverse(Xs, [], Ys, Ys).
  399
  400reverse([], Ys, Ys, []).
  401reverse([X|Xs], Rs, Ys, [_|Bound]) :-
  402    reverse(Xs, [X|Rs], Ys, Bound).
 permutation(?Xs, ?Ys) is nondet
True when Xs is a permutation of Ys. This can solve for Ys given Xs or Xs given Ys, or even enumerate Xs and Ys together. The predicate permutation/2 is primarily intended to generate permutations. Note that a list of length N has N! permutations, and unbounded permutation generation becomes prohibitively expensive, even for rather short lists (10! = 3,628,800).

If both Xs and Ys are provided and both lists have equal length the order is |Xs|^2. Simply testing whether Xs is a permutation of Ys can be achieved in order log(|Xs|) using msort/2 as illustrated below with the semidet predicate is_permutation/2:

is_permutation(Xs, Ys) :-
  msort(Xs, Sorted),
  msort(Ys, Sorted).

The example below illustrates that Xs and Ys being proper lists is not a sufficient condition to use the above replacement.

?- permutation([1,2], [X,Y]).
X = 1, Y = 2 ;
X = 2, Y = 1 ;
false.
Errors
- type_error(list, Arg) if either argument is not a proper or partial list.
  438permutation(Xs, Ys) :-
  439    '$skip_list'(Xlen, Xs, XTail),
  440    '$skip_list'(Ylen, Ys, YTail),
  441    (   XTail == [], YTail == []            % both proper lists
  442    ->  Xlen == Ylen
  443    ;   var(XTail), YTail == []             % partial, proper
  444    ->  length(Xs, Ylen)
  445    ;   XTail == [], var(YTail)             % proper, partial
  446    ->  length(Ys, Xlen)
  447    ;   var(XTail), var(YTail)              % partial, partial
  448    ->  length(Xs, Len),
  449        length(Ys, Len)
  450    ;   must_be(list, Xs),                  % either is not a list
  451        must_be(list, Ys)
  452    ),
  453    perm(Xs, Ys).
  454
  455perm([], []).
  456perm(List, [First|Perm]) :-
  457    select(First, List, Rest),
  458    perm(Rest, Perm).
 flatten(+NestedList, -FlatList) is det
Is true if FlatList is a non-nested version of NestedList. Note that empty lists are removed. In standard Prolog, this implies that the atom '[]' is removed too. In SWI7, [] is distinct from '[]'.

Ending up needing flatten/2 often indicates, like append/3 for appending two lists, a bad design. Efficient code that generates lists from generated small lists must use difference lists, often possible through grammar rules for optimal readability.

See also
- append/2
  474flatten(List, FlatList) :-
  475    flatten(List, [], FlatList0),
  476    !,
  477    FlatList = FlatList0.
  478
  479flatten(Var, Tl, [Var|Tl]) :-
  480    var(Var),
  481    !.
  482flatten([], Tl, Tl) :- !.
  483flatten([Hd|Tl], Tail, List) :-
  484    !,
  485    flatten(Hd, FlatHeadTail, List),
  486    flatten(Tl, Tail, FlatHeadTail).
  487flatten(NonList, Tl, [NonList|Tl]).
  488
  489
  490                 /*******************************
  491                 *       ORDER OPERATIONS       *
  492                 *******************************/
 max_member(-Max, +List) is semidet
True when Max is the largest member in the standard order of terms. Fails if List is empty.
See also
- compare/3
- max_list/2 for the maximum of a list of numbers.
  502max_member(Max, [H|T]) :-
  503    max_member_(T, H, Max).
  504
  505max_member_([], Max, Max).
  506max_member_([H|T], Max0, Max) :-
  507    (   H @=< Max0
  508    ->  max_member_(T, Max0, Max)
  509    ;   max_member_(T, H, Max)
  510    ).
 min_member(-Min, +List) is semidet
True when Min is the smallest member in the standard order of terms. Fails if List is empty.
See also
- compare/3
- min_list/2 for the minimum of a list of numbers.
  521min_member(Min, [H|T]) :-
  522    min_member_(T, H, Min).
  523
  524min_member_([], Min, Min).
  525min_member_([H|T], Min0, Min) :-
  526    (   H @>= Min0
  527    ->  min_member_(T, Min0, Min)
  528    ;   min_member_(T, H, Min)
  529    ).
  530
  531
  532                 /*******************************
  533                 *       LISTS OF NUMBERS       *
  534                 *******************************/
 sum_list(+List, -Sum) is det
Sum is the result of adding all numbers in List.
  540sum_list(Xs, Sum) :-
  541    sum_list(Xs, 0, Sum).
  542
  543sum_list([], Sum, Sum).
  544sum_list([X|Xs], Sum0, Sum) :-
  545    Sum1 is Sum0 + X,
  546    sum_list(Xs, Sum1, Sum).
 max_list(+List:list(number), -Max:number) is semidet
True if Max is the largest number in List. Fails if List is empty.
See also
- max_member/2.
  555max_list([H|T], Max) :-
  556    max_list(T, H, Max).
  557
  558max_list([], Max, Max).
  559max_list([H|T], Max0, Max) :-
  560    Max1 is max(H, Max0),
  561    max_list(T, Max1, Max).
 min_list(+List:list(number), -Min:number) is semidet
True if Min is the smallest number in List. Fails if List is empty.
See also
- min_member/2.
  571min_list([H|T], Min) :-
  572    min_list(T, H, Min).
  573
  574min_list([], Min, Min).
  575min_list([H|T], Min0, Min) :-
  576    Min1 is min(H, Min0),
  577    min_list(T, Min1, Min).
 numlist(+Low, +High, -List) is semidet
List is a list [Low, Low+1, ... High]. Fails if High < Low.
Errors
- type_error(integer, Low)
- type_error(integer, High)
  587numlist(L, U, Ns) :-
  588    must_be(integer, L),
  589    must_be(integer, U),
  590    L =< U,
  591    numlist_(L, U, Ns).
  592
  593numlist_(U, U, List) :-
  594    !,
  595    List = [U].
  596numlist_(L, U, [L|Ns]) :-
  597    L2 is L+1,
  598    numlist_(L2, U, Ns).
  599
  600
  601                /********************************
  602                *       SET MANIPULATION        *
  603                *********************************/
 is_set(@Set) is semidet
True if Set is a proper list without duplicates. Equivalence is based on ==/2. The implementation uses sort/2, which implies that the complexity is N*log(N) and the predicate may cause a resource-error. There are no other error conditions.
  612is_set(Set) :-
  613    '$skip_list'(Len, Set, Tail),
  614    Tail == [],                             % Proper list
  615    sort(Set, Sorted),
  616    length(Sorted, Len).
 list_to_set(+List, ?Set) is det
True when Set has the same elements as List in the same order. The left-most copy of duplicate elements is retained. List may contain variables. Elements E1 and E2 are considered duplicates iff E1 == E2 holds. The complexity of the implementation is N*log(N).
Errors
- List is type-checked.
See also
- sort/2 can be used to create an ordered set. Many set operations on ordered sets are order N rather than order N**2. The list_to_set/2 predicate is more expensive than sort/2 because it involves, two sorts and a linear scan.
Compatibility
- Up to version 6.3.11, list_to_set/2 had complexity N**2 and equality was tested using =/2.
  636list_to_set(List, Set) :-
  637    must_be(list, List),
  638    number_list(List, 1, Numbered),
  639    sort(1, @=<, Numbered, ONum),
  640    remove_dup_keys(ONum, NumSet),
  641    sort(2, @=<, NumSet, ONumSet),
  642    pairs_keys(ONumSet, Set).
  643
  644number_list([], _, []).
  645number_list([H|T0], N, [H-N|T]) :-
  646    N1 is N+1,
  647    number_list(T0, N1, T).
  648
  649remove_dup_keys([], []).
  650remove_dup_keys([H|T0], [H|T]) :-
  651    H = V-_,
  652    remove_same_key(T0, V, T1),
  653    remove_dup_keys(T1, T).
  654
  655remove_same_key([V1-_|T0], V, T) :-
  656    V1 == V,
  657    !,
  658    remove_same_key(T0, V, T).
  659remove_same_key(L, _, L).
 intersection(+Set1, +Set2, -Set3) is det
True if Set3 unifies with the intersection of Set1 and Set2. The complexity of this predicate is |Set1|*|Set2|
See also
- ord_intersection/3.
  669intersection([], _, []) :- !.
  670intersection([X|T], L, Intersect) :-
  671    memberchk(X, L),
  672    !,
  673    Intersect = [X|R],
  674    intersection(T, L, R).
  675intersection([_|T], L, R) :-
  676    intersection(T, L, R).
 union(+Set1, +Set2, -Set3) is det
True if Set3 unifies with the union of Set1 and Set2. The complexity of this predicate is |Set1|*|Set2|
See also
- ord_union/3.
  686union([], L, L) :- !.
  687union([H|T], L, R) :-
  688    memberchk(H, L),
  689    !,
  690    union(T, L, R).
  691union([H|T], L, [H|R]) :-
  692    union(T, L, R).
 subset(+SubSet, +Set) is semidet
True if all elements of SubSet belong to Set as well. Membership test is based on memberchk/2. The complexity is |SubSet|*|Set|.
See also
- ord_subset/2.
  702subset([], _) :- !.
  703subset([E|R], Set) :-
  704    memberchk(E, Set),
  705    subset(R, Set).
 subtract(+Set, +Delete, -Result) is det
Delete all elements in Delete from Set. Deletion is based on unification using memberchk/2. The complexity is |Delete|*|Set|.
See also
- ord_subtract/3.
  715subtract([], _, []) :- !.
  716subtract([E|T], D, R) :-
  717    memberchk(E, D),
  718    !,
  719    subtract(T, D, R).
  720subtract([H|T], D, [H|R]) :-
  721    subtract(T, D, R)