Skip to content

Commit

Permalink
hidden_path: use distinct source and build paths
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed May 2, 2024
1 parent 91c05c7 commit c2d0346
Show file tree
Hide file tree
Showing 9 changed files with 58 additions and 21 deletions.
5 changes: 3 additions & 2 deletions src/dot-merlin/dot_merlin_reader.ml
Original file line number Diff line number Diff line change
Expand Up @@ -326,7 +326,7 @@ let empty_config = {
let prepend_config ~cwd ~cfg =
List.fold_left ~init:cfg ~f:(fun cfg (d : Merlin_dot_protocol.Directive.Raw.t) ->
match d with
| `B _ | `H _ | `S _ | `CMI _ | `CMT _ as directive ->
| `B _ | `S _ | `BH _ | `SH _ | `CMI _ | `CMT _ as directive ->
{ cfg with to_canonicalize = (cwd, directive) :: cfg.to_canonicalize }
| `EXT _ | `SUFFIX _ | `FLG _ | `READER _
| (`EXCLUDE_QUERY_DIR | `USE_PPX_CACHE | `UNKNOWN_TAG _) as directive ->
Expand Down Expand Up @@ -454,8 +454,9 @@ let postprocess cfg =
let dirs =
match directive with
| `B path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `B p)
| `H path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `H p)
| `S path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `S p)
| `BH path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `BH p)
| `SH path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `SH p)
| `CMI path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `CMI p)
| `CMT path -> List.map (expand ~stdlib dir path) ~f:(fun p -> `CMT p)
in
Expand Down
13 changes: 10 additions & 3 deletions src/dot-protocol/merlin_dot_protocol.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,12 @@ open Merlin_utils.Std.Result

module Directive = struct
type include_path =
[ `B of string | `H of string | `S of string | `CMI of string | `CMT of string ]
[ `B of string
| `S of string
| `BH of string
| `SH of string
| `CMI of string
| `CMT of string ]

type no_processing_required =
[ `EXT of string list
Expand Down Expand Up @@ -82,7 +87,8 @@ module Sexp = struct
begin match tag with
| "S" -> `S value
| "B" -> `B value
| "H" -> `H value
| "SH" -> `SH value
| "BH" -> `BH value
| "CMI" -> `CMI value
| "CMT" -> `CMT value
| "STDLIB" -> `STDLIB value
Expand Down Expand Up @@ -112,8 +118,9 @@ module Sexp = struct
let single s = [ Atom s ] in
match t with
| `B s -> ("B", single s)
| `H s -> ("H", single s)
| `S s -> ("S", single s)
| `BH s -> ("BH", single s)
| `SH s -> ("SH", single s)
| `CMI s -> ("CMI", single s)
| `CMT s -> ("CMT", single s)
| `EXT ss -> ("EXT", [ List (atoms_of_strings ss) ])
Expand Down
7 changes: 6 additions & 1 deletion src/dot-protocol/merlin_dot_protocol.mli
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,12 @@ really do not want to load them. *)

