Skip to content

Commit

Permalink
Add a command to print the path of ocamllsp and ocamlformat executabl…
Browse files Browse the repository at this point in the history
…es (#11243)

Signed-off-by: Sudha Parimala <sudharg247@gmail.com>
  • Loading branch information
Sudha247 authored Dec 31, 2024
1 parent 8bf833a commit 56b10d8
Show file tree
Hide file tree
Showing 6 changed files with 118 additions and 48 deletions.
57 changes: 37 additions & 20 deletions bin/tools/ocamlformat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,25 +37,42 @@ let build_dev_tool common =
| Ok () -> ())
;;

let term =
let+ builder = Common.Builder.term
and+ args = Arg.(value & pos_all string [] (info [] ~docv:"ARGS")) in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamlformat () |> Memo.run in
let+ () = build_dev_tool common in
run_dev_tool (Common.root common) ~args)
;;
module Exec = struct
let term =
let+ builder = Common.Builder.term
and+ args = Arg.(value & pos_all string [] (info [] ~docv:"ARGS")) in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamlformat () |> Memo.run in
let+ () = build_dev_tool common in
run_dev_tool (Common.root 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').|}
in
Cmd.info "ocamlformat" ~doc
;;
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').|}
in
Cmd.info "ocamlformat" ~doc
;;

let command = Cmd.v info term
end

module Which = struct
let term =
let+ builder = Common.Builder.term in
let _ : Common.t * Dune_config_file.Dune_config.t = Common.init builder in
print_endline (Path.to_string exe_path)
;;

let info =
let doc = {|Prints the path to the ocamlformat binary.|} in
Cmd.info "ocamlformat" ~doc
;;

let command = Cmd.v info term
let command = Cmd.v info term
end
8 changes: 7 additions & 1 deletion bin/tools/ocamlformat.mli
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
open! Import

val command : unit Cmd.t
module Exec : sig
val command : unit Cmd.t
end

module Which : sig
val command : unit Cmd.t
end
65 changes: 41 additions & 24 deletions bin/tools/ocamllsp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,29 +34,46 @@ let is_in_dune_project builder =
|> Result.is_ok
;;

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 ->
User_error.raise
[ Pp.textf
"Unable to run %s as a dev-tool because you don't appear to be inside a dune \
project."
ocamllsp_exe_name
]
| true ->
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamllsp () |> Memo.run in
let+ () = build_ocamllsp common in
run_ocamllsp (Common.root common) ~args)
;;
module Exec = struct
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 ->
User_error.raise
[ Pp.textf
"Unable to run %s as a dev-tool because you don't appear to be inside a dune \
project."
ocamllsp_exe_name
]
| true ->
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamllsp () |> Memo.run in
let+ () = build_ocamllsp common in
run_ocamllsp (Common.root common) ~args)
;;

let info =
let doc = "Run ocamllsp, installing it as a dev tool if necessary." in
Cmd.info "ocamllsp" ~doc
;;
let info =
let doc = "Run ocamllsp, installing it as a dev tool if necessary." in
Cmd.info "ocamllsp" ~doc
;;

let command = Cmd.v info term
end

module Which = struct
let term =
let+ builder = Common.Builder.term in
let _ : Common.t * Dune_config_file.Dune_config.t = Common.init builder in
print_endline (Path.to_string ocamllsp_exe_path)
;;

let info =
let doc = "Prints the path to the ocamllsp binary." in
Cmd.info "ocamllsp" ~doc
;;

let command = Cmd.v info term
let command = Cmd.v info term
end
11 changes: 10 additions & 1 deletion bin/tools/ocamllsp.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,13 @@
open! Import

(** Command to run ocamllsp, installing it if necessary *)
val command : unit Cmd.t

module Exec : sig
val command : unit Cmd.t
end

(** Command to print ocamllsp's path if exists *)

module Which : sig
val command : unit Cmd.t
end
10 changes: 8 additions & 2 deletions bin/tools/tools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,15 @@ open! Import
module Exec = struct
let doc = "Command group for running wrapped tools."
let info = Cmd.info ~doc "exec"
let group = Cmd.group info [ Ocamlformat.command; Ocamllsp.command ]
let group = Cmd.group info [ Ocamlformat.Exec.command; Ocamllsp.Exec.command ]
end

module Which = struct
let doc = "Command group for printing the path to wrapped tools."
let info = Cmd.info ~doc "which"
let group = Cmd.group info [ Ocamlformat.Which.command; Ocamllsp.Which.command ]
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; Which.group ]
15 changes: 15 additions & 0 deletions test/blackbox-tests/test-cases/pkg/dev-tools-which.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Tests for the `dune tools which` command.

The ocamlformat case:
$ cat >dune-project <<EOF
> (lang dune 3.11)
> EOF
$ dune tools which ocamlformat
_build/_private/default/.dev-tool/ocamlformat/ocamlformat/target/bin/ocamlformat

The ocamllsp case:
$ cat >dune-project <<EOF
> (lang dune 3.11)
> EOF
$ dune tools which ocamllsp
_build/_private/default/.dev-tool/ocaml-lsp-server/ocaml-lsp-server/target/bin/ocamllsp

0 comments on commit 56b10d8

Please sign in to comment.