Skip to content

Commit

Permalink
stdlib: add List.is_empty (#10464)
Browse files Browse the repository at this point in the history
As of #10681, the native compiler is able to simplify this
pattern-matching to use bitwise operations rather than an explicit
branch (as was previously the case) or an integer comparison (as is the
case for the implementation using `( = )`).

Co-authored-by: David Allsopp <david.allsopp@metastack.com>
  • Loading branch information
craigfe and dra27 committed Oct 31, 2022
1 parent cc3d9cb commit fc06c7d
Show file tree
Hide file tree
Showing 6 changed files with 25 additions and 2 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -858,6 +858,9 @@ OCaml 4.14.0 (28 March 2022)
- #10786: The implementation of Complex.norm now uses Float.hypot.
(Christophe Troestler, review by David Allsopp and Xavier Leroy)

- #10464: Add List.is_empty.
(Craig Ferguson, review by David Allsopp)

### Other libraries:

- #10192: Add support for Unix domain sockets on Windows and use them
Expand Down
4 changes: 4 additions & 0 deletions stdlib/list.ml
Original file line number Diff line number Diff line change
Expand Up @@ -551,6 +551,10 @@ let rec compare_length_with l n =
if n <= 0 then 1 else
compare_length_with l (n-1)

let is_empty = function
| [] -> true
| _ :: _ -> false

(** {1 Comparison} *)

(* Note: we are *not* shortcutting the list by using
Expand Down
6 changes: 6 additions & 0 deletions stdlib/list.mli
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,12 @@ val compare_length_with : 'a list -> int -> int
@since 4.05.0
*)

val is_empty : 'a list -> bool
(** [is_empty l] is true if and only if [l] has no elements. It is equivalent to
[compare_length_with l 0 = 0].
@since 5.1
*)

val cons : 'a -> 'a list -> 'a list
(** [cons x xs] is [x :: xs]
@since 4.03.0 (4.05.0 in ListLabels)
Expand Down
6 changes: 6 additions & 0 deletions stdlib/listLabels.mli
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,12 @@ val compare_length_with : 'a list -> len:int -> int
@since 4.05.0
*)

val is_empty : 'a list -> bool
(** [is_empty l] is true if and only if [l] has no elements. It is equivalent to
[compare_length_with l 0 = 0].
@since 5.1
*)

val cons : 'a -> 'a list -> 'a list
(** [cons x xs] is [x :: xs]
@since 4.03.0 (4.05.0 in ListLabels)
Expand Down
4 changes: 4 additions & 0 deletions testsuite/tests/lib-list/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,10 @@ let () =
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 (
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,7 @@
(apply f (field_imm 0 param) (field_imm 1 param)))
map =
(function f l
(apply (field_imm 18 (global Stdlib__List!))
(apply (field_imm 19 (global Stdlib__List!))
(apply uncurry f) l)))
(makeblock 0
(makeblock 0 (apply map gen_cmp vec) (apply map cmp vec))
Expand Down Expand Up @@ -198,7 +198,7 @@
(apply f (field_imm 0 param) (field_imm 1 param)))
map =
(function f l
(apply (field_imm 18 (global Stdlib__List!))
(apply (field_imm 19 (global Stdlib__List!))
(apply uncurry f) l)))
(makeblock 0
(makeblock 0 (apply map eta_gen_cmp vec)
Expand Down

0 comments on commit fc06c7d

Please sign in to comment.