Skip to content

Commit

Permalink
Add dune tools env to configure PATH
Browse files Browse the repository at this point in the history
Signed-off-by: ArthurW <[email protected]>
  • Loading branch information
art-w committed Jan 29, 2025
1 parent e43cb9d commit fe815fe
Show file tree
Hide file tree
Showing 9 changed files with 120 additions and 5 deletions.
3 changes: 2 additions & 1 deletion bin/tools/ocamllsp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,8 @@ let run_ocamllsp common ~args =
~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 env = Shell_env.add_path Env.initial in
restore_cwd_and_execve common exe_path_string (exe_path_string :: args) env
;;

let build_ocamllsp common =
Expand Down
41 changes: 41 additions & 0 deletions bin/tools/shell_env.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 all_tools = List.map ~f:Pkg_dev_tool.exe_name [ Ocamlformat; Ocamllsp ]
let bin_path () = Path.build (Pkg_dev_tool.bin_path ())

let shell_script = {|#!/bin/sh
dune tools exec $(basename $0) -- "$@"
|}

let setup path =
if not (Path.exists path) then Path.mkdir_p path;
List.iter all_tools ~f:(fun tool ->
let tool_path = Path.relative path tool in
if not (Path.exists tool_path) then Io.write_file ~perm:0o777 tool_path shell_script)
;;

let add_path env =
let dir = bin_path () in
setup dir;
Env_path.cons env ~dir
;;

let term =
let+ builder = Common.Builder.term in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
let env = add_path Env.initial in
Format.printf
"%s=%s@."
Env_path.var
(Option.value ~default:"" (Env.get env Env_path.var));
Fiber.return ())
;;

let info =
let doc = "Configure shell environment" in
Cmd.info "env" ~doc
;;

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

val add_path : Env.t -> Env.t
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 @@ -14,4 +14,4 @@ end

let doc = "Command group for wrapped tools."
let info = Cmd.info ~doc "tools"
let group = Cmd.group info [ Exec.group; Which.group ]
let group = Cmd.group info [ Exec.group; Which.group; Shell_env.command ]
4 changes: 3 additions & 1 deletion otherlibs/stdune/src/bin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,11 @@ let encode_strings paths = String.concat ~sep:(String.make 1 path_sep) paths

let cons_path ?(path_sep = path_sep) p ~_PATH =
let p = Path.to_absolute_filename p in
let p_sep = p ^ String.make 1 path_sep in
match _PATH with
| None -> p
| Some s -> Printf.sprintf "%s%c%s" p path_sep s
| Some s when String.is_prefix s ~prefix:p_sep -> s
| Some s -> p_sep ^ s
;;

let exe = if Sys.win32 then ".exe" else ""
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/pkg_dev_tool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,3 +28,5 @@ let exe_path t =
(package_install_path t)
("target" :: exe_path_components_within_package t)
;;

let bin_path () = Path.Build.relative (Lazy.force install_path_base) "bin"
3 changes: 3 additions & 0 deletions src/dune_rules/pkg_dev_tool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,3 +14,6 @@ val package_install_path : t -> Path.Build.t

(** The path to the executable for running the given dev tool *)
val exe_path : t -> Path.Build.t

(** The path to the shell executables for running a dev tool with dune *)
val bin_path : unit -> Path.Build.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
Check that `dune tools exec ocamllsp` can call the dune tools version of ocamlformat:

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

$ mkrepo
$ mkpkg ocaml 5.2.0
$ 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" "echo ocamlformat >> %{bin}%/ocamllsp" ]
> [ "sh" "-c" "chmod a+x %{bin}%/ocamllsp" ]
> ]
> EOF
$ mkpkg ocamlformat <<EOF
> install: [
> [ "sh" "-c" "echo '#!/bin/sh' > %{bin}%/ocamlformat" ]
> [ "sh" "-c" "echo 'echo hello from fake ocamlformat' >> %{bin}%/ocamlformat" ]
> [ "sh" "-c" "chmod a+x %{bin}%/ocamlformat" ]
> ]
> EOF

$ setup_ocamllsp_workspace

$ cat > dune-project <<EOF
> (lang dune 3.16)
> 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
Solution for dev-tools.locks/ocamlformat:
- ocamlformat.0.0.1
Running 'ocamlformat'
hello from fake ocamlformat

Users can also configure their PATH variable environment:

$ eval $(dune tools env)
$ echo $PATH | sed 's/:.*//'
$TESTCASE_ROOT/_build/_private/default/.dev-tool/bin
$ which ocamllsp
$TESTCASE_ROOT/_build/_private/default/.dev-tool/bin/ocamllsp
$ which ocamlformat
$TESTCASE_ROOT/_build/_private/default/.dev-tool/bin/ocamlformat
$ ocamllsp
Running 'ocamllsp'
hello from fake ocamllsp
Running 'ocamlformat'
hello from fake ocamlformat
7 changes: 5 additions & 2 deletions test/blackbox-tests/test-cases/pkg/ocamllsp/helpers.sh
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,11 @@ setup_ocamllsp_workspace() {
(lock_dir
(path "dev-tools.locks/ocaml-lsp-server")
(repositories mock))
(lock_dir
(repositories mock))
(lock_dir
(path "dev-tools.locks/ocamlformat")
(repositories mock))
(lock_dir
(repositories mock))
(repository
(name mock)
(url "file://$(pwd)/mock-opam-repository"))
Expand Down

0 comments on commit fe815fe

Please sign in to comment.