Skip to content

Commit

Permalink
fix(melange): check rules (#6789)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Dec 28, 2022
1 parent cc6c138 commit da010e0
Show file tree
Hide file tree
Showing 5 changed files with 21 additions and 7 deletions.
9 changes: 7 additions & 2 deletions src/dune_rules/check_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,15 @@ let dev_files =
let ext = Filename.extension p in
List.mem exts ext ~equal:String.equal)

let add_obj_dir sctx ~obj_dir =
let add_obj_dir sctx ~obj_dir mode =
if (Super_context.context sctx).merlin then
let dir_glob =
let dir = Path.build (Obj_dir.byte_dir obj_dir) in
let dir =
Path.build
(match mode with
| `Melange -> Obj_dir.melange_dir obj_dir
| `Bytecode -> Obj_dir.byte_dir obj_dir)
in
File_selector.create ~dir dev_files
in
Rules.Produce.Alias.add_deps
Expand Down
5 changes: 4 additions & 1 deletion src/dune_rules/check_rules.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
open Import

val add_obj_dir :
Super_context.t -> obj_dir:Path.Build.t Obj_dir.t -> unit Memo.t
Super_context.t
-> obj_dir:Path.Build.t Obj_dir.t
-> [ `Melange | `Bytecode ]
-> unit Memo.t

val add_files :
Super_context.t -> dir:Path.Build.t -> Path.t list -> unit Memo.t
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
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 in
let* () = Check_rules.add_obj_dir sctx ~obj_dir `Bytecode in
let ctx = Super_context.context sctx in
let project = Scope.project scope in
let programs = programs ~modules ~exes in
Expand Down
10 changes: 8 additions & 2 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -485,14 +485,20 @@ let library_rules (lib : Library.t) ~local_lib ~cctx ~source_modules
Memo.Option.iter vimpl
~f:(Virtual_rules.setup_copy_rules_for_impl ~sctx ~dir)
in
let* () = Check_rules.add_obj_dir sctx ~obj_dir in
let* () = Check_rules.add_cycle_check sctx ~dir top_sorted_modules in
let* () = gen_wrapped_compat_modules lib cctx
and* () = Module_compilation.build_all cctx
and* expander = Super_context.expander sctx ~dir
and* lib_info =
let lib_config = (Super_context.context sctx).lib_config in
Library.to_lib_info lib ~dir ~lib_config
let* info = Library.to_lib_info lib ~dir ~lib_config in
let mode =
match Lib_info.modes info with
| { ocaml = { byte = false; native = _ }; melange = true } -> `Melange
| _ -> `Bytecode
in
let+ () = Check_rules.add_obj_dir sctx ~obj_dir mode in
info
in
let+ () =
Memo.when_
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,7 @@ let setup_emit_cmj_rules ~sctx ~dir ~scope ~expander ~dir_contents
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules_and_obj_dir ~for_:(Melange { target = mel.target })
in
let* () = Check_rules.add_obj_dir sctx ~obj_dir in
let* () = Check_rules.add_obj_dir sctx ~obj_dir `Melange in
let* modules, pp =
Buildable_rules.modules_rules sctx
(Melange
Expand Down

0 comments on commit da010e0

Please sign in to comment.