summaryrefslogtreecommitdiffstats
path: root/stdlib/list.mli
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1995-08-09 13:15:01 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1995-08-09 13:15:01 +0000
commitd0012c733a00d8d0bb3195ac59e965192660eec2 (patch)
tree5a31e9dc58e792d8e39f35da37d5a0f9b9ed4bc0 /stdlib/list.mli
parentd2e588b4f03ebb1f387460b9ad8c028857c2586c (diff)
MAJ des commentaires de doc dans les interfaces
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@190 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/list.mli')
-rw-r--r--stdlib/list.mli81
1 files changed, 79 insertions, 2 deletions
diff --git a/stdlib/list.mli b/stdlib/list.mli
index 56fba7b72..14cff7949 100644
--- a/stdlib/list.mli
+++ b/stdlib/list.mli
@@ -1,25 +1,102 @@
-(* List operations *)
+(* Module [List]: list operations *)
val length : 'a list -> int
+ (* Return the length (number of elements) of the given list. *)
val hd : 'a list -> 'a
+ (* Return the first element of the given list. Raise
+ [Failure "hd"] if the list is empty. *)
val tl : 'a list -> 'a list
+ (* Return the given list without its first element. Raise
+ [Failure "tl"] if the list is empty. *)
val nth : 'a list -> int -> 'a
+ (* 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. *)
val rev : 'a list -> 'a list
+ (* List reversal. *)
val flatten : 'a list list -> 'a list
+ (* Catenate (flatten) a list of lists. *)
+
+(** Iterators *)
+
val iter : ('a -> 'b) -> 'a list -> unit
+ (* [List.iter f [a1; ...; an]] applies function [f] in turn to
+ [a1; ...; an], discarding all the results. It is equivalent to
+ [begin f a1; f a2; ...; f an; () end]. *)
val map : ('a -> 'b) -> 'a list -> 'b list
+ (* [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]. *)
val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
+ (* [List.fold_left f a [b1; ...; bn]] is
+ [f (... (f (f a b1) b2) ...) bn]. *)
val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
-val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
+ (* [List.fold_right f [a1; ...; an] b] is
+ [f a1 (f a2 (... (f an b) ...))]. *)
+
+(** Iterators on two lists *)
+
val iter2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> unit
+ (* [List.iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn
+ [f a1 b1; ...; f an bn], discarding the results.
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
+val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
+ (* [List.map2 f [a1; ...; an] [b1; ...; bn]] is
+ [[f a1 b1; ...; f an bn]].
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b list -> 'c list -> 'a
+ (* [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. *)
val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c
+ (* [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. *)
+
+(** List scanning *)
+
val for_all : ('a -> bool) -> 'a list -> bool
+ (* [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)]. *)
val exists : ('a -> bool) -> 'a list -> bool
+ (* [exists p [a1; ...; an]] checks if at least one element of the list
+ satisfies the predicate [p]. That is, it returns
+ [(p a1) or (p a2) or ... or (p an)]. *)
val mem : 'a -> 'a list -> bool
+ (* [mem a l] is true if and only if [a] is equal
+ to an element of [l]. *)
+
+(** Association lists *)
+
val assoc : 'a -> ('a * 'b) list -> 'b
+ (* [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]. *)
val mem_assoc : 'a -> ('a * 'b) list -> bool
+ (* Same as [assoc], but simply return true if a binding exists,
+ and false if no bindings exist for the given key. *)
val assq : 'a -> ('a * 'b) list -> 'b
+ (* Same as [assoc], but use physical equality instead of structural
+ equality to compare keys. *)
+
+(** Lists of pairs *)
+
val split : ('a * 'b) list -> 'a list * 'b list
+ (* Transform a list of pairs into a pair of lists:
+ [split [(a1,b1); ...; (an,bn)]] is [([a1; ...; an], [b1; ...; bn])]
+ *)
val combine : 'a list -> 'b list -> ('a * 'b) list
+ (* 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. *)