module Directive : sig
type include_path =
[ `B of string | `H of string| `S of string | `CMI of string | `CMT of string ]
[ `B of string
| `S of string
| `BH of string
| `SH of string
| `CMI of string
| `CMT of string ]

type no_processing_required =
[ `EXT of string list
Expand Down
30 changes: 23 additions & 7 deletions src/kernel/mconfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,9 @@ let marg_commandline f =

type merlin = {
build_path : string list;
hidden_path : string list;
source_path : string list;
hidden_build_path : string list;
hidden_source_path : string list;
cmi_path : string list;
cmt_path : string list;
extensions : string list;
Expand Down Expand Up @@ -105,6 +106,8 @@ let dump_merlin x =
`Assoc [
"build_path" , `List (List.map ~f:Json.string x.build_path);
"source_path" , `List (List.map ~f:Json.string x.source_path);
"hidden_build_path" , `List (List.map ~f:Json.string x.hidden_build_path);
"hidden_source_path", `List (List.map ~f:Json.string x.hidden_source_path);
"cmi_path" , `List (List.map ~f:Json.string x.cmi_path);
"cmt_path" , `List (List.map ~f:Json.string x.cmt_path);
"flags_applied", `List (List.map ~f:dump_flag_list x.flags_applied);
Expand Down Expand Up @@ -235,10 +238,10 @@ let rec normalize t =

let merge_merlin_config dot merlin ~failures ~config_path =
{ merlin with
build_path = dot.Mconfig_dot.build_path @ merlin.build_path;
build_path = dot.build_path @ merlin.build_path;
source_path = dot.source_path @ merlin.source_path;
cmi_path = dot.cmi_path @ merlin.cmi_path;
cmt_path = dot.cmt_path @ merlin.cmt_path;
hidden_build_path = dot.hidden_build_path @ merlinhidden_build_path;
hidden_source_path = dot.hidden_source_path @ merlinhidden_source_path;
exclude_query_dir = dot.exclude_query_dir || merlin.exclude_query_dir;
use_ppx_cache = dot.use_ppx_cache || merlin.use_ppx_cache;
extensions = dot.extensions @ merlin.extensions;
Expand Down Expand Up @@ -276,6 +279,18 @@ let merlin_flags = [
{merlin with source_path = dir :: merlin.source_path}),
"<dir> Add <dir> to merlin source path"
);
(
"-hidden-build-path",
marg_path (fun dir merlin ->
{merlin with hidden_build_path = dir :: merlin.hidden_build_path}),
"<dir> Add <dir> to merlin hidden build path"
);
(
"-hidden-source-path",
marg_path (fun dir merlin ->
{merlin with hidden_source_path = dir :: merlin.hidden_source_path}),
"<dir> Add <dir> to merlin hidden source path"
);
(
"-cmi-path",
marg_path (fun dir merlin ->
Expand Down Expand Up @@ -617,8 +632,9 @@ let initial = {
};
merlin = {
build_path = [];
hidden_path = [];
source_path = [];
hidden_build_path = [];
hidden_source_path = [];
cmi_path = [];
cmt_path = [];
extensions = [];
Expand Down Expand Up @@ -764,8 +780,8 @@ let build_path config = (
result'
)

let hidden_path config =
config.merlin.hidden_path @ config.ocaml.hidden_dirs
let hidden_build_path config =
config.merlin.hidden_build_path @ config.ocaml.hidden_dirs

let cmt_path config = (
let dirs =
Expand Down
5 changes: 3 additions & 2 deletions src/kernel/mconfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,9 @@ val dump_ocaml : ocaml -> json

type merlin = {
build_path : string list;
hidden_path : string list;
source_path : string list;
hidden_build_path : string list;
hidden_source_path : string list;
cmi_path : string list;
cmt_path : string list;
extensions : string list;
Expand Down Expand Up @@ -115,7 +116,7 @@ val source_path : t -> string list

val build_path : t -> string list

val hidden_path : t -> string list
val hidden_build_path : t -> string list

val cmt_path : t -> string list

Expand Down
12 changes: 8 additions & 4 deletions src/kernel/mconfig_dot.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,9 @@ type directive = Merlin_dot_protocol.directive

type config = {
build_path : string list;
hidden_path : string list;
source_path : string list;
hidden_build_path : string list;
hidden_source_path : string list;
cmi_path : string list;
cmt_path : string list;
flags : string list with_workdir list;
Expand All @@ -49,7 +50,8 @@ type config = {

let empty_config = {
build_path = [];
hidden_path = [];
hidden_build_path =[];
hidden_source_path = [];
source_path = [];
cmi_path = [];
cmt_path = [];
Expand Down Expand Up @@ -236,8 +238,9 @@ let prepend_config ~dir:cwd configurator (directives : directive list) config =
List.fold_left ~init:(config, []) ~f:(fun (config, errors) ->
function
| `B path -> {config with build_path = path :: config.build_path}, errors
| `H path -> {config with hidden_path = path :: config.hidden_path}, errors
| `S path -> {config with source_path = path :: config.source_path}, errors
| `BH path -> {config with hidden_build_path = path :: config.hidden_build_path}, errors
| `SH path -> {config with hidden_source_path = path :: config.hidden_source_path}, errors
| `CMI path -> {config with cmi_path = path :: config.cmi_path}, errors
| `CMT path -> {config with cmt_path = path :: config.cmt_path}, errors
| `EXT exts ->
Expand Down Expand Up @@ -270,8 +273,9 @@ let postprocess_config config =
let clean list = List.rev (List.filter_dup list) in
{
build_path = clean config.build_path;
hidden_path = clean config.hidden_path;
source_path = clean config.source_path;
hidden_build_path = clean config.hidden_build_path;
hidden_source_path = clean config.hidden_source_path;
cmi_path = clean config.cmi_path;
cmt_path = clean config.cmt_path;
extensions = clean config.extensions;
Expand Down
3 changes: 2 additions & 1 deletion src/kernel/mconfig_dot.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,9 @@ end

type config = {
build_path : string list;
hidden_path : string list;
source_path : string list;
hidden_build_path : string list;
hidden_source_path : string list;
cmi_path : string list;
cmt_path : string list;
flags : string list with_workdir list;
Expand Down
2 changes: 1 addition & 1 deletion src/kernel/mocaml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ let setup_reader_config config = (
let setup_typer_config config = (
setup_reader_config config;
let visible = Mconfig.build_path config in
let hidden = Mconfig.hidden_path config in
let hidden = Mconfig.hidden_build_path config in
Load_path.(init ~auto_include:no_auto_include ~visible ~hidden);
)

Expand Down
2 changes: 2 additions & 0 deletions tests/test-dirs/config/dot-merlin-reader/quoting.t
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@
{
"build_path": [],
"source_path": [],
"hidden_build_path": [],
"hidden_source_path": [],
"cmi_path": [],
"cmt_path": [],
"flags_applied": [
Expand Down

0 comments on commit c2d0346

Please sign in to comment.