Skip to content

Commit

Permalink
Merge pull request #10915 from gridbugs/dev-tool-ocamllsp
Browse files Browse the repository at this point in the history
Add ocamllsp dev tool
  • Loading branch information
gridbugs committed Sep 23, 2024
2 parents 12462ed + 32fc569 commit dedfb76
Show file tree
Hide file tree
Showing 17 changed files with 271 additions and 1 deletion.
1 change: 1 addition & 0 deletions bin/lock_dev_tool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -208,3 +208,4 @@ let lock_ocamlformat () =
;;

let lock_odoc () = lock_dev_tool Odoc None
let lock_ocamllsp () = lock_dev_tool Ocamllsp None
1 change: 1 addition & 0 deletions bin/lock_dev_tool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,4 @@ open! Import
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
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
; Tools.group
]
in
terms @ groups
Expand Down
62 changes: 62 additions & 0 deletions bin/tools/ocamllsp.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,62 @@
open! Import
module Pkg_dev_tool = Dune_rules.Pkg_dev_tool

let ocamllsp_exe_path = Path.build @@ Pkg_dev_tool.exe_path Ocamllsp
let ocamllsp_exe_name = Pkg_dev_tool.exe_name Ocamllsp

(* Replace the current dune process with ocamllsp. *)
let run_ocamllsp common ~args =
let exe_path_string = Path.to_string ocamllsp_exe_path in
Console.print_user_message
(Dune_rules.Pkg_build_progress.format_user_message
~verb:"Running"
~object_:
(User_message.command (String.concat ~sep:" " (ocamllsp_exe_name :: args))));
Console.finish ();
restore_cwd_and_execve common exe_path_string (exe_path_string :: args) Env.initial
;;

let build_ocamllsp common =
let open Fiber.O in
let+ result =
Build_cmd.run_build_system ~common ~request:(fun _build_system ->
Action_builder.path ocamllsp_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
;;

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 ~args)
;;

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
4 changes: 4 additions & 0 deletions bin/tools/ocamllsp.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
open! Import

(** Command to run ocamllsp, installing it if necessary *)
val command : unit Cmd.t
11 changes: 11 additions & 0 deletions bin/tools/tools.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
open! Import

module Exec = struct
let doc = "Command group for running wrapped tools."
let info = Cmd.info ~doc "exec"
let group = Cmd.group info [ Ocamllsp.command ]
end

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

val group : unit Cmd.t
9 changes: 8 additions & 1 deletion src/dune_pkg/dev_tool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,40 +3,47 @@ open! Import
type t =
| Ocamlformat
| Odoc
| Ocamllsp

let all = [ Ocamlformat; Odoc ]
let all = [ Ocamlformat; Odoc; Ocamllsp ]

let equal a b =
match a, b with
| Ocamlformat, Ocamlformat -> true
| Odoc, Odoc -> true
| Ocamllsp, Ocamllsp -> true
| _ -> false
;;

let package_name = function
| Ocamlformat -> Package_name.of_string "ocamlformat"
| Odoc -> Package_name.of_string "odoc"
| Ocamllsp -> Package_name.of_string "ocaml-lsp-server"
;;

let of_package_name package_name =
match Package_name.to_string package_name with
| "ocamlformat" -> Ocamlformat
| "odoc" -> Odoc
| "ocaml-lsp-server" -> Ocamllsp
| other -> User_error.raise [ Pp.textf "No such dev tool: %s" other ]
;;

let exe_name = function
| Ocamlformat -> "ocamlformat"
| Odoc -> "odoc"
| Ocamllsp -> "ocamllsp"
;;

let exe_path_components_within_package t =
match t with
| Ocamlformat -> [ "bin"; exe_name t ]
| Odoc -> [ "bin"; exe_name t ]
| Ocamllsp -> [ "bin"; exe_name t ]
;;

let needs_to_build_with_same_compiler_as_project = function
| Ocamlformat -> false
| Odoc -> true
| Ocamllsp -> true
;;
1 change: 1 addition & 0 deletions src/dune_pkg/dev_tool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ open! Import
type t =
| Ocamlformat
| Odoc
| Ocamllsp

val all : t list
val equal : t -> t -> bool
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,8 @@ module Executables = Executables
module Tests = Tests
module Stanzas = Stanzas
module Lock_dir = Lock_dir
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,32 @@
Test that the "dune tools exec ocamllsp" command causes ocamllsp to be
locked, built and run when the command is run from a dune project with
a lockdir containing an "ocaml" lockfile.

$ . ../helpers.sh
$ . ./helpers.sh

$ mkrepo
$ make_mock_ocamllsp_package
$ mkpkg ocaml 5.2.0

$ setup_ocamllsp_workspace

$ cat > dune-project <<EOF
> (lang dune 3.16)
>
> (package
> (name foo)
> (allow_empty))
> EOF

$ make_lockdir
$ cat > dune.lock/ocaml.pkg <<EOF
> (version 5.2.0)
> EOF

