Skip to content

Commit

Permalink
refactor(merlin): dump config sub command
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

ps-id: 6a89ece2-5e85-4040-af98-f7e423facd87
  • Loading branch information
rgrinberg committed Nov 23, 2022
1 parent 557a001 commit 19be49d
Show file tree
Hide file tree
Showing 17 changed files with 62 additions and 48 deletions.
1 change: 1 addition & 0 deletions bin/ocaml_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,4 +9,5 @@ let group =
; Ocaml_merlin.Dump_dot_merlin.command
; Top.command
; Top.module_command
; Ocaml_merlin.group
]
51 changes: 31 additions & 20 deletions bin/ocaml_merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -173,6 +173,25 @@ end = struct
main ()
end

module Dump_config = struct
let info =
Cmd.info
~doc:
"Prints the entire content of the merlin configuration for the given \
folder in a user friendly form. This is for testing and debugging \
purposes only and should not be considered as a stable output."
"dump-config"

let term =
let+ common = Common.term
and+ dir = Arg.(value & pos 0 dir "" & info [] ~docv:"PATH") in
let common = Common.forbid_builds common in
let config = Common.init ~log_file:No_log_file common in
Scheduler.go ~common ~config (fun () -> Server.dump dir)

let command = Cmd.v info term
end

let doc = "Start a merlin configuration server"

let man =
Expand All @@ -185,29 +204,15 @@ let man =
; Common.footer
]

let info = Cmd.info "ocaml-merlin" ~doc ~man

let term =
let+ common = Common.term
and+ dump_config =
Arg.(
value
& opt ~vopt:(Some ".") (some string) None
& info [ "dump-config" ]
~doc:
"Prints the entire content of the merlin configuration for the \
given folder in a user friendly form. This is for testing and \
debugging purposes only and should not be considered as a stable \
output.")
in
let start_session_info name = Cmd.info name ~doc ~man

let start_session_term =
let+ common = Common.term in
let common = Common.forbid_builds common in
let config = Common.init common ~log_file:No_log_file in
Scheduler.go ~common ~config (fun () ->
match dump_config with
| Some s -> Server.dump s
| None -> Server.start ())
Scheduler.go ~common ~config Server.start

let command = Cmd.v info term
let command = Cmd.v (start_session_info "ocaml-merlin") start_session_term

module Dump_dot_merlin = struct
let doc = "Print Merlin configuration"
Expand Down Expand Up @@ -245,3 +250,9 @@ module Dump_dot_merlin = struct

let command = Cmd.v info term
end

let group =
Cmdliner.Cmd.group (Cmd.info "merlin")
[ Dump_config.command
; Cmd.v (start_session_info "start-session") start_session_term
]
2 changes: 2 additions & 0 deletions bin/ocaml_merlin.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,5 @@ val command : unit Cmd.t
module Dump_dot_merlin : sig
val command : unit Cmd.t
end

val group : unit Cmd.t
2 changes: 1 addition & 1 deletion doc/usage.rst
Original file line number Diff line number Diff line change
Expand Up @@ -558,7 +558,7 @@ purposes:

::

$ dune ocaml-merlin --dump-config
$ dune ocaml merlin dump-config

This command prints the distinct configuration of each module present in the
current directory. This directory must be in a Dune workspace and the project
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/github1946.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ in the same dune file, but require different ppx specifications
$ export BUILD_PATH_PREFIX_MAP="/OCAMLC_WHERE=$ocamlc_where:$BUILD_PATH_PREFIX_MAP"

$ dune build @all --profile release
$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Usesppx1
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/github2206.t/run.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
copy_files would break the generation of the preprocessing flags
$ dune build copy_files/.merlin-conf/exe-foo
$ dune ocaml-merlin --dump-config=$PWD/copy_files |
$ dune ocaml merlin dump-config $PWD/copy_files |
> grep -B 1 -A 0 "pp"
(FLG
(-pp
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/github759.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
$ export BUILD_PATH_PREFIX_MAP="/OCAMLC_WHERE=$ocamlc_where:$BUILD_PATH_PREFIX_MAP"

$ dune build foo.cma --profile release
$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand All @@ -14,7 +14,7 @@

$ rm -f .merlin
$ dune build foo.cma --profile release
$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand All @@ -26,7 +26,7 @@

$ echo toto > .merlin
$ dune build foo.cma --profile release
$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/melange/merlin.t
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@

$ touch bar.ml $lib.ml
$ dune build @check
$ dune ocaml-merlin --dump-config="$PWD" | grep -i "$lib"
$ dune ocaml merlin dump-config "$PWD" | grep -i "$lib"
Foo
$TESTCASE_ROOT/_build/default/.foo.objs/melange)
Foo__
Expand All @@ -35,5 +35,5 @@

$ touch main.ml
$ dune build @check
$ dune ocaml-merlin --dump-config="$PWD" | grep -i "$target"
$ dune ocaml merlin dump-config "$PWD" | grep -i "$target"
$TESTCASE_ROOT/_build/default/.output.mobjs/melange)
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ If Merlin field is absent, default context is chosen
..
lib-foo

