Home Contents Index Summary Previous Next

4.29 Built-in list operations

Most list operations are defined in the library library(lists) described in section ??. Some that are implemented with more low-level primitives are built-in and described here.

is_list(+Term)
Succeeds if Term is bound to the empty list () or a term with functor `.' and arity 2 and the second argument is a list. (39) This predicate acts as if defined by the following definition:


is_list(X) :-
        var(X), !,
        fail.
is_list([]).
is_list([_|T]) :-
        is_list(T).

memberchk(?Elem, +List)
Equivalent to member/2, but leaves no choice point.

length(?List, ?Int)
Succeeds if Int represents the number of elements of list List. Can be used to create a list holding only variables.

sort(+List, -Sorted)
Succeeds if Sorted can be unified with a list holding the elements of List, sorted to the standard order of terms (see section 4.6). Duplicates are removed. The implementation is in C, using natural merge sort (40)

msort(+List, -Sorted)
Equivalent to sort/2, but does not remove duplicates.

keysort(+List, -Sorted)
List is a proper list whose elements are Key-Value, that is, terms whose principal functor is (-)/2, whose first argument is the sorting key, and whose second argument is the satellite data to be carried along with the key. keysort/2 sorts List like msort/2, but only compares the keys. It is used to sort terms not on standard order, but on any criterion that can be expressed on a multi-dimensional scale. Sorting on more than one criterion can be done using terms as keys, putting the first criterion as argument 1, the second as argument 2, etc. The order of multiple elements that have the same Key is not changed. The implementation is in C, using natural merge sort.

predsort(+Pred, +List, -Sorted)
Sorts similar to sort/2, but determines the order of two terms by calling Pred(-Delta, +E1, +E2) . This call must unify Delta with one of <, const> or =. If built-in predicate compare/3 is used, the result is the same as sort/2. See also keysort/2. (41)

merge(+List1, +List2, -List3)
List1 and List2 are lists, sorted to the standard order of terms (see section 4.6). List3 will be unified with an ordered list holding both the elements of List1 and List2. Duplicates are not removed.

merge_set(+Set1, +Set2, -Set3)
Set1 and Set2 are lists without duplicates, sorted to the standard order of terms. Set3 is unified with an ordered list without duplicates holding the union of the elements of Set1 and Set2.