$ dune tools exec ocamllsp
Solution for dev-tools.locks/ocaml-lsp-server:
- ocaml.5.2.0
- ocaml-lsp-server.0.0.1
Running 'ocamllsp'
hello from fake ocamllsp
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Exercise the behaviour of "dune tools exec ocamllsp" when run in a
dune project with no lockdir.

$ cat > dune-project <<EOF
> (lang dune 3.16)
>
> (package
> (name foo)
> (allow_empty))
> EOF

$ dune tools exec ocamllsp
Error: Unable to load the lockdir for the default build context.
Hint: Try running 'dune pkg lock'
[1]
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
Exercise the behaviour of "dune tools exec ocamllsp" when the lockdir
doesn't contain a lockfile for the "ocaml" package.

$ . ../helpers.sh

$ cat > dune-project <<EOF
> (lang dune 3.16)
>
> (package
> (name foo)
> (allow_empty))
> EOF

$ make_lockdir

$ dune tools exec ocamllsp
Error: The lockdir doesn't contain a lockfile for the package "ocaml".
Hint: Add a dependency on "ocaml" to one of the packages in dune-project and
then run 'dune pkg lock'
[1]
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
Exercise the behaviour of "dune tools exec ocamllsp" when run outside
of a dune project.


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 tools exec ocamllsp
Error: Unable to run ocamllsp as a dev-tool because you don't appear to be
inside a dune project.
[1]
Original file line number Diff line number Diff line change
@@ -0,0 +1,63 @@
Test that if the version of the "ocaml" package in the project's
lockdir changes then the ocamllsp dev tool is re-locked to be built
with the version of the ocaml compiler now in the project's
lockdir. This is necessary because ocamllsp must be compiled with the
same version of the ocaml compiler as the code that it's analyzing.

$ . ../helpers.sh
$ . ./helpers.sh

$ mkrepo
$ make_mock_ocamllsp_package
$ mkpkg ocaml 5.2.0
$ mkpkg ocaml 5.1.0

$ setup_ocamllsp_workspace

$ cat > dune-project <<EOF
> (lang dune 3.16)
>
> (package
> (name foo)
> (allow_empty))
> EOF

$ make_lockdir
$ cat > dune.lock/ocaml.pkg <<EOF
> (version 5.2.0)
> EOF

Initially ocamllsp will be depend on ocaml.5.2.0 to match the project.
$ dune tools exec ocamllsp
Solution for dev-tools.locks/ocaml-lsp-server:
- ocaml.5.2.0
- ocaml-lsp-server.0.0.1
Running 'ocamllsp'
hello from fake ocamllsp
$ cat dev-tools.locks/ocaml-lsp-server/ocaml.pkg
(version 5.2.0)

We can re-run "dune tools exec ocamllsp" without relocking or rebuilding.
$ dune tools exec ocamllsp
Running 'ocamllsp'
hello from fake ocamllsp

Change the version of ocaml that the project depends on.
$ cat > dune.lock/ocaml.pkg <<EOF
> (version 5.1.0)
> EOF

Running "dune tools exec ocamllsp" causes ocamllsp to be relocked and rebuilt
before running. Ocamllsp now depends on ocaml.5.1.0.
$ dune tools exec ocamllsp
The version of the compiler package ("ocaml") in this project's lockdir has
changed to 5.1.0 (formerly the compiler version was 5.2.0). The dev-tool
"ocaml-lsp-server" will be re-locked and rebuilt with this version of the
compiler.
Solution for dev-tools.locks/ocaml-lsp-server:
- ocaml.5.1.0
- ocaml-lsp-server.0.0.1
Running 'ocamllsp'
hello from fake ocamllsp
$ cat dev-tools.locks/ocaml-lsp-server/ocaml.pkg
(version 5.1.0)
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/pkg/ocamllsp/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(cram
(deps helpers.sh)
(applies_to :whole_subtree))
27 changes: 27 additions & 0 deletions test/blackbox-tests/test-cases/pkg/ocamllsp/helpers.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
# Create a dune-workspace file with mock repos set up for the main
# project and the ocamllsp lockdir.
setup_ocamllsp_workspace() {
cat > dune-workspace <<EOF
(lang dune 3.16)
(lock_dir
(path "dev-tools.locks/ocaml-lsp-server")
(repositories mock))
(lock_dir
(repositories mock))
(repository
(name mock)
(source "file://$(pwd)/mock-opam-repository"))
EOF
}

# Create a fake ocaml-lsp-server package containing an executable that
# just prints a message.
make_mock_ocamllsp_package() {
mkpkg ocaml-lsp-server <<EOF
install: [
[ "sh" "-c" "echo '#!/bin/sh' > %{bin}%/ocamllsp" ]
[ "sh" "-c" "echo 'echo hello from fake ocamllsp' >> %{bin}%/ocamllsp" ]
[ "sh" "-c" "chmod a+x %{bin}%/ocamllsp" ]
]
EOF
}

0 comments on commit dedfb76

Please sign in to comment.