(* TEST *) let is_even x = (x mod 2 = 0) let string_of_even_opt x = if is_even x then Some (string_of_int x) else None let string_of_even_or_int x = if is_even x then Either.Left (string_of_int x) else Either.Right x (* Standard test case *) let () = let l = List.init 10 (fun x -> x) in let sl = List.init 10 string_of_int in assert (List.exists (fun a -> a < 10) l); assert (List.exists (fun a -> a > 0) l); assert (List.exists (fun a -> a = 0) l); assert (List.exists (fun a -> a = 1) l); assert (List.exists (fun a -> a = 2) l); assert (List.exists (fun a -> a = 3) l); assert (List.exists (fun a -> a = 4) l); assert (List.exists (fun a -> a = 5) l); assert (List.exists (fun a -> a = 6) l); assert (List.exists (fun a -> a = 7) l); assert (List.exists (fun a -> a = 8) l); assert (List.exists (fun a -> a = 9) l); assert (not (List.exists (fun a -> a < 0) l)); assert (not (List.exists (fun a -> a > 9) l)); assert (List.exists (fun _ -> true) l); assert (List.equal (=) [1; 2; 3] [1; 2; 3]); assert (not (List.equal (=) [1; 2; 3] [1; 2])); assert (not (List.equal (=) [1; 2; 3] [1; 3; 2])); (* The current implementation of List.equal calls the comparison function even for different-size lists. This is not part of the specification, so it would be valid to change this behavior, but we don't want to change it without noticing so here is a test for it. *) assert (let c = ref 0 in not (List.equal (fun _ _ -> incr c; true) [1; 2] [1; 2; 3]) && !c = 2); assert (List.compare compare [1; 2; 3] [1; 2; 3] = 0); assert (List.compare compare [1; 2; 3] [1; 2] > 0); assert (List.compare compare [1; 2; 3] [1; 3; 2] < 0); assert (List.compare compare [3] [2; 1] > 0); begin let f ~limit a = if a >= limit then Some (a, limit) else None in assert (List.find_map (f ~limit:3) [] = None); assert (List.find_map (f ~limit:3) l = Some (3, 3)); assert (List.find_map (f ~limit:30) l = None); end; assert (List.filteri (fun i _ -> i < 2) (List.rev l) = [9; 8]); let hello = ['H';'e';'l';'l';'o'] in let world = ['W';'o';'r';'l';'d';'!'] in let hello_world = hello @ [' '] @ world in assert (List.take 5 hello_world = hello); assert (List.take 3 [1; 2; 3; 4; 5] = [1; 2; 3]); assert (List.take 3 [1; 2] = [1; 2]); assert (List.take 3 [] = []); assert ((try List.take (-1) [1; 2] with Invalid_argument _ -> [999]) = [999]); assert (List.take 0 [1; 2] = []); assert (List.drop 6 hello_world = world); assert (List.drop 3 [1; 2; 3; 4; 5] = [4; 5]); assert (List.drop 3 [1; 2] = []); assert (List.drop 3 [] = []); assert ((try List.drop (-1) [1; 2] with Invalid_argument _ -> [999]) = [999]); assert (List.drop 0 [1; 2] = [1; 2]); assert (List.take_while (fun x -> x < 3) [1; 2; 3; 4; 1; 2; 3; 4] = [1; 2]); assert (List.take_while (fun x -> x < 9) [1; 2; 3] = [1; 2; 3]); assert (List.take_while (fun x -> x < 0) [1; 2; 3] = []); assert (List.drop_while (fun x -> x < 3) [1; 2; 3; 4; 5; 1; 2; 3] = [3; 4; 5; 1; 2; 3]); assert (List.drop_while (fun x -> x < 9) [1; 2; 3] = []); assert (List.drop_while (fun x -> x < 0) [1; 2; 3] = [1; 2; 3]); assert (List.partition is_even [1; 2; 3; 4; 5] = ([2; 4], [1; 3; 5])); assert (List.partition_map string_of_even_or_int [1; 2; 3; 4; 5] = (["2"; "4"], [1; 3; 5])); assert (List.compare_lengths [] [] = 0); assert (List.compare_lengths [1;2] ['a';'b'] = 0); assert (List.compare_lengths [] [1;2] < 0); assert (List.compare_lengths ['a'] [1;2] < 0); assert (List.compare_lengths [1;2] [] > 0); assert (List.compare_lengths [1;2] ['a'] > 0); assert (List.compare_length_with [] 0 = 0); assert (List.compare_length_with [] 1 < 0); assert (List.compare_length_with [] (-1) > 0); assert (List.compare_length_with [] max_int < 0); assert (List.compare_length_with [] min_int > 0); assert (List.compare_length_with [1] 0 > 0); assert (List.compare_length_with ['1'] 1 = 0); assert (List.compare_length_with ['1'] 2 < 0); assert (List.is_empty []); assert (not (List.is_empty [1])); assert (List.filter_map string_of_even_opt l = ["0";"2";"4";"6";"8"]); assert (List.concat_map (fun i -> [i; i+1]) [1; 5] = [1; 2; 5; 6]); assert ( let count = ref 0 in List.concat_map (fun i -> incr count; [i; !count]) [1; 5] = [1; 1; 5; 2]); assert (List.fold_left_map (fun a b -> a + b, b) 0 l = (45, l)); assert (List.fold_left_map (fun a b -> assert false) 0 [] = (0, [])); assert ( let f a b = a + b, string_of_int b in List.fold_left_map f 0 l = (45, sl)); (* [find_index] *) assert (List.find_index (fun x -> x=1) [] = None); let xs = [1;2;3;4;5] in assert (List.find_index (fun x -> x=1) xs = Some 0); assert (List.find_index (fun x -> x=3) xs = Some 2); assert (List.find_index (fun x -> x=5) xs = Some 4); assert (List.find_index (fun x -> x=6) xs = None); (* [find_mapi] *) assert (List.find_mapi (fun i x -> if x+i=3 then Some(i, x) else None) [] = None); let xs = [3;3;3;42;42] in assert (List.find_mapi (fun i x -> if x+i=3 then Some(i, x) else None) xs = Some (0, 3)); assert (List.find_mapi (fun i x -> if x+i=4 then Some(i, x) else None) xs = Some (1, 3)); assert (List.find_mapi (fun i x -> if x+i=5 then Some(i, x) else None) xs = Some (2, 3)); assert (List.find_mapi (fun i x -> if x+i=7 then Some(i, x) else None) xs = None); () ;; (* Check that List.sort_uniq keeps first occurrences of duplicates. *) let () = let keep_first_duplicates l = let tagged = List.combine l (List.init (List.length l) Fun.id) in let sorted = List.sort_uniq (fun c1 c2 -> Int.compare (fst c1) (fst c2)) tagged in let is_first_tag (x, y) = (* Check whether the second component of the argument is the element first associated by [tagged] with the first component of the argument. *) List.assoc x tagged = y in List.for_all is_first_tag sorted in let randlist maxlen = let len = Random.int maxlen in (* Take values in [0, (3 * len) / 2] to have some collisions. *) List.init len (fun _ -> Random.int ( 1 + (3 * len) / 2 )) in for _ = 0 to 20 do let l = randlist 99 in if not (keep_first_duplicates l) then ( Format.printf "List.sort_uniq did not keep first duplicates when sorting the list@ \ @[[%a]@]@." Format.( pp_print_list ~pp_sep:(fun out () -> fprintf out ";@ ") pp_print_int) l; assert false) done ;; (* Empty test case *) let () = assert ((List.init 0 (fun x -> x)) = []); ;; (* Erroneous test case *) let () = let result = try let _ = List.init (-1) (fun x -> x) in false with Invalid_argument e -> true (* Exception caught *) in assert result; ;; (* Evaluation order *) let () = let test n = let result = ref false in let _ = List.init n (fun x -> result := (x = n - 1)) in assert !result in (* Threshold must equal the value in stdlib/list.ml *) let threshold = 10_000 in test threshold; (* Non tail-recursive case *) test (threshold + 1) (* Tail-recursive case *) ;; let () = print_endline "OK";;