List.find_map : ('a -> 'b option) -> 'a list -> 'b option (#8832)

master
Gabriel Scherer 2019-09-13 17:58:01 +02:00 committed by Alain Frisch
parent 2ed8badb40
commit 5c7c619d4d
5 changed files with 33 additions and 0 deletions

View File

@ -125,6 +125,10 @@ Working version
### Standard library:
- #8832: List.find_map : ('a -> 'b option) -> 'a list -> 'b option
(Gabriel Scherer, review by Jeremy Yallop, Nicolás Ojeda Bär
and Daniel Bünzli)
- #8657: Optimization in [Array.make] when initializing with unboxed
or young values.
(Jacques-Henri Jourdan, review by Gabriel Scherer and Stephen Dolan)

View File

@ -228,6 +228,14 @@ let rec find_opt p = function
| [] -> None
| x :: l -> if p x then Some x else find_opt p l
let rec find_map f = function
| [] -> None
| x :: l ->
begin match f x with
| Some _ as result -> result
| None -> find_map f l
end
let find_all p =
let rec find accu = function
| [] -> rev accu

View File

@ -230,6 +230,13 @@ val find_opt: ('a -> bool) -> 'a list -> 'a option
satisfies [p] in the list [l].
@since 4.05 *)
val find_map: ('a -> 'b option) -> 'a list -> 'b option
(** [find_map f l] applies [f] to the elements of [l] in order,
and returns the first result of the form [Some v], or [None]
if none exist.
@since 4.10.0
*)
val filter : ('a -> bool) -> 'a list -> 'a list
(** [filter p l] returns all the elements of the list [l]
that satisfy the predicate [p]. The order of the elements

View File

@ -235,6 +235,13 @@ val find_opt: f:('a -> bool) -> 'a list -> 'a option
list [l].
@since 4.05 *)
val find_map: f:('a -> 'b option) -> 'a list -> 'b option
(** [find_map f l] applies [f] to the elements of [l] in order,
and returns the first result of the form [Some v], or [None]
if none exist.
@since 4.10.0
*)
val filter : f:('a -> bool) -> 'a list -> 'a list
(** [filter p l] returns all the elements of the list [l]
that satisfy the predicate [p]. The order of the elements

View File

@ -26,6 +26,13 @@ let () =
assert (not (List.exists (fun a -> a > 9) l));
assert (List.exists (fun _ -> true) l);
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.compare_lengths [] [] = 0);
assert (List.compare_lengths [1;2] ['a';'b'] = 0);
assert (List.compare_lengths [] [1;2] < 0);