Skip to content

Commit

Permalink
refactor: remove action runners from public dune
Browse files Browse the repository at this point in the history
Action runners in this dune are a rather old version that it is very
much out of date with the state of the actual feature and has many bugs
and limitations that need a lot of upstreaming to fix. In its current
state, it does not provide any value to users of public dune.

If we ever want to upstream this feature, it will be easier to just do
it from scratch anyway instead of resolving the conflicts against some
old version. This is due to the fact that the action runner API with the
engine is rather small and well defined.

Once we introduce a better abstraction for action execution (as we are
indeed planning), it will be probably be even simpler to upstream action
runners.

All in all, we gain nothing on either team by keeping this dead weight
around.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

<!-- ps-id: b913f829-def9-4d41-90d6-07da8060063b -->
  • Loading branch information
rgrinberg committed Aug 3, 2024
1 parent 42ed194 commit 1154bcd
Show file tree
Hide file tree
Showing 12 changed files with 14 additions and 539 deletions.
24 changes: 1 addition & 23 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -552,14 +552,6 @@ let cache_debug_flags_term : Cache_debug_flags.t Term.t =
value initial
;;

module Action_runner = struct
type t =
| No
| Yes of
(Dune_lang.Dep_conf.t Dune_rpc_impl.Server.t
-> (Dune_engine.Action_exec.input -> Dune_engine.Action_runner.t option) Staged.t)
end

module Builder = struct
type t =
{ debug_dep_path : bool
Expand Down Expand Up @@ -601,14 +593,12 @@ module Builder = struct
; stats_trace_extended : bool
; allow_builds : bool
; default_root_is_cwd : bool
; action_runner : Action_runner.t
; log_file : Dune_util.Log.File.t
}

let set_root t root = { t with root = Some root }
let forbid_builds t = { t with allow_builds = false; no_print_directory = true }
let set_default_root_is_cwd t x = { t with default_root_is_cwd = x }
let set_action_runner t x = { t with action_runner = x }
let set_log_file t x = { t with log_file = x }
let disable_log_file t = { t with log_file = No_log_file }
let set_promote t v = { t with promote = Some v }
Expand Down Expand Up @@ -1028,7 +1018,6 @@ module Builder = struct
; stats_trace_extended
; allow_builds = true
; default_root_is_cwd = false
; action_runner = No
; log_file = Default
}
;;
Expand Down Expand Up @@ -1159,16 +1148,14 @@ let build (builder : Builder.t) =
| Yes Passive -> Some 1.0
| _ -> None
in
let action_runner = Dune_engine.Action_runner.Rpc_server.create () in
Dune_rpc_impl.Server.create
~lock_timeout
~registry
~root:root.dir
~handle:Dune_rules_rpc.register
~watch_mode_config:builder.watch
~parse_build:Dune_rules_rpc.parse_build
stats
action_runner))
stats))
else `Forbid_builds
in
if builder.print_metrics then Dune_metrics.enable ();
Expand Down Expand Up @@ -1225,16 +1212,7 @@ let init (builder : Builder.t) =
"Shared cache location: %s"
(Path.to_string Dune_cache_storage.Layout.root_dir)
];
let action_runner =
match builder.action_runner with
| No -> None
| Yes f ->
(match rpc c with
| `Forbid_builds -> Code_error.raise "action runners require building" []
| `Allow server -> Some (Staged.unstage @@ f server))
in
Dune_rules.Main.init
?action_runner
~stats:c.stats
~sandboxing_preference:config.sandboxing_preference
~cache_config
Expand Down
9 changes: 0 additions & 9 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,22 +24,13 @@ val watch : t -> Dune_rpc_impl.Watch_mode_config.t
val file_watcher : t -> Dune_engine.Scheduler.Run.file_watcher
val prefix_target : t -> string -> string

module Action_runner : sig
type t =
| No
| Yes of
(Dune_lang.Dep_conf.t Dune_rpc_impl.Server.t
-> (Dune_engine.Action_exec.input -> Dune_engine.Action_runner.t option) Staged.t)
end

(** [Builder] describes how to initialize Dune. *)
module Builder : sig
type t

val set_root : t -> string -> t
val forbid_builds : t -> t
val set_default_root_is_cwd : t -> bool -> t
val set_action_runner : t -> Action_runner.t -> t
val set_log_file : t -> Dune_util.Log.File.t -> t
val disable_log_file : t -> t
val set_promote : t -> Dune_engine.Clflags.Promote.t -> t
Expand Down
Loading

0 comments on commit 1154bcd

Please sign in to comment.