Skip to content

Commit a1322c4

Browse files
rgrinbergLeonidas-from-XIV
authored andcommitted
refactor: get rid of dummy ocamlobjinfo targets (#12533)
Now they're invisible to the user. Signed-off-by: Rudi Grinberg <[email protected]>
1 parent fb1c309 commit a1322c4

File tree

5 files changed

+23
-15
lines changed

5 files changed

+23
-15
lines changed

src/dune_rules/command.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -137,13 +137,13 @@ let run ~dir ?sandbox ?stdout_to prog args =
137137
run_dyn_prog ~dir ?sandbox ?stdout_to (Action_builder.return prog) args
138138
;;
139139

140-
let run' ~dir prog args =
140+
let run' ?sandbox ~dir prog args =
141141
let open Action_builder.O in
142142
let+ () = dep_prog prog
143143
and+ args = expand_no_targets ~dir (S args) in
144144
Action.Run (prog, Appendable_list.to_immutable_array args)
145145
|> Action.chdir dir
146-
|> Action.Full.make
146+
|> Action.Full.make ?sandbox
147147
;;
148148

149149
let quote_args =

src/dune_rules/command.mli

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,8 @@ val run
9090

9191
(** Same as [run], but for actions that don't produce targets *)
9292
val run'
93-
: dir:Path.t
93+
: ?sandbox:Sandbox_config.t
94+
-> dir:Path.t
9495
-> Action.Prog.t
9596
-> Args.without_targets Args.t list
9697
-> Action.Full.t Action_builder.t

src/dune_rules/dep_rules.ml

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ let ooi_deps
2020
(sourced_module : Modules.Sourced_module.t)
2121
=
2222
let m = Modules.Sourced_module.to_module sourced_module in
23-
let* write, read =
23+
let* read =
2424
let unit =
2525
let cm_kind =
2626
match ml_kind with
@@ -50,8 +50,7 @@ let ooi_deps
5050
then None
5151
else Module_name.Unique.Map.find vlib_obj_map dep))
5252
in
53-
let+ () = add_rule write
54-
and+ () =
53+
let+ () =
5554
add_rule
5655
(let target =
5756
Obj_dir.Module.dep obj_dir (Transitive (m, ml_kind)) |> Option.value_exn

src/dune_rules/ocamlobjinfo.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ val rules
1111
-> dir:Path.Build.t
1212
-> sandbox:Sandbox_config.t option
1313
-> unit:Path.t
14-
-> Action.Full.t Action_builder.With_targets.t * t Action_builder.t
14+
-> t Action_builder.t
1515

1616
(** For testing only *)
1717
val parse : string -> t

src/dune_rules/ocamlobjinfo.mll

Lines changed: 16 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -39,10 +39,6 @@ and impls acc = parse
3939
let parse s = ocamlobjinfo empty (Lexing.from_string s)
4040

4141
let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
42-
let output =
43-
Path.Build.relative dir (Path.basename unit)
44-
|> Path.Build.extend_basename ~suffix:".ooi-deps"
45-
in
4642
let no_approx =
4743
if Ocaml.Version.ooi_supports_no_approx ocaml.version then
4844
[Command.Args.A "-no-approx"]
@@ -55,14 +51,26 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
5551
else
5652
[]
5753
in
58-
( Command.run ?sandbox
54+
let observing_facts =
55+
Dep.Facts.singleton (Dep.file unit) (Dep.Fact.nothing)
56+
in
57+
let open Action_builder.O in
58+
let* action =
59+
Command.run' ?sandbox
5960
~dir:(Path.build dir) ocaml.ocamlobjinfo
6061
(List.concat
6162
[ no_approx
6263
; no_code
6364
; [ Dep unit ]
6465
])
65-
~stdout_to:output
66-
, Action_builder.map ~f:parse (Action_builder.contents (Path.build output))
67-
)
66+
in
67+
(Dune_engine.Build_system.execute_action_stdout
68+
~observing_facts
69+
{ Rule.Anonymous_action.action
70+
; loc = Loc.none
71+
; dir
72+
; alias = None
73+
}
74+
|> Action_builder.of_memo)
75+
>>| parse
6876
}

0 commit comments

Comments
 (0)