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 *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* List operations *)
|
|
|
|
|
|
|
|
let rec length = function
|
|
|
|
[] -> 0
|
|
|
|
| a::l -> 1 + length l
|
|
|
|
|
|
|
|
let hd = function
|
|
|
|
[] -> failwith "hd"
|
|
|
|
| a::l -> a
|
|
|
|
|
|
|
|
let tl = function
|
|
|
|
[] -> failwith "tl"
|
|
|
|
| a::l -> l
|
|
|
|
|
1995-06-18 07:45:56 -07:00
|
|
|
let rec nth l n =
|
|
|
|
match l with
|
|
|
|
[] -> failwith "nth"
|
1997-02-16 05:37:16 -08:00
|
|
|
| a::l ->
|
|
|
|
if n = 0 then a else
|
|
|
|
if n > 0 then nth l (n-1) else
|
1997-02-16 09:18:54 -08:00
|
|
|
invalid_arg "List.nth"
|
1995-06-18 07:45:56 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec rev_append accu = function
|
|
|
|
[] -> accu
|
|
|
|
| a::l -> rev_append (a :: accu) l
|
|
|
|
|
|
|
|
let rev l = rev_append [] l
|
|
|
|
|
|
|
|
let rec flatten = function
|
|
|
|
[] -> []
|
|
|
|
| l::r -> l @ flatten r
|
|
|
|
|
1997-02-25 06:41:37 -08:00
|
|
|
let concat = flatten
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec map f = function
|
|
|
|
[] -> []
|
|
|
|
| a::l -> let r = f a in r :: map f l
|
|
|
|
|
|
|
|
let rec iter f = function
|
|
|
|
[] -> ()
|
|
|
|
| a::l -> f a; iter f l
|
|
|
|
|
|
|
|
let rec fold_left f accu l =
|
|
|
|
match l with
|
|
|
|
[] -> accu
|
|
|
|
| a::l -> fold_left f (f accu a) l
|
|
|
|
|
|
|
|
let rec fold_right f l accu =
|
|
|
|
match l with
|
|
|
|
[] -> accu
|
|
|
|
| a::l -> f a (fold_right f l accu)
|
|
|
|
|
|
|
|
let rec map2 f l1 l2 =
|
|
|
|
match (l1, l2) with
|
|
|
|
([], []) -> []
|
1995-11-19 08:54:24 -08:00
|
|
|
| (a1::l1, a2::l2) -> let r = f a1 a2 in r :: map2 f l1 l2
|
1995-05-04 03:15:53 -07:00
|
|
|
| (_, _) -> invalid_arg "List.map2"
|
|
|
|
|
|
|
|
let rec iter2 f l1 l2 =
|
|
|
|
match (l1, l2) with
|
|
|
|
([], []) -> ()
|
|
|
|
| (a1::l1, a2::l2) -> f a1 a2; iter2 f l1 l2
|
|
|
|
| (_, _) -> invalid_arg "List.iter2"
|
|
|
|
|
|
|
|
let rec fold_left2 f accu l1 l2 =
|
|
|
|
match (l1, l2) with
|
|
|
|
([], []) -> accu
|
|
|
|
| (a1::l1, a2::l2) -> fold_left2 f (f accu a1 a2) l1 l2
|
|
|
|
| (_, _) -> invalid_arg "List.fold_left2"
|
|
|
|
|
|
|
|
let rec fold_right2 f l1 l2 accu =
|
|
|
|
match (l1, l2) with
|
|
|
|
([], []) -> accu
|
|
|
|
| (a1::l1, a2::l2) -> f a1 a2 (fold_right2 f l1 l2 accu)
|
|
|
|
| (_, _) -> invalid_arg "List.fold_right2"
|
|
|
|
|
|
|
|
let rec for_all p = function
|
|
|
|
[] -> true
|
|
|
|
| a::l -> p a & for_all p l
|
|
|
|
|
|
|
|
let rec exists p = function
|
|
|
|
[] -> false
|
|
|
|
| a::l -> p a or exists p l
|
|
|
|
|
1995-09-28 03:42:18 -07:00
|
|
|
let rec for_all2 p l1 l2 =
|
|
|
|
match (l1, l2) with
|
|
|
|
([], []) -> true
|
|
|
|
| (a1::l1, a2::l2) -> p a1 a2 & for_all2 p l1 l2
|
|
|
|
| (_, _) -> invalid_arg "List.for_all2"
|
|
|
|
|
|
|
|
let rec exists2 p l1 l2 =
|
|
|
|
match (l1, l2) with
|
1996-07-01 05:44:01 -07:00
|
|
|
([], []) -> false
|
1995-09-28 03:42:18 -07:00
|
|
|
| (a1::l1, a2::l2) -> p a1 a2 or exists2 p l1 l2
|
|
|
|
| (_, _) -> invalid_arg "List.exists2"
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec mem x = function
|
|
|
|
[] -> false
|
|
|
|
| a::l -> a = x or mem x l
|
|
|
|
|
1995-09-19 06:33:02 -07:00
|
|
|
let rec memq x = function
|
|
|
|
[] -> false
|
1995-10-19 09:28:21 -07:00
|
|
|
| a::l -> a == x or memq x l
|
1995-09-19 06:33:02 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec assoc x = function
|
|
|
|
[] -> raise Not_found
|
|
|
|
| (a,b)::l -> if a = x then b else assoc x l
|
|
|
|
|
|
|
|
let rec mem_assoc x = function
|
|
|
|
[] -> false
|
|
|
|
| (a,b)::l -> a = x or mem_assoc x l
|
|
|
|
|
|
|
|
let rec assq x = function
|
|
|
|
[] -> raise Not_found
|
|
|
|
| (a,b)::l -> if a == x then b else assq x l
|
|
|
|
|
|
|
|
let rec split = function
|
|
|
|
[] -> ([], [])
|
|
|
|
| (x,y)::l ->
|
|
|
|
let (rx, ry) = split l in (x::rx, y::ry)
|
|
|
|
|
1995-07-02 09:46:44 -07:00
|
|
|
let rec combine l1 l2 =
|
|
|
|
match (l1, l2) with
|
1995-05-04 03:15:53 -07:00
|
|
|
([], []) -> []
|
1995-07-02 09:46:44 -07:00
|
|
|
| (a1::l1, a2::l2) -> (a1, a2) :: combine l1 l2
|
1995-05-04 03:15:53 -07:00
|
|
|
| (_, _) -> invalid_arg "List.combine"
|