Skip to content

Commit

Permalink
stdlib: add Array.fold_left_map (ocaml#9961)
Browse files Browse the repository at this point in the history
  • Loading branch information
craigfe authored and Nicolas Chataing committed Jun 29, 2021
1 parent 6a80378 commit 853de2d
Show file tree
Hide file tree
Showing 5 changed files with 44 additions and 0 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -179,6 +179,9 @@ Working version
- #9582: Add Array.{find_opt,find_map,split,combine}.
(Nicolás Ojeda Bär, review by Daniel Bünzli and Gabriel Scherer)

- #9961: Add Array.fold_left_map.
(Craig Ferguson, review by Damien Doligez)

- #10097: Lazy.map, Lazy.map_val: ('a -> 'b) -> 'a Lazy.t -> 'b Lazy.t
(map f x) is always (lazy (f (force x))), whereas (map_val f x)
applies f directly if x is already forced.
Expand Down
14 changes: 14 additions & 0 deletions stdlib/array.ml
Original file line number Diff line number Diff line change
Expand Up @@ -164,6 +164,20 @@ let fold_left f x a =
done;
!r

let fold_left_map f acc input_array =
let len = length input_array in
if len = 0 then (acc, [||]) else begin
let acc, elt = f acc (unsafe_get input_array 0) in
let output_array = create len elt in
let acc = ref acc in
for i = 1 to len - 1 do
let acc', elt = f !acc (unsafe_get input_array i) in
acc := acc';
unsafe_set output_array i elt;
done;
!acc, output_array
end

let fold_right f a x =
let r = ref x in
for i = length a - 1 downto 0 do
Expand Down
6 changes: 6 additions & 0 deletions stdlib/array.mli
Original file line number Diff line number Diff line change
Expand Up @@ -184,6 +184,12 @@ val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a
[f (... (f (f init a.(0)) a.(1)) ...) a.(n-1)],
where [n] is the length of the array [a]. *)

val fold_left_map :
('a -> 'b -> 'a * 'c) -> 'a -> 'b array -> 'a * 'c array
(** [fold_left_map] is a combination of {!fold_left} and {!map} that threads an
accumulator through calls to [f].
@since 4.13.0 *)

val fold_right : ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
(** [fold_right f a init] computes
[f a.(0) (f a.(1) ( ... (f a.(n-1) init) ...))],
Expand Down
6 changes: 6 additions & 0 deletions stdlib/arrayLabels.mli
Original file line number Diff line number Diff line change
Expand Up @@ -184,6 +184,12 @@ val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
[f (... (f (f init a.(0)) a.(1)) ...) a.(n-1)],
where [n] is the length of the array [a]. *)

val fold_left_map :
f:('a -> 'b -> 'a * 'c) -> init:'a -> 'b array -> 'a * 'c array
(** [fold_left_map] is a combination of {!fold_left} and {!map} that threads an
accumulator through calls to [f].
@since 4.13.0 *)

val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
(** [fold_right ~f a ~init] computes
[f a.(0) (f a.(1) ( ... (f a.(n-1) init) ...))],
Expand Down
15 changes: 15 additions & 0 deletions testsuite/tests/lib-array/test_array.ml
Original file line number Diff line number Diff line change
Expand Up @@ -114,3 +114,18 @@ let _ = Array.find_map (fun _ -> None) a;;
val a : int array = [|1; 2|]
- : 'a option = None
|}]

let a = Array.init 8 succ;;
let _ = Array.fold_left_map (fun a b -> a + b, string_of_int b) 0 a;;
a (* [a] is unchanged *);;
[%%expect {|
val a : int array = [|1; 2; 3; 4; 5; 6; 7; 8|]
- : int * string array = (36, [|"1"; "2"; "3"; "4"; "5"; "6"; "7"; "8"|])
- : int array = [|1; 2; 3; 4; 5; 6; 7; 8|]
|}]

let (_ : (_ * unit array)) =
Array.fold_left_map (fun _ _ -> assert false) 0 [||];;
[%%expect{|
- : int * unit array = (0, [||])
|}]

0 comments on commit 853de2d

Please sign in to comment.