Skip to content

Commit

Permalink
Merge pull request #990 from ocaml/list-find-exn
Browse files Browse the repository at this point in the history
Add List.find_exn
  • Loading branch information
emillon authored Jul 10, 2018
2 parents 64b3b0e + 8c3690c commit 1c28d73
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 11 deletions.
13 changes: 5 additions & 8 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -181,9 +181,10 @@ let find_root () =
List.fold_left l ~init:max_int ~f:(fun acc (prio, _, _) ->
min acc prio)
in
match List.find l ~f:(fun (prio, _, _) -> prio = lowest_priority) with
| None -> assert false
| Some (_, dir, to_cwd) -> (dir, to_cwd)
let (_, dir, to_cwd) =
List.find_exn l ~f:(fun (prio, _, _) -> prio = lowest_priority)
in
(dir, to_cwd)

let package_name =
Arg.conv ((fun p -> Ok (Package.Name.of_string p)), Package.Name.pp)
Expand Down Expand Up @@ -896,11 +897,7 @@ let external_lib_deps =
in
if only_missing then begin
let context =
match
List.find setup.contexts ~f:(fun c -> c.name = context_name)
with
| None -> assert false
| Some c -> c
List.find_exn setup.contexts ~f:(fun c -> c.name = context_name)
in
let missing =
String.Map.filteri externals ~f:(fun name _ ->
Expand Down
6 changes: 3 additions & 3 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -160,9 +160,9 @@ module Internal_rule = struct
last_requested_file :: acc
else
let requested_file, rev_dep =
Option.value_exn
(List.find t.rev_deps ~f:(fun (_, t) ->
Id.Set.mem t.transitive_rev_deps last.id))
List.find_exn
t.rev_deps
~f:(fun (_, t) -> Id.Set.mem t.transitive_rev_deps last.id)
in
build_loop (requested_file :: acc) rev_dep
in
Expand Down
5 changes: 5 additions & 0 deletions src/stdune/list.ml
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,11 @@ let rec find l ~f =
| [] -> None
| x :: l -> if f x then Some x else find l ~f

let find_exn l ~f =
match find l ~f with
| Some x -> x
| None -> invalid_arg "List.find_exn"

let rec last = function
| [] -> None
| [x] -> Some x
Expand Down
1 change: 1 addition & 0 deletions src/stdune/list.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ val rev_filter_partition_map
-> 'b t * 'c t

val find : 'a t -> f:('a -> bool ) -> 'a option
val find_exn : 'a t -> f:('a -> bool ) -> 'a
val find_map : 'a t -> f:('a -> 'b option) -> 'b option

val last : 'a t -> 'a option
Expand Down

0 comments on commit 1c28d73

Please sign in to comment.