summaryrefslogtreecommitdiffstats
path: root/stdlib/list.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1997-03-21 10:46:38 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1997-03-21 10:46:38 +0000
commitd096a4596170a85a0436fc65314e77cb745edb70 (patch)
tree1bb67fd7ffb498a73ac172c0c8154b103ecc53b8 /stdlib/list.ml
parentec2ab0e1b13734ed2f7f411bca5637e6dd64cf4d (diff)
hashtbl.ml: un parametre inutilise lors du redimensionnement.
list.ml: List.length tail-rec. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1427 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/list.ml')
-rw-r--r--stdlib/list.ml8
1 files changed, 5 insertions, 3 deletions
diff --git a/stdlib/list.ml b/stdlib/list.ml
index f80c171d8..bd7041961 100644
--- a/stdlib/list.ml
+++ b/stdlib/list.ml
@@ -13,9 +13,11 @@
(* List operations *)
-let rec length = function
- [] -> 0
- | a::l -> 1 + length l
+let rec length_aux len = function
+ [] -> len
+ | a::l -> length_aux (len + 1) l
+
+let length l = length_aux 0 l
let hd = function
[] -> failwith "hd"