Skip to content

Commit

Permalink
Add command wrapping ocamlformat
Browse files Browse the repository at this point in the history
Adds a command `dune tool ocamlformat` which downloads and builds
ocamlformat as a dev tool before running it, passing all positional
arguments to the ocamlformat executable. This is intended to be run by
text editors.

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs committed Sep 17, 2024
1 parent 4f86203 commit 192611d
Show file tree
Hide file tree
Showing 8 changed files with 185 additions and 0 deletions.
1 change: 1 addition & 0 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ let all : _ Cmdliner.Cmd.t list =
; Promotion.group
; Pkg.group
; Pkg.Alias.group
; Tool.group
]
in
terms @ groups
Expand Down
133 changes: 133 additions & 0 deletions bin/tool/ocamlformat.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,133 @@
open! Import
module Pkg_dev_tool = Dune_rules.Pkg_dev_tool

let exe_path = Path.build @@ Pkg_dev_tool.exe_path Ocamlformat
let exe_name = Pkg_dev_tool.exe_name Ocamlformat

let run_dev_tool common ~args =
let exe_path_string = Path.to_string exe_path in
Console.print_user_message
(Dune_rules.Pkg_build_progress.format_user_message
~verb:"Running"
~object_:(User_message.command (String.concat ~sep:" " (exe_name :: args))));
Console.finish ();
restore_cwd_and_execve common exe_path_string (exe_path_string :: args) Env.initial
;;

let dev_tool_exe_exists () = Path.exists exe_path

let build_dev_tool common =
match dev_tool_exe_exists () with
| true ->
(* Avoid running the build system if the executable already exists
to reduce unnecessary latency in the common case. *)
Fiber.return ()
| false ->
let open Fiber.O in
let+ result =
Build_cmd.run_build_system ~common ~request:(fun _build_system ->
Action_builder.path exe_path)
in
(match result with
| Error `Already_reported -> raise Dune_util.Report_error.Already_reported
| Ok () -> ())
;;

let is_in_dune_project builder =
Workspace_root.create
~default_is_cwd:(Common.Builder.default_root_is_cwd builder)
~specified_by_user:(Common.Builder.root builder)
|> Result.is_ok
;;

module Fallback = struct
let run_command prog args env =
let prog_string = Path.to_string prog in
let argv = prog_string :: args in
Console.print_user_message
(Dune_rules.Pkg_build_progress.format_user_message
~verb:"Running"
~object_:(User_message.command (String.concat ~sep:" " argv)));
Console.finish ();
Proc.restore_cwd_and_execve prog_string argv ~env
;;

let run_via_opam args env =
match Bin.which ~path:(Env_path.path env) "opam" with
| None -> Error ()
| Some opam_path ->
Console.print_user_message
(User_message.make
[ Pp.textf
"Not in a dune project but opam appears to be installed. Dune will \
attempt to run %s via opam."
exe_name
]);
run_command opam_path ([ "exec"; exe_name; "--" ] @ args) env
;;

let run_via_path args env =
match Bin.which ~path:(Env_path.path env) exe_name with
| None -> Error ()
| Some path ->
Console.print_user_message
(User_message.make
[ Pp.textf
"Not in a dune project but %s appears to be installed. Dune will attempt \
to run %s from your PATH."
exe_name
exe_name
]);
run_command path args env
;;

(* Attempt to launch ocamlformat from the current opam switch, and
failing that from the PATH. This is necessary so that editors
configured to run ocamlformat via dune can still be used to format
ocaml code outside of dune projects. *)
let run args env =
match run_via_opam args env with
| Ok () -> ()
| Error () ->
(match run_via_path args env with
| Ok () -> ()
| Error () ->
User_error.raise
[ Pp.textf
"Not in a dune project and %s doesn't appear to be installed."
exe_name
])
;;
end

let term =
let+ builder = Common.Builder.term
and+ args = Arg.(value & pos_all string [] (info [] ~docv:"ARGS")) in
match is_in_dune_project builder with
| false -> Fallback.run args Env.initial
| true ->
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamlformat () in
let+ () = build_dev_tool common in
run_dev_tool common ~args)
;;

let info =
let doc =
{|Wrapper for running ocamlformat intended to be run automatically
by a text editor. All positional arguments will be passed to the
ocamlformat executable (pass flags to ocamlformat after the '--'
argument, such as 'dune ocamlformat -- --help'). If this command
is run from inside a dune project, dune will download and build
the ocamlformat opam package and run the ocamlformat executable
from there rather. Otherwise, dune will attempt to run the
ocamlformat executable from your current opam switch. If opam is
not installed, dune will attempt to run ocamlformat from your
PATH.|}
in
Cmd.info "ocamlformat" ~doc
;;

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

val command : unit Cmd.t
5 changes: 5 additions & 0 deletions bin/tool/tool.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
open! Import

let doc = "Command group for running wrapped tools."
let info = Cmd.info ~doc "tool"
let group = Cmd.group info [ Ocamlformat.command ]
3 changes: 3 additions & 0 deletions bin/tool/tool.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
open Import

val group : unit Cmd.t
2 changes: 2 additions & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,8 @@ module Melange_stanzas = Melange_stanzas
module Executables = Executables
module Tests = Tests
module Stanzas = Stanzas
module Pkg_dev_tool = Pkg_dev_tool
module Pkg_build_progress = Pkg_build_progress

module Install_rules = struct
let install_file = Install_rules.install_file
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
Exercise running the ocamlformat wrapper command outside of a dune
project.

Make a fake ocamlformat executable and add it to PATH.
$ mkdir -p bin
$ cat > bin/ocamlformat << EOF
> #!/bin/sh
> echo "Hello, World!"
> EOF
$ chmod a+x bin/ocamlformat
$ export PATH=$PWD/bin:$PATH

This is necessary for dune to act as it normally would outside of a
dune workspace.
$ unset INSIDE_DUNE

Run the wrapper command from a temporary directory. With INSIDE_DUNE
unset dune would otherwise pick up the dune project itself as the
current workspace.
$ cd $(mktemp -d)
$ dune tool ocamlformat 2> /dev/null
Hello, World!
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
Exercise running the ocamlformat wrapper command.

$ . ./helpers.sh
$ mkrepo

$ make_fake_ocamlformat "0.26.2"
$ make_ocamlformat_opam_pkg "0.26.2"
$ make_project_with_dev_tool_lockdir

$ dune tool ocamlformat
Solution for dev-tools.locks/ocamlformat:
- ocamlformat.0.26.2
Downloading ocamlformat.0.26.2
Building ocamlformat.0.26.2
Running 'ocamlformat'
formatted with version 0.26.2

0 comments on commit 192611d

Please sign in to comment.