summaryrefslogtreecommitdiffstats
path: root/stdlib/list.ml
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>1999-09-19 12:55:01 +0000
committerDamien Doligez <damien.doligez-inria.fr>1999-09-19 12:55:01 +0000
commitfe764d8d254ca5b68a3f59d7865b559680053632 (patch)
treec1c3790f3ddd01c5bea0987c080f5e147017a620 /stdlib/list.ml
parent7780cf7ef6aaa9e17289447e834dc7f1f58c71e6 (diff)
Documentation des fonctions non-tail-rec
Ajout de rev_map rev_map2 git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2409 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/list.ml')
-rw-r--r--stdlib/list.ml18
1 files changed, 18 insertions, 0 deletions
diff --git a/stdlib/list.ml b/stdlib/list.ml
index 170b803d6..252b42bcb 100644
--- a/stdlib/list.ml
+++ b/stdlib/list.ml
@@ -54,6 +54,14 @@ let rec map f = function
[] -> []
| a::l -> let r = f a in r :: map f l
+let rev_map f l =
+ let rec rmap_f accu = function
+ | [] -> accu
+ | a::l -> rmap_f (f a :: accu) l
+ in
+ rmap_f [] l
+;;
+
let rec iter f = function
[] -> ()
| a::l -> f a; iter f l
@@ -74,6 +82,16 @@ let rec map2 f l1 l2 =
| (a1::l1, a2::l2) -> let r = f a1 a2 in r :: map2 f l1 l2
| (_, _) -> invalid_arg "List.map2"
+let rev_map2 f l1 l2 =
+ let rec rmap2_f accu l1 l2 =
+ match (l1, l2) with
+ | ([], []) -> []
+ | (a1::l1, a2::l2) -> rmap2_f (f a1 a2 :: accu) l1 l2
+ | (_, _) -> invalid_arg "List.rev_map2"
+ in
+ rmap2_f [] l1 l2
+;;
+
let rec iter2 f l1 l2 =
match (l1, l2) with
([], []) -> ()