1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the GNU Library General Public License. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** List operations.
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
Some functions are flagged as not tail-recursive. A tail-recursive
|
1999-09-19 05:55:01 -07:00
|
|
|
function uses constant stack space, while a non-tail-recursive function
|
|
|
|
uses stack space proportional to the length of its list argument, which
|
|
|
|
can be a problem with very long lists. When the function takes several
|
2000-01-21 10:50:26 -08:00
|
|
|
list arguments, an approximate formula giving stack usage (in some
|
|
|
|
unspecified constant unit) is shown in parentheses.
|
1999-09-19 05:55:01 -07:00
|
|
|
|
|
|
|
The above considerations can usually be ignored if your lists are not
|
|
|
|
longer than about 10000 elements.
|
|
|
|
*)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val length : 'a list -> int
|
2001-12-03 14:16:03 -08:00
|
|
|
(** Return the length (number of elements) of the given list. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val hd : 'a list -> 'a
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Return the first element of the given list. Raise
|
|
|
|
[Failure "hd"] if the list is empty. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val tl : 'a list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Return the given list without its first element. Raise
|
|
|
|
[Failure "tl"] if the list is empty. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val nth : 'a list -> int -> 'a
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Return the n-th element of the given list.
|
|
|
|
The first element (head of the list) is at position 0.
|
|
|
|
Raise [Failure "nth"] if the list is too short. *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val rev : 'a list -> 'a list
|
2001-12-03 14:16:03 -08:00
|
|
|
(** List reversal. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val append : 'a list -> 'a list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Catenate two lists. Same function as the infix operator [@].
|
|
|
|
Not tail-recursive (length of the first argument). The [@]
|
|
|
|
operator is not tail-recursive either. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val rev_append : 'a list -> 'a list -> 'a list
|
2001-12-04 13:30:02 -08:00
|
|
|
(** [List.rev_append l1 l2] reverses [l1] and concatenates it to [l2].
|
2001-10-26 15:38:48 -07:00
|
|
|
This is equivalent to {!List.rev}[ l1 @ l2], but [rev_append] is
|
|
|
|
tail-recursive and more efficient. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val concat : 'a list list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Concatenate a list of lists. Not tail-recursive
|
|
|
|
(length of the argument + length of the longest sub-list). *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val flatten : 'a list list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Flatten a list of lists. Not tail-recursive
|
|
|
|
(length of the argument + length of the longest sub-list). *)
|
1995-08-09 06:15:01 -07:00
|
|
|
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 Iterators} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val iter : ('a -> unit) -> 'a list -> unit
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.iter f [a1; ...; an]] applies function [f] in turn to
|
|
|
|
[a1; ...; an]. It is equivalent to
|
|
|
|
[begin f a1; f a2; ...; f an; () end]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val map : ('a -> 'b) -> 'a list -> 'b list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.map f [a1; ...; an]] applies function [f] to [a1, ..., an],
|
|
|
|
and builds the list [[f a1; ...; f an]]
|
|
|
|
with the results returned by [f]. Not tail-recursive. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val rev_map : ('a -> 'b) -> 'a list -> 'b list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.rev_map f l] gives the same result as
|
|
|
|
{!List.rev}[ (]{!List.map}[ f l)], but is tail-recursive and
|
|
|
|
more efficient. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.fold_left f a [b1; ...; bn]] is
|
|
|
|
[f (... (f (f a b1) b2) ...) bn]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.fold_right f [a1; ...; an] b] is
|
|
|
|
[f a1 (f a2 (... (f an b) ...))]. Not tail-recursive. *)
|
1995-08-09 06:15:01 -07:00
|
|
|
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 Iterators on two lists} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val iter2 : ('a -> 'b -> unit) -> 'a list -> 'b list -> unit
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn
|
|
|
|
[f a1 b1; ...; f an bn].
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.map2 f [a1; ...; an] [b1; ...; bn]] is
|
|
|
|
[[f a1 b1; ...; f an bn]].
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. Not tail-recursive. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val rev_map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.rev_map2 f l] gives the same result as
|
|
|
|
{!List.rev}[ (]{!List.map2}[ f l)], but is tail-recursive and
|
|
|
|
more efficient. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b list -> 'c list -> 'a
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.fold_left2 f a [b1; ...; bn] [c1; ...; cn]] is
|
|
|
|
[f (... (f (f a b1 c1) b2 c2) ...) bn cn].
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [List.fold_right2 f [a1; ...; an] [b1; ...; bn] c] is
|
|
|
|
[f a1 b1 (f a2 b2 (... (f an bn c) ...))].
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. Not tail-recursive. *)
|
1995-08-09 06:15:01 -07:00
|
|
|
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 List scanning} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val for_all : ('a -> bool) -> 'a list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [for_all p [a1; ...; an]] checks if all elements of the list
|
|
|
|
satisfy the predicate [p]. That is, it returns
|
|
|
|
[(p a1) && (p a2) && ... && (p an)]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val exists : ('a -> bool) -> 'a list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [exists p [a1; ...; an]] checks if at least one element of
|
|
|
|
the list satisfies the predicate [p]. That is, it returns
|
|
|
|
[(p a1) || (p a2) || ... || (p an)]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val for_all2 : ('a -> 'b -> bool) -> 'a list -> 'b list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.for_all}, but for a two-argument predicate.
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val exists2 : ('a -> 'b -> bool) -> 'a list -> 'b list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.exists}, but for a two-argument predicate.
|
|
|
|
Raise [Invalid_argument] if the two lists have
|
|
|
|
different lengths. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val mem : 'a -> 'a list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [mem a l] is true if and only if [a] is equal
|
|
|
|
to an element of [l]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val memq : 'a -> 'a list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.mem}, but uses physical equality instead of structural
|
|
|
|
equality to compare list elements. *)
|
1995-08-09 06:15:01 -07:00
|
|
|
|
1999-01-04 02:35:49 -08:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 List searching} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val find : ('a -> bool) -> 'a list -> 'a
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [find p l] returns the first element of the list [l]
|
|
|
|
that satisfies the predicate [p].
|
|
|
|
Raise [Not_found] if there is no value that satisfies [p] in the
|
|
|
|
list [l]. *)
|
1999-01-04 02:35:49 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val filter : ('a -> bool) -> 'a list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [filter p l] returns all the elements of the list [l]
|
|
|
|
that satisfy the predicate [p]. The order of the elements
|
|
|
|
in the input list is preserved. *)
|
|
|
|
|
2001-09-06 01:52:32 -07:00
|
|
|
val find_all : ('a -> bool) -> 'a list -> 'a list
|
2001-12-03 14:16:03 -08:00
|
|
|
(** [find_all] is another name for {!List.filter}. *)
|
1999-01-04 02:35:49 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val partition : ('a -> bool) -> 'a list -> 'a list * 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [partition p l] returns a pair of lists [(l1, l2)], where
|
|
|
|
[l1] is the list of all the elements of [l] that
|
|
|
|
satisfy the predicate [p], and [l2] is the list of all the
|
|
|
|
elements of [l] that do not satisfy [p].
|
|
|
|
The order of the elements in the input list is preserved. *)
|
1999-01-04 02:35:49 -08:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 Association lists} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val assoc : 'a -> ('a * 'b) list -> 'b
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [assoc a l] returns the value associated with key [a] in the list of
|
|
|
|
pairs [l]. That is,
|
|
|
|
[assoc a [ ...; (a,b); ...] = b]
|
|
|
|
if [(a,b)] is the leftmost binding of [a] in list [l].
|
|
|
|
Raise [Not_found] if there is no value associated with [a] in the
|
|
|
|
list [l]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val assq : 'a -> ('a * 'b) list -> 'b
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.assoc}, but uses physical equality instead of structural
|
|
|
|
equality to compare keys. *)
|
1998-11-05 00:04:09 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val mem_assoc : 'a -> ('a * 'b) list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.assoc}, but simply return true if a binding exists,
|
|
|
|
and false if no bindings exist for the given key. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val mem_assq : 'a -> ('a * 'b) list -> bool
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.mem_assoc}, but uses physical equality instead of
|
|
|
|
structural equality to compare keys. *)
|
1998-11-05 00:04:09 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val remove_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [remove_assoc a l] returns the list of
|
|
|
|
pairs [l] without the first pair with key [a], if any.
|
|
|
|
Not tail-recursive. *)
|
1998-11-05 00:04:09 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list
|
2001-10-26 16:43:11 -07:00
|
|
|
(** Same as {!List.remove_assoc}, but uses physical equality instead
|
2001-10-26 15:38:48 -07:00
|
|
|
of structural equality to compare keys. Not tail-recursive. *)
|
1995-08-09 06:15:01 -07:00
|
|
|
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** {2 Lists of pairs} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val split : ('a * 'b) list -> 'a list * 'b list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Transform a list of pairs into a pair of lists:
|
|
|
|
[split [(a1,b1); ...; (an,bn)]] is [([a1; ...; an], [b1; ...; bn])].
|
|
|
|
Not tail-recursive.
|
|
|
|
*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val combine : 'a list -> 'b list -> ('a * 'b) list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Transform a pair of lists into a list of pairs:
|
|
|
|
[combine [a1; ...; an] [b1; ...; bn]] is
|
|
|
|
[[(a1,b1); ...; (an,bn)]].
|
|
|
|
Raise [Invalid_argument] if the two lists
|
|
|
|
have different lengths. Not tail-recursive. *)
|
2000-04-14 03:05:33 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
|
|
|
|
(** {2 Sorting} *)
|
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val sort : ('a -> 'a -> int) -> 'a list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Sort a list in increasing order according to a comparison
|
|
|
|
function. The comparison function must return 0 if it arguments
|
|
|
|
compare as equal, a positive integer if the first is greater,
|
|
|
|
and a negative integer if the first is smaller. For example,
|
|
|
|
the [compare] function is a suitable comparison function.
|
|
|
|
The resulting list is sorted in increasing order.
|
|
|
|
[List.sort] is guaranteed to run in constant heap space
|
|
|
|
(in addition to the size of the result list) and logarithmic
|
|
|
|
stack space.
|
|
|
|
|
|
|
|
The current implementation uses Merge Sort and is the same as
|
|
|
|
{!List.stable_sort}.
|
|
|
|
*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val stable_sort : ('a -> 'a -> int) -> 'a list -> 'a list
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Same as {!List.sort}, but the sorting algorithm is stable.
|
|
|
|
|
|
|
|
The current implementation is Merge Sort. It runs in constant
|
|
|
|
heap space and logarithmic stack space.
|
|
|
|
*)
|
2001-02-27 04:17:27 -08:00
|
|
|
|