File tree Expand file tree Collapse file tree 4 files changed +54
-4
lines changed
test/blackbox-tests/test-cases/pkg/ocamllsp Expand file tree Collapse file tree 4 files changed +54
-4
lines changed Original file line number Diff line number Diff line change 3333
3434let doc = " Command group for wrapped tools."
3535let info = Cmd. info ~doc " tools"
36- let group = Cmd. group info [ Exec. group; Install. group; Which. group ]
36+
37+ let group =
38+ Cmd. group info [ Exec. group; Install. group; Which. group; Tools_common. env_command ]
39+ ;;
Original file line number Diff line number Diff line change 11open ! Import
22module Pkg_dev_tool = Dune_rules. Pkg_dev_tool
33
4+ let dev_tool_bin_dirs =
5+ List. map Pkg_dev_tool. all ~f: (fun tool ->
6+ Pkg_dev_tool. exe_path tool |> Path.Build. parent_exn |> Path. build)
7+ ;;
8+
49let add_dev_tools_to_path env =
5- List. fold_left Pkg_dev_tool. all ~init: env ~f: (fun acc tool ->
6- let dir = Pkg_dev_tool. exe_path tool |> Path.Build. parent_exn |> Path. build in
7- Env_path. cons acc ~dir )
10+ List. fold_left dev_tool_bin_dirs ~init: env ~f: (fun acc dir -> Env_path. cons acc ~dir )
811;;
912
1013let dev_tool_exe_path dev_tool = Path. build @@ Pkg_dev_tool. exe_path dev_tool
@@ -134,3 +137,40 @@ let exec_command dev_tool =
134137 in
135138 Cmd. v info term
136139;;
140+
141+ let env_command =
142+ let term =
143+ let + builder = Common.Builder. term
144+ and + fish =
145+ Arg. (
146+ value
147+ & flag
148+ & info [ " fish" ] ~doc: " Print command for the fish shell raher than posix shells" )
149+ in
150+ let _ = Common. init builder in
151+ if fish
152+ then (
153+ let space_separated_dev_tool_paths =
154+ List. map dev_tool_bin_dirs ~f: Path. to_string_maybe_quoted
155+ |> String. concat ~sep: " "
156+ in
157+ print_endline (sprintf " fish_add_path --prepend %s" space_separated_dev_tool_paths))
158+ else (
159+ let initial_path = Env. get Env. initial Env_path. var in
160+ let new_path =
161+ List. fold_left dev_tool_bin_dirs ~init: initial_path ~f: (fun acc bin_dir ->
162+ Some (Bin. cons_path bin_dir ~_PATH:acc))
163+ in
164+ match new_path with
165+ | None -> ()
166+ | Some new_path -> print_endline (sprintf " export %s=%s" Env_path. var new_path))
167+ in
168+ let info =
169+ let doc =
170+ " Print a command which can be eval'd to enter an environment where all dev tools \
171+ are runnable as commands."
172+ in
173+ Cmd. info " env" ~doc
174+ in
175+ Cmd. v info term
176+ ;;
Original file line number Diff line number Diff line change @@ -13,3 +13,4 @@ val lock_build_and_run_dev_tool
1313val which_command : Dune_pkg.Dev_tool .t -> unit Cmd .t
1414val install_command : Dune_pkg.Dev_tool .t -> unit Cmd .t
1515val exec_command : Dune_pkg.Dev_tool .t -> unit Cmd .t
16+ val env_command : unit Cmd .t
Original file line number Diff line number Diff line change @@ -30,3 +30,9 @@ a lockdir containing an "ocaml" lockfile.
3030 - ocaml-lsp-server. 0. 0. 1
3131 Running ' ocamllsp'
3232 hello from fake ocamllsp
33+
34+ Make sure that after evaling the output of ' dune tools env' , the first ocamllsp
35+ executable in PATH is the one installed by dune as a dev tool.
36+ $ DUNE_CONFIG__LOCK_DEV_TOOL= enabled eval $ (dune tools env)
37+ $ which ocamllsp
38+ $ TESTCASE_ROOT / _build/ _private/ default /. dev-tool/ ocaml-lsp-server/ ocaml-lsp-server/ target/ bin/ ocamllsp
You can’t perform that action at this time.
0 commit comments