Skip to content

Commit

Permalink
refactor: replace >>= with let* where possible (#8529)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Aug 28, 2023
1 parent ab125e0 commit 104d242
Show file tree
Hide file tree
Showing 6 changed files with 16 additions and 13 deletions.
10 changes: 6 additions & 4 deletions bin/describe/describe_workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -446,10 +446,12 @@ module Crawl = struct
match Lib.is_local lib with
| false -> Memo.return []
| true ->
Dir_contents.get sctx ~dir:(Path.as_in_build_dir_exn src_dir)
>>= Dir_contents.ocaml
>>| Ml_sources.modules_and_obj_dir ~for_:(Library name)
>>= fun (modules_, obj_dir_) ->
(* XXX why do we have a second object directory? *)
let* modules_, obj_dir_ =
Dir_contents.get sctx ~dir:(Path.as_in_build_dir_exn src_dir)
>>= Dir_contents.ocaml
>>| Ml_sources.modules_and_obj_dir ~for_:(Library name)
in
let pp_map =
Staged.unstage
@@
Expand Down
3 changes: 1 addition & 2 deletions src/dune_rules/coq/coq_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -478,8 +478,7 @@ let deps_of ~dir ~boot_type ~wrapper_name ~mode coq_module =
in
Path.set_extension ~ext (Coq_module.source coq_module)
in
get_dep_map ~dir ~wrapper_name
>>= fun dep_map ->
let* dep_map = get_dep_map ~dir ~wrapper_name in
match Dep_map.find dep_map vo_target with
| None ->
Code_error.raise
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -583,7 +583,7 @@ module Toggle = struct
let decode =
match check with
| None -> decode
| Some check -> check >>= fun () -> decode
| Some check -> check >>> decode
in
field_o name decode
;;
Expand Down
4 changes: 1 addition & 3 deletions src/dune_rules/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -300,9 +300,7 @@ module Context = struct
let decode =
let+ common = Common.decode
and+ name =
field_o
"name"
(Dune_lang.Syntax.since syntax (1, 10) >>= fun () -> Context_name.decode)
field_o "name" (Dune_lang.Syntax.since syntax (1, 10) >>> Context_name.decode)
and+ lock =
(* TODO
1. guard before version check before releasing
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -46,8 +46,7 @@ let get_events ~try_to_get_events ~expected =
assert (n > 0);
retry_loop ~period:0.01 ~timeout:3.0 ~f:(fun () ->
let open Option.O in
try_to_get_events ()
>>= fun events ->
let* events = try_to_get_events () in
collected := !collected @ events;
if List.length !collected >= expected then Some `Enough else None)
in
Expand Down
7 changes: 6 additions & 1 deletion test/expect-tests/memo/memoize_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -408,7 +408,12 @@ let%expect_test "fib linked list" =
let seventh = run (Memo.exec memo 7) in
printf "7th: %d\n" seventh.value;
printf "prev: %d\n" (run (force seventh.prev_cell)).value;
printf "prev: %d\n" (run (force seventh.prev_cell >>= fun x -> force x.prev_cell)).value;
printf
"prev: %d\n"
(run
(let* x = force seventh.prev_cell in
force x.prev_cell))
.value;
[%expect
{|
computing 4
Expand Down

0 comments on commit 104d242

Please sign in to comment.