Skip to content

Commit

Permalink
code review
Browse files Browse the repository at this point in the history
Signed-off-by: Jeremie Dimino <jeremie@dimino.org>
  • Loading branch information
jeremiedimino committed Nov 27, 2018
1 parent 54ece00 commit 27bbbd9
Show file tree
Hide file tree
Showing 7 changed files with 27 additions and 24 deletions.
31 changes: 13 additions & 18 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1557,30 +1557,25 @@ let package_deps t pkg files =
acc
else begin
rules_seen := Rule.Id.Set.add !rules_seen ir.id;
match Fiber.Once.peek ir.static_deps with
| None ->
(* We know that at this point of execution, all the relevant
ivars have been filled *)
assert false
| Some static_deps ->
let rule_deps = Static_deps.rule_deps static_deps in
match Rule_fn.peek (Fdecl.get t.build_rule_def) ir with
| None -> assert false
| Some (_, deps) ->
let dyn_deps = Deps.path_diff deps rule_deps in
let action_deps =
Static_deps.action_deps static_deps |> Deps.paths
in
Path.Set.fold (Path.Set.union action_deps dyn_deps)
~init:acc ~f:loop
(* We know that at this point of execution, all the relevant
ivars have been filled so the following calsl to
[X.peek_exn] cannot raise. *)
let static_deps = Fiber.Once.peek_exn ir.static_deps in
let rule_deps = Static_deps.rule_deps static_deps in
let _, deps = Rule_fn.peek_exn (Fdecl.get t.build_rule_def) ir in
let dyn_deps = Deps.path_diff deps rule_deps in
let action_deps =
Static_deps.action_deps static_deps |> Deps.paths
in
Path.Set.fold (Path.Set.union action_deps dyn_deps)
~init:acc ~f:loop
end
in
let open Build.O in
Build.paths_for_rule files >>^ fun () ->
(* We know that at this point of execution, all the relevant ivars
have been filled *)
Path.Set.fold files ~init:Package.Name.Set.empty
~f:(fun f acc -> loop_deps f acc)
Path.Set.fold files ~init:Package.Name.Set.empty ~f:loop_deps

(* +-----------------------------------------------------------------+
| Adding rules to the system |
Expand Down
2 changes: 2 additions & 0 deletions src/fiber/fiber.ml
Original file line number Diff line number Diff line change
Expand Up @@ -398,6 +398,8 @@ module Once = struct
match t.state with
| Running fut -> Future.peek fut
| _ -> None

let peek_exn t = Option.value_exn (peek t)
end

module Mutex = struct
Expand Down
1 change: 1 addition & 0 deletions src/fiber/fiber.mli
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,7 @@ module Once : sig
(** [peek t] returns [Some v] if [get t] has already been called and
has yielded a value [v]. *)
val peek : 'a t -> 'a option
val peek_exn : 'a t -> 'a
end with type 'a fiber := 'a t

(** {1 Local storage} *)
Expand Down
2 changes: 2 additions & 0 deletions src/memo/memo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -324,6 +324,8 @@ module Make(Input : Data) : S with type input := Input.t = struct
else
None

let peek_exn t inp = Option.value_exn (peek t inp)

module Stack_frame = struct
let input (Dep_node.T dep_node) : Input.t option =
match dep_node.spec.witness with
Expand Down
1 change: 1 addition & 0 deletions src/memo/memo_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ module type S = sig

(** Check whether we already have a value for the given call *)
val peek : 'a t -> input -> 'a option
val peek_exn : 'a t -> input -> 'a

(** After running a memoization function with a given name and
input, it is possibly to query which dependencies that function
Expand Down
12 changes: 6 additions & 6 deletions test/unit-tests/dag.mlt
Original file line number Diff line number Diff line change
Expand Up @@ -91,16 +91,16 @@ val dag_pp_mynode : node Fmt.t = <fun>
- : node =
(1: k=1, i=-6) (root) [(3: k=1, i=-3) (child 1 2) [(4: k=2, i=-9) (child 2 1) [
(5: k=2, i=-8) (child 3 1) [
]; ]; ];
(2: k=1, i=-2) (child 1 1) []; ]
]]];
(2: k=1, i=-2) (child 1 1) []]
val node41 : node = (6: k=1, i=-10) (child 4 1) []
- : unit = ()
- : node =
(1: k=1, i=-6) (root) [(3: k=1, i=-3) (child 1 2) [(4: k=2, i=-13) (child 2 1) [
(5: k=2, i=-12) (child 3 1) [
(6: k=2, i=-11) (child 4 1) [
]; ]; ]; ];
(2: k=1, i=-2) (child 1 1) []; ]
]]]];
(2: k=1, i=-2) (child 1 1) []]
- : int = 2
- : string list option =
Some
Expand All @@ -109,6 +109,6 @@ Some
(1: k=3, i=-6) (root) [(3: k=3, i=-3) (child 1 2) [(4: k=3, i=-13) (child 2 1) [
(5: k=3, i=-12) (child 3 1) [
(6: k=2, i=-11) (child 4 1) [
]; ]; ]; ];
(2: k=1, i=-2) (child 1 1) []; ]
]]]];
(2: k=1, i=-2) (child 1 1) []]
|}]
2 changes: 2 additions & 0 deletions test/unit-tests/memoize.mlt
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module String_fn :
(string -> 'a Fiber.t) -> 'a t
val exec : 'a t -> string -> 'a Fiber.t
val peek : 'a t -> string -> 'a option
val peek_exn : 'a t -> string -> 'a
val get_deps : 'a t -> string -> (string * Sexp.t) list option
module Stack_frame :
sig
Expand All @@ -35,6 +36,7 @@ module Int_fn :
(int -> 'a Fiber.t) -> 'a t
val exec : 'a t -> int -> 'a Fiber.t
val peek : 'a t -> int -> 'a option
val peek_exn : 'a t -> int -> 'a
val get_deps : 'a t -> int -> (string * Sexp.t) list option
module Stack_frame :
sig
Expand Down

0 comments on commit 27bbbd9

Please sign in to comment.