$ dune ocaml-merlin --dump-config="$PWD"
$ dune ocaml merlin dump-config "$PWD"
Foo
((STDLIB OPAM_PREFIX)
(EXCLUDE_QUERY_DIR)
Expand Down Expand Up @@ -58,7 +58,7 @@ If Merlin field is present, this context is chosen
$ [ ! -d _build/default/.merlin-conf ] && echo "No config in default"
No config in default

$ dune ocaml-merlin --dump-config="$PWD"
$ dune ocaml merlin dump-config "$PWD"
Foo
((STDLIB OPAM_PREFIX)
(EXCLUDE_QUERY_DIR)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/merlin/github4125.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ We call `$(opam switch show)` so that this test always uses an existing switch
..
lib-foo

$ dune ocaml-merlin --dump-config="$PWD"
$ dune ocaml merlin dump-config "$PWD"
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ We build the project
bar

Verify that merlin configuration was generated...
$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Test
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down Expand Up @@ -43,7 +43,7 @@ Verify that merlin configuration was generated...
-keep-locs)))

...but not in the sub-folder whose content was copied
$ dune ocaml-merlin --dump-config=$PWD/411
$ dune ocaml merlin dump-config $PWD/411

Now we check that both querying from the root and the subfolder works
$ FILE=$PWD/foo.ml
Expand Down
10 changes: 5 additions & 5 deletions test/blackbox-tests/test-cases/merlin/merlin-tests.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

CRAM sanitization
$ dune build ./exe/.merlin-conf/exe-x --profile release
$ dune ocaml-merlin --dump-config=$PWD/exe
$ dune ocaml merlin dump-config $PWD/exe
X
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand All @@ -27,7 +27,7 @@ CRAM sanitization
(FLG (-w -40)))

$ dune build ./lib/.merlin-conf/lib-foo ./lib/.merlin-conf/lib-bar --profile release
$ dune ocaml-merlin --dump-config=$PWD/lib
$ dune ocaml merlin dump-config $PWD/lib
File
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down Expand Up @@ -102,12 +102,12 @@ CRAM sanitization
(FLG (-open Foo -w -40)))

Make sure a ppx directive is generated (if not, the [grep ppx] step fails)
$ dune ocaml-merlin --dump-config=$PWD/lib | grep ppx > /dev/null
$ dune ocaml merlin dump-config $PWD/lib | grep ppx > /dev/null

Make sure pp flag is correct and variables are expanded

$ dune build ./pp-with-expand/.merlin-conf/exe-foobar --profile release
$ dune ocaml-merlin --dump-config=$PWD/pp-with-expand
$ dune ocaml merlin dump-config $PWD/pp-with-expand
Foobar
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand All @@ -123,7 +123,7 @@ Make sure pp flag is correct and variables are expanded

Check hash of executables names if more than one
$ dune build ./exes/.merlin-conf/exe-x-6562915302827c6dce0630390bfa68b7
$ dune ocaml-merlin --dump-config=$PWD/exes
$ dune ocaml merlin dump-config $PWD/exes
Y
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
We dump the config for Foo and Bar modules but the pp.exe preprocessor
should appear only once since only Foo is using it.

$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/merlin/src-dirs-of-deps.t
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ library also has more than one src dir.
$ export BUILD_PATH_PREFIX_MAP="/OPAM_PREFIX=$opam_prefix:$BUILD_PATH_PREFIX_MAP"

$ dune build lib2/.merlin-conf/lib-lib2
$ dune ocaml-merlin --dump-config=$PWD/lib2
$ dune ocaml merlin dump-config $PWD/lib2
Lib2
((STDLIB /OPAM_PREFIX)
(EXCLUDE_QUERY_DIR)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/merlin/suffix.t/run.t
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
$ dune build @check

$ dune ocaml-merlin --dump-config=$(pwd) | grep SUFFIX
$ dune ocaml merlin dump-config $PWD | grep SUFFIX
(SUFFIX ".aml .amli")
(SUFFIX ".baml .bamli"))
10 changes: 5 additions & 5 deletions test/blackbox-tests/test-cases/merlin/symlinks.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -10,25 +10,25 @@ directory in these tests.

Absolute path with symlinks won't match with Dune's root path in which symlinks
are resolved:
$ dune ocaml-merlin --dump-config="$PWD/realsrc" --root="."
$ dune ocaml merlin dump-config "$PWD/realsrc" --root="."
Path $TESTCASE_ROOT/linkroot/realsrc is not in dune workspace ($TESTCASE_ROOT/realroot).

Absolute path with resolved symlinks will match with Dune's root path:
$ dune ocaml-merlin \
> --dump-config="$(pwd | sed 's/linkroot/realroot/')/realsrc" \
$ dune ocaml merlin \
> dump-config "$(pwd | sed 's/linkroot/realroot/')/realsrc" \
> --root="." | head -n 1
Foo


Dune ocaml-merlin also accepts paths relative to the current directory
$ dune ocaml-merlin --dump-config="realsrc" --root="." | head -n 1
$ dune ocaml merlin dump-config "realsrc" --root="." | head -n 1
Foo

$ cd realsrc

$ ocamlc_where="$(ocamlc -where)"
$ export BUILD_PATH_PREFIX_MAP="/OCAMLC_WHERE=$ocamlc_where:$BUILD_PATH_PREFIX_MAP"

$ dune ocaml-merlin --dump-config="." --root=".." | head -n 2
$ dune ocaml merlin dump-config "." --root=".." | head -n 2
Foo
((STDLIB /OCAMLC_WHERE)
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
$ dune exec ./foo.exe
42

$ dune ocaml-merlin --dump-config=$PWD
$ dune ocaml merlin dump-config $PWD
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand All @@ -24,7 +24,7 @@
-short-paths
-keep-locs)))

$ dune ocaml-merlin --dump-config=$PWD/foo
$ dune ocaml merlin dump-config $PWD/foo
Bar
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
Expand Down

0 comments on commit 19be49d

Please sign in to comment.