Skip to content

Commit

Permalink
Add Array.{find_opt,find_map,split,combine} (ocaml#9582)
Browse files Browse the repository at this point in the history
  • Loading branch information
nojb authored and dbuenzli committed Mar 25, 2021
1 parent cd0167c commit 0d8ea47
Show file tree
Hide file tree
Showing 5 changed files with 162 additions and 0 deletions.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -16,6 +16,9 @@ Working version

### Standard library:

- #9582: Add Array.{find_opt,find_map,split,combine}.
(Nicolás Ojeda Bär, review by Daniel Bünzli and Gabriel Scherer)

### Other libraries:

### Tools:
Expand Down
50 changes: 50 additions & 0 deletions stdlib/array.ml
Expand Up @@ -223,6 +223,56 @@ let memq x a =
else loop (succ i) in
loop 0

let find_opt p a =
let n = length a in
let rec loop i =
if i = n then None
else
let x = unsafe_get a i in
if p x then Some x
else loop (succ i)
in
loop 0

let find_map f a =
let n = length a in
let rec loop i =
if i = n then None
else
match f (unsafe_get a i) with
| None -> loop (succ i)
| Some _ as r -> r
in
loop 0

let split x =
if x = [||] then [||], [||]
else begin
let a0, b0 = unsafe_get x 0 in
let n = length x in
let a = create n a0 in
let b = create n b0 in
for i = 1 to n - 1 do
let ai, bi = unsafe_get x i in
unsafe_set a i ai;
unsafe_set b i bi
done;
a, b
end

let combine a b =
let na = length a in
let nb = length b in
if na <> nb then invalid_arg "Array.combine";
if na = 0 then [||]
else begin
let x = create na (unsafe_get a 0, unsafe_get b 0) in
for i = 1 to na - 1 do
unsafe_set x i (unsafe_get a i, unsafe_get b i)
done;
x
end

exception Bottom of int
let sort cmp a =
let maxson l i =
Expand Down
25 changes: 25 additions & 0 deletions stdlib/array.mli
Expand Up @@ -243,6 +243,31 @@ val memq : 'a -> 'a array -> bool
instead of structural equality to compare list elements.
@since 4.03.0 *)

val find_opt : ('a -> bool) -> 'a array -> 'a option
(** [find_opt f a] returns the first element of the array [a] that satisfies
the predicate [f], or [None] if there is no value that satisfies [f] in the
array [a].
@since 4.13.0 *)

val find_map : ('a -> 'b option) -> 'a array -> 'b option
(** [find_map f a] applies [f] to the elements of [a] in order, and returns the
first result of the form [Some v], or [None] if none exist.
@since 4.13.0 *)

(** {1 Arrays of pairs} *)

val split : ('a * 'b) array -> 'a array * 'b array
(** [split [|(a1,b1); ...; (an,bn)|]] is [([|a1; ...; an|], [|b1; ...; bn|])].
@since 4.13.0 *)

val combine : 'a array -> 'b array -> ('a * 'b) array
(** [combine [|a1; ...; an|] [|b1; ...; bn|]] is [[|(a1,b1); ...; (an,bn)|]].
Raise [Invalid_argument] if the two arrays have different lengths.
@since 4.13.0 *)

(** {1 Sorting} *)

Expand Down
25 changes: 25 additions & 0 deletions stdlib/arrayLabels.mli
Expand Up @@ -243,6 +243,31 @@ val memq : 'a -> set:'a array -> bool
instead of structural equality to compare list elements.
@since 4.03.0 *)

val find_opt : f:('a -> bool) -> 'a array -> 'a option
(** [find_opt ~f a] returns the first element of the array [a] that satisfies
the predicate [f], or [None] if there is no value that satisfies [f] in the
array [a].
@since 4.13.0 *)

val find_map : f:('a -> 'b option) -> 'a array -> 'b option
(** [find_map ~f a] applies [f] to the elements of [a] in order, and returns the
first result of the form [Some v], or [None] if none exist.
@since 4.13.0 *)

(** {1 Arrays of pairs} *)

val split : ('a * 'b) array -> 'a array * 'b array
(** [split [|(a1,b1); ...; (an,bn)|]] is [([|a1; ...; an|], [|b1; ...; bn|])].
@since 4.13.0 *)

val combine : 'a array -> 'b array -> ('a * 'b) array
(** [combine [|a1; ...; an|] [|b1; ...; bn|]] is [[|(a1,b1); ...; (an,bn)|]].
Raise [Invalid_argument] if the two arrays have different lengths.
@since 4.13.0 *)

(** {1 Sorting} *)

Expand Down
59 changes: 59 additions & 0 deletions testsuite/tests/lib-array/test_array.ml
Expand Up @@ -55,3 +55,62 @@ val a : float array = [|0.; 0.; 0.; 0.; 0.; 0.; 0.; 0.|]
- : unit = ()
- : float array = [|0.; 0.; 42.; 42.; 42.; 0.; 0.; 0.|]
|}]

let a = [|(1, 'a'); (2, 'b'); (3, 'c')|];;
let _ = Array.split a;;
[%%expect{|
val a : (int * char) array = [|(1, 'a'); (2, 'b'); (3, 'c')|]
- : int array * char array = ([|1; 2; 3|], [|'a'; 'b'; 'c'|])
|}]

let a = [|1; 2; 3|];;
let b = [|'a'; 'b'; 'c'|];;
let _ = Array.combine a b;;
[%%expect{|
val a : int array = [|1; 2; 3|]
val b : char array = [|'a'; 'b'; 'c'|]
- : (int * char) array = [|(1, 'a'); (2, 'b'); (3, 'c')|]
|}]

let _ : int array * char array = Array.split [||];;
[%%expect{|
- : int array * char array = ([||], [||])
|}]

let _ : (int * char) array = Array.combine [||] [||];;
[%%expect{|
- : (int * char) array = [||]
|}]

let _ = Array.combine [||] [|1|];;
[%%expect{|
Exception: Invalid_argument "Array.combine".
|}]

let a = [|1; 2; 3|];;
let _ = Array.find_opt (function 2 -> true | _ -> false) a;;
[%%expect{|
val a : int array = [|1; 2; 3|]
- : int option = Some 2
|}]

let a = [|'a'; 'b'; 'c'|];;
let _ = Array.find_map (function 'b' -> Some 121 | _ -> None) a;;
[%%expect{|
val a : char array = [|'a'; 'b'; 'c'|]
- : int option = Some 121
|}]

let a = [|1; 2|];;
let _ = Array.find_opt (function 101 -> true | _ -> false) a;;
[%%expect{|
val a : int array = [|1; 2|]
- : int option = None
|}]

let a = [|1; 2|];;
let _ = Array.find_map (fun _ -> None) a;;
[%%expect{|
val a : int array = [|1; 2|]
- : 'a option = None
|}]

0 comments on commit 0d8ea47

Please sign in to comment.