Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
46 changes: 35 additions & 11 deletions bin/ocaml/ocaml_merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -99,21 +99,45 @@ end = struct
let load_merlin_file file =
(* We search for an appropriate merlin configuration in the current
directory and its parents *)
let get_file_config_at_path p =
match Merlin.Processed.load_file p with
| Error msg -> Some (Merlin_conf.make_error msg)
| Ok config -> Merlin.Processed.get config ~file
in
let basename = Path.Build.set_extension file ~ext:"" |> Path.Build.basename in
let good_names =
List.map
~f:(fun pref -> Printf.sprintf "%s-%s" pref basename)
[ "lib"; "exe"; "melange" ]
in
let rec find_closest path =
let merlin_paths = get_merlin_files_paths path in
(* Now we want to look for:
1. an exact match
2. an approximate match
3. recursing to parent directory
*)
match
get_merlin_files_paths path
|> List.find_map ~f:(fun file_path ->
(* FIXME we are racing against the build system writing these
files here *)
match Merlin.Processed.load_file file_path with
| Error msg -> Some (Merlin_conf.make_error msg)
| Ok config -> Merlin.Processed.get config ~file)
List.find merlin_paths ~f:(fun p ->
List.mem good_names (Path.basename p) ~equal:String.equal)
with
| Some p -> Some p
| Some p ->
(* Found exact match: we are done *)
get_file_config_at_path p
| None ->
(match Path.Build.parent path with
| None -> None
| Some dir -> find_closest dir)
(* looking for approximate match *)
(match
List.find_map merlin_paths ~f:(fun file_path ->
(* FIXME we are racing against the build system writing these
files here *)
get_file_config_at_path file_path)
with
| Some p -> Some p
| None ->
(* Otherwise, recurse upwards *)
(match Path.Build.parent path with
| None -> None
| Some dir -> find_closest dir))
in
match find_closest (Path.Build.parent_exn file) with
| Some x -> x
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.10)
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
(executable
(name b))

(executable
(name c)
(libraries lib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(library
(name lib))
15 changes: 15 additions & 0 deletions test/blackbox-tests/test-cases/merlin/merlin-multi-exes.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
$ ocamlc_where="$(ocamlc -where)"
$ export BUILD_PATH_PREFIX_MAP="/OCAMLC_WHERE=$ocamlc_where:$BUILD_PATH_PREFIX_MAP"

$ FILE=$PWD/multi-exes/bin/b.ml
$ printf "(4:File%d:%s)" ${#FILE} $FILE | dune ocaml-merlin
((5:ERROR71:No config found for file multi-exes/bin/b.ml. Try calling 'dune build'.))

$ dune build @check

$ printf "(4:File%d:%s)" ${#FILE} $FILE | dune ocaml-merlin | sed -E "s/[[:digit:]]+:/\?:/g"
((?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.c.eobjs/cctx.ocaml-index)(?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.b.eobjs/cctx.ocaml-index)(?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/lib/.lib.objs/cctx.ocaml-index)(?:STDLIB?:/OCAMLC_WHERE)(?:SOURCE_ROOT?:$TESTCASE_ROOT)(?:EXCLUDE_QUERY_DIR)(?:B?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.b.eobjs/byte)(?:S?:$TESTCASE_ROOT/multi-exes/bin)(?:FLG(?:-w?:@1..3@5..28@30..39@43@46..47@49..57@61..62-?:-strict-sequence?:-strict-formats?:-short-paths?:-keep-locs?:-g))(?:UNIT_NAME?:b))

$ FILE=$PWD/multi-exes/bin/c.ml
$ printf "(4:File%d:%s)" ${#FILE} $FILE | dune ocaml-merlin | sed -E "s/[[:digit:]]+:/\?:/g"
((?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.c.eobjs/cctx.ocaml-index)(?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.b.eobjs/cctx.ocaml-index)(?:INDEX?:$TESTCASE_ROOT/_build/default/multi-exes/lib/.lib.objs/cctx.ocaml-index)(?:STDLIB?:/OCAMLC_WHERE)(?:SOURCE_ROOT?:$TESTCASE_ROOT)(?:EXCLUDE_QUERY_DIR)(?:B?:$TESTCASE_ROOT/_build/default/multi-exes/bin/.c.eobjs/byte)(?:B?:$TESTCASE_ROOT/_build/default/multi-exes/lib/.lib.objs/byte)(?:S?:$TESTCASE_ROOT/multi-exes/bin)(?:S?:$TESTCASE_ROOT/multi-exes/lib)(?:FLG(?:-w?:@1..3@5..28@30..39@43@46..47@49..57@61..62-?:-strict-sequence?:-strict-formats?:-short-paths?:-keep-locs?:-g))(?:UNIT_NAME?:c))
Loading