Skip to content

Commit

Permalink
refactor(merlin): configure with source modules
Browse files Browse the repository at this point in the history
We pass source modules (before preprocessing) when configuring merlin.

Signed-off-by: Andrey Popp <8mayday@gmail.com>
  • Loading branch information
andreypopp committed Sep 4, 2023
1 parent fcf687d commit 7c9c6cb
Show file tree
Hide file tree
Showing 5 changed files with 30 additions and 22 deletions.
8 changes: 4 additions & 4 deletions src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -117,15 +117,15 @@ let executables_rules
=
(* Use "eobjs" rather than "objs" to avoid a potential conflict with a library
of the same name *)
let* modules, obj_dir =
let* source_modules, obj_dir =
let first_exe = first_exe exes in
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules_and_obj_dir ~for_:(Exe { first_exe })
in
let* () = Check_rules.add_obj_dir sctx ~obj_dir (Ocaml Byte) in
let ctx = Super_context.context sctx in
let project = Scope.project scope in
let programs = programs ~modules ~exes in
let programs = programs ~modules:source_modules ~exes in
let explicit_js_mode = Dune_project.explicit_js_mode project in
let linkages = linkages ctx ~exes ~explicit_js_mode in
let* flags = Buildable_rules.ocaml_flags sctx ~dir exes.buildable.flags in
Expand All @@ -136,7 +136,7 @@ let executables_rules
expander
~dir
scope
modules
source_modules
in
let* cctx =
let requires_compile = Lib.Compile.direct_requires compile_info in
Expand Down Expand Up @@ -249,7 +249,7 @@ let executables_rules
~requires:requires_compile
~stdlib_dir
~flags
~modules
~source_modules
~source_dirs:Path.Source.Set.empty
~libname:None
~obj_dir
Expand Down
14 changes: 9 additions & 5 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -559,9 +559,6 @@ let library_rules
~dir_contents
~compile_info
=
let source_modules =
Modules.fold_user_written source_modules ~init:[] ~f:(fun m acc -> m :: acc)
in
let modules = Compilation_context.modules cctx in
let obj_dir = Compilation_context.obj_dir cctx in
let vimpl = Compilation_context.vimpl cctx in
Expand Down Expand Up @@ -611,14 +608,21 @@ let library_rules
and+ () = Odoc.setup_library_odoc_rules cctx local_lib
and+ () =
Sub_system.gen_rules
{ super_context = sctx; dir; stanza = lib; scope; source_modules; compile_info }
{ super_context = sctx
; dir
; stanza = lib
; scope
; source_modules =
Modules.fold_user_written source_modules ~init:[] ~f:(fun m acc -> m :: acc)
; compile_info
}
in
( cctx
, Merlin.make
~requires:requires_compile
~stdlib_dir
~flags
~modules
~source_modules
~source_dirs:Path.Source.Set.empty
~preprocess:(Preprocess.Per_module.without_instrumentation lib.buildable.preprocess)
~libname:(Some (snd lib.name))
Expand Down
6 changes: 3 additions & 3 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ let setup_emit_cmj_rules
let f () =
(* Use "mobjs" rather than "objs" to avoid a potential conflict with a library
of the same name *)
let* modules, obj_dir =
let* source_modules, obj_dir =
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules_and_obj_dir ~for_:(Melange { target = mel.target })
in
Expand All @@ -230,7 +230,7 @@ let setup_emit_cmj_rules
expander
~dir
scope
modules
source_modules
in
let requires_link = Lib.Compile.requires_link compile_info in
let* flags = ocaml_flags sctx ~dir mel.compile_flags in
Expand Down Expand Up @@ -287,7 +287,7 @@ let setup_emit_cmj_rules
~requires:requires_compile
~stdlib_dir
~flags
~modules
~source_modules
~source_dirs:Path.Source.Set.empty
~libname:None
~preprocess:(Preprocess.Per_module.without_instrumentation mel.preprocess)
Expand Down
22 changes: 13 additions & 9 deletions src/dune_rules/merlin/merlin.ml
Original file line number Diff line number Diff line change
@@ -1,9 +1,13 @@
open Import

let remove_extension file =
let strip_pp_extensions file =
let dir = Path.Build.parent_exn file in
let basename, _ext = String.lsplit2_exn (Path.Build.basename file) ~on:'.' in
Path.Build.relative dir basename
let basename = Path.Build.basename file in
match String.split basename ~on:'.' with
| [] | [ _ ] | [ _; _ ] -> file
| name :: exts ->
let ext = Option.value_exn (List.last exts) in
Path.Build.relative dir (sprintf "%s.%s" name ext)
;;

module Processed = struct
Expand Down Expand Up @@ -249,8 +253,9 @@ module Processed = struct
let open Option.O in
let+ { module_; opens } =
let find file =
let file_without_ext = remove_extension file in
Path.Build.Map.find per_module_config file_without_ext
match Path.Build.Map.find per_module_config file with
| Some _ as s -> s
| None -> Path.Build.Map.find per_module_config (strip_pp_extensions file)
in
match find file with
| Some _ as s -> s
Expand Down Expand Up @@ -372,7 +377,7 @@ module Unprocessed = struct
~preprocess
~libname
~source_dirs
~modules
~source_modules
~obj_dir
~dialects
~ident
Expand Down Expand Up @@ -407,7 +412,7 @@ module Unprocessed = struct
; extensions
}
in
{ ident; config; modules }
{ ident; config; modules = source_modules }
;;

let encode_command =
Expand Down Expand Up @@ -600,8 +605,7 @@ module Unprocessed = struct
(* And copy for each module the resulting pp flags *)
Modules.fold_no_vlib modules ~init:[] ~f:(fun m init ->
Module.sources m
|> Path.Build.Set.of_list_map ~f:(fun src ->
Path.as_in_build_dir_exn src |> remove_extension)
|> Path.Build.Set.of_list_map ~f:(fun src -> Path.as_in_build_dir_exn src)
|> Path.Build.Set.fold ~init ~f:(fun src acc ->
let config =
{ Processed.module_ = Module.set_pp m None
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/merlin/merlin.mli
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ val make
-> preprocess:Preprocess.Without_instrumentation.t Preprocess.t Module_name.Per_item.t
-> libname:Lib_name.Local.t option
-> source_dirs:Path.Source.Set.t
-> modules:Modules.t
-> source_modules:Modules.t
-> obj_dir:Path.Build.t Obj_dir.t
-> dialects:Dialect.DB.t
-> ident:Merlin_ident.t
Expand Down

0 comments on commit 7c9c6cb

Please sign in to comment.