Skip to content

Commit

Permalink
Merge pull request #10998 from thierry-martinez/fix.doc.seq_fold_lefti
Browse files Browse the repository at this point in the history
Make `Seq.fold_lefti` documentation and implementation consistent with respect to argument order

(cherry picked from commit f46f3ee)
  • Loading branch information
gasche committed Feb 9, 2022
1 parent f9b3a4e commit 6aa8b02
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 10 deletions.
7 changes: 4 additions & 3 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -107,10 +107,11 @@ OCaml 4.14.0
(Nicolás Ojeda Bär, review by John Whitington, Daniel Bünzli, David Allsopp
and Xavier Leroy)

* #10583: Add over 40 new functions in Seq.
* #10583, #10998: Add over 40 new functions in Seq.
(François Pottier and Simon Cruanes, review by Nicolás Ojeda Bär,
Daniel Bünzli, Naëla Courant, Craig Ferguson, Wiktor Kuchta, Xavier
Leroy, Guillaume Munch-Maccagnoni, Raphaël Proust, and Gabriel Scherer)
Daniel Bünzli, Naëla Courant, Craig Ferguson, Wiktor Kuchta,
Xavier Leroy, Guillaume Munch-Maccagnoni, Raphaël Proust, Gabriel Scherer
and Thierry Martinez)

- #10596, #10978: Add with_open_bin, with_open_text and with_open_gen to
In_channel and Out_channel. Also, add In_channel.input_all.
Expand Down
8 changes: 4 additions & 4 deletions stdlib/seq.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,16 +118,16 @@ let rec iteri_aux f i xs =
let[@inline] iteri f xs =
iteri_aux f 0 xs

let rec fold_lefti_aux f i accu xs =
let rec fold_lefti_aux f accu i xs =
match xs() with
| Nil ->
accu
| Cons (x, xs) ->
let accu = f i accu x in
fold_lefti_aux f (i+1) accu xs
let accu = f accu i x in
fold_lefti_aux f accu (i+1) xs

let[@inline] fold_lefti f accu xs =
fold_lefti_aux f 0 accu xs
fold_lefti_aux f accu 0 xs

let rec for_all p xs =
match xs() with
Expand Down
4 changes: 2 additions & 2 deletions stdlib/seq.mli
Original file line number Diff line number Diff line change
Expand Up @@ -187,11 +187,11 @@ val iteri : (int -> 'a -> unit) -> 'a t -> unit
@since 4.14 *)

val fold_lefti : (int -> 'b -> 'a -> 'b) -> 'b -> 'a t -> 'b
val fold_lefti : ('b -> int -> 'a -> 'b) -> 'b -> 'a t -> 'b
(** [fold_lefti f _ xs] invokes [f _ i x] successively
for every element [x] located at index [i] of the sequence [xs].
An accumulator of type ['a] is threaded through the calls to [f].
An accumulator of type ['b] is threaded through the calls to [f].
It terminates only if the sequence [xs] is finite.
Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/lib-seq/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ let () =
let () =
let xs = !?["a"; "b"] in
assert (
Seq.fold_lefti (fun i acc x -> (i, x) :: acc) [] xs = [ 1, "b"; 0, "a" ]
Seq.fold_lefti (fun acc i x -> (i, x) :: acc) [] xs = [ 1, "b"; 0, "a" ]
)

(* [scan] *)
Expand Down

0 comments on commit 6aa8b02

Please sign in to comment.