Skip to content

Commit

Permalink
Implement find_first, find_last for maps
Browse files Browse the repository at this point in the history
Finds the first/last binding where the key satisfies a monotonic
predicate, returning an option.

Followup to ocaml#885.
  • Loading branch information
g2p committed Nov 8, 2016
1 parent 4069747 commit ac8735e
Show file tree
Hide file tree
Showing 6 changed files with 80 additions and 0 deletions.
38 changes: 38 additions & 0 deletions stdlib/map.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,9 @@ module type S =
val find: key -> 'a t -> 'a
val find_opt: key -> 'a t -> 'a option
val find_first: (key -> bool) -> 'a t -> key * 'a
val find_first_opt: (key -> bool) -> 'a t -> (key * 'a) option
val find_last: (key -> bool) -> 'a t -> key * 'a
val find_last_opt: (key -> bool) -> 'a t -> (key * 'a) option
val map: ('a -> 'b) -> 'a t -> 'b t
val mapi: (key -> 'a -> 'b) -> 'a t -> 'b t
end
Expand Down Expand Up @@ -149,6 +151,24 @@ module Make(Ord: OrderedType) = struct
else
find_first f r

let rec find_first_opt_aux v0 d0 f = function
Empty ->
Some (v0, d0)
| Node(l, v, d, r, _) ->
if f v then
find_first_opt_aux v d f l
else
find_first_opt_aux v0 d0 f r

let rec find_first_opt f = function
Empty ->
None
| Node(l, v, d, r, _) ->
if f v then
find_first_opt_aux v d f l
else
find_first_opt f r

let rec find_last_aux v0 d0 f = function
Empty ->
(v0, d0)
Expand All @@ -167,6 +187,24 @@ module Make(Ord: OrderedType) = struct
else
find_last f l

let rec find_last_opt_aux v0 d0 f = function
Empty ->
Some (v0, d0)
| Node(l, v, d, r, _) ->
if f v then
find_last_opt_aux v d f r
else
find_last_opt_aux v0 d0 f l

let rec find_last_opt f = function
Empty ->
None
| Node(l, v, d, r, _) ->
if f v then
find_last_opt_aux v d f r
else
find_last_opt f l

let rec find_opt x = function
Empty ->
None
Expand Down
10 changes: 10 additions & 0 deletions stdlib/map.mli
Original file line number Diff line number Diff line change
Expand Up @@ -243,11 +243,21 @@ module type S =
returns the binding of [m] with the lowest key [k] such that [f k],
or raises [Not_found] if no such key exists. *)

val find_first_opt: (key -> bool) -> 'a t -> (key * 'a) option
(** [find_first_opt f m], where f is a monotonically increasing function,
returns an option containing the binding of [m] with the lowest key [k]
such that [f k], or the [None] option if no such key exists. *)

val find_last: (key -> bool) -> 'a t -> key * 'a
(** [find_last f m], where f is a monotonically decreasing function,
returns the binding of [m] with the highest key [k] such that [f k],
or raises [Not_found] if no such key exists. *)

val find_last_opt: (key -> bool) -> 'a t -> (key * 'a) option
(** [find_last_opt f m], where f is a monotonically decreasing function,
returns an option containing the binding of [m] with the highest key [k]
such that [f k], or the [None] option if no such key exists. *)

val map: ('a -> 'b) -> 'a t -> 'b t
(** [map f m] returns a map with same domain as [m], where the
associated value [a] of all bindings of [m] has been
Expand Down
2 changes: 2 additions & 0 deletions stdlib/moreLabels.mli
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,9 @@ module Map : sig
val find : key -> 'a t -> 'a
val find_opt: key -> 'a t -> 'a option
val find_first : f:(key -> bool) -> 'a t -> key * 'a
val find_first_opt : f:(key -> bool) -> 'a t -> (key * 'a) option
val find_last : f:(key -> bool) -> 'a t -> key * 'a
val find_last_opt : f:(key -> bool) -> 'a t -> (key * 'a) option
val map : f:('a -> 'b) -> 'a t -> 'b t
val mapi : f:(key -> 'a -> 'b) -> 'a t -> 'b t
end
Expand Down
24 changes: 24 additions & 0 deletions testsuite/tests/lib-set/testmap.ml
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,18 @@ let test x v s1 s2 =
None -> (k, v) = M.min_binding r
| Some v1 -> (k, v) = (x, v1));

checkbool "find_first_opt"
(let (l, p, r) = M.split x s1 in
if p = None && M.is_empty r then
match M.find_first_opt (fun k -> k >= x) s1 with
None -> true
| _ -> false
else
let Some (k, v) = M.find_first_opt (fun k -> k >= x) s1 in
match p with
None -> (k, v) = M.min_binding r
| Some v1 -> (k, v) = (x, v1));

checkbool "find_last"
(let (l, p, r) = M.split x s1 in
if p = None && M.is_empty l then
Expand All @@ -129,6 +141,18 @@ let test x v s1 s2 =
None -> (k, v) = M.max_binding l
| Some v1 -> (k, v) = (x, v1));

checkbool "find_last_opt"
(let (l, p, r) = M.split x s1 in
if p = None && M.is_empty l then
match M.find_last_opt (fun k -> k <= x) s1 with
None -> true
| _ -> false
else
let Some (k, v) = M.find_last_opt (fun k -> k <= x) s1 in
match p with
None -> (k, v) = M.max_binding l
| Some v1 -> (k, v) = (x, v1));

check "split"
(let (l, p, r) = M.split x s1 in
fun i ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -107,7 +107,9 @@ module type MapT =
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
type data
Expand Down Expand Up @@ -151,7 +153,9 @@ module SSMap :
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
type data = string
Expand Down
2 changes: 2 additions & 0 deletions testsuite/tests/typing-short-paths/short-paths.ml.reference
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,9 @@
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
end
Expand Down

0 comments on commit ac8735e

Please sign in to comment.