Skip to content

Commit

Permalink
pkg: Install all the dev-tools that are available
Browse files Browse the repository at this point in the history
Signed-off-by: Alpha DIALLO <[email protected]>
  • Loading branch information
moyodiallo committed Oct 20, 2024
1 parent dce464e commit 8993d66
Show file tree
Hide file tree
Showing 5 changed files with 54 additions and 1 deletion.
7 changes: 7 additions & 0 deletions bin/lock_dev_tool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -209,3 +209,10 @@ let lock_ocamlformat () =

let lock_odoc () = lock_dev_tool Odoc None
let lock_ocamllsp () = lock_dev_tool Ocamllsp None

let lock_tools (tools : Dune_pkg.Dev_tool.t list) =
List.map tools ~f:(function
| Dune_pkg.Dev_tool.Odoc -> lock_odoc ()
| Ocamllsp -> lock_ocamllsp ()
| Ocamlformat -> lock_ocamlformat ())
;;
1 change: 1 addition & 0 deletions bin/lock_dev_tool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,3 +4,4 @@ val is_enabled : bool Lazy.t
val lock_ocamlformat : unit -> unit Memo.t
val lock_odoc : unit -> unit Memo.t
val lock_ocamllsp : unit -> unit Memo.t
val lock_tools : Dune_pkg.Dev_tool.t list -> unit Memo.t list
41 changes: 41 additions & 0 deletions bin/tools/install_tools.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
open! Import
module Pkg_dev_tool = Dune_rules.Pkg_dev_tool

let build_dev_tools dev_tools common =
let open Fiber.O in
let+ result =
let dev_tools_path =
List.map dev_tools ~f:(fun path -> Pkg_dev_tool.exe_path path |> Path.build)
in
Build_cmd.run_build_system ~common ~request:(fun _build_system ->
List.map dev_tools_path ~f:Action_builder.path |> Action_builder.all_unit)
in
match result with
| Error `Already_reported -> raise Dune_util.Report_error.Already_reported
| Ok () -> ()
;;

let term =
let+ builder = Common.Builder.term in
let common, config = Common.init builder in
let all_dev_tool = Dune_pkg.Dev_tool.all in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
if Lazy.force Lock_dev_tool.is_enabled
then
let* () =
Dune_pkg.Dev_tool.all
|> Lock_dev_tool.lock_tools
|> List.map ~f:Memo.run
|> Fiber.all_concurrently_unit
in
build_dev_tools all_dev_tool common
else Fiber.return ())
;;

let info =
let doc = "Install all the dev-tools that are available" in
Cmd.info "install" ~doc
;;

let command = Cmd.v info term
4 changes: 4 additions & 0 deletions bin/tools/install_tools.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
open! Import

(** Command install all the available dev-tools*)
val command : unit Cmd.t
2 changes: 1 addition & 1 deletion bin/tools/tools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ end

let doc = "Command group for wrapped tools."
let info = Cmd.info ~doc "tools"
let group = Cmd.group info [ Exec.group ]
let group = Cmd.group info [ Exec.group; Install_tools.command ]

0 comments on commit 8993d66

Please sign in to comment.