Skip to content

Commit

Permalink
fix: read the processed file in Ocamldep.read_immediate_deps_of
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro committed Mar 22, 2024
1 parent bdf25d6 commit 6715575
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 36 deletions.
52 changes: 31 additions & 21 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,8 +40,21 @@ let make_js_name ~js_ext ~output m =
Path.Build.relative dst_dir basename
;;

let impl_only_modules_defined_in_this_lib sctx lib =
let+ modules = Dir_contents.modules_of_lib sctx lib in
let modules_in_obj_dir ~sctx ~scope ~preprocess modules =
let* ocaml = Context.ocaml (Super_context.context sctx) in
let version = ocaml.version in
let* preprocess =
Resolve.Memo.read_memo
(Preprocess.Per_module.with_instrumentation
preprocess
~instrumentation_backend:(Lib.DB.instrumentation_backend (Scope.libs scope)))
in
let pped_map = Staged.unstage (Preprocessing.pped_modules_map preprocess version) in
Modules.map_user_written modules ~f:(fun m -> Memo.return @@ pped_map m)
;;

let impl_only_modules_defined_in_this_lib ~sctx ~scope lib =
let* modules = Dir_contents.modules_of_lib sctx lib in
match modules with
| None ->
User_error.raise
Expand All @@ -52,8 +65,12 @@ let impl_only_modules_defined_in_this_lib sctx lib =
(Lib.name lib |> Lib_name.to_string)
]
| Some modules ->
let info = Lib.info lib in
let+ modules =
let preprocess = Lib_info.preprocess info in
modules_in_obj_dir ~sctx ~scope ~preprocess modules
in
let () =
let info = Lib.info lib in
let modes = Lib_info.modes info in
match modes.melange with
| false ->
Expand Down Expand Up @@ -133,11 +150,11 @@ let js_targets_of_modules modules ~module_systems ~output =
|> Path.Set.union_all
;;

let js_targets_of_libs sctx libs ~module_systems ~target_dir =
let js_targets_of_libs ~sctx ~scope ~module_systems ~target_dir libs =
Resolve.Memo.List.concat_map module_systems ~f:(fun (_, js_ext) ->
let open Memo.O in
let of_lib lib =
let+ modules = impl_only_modules_defined_in_this_lib sctx lib in
let+ modules = impl_only_modules_defined_in_this_lib ~sctx ~scope lib in
let output = output_of_lib ~target_dir lib in
List.rev_map modules ~f:(fun m -> Path.build @@ make_js_name ~output ~js_ext m)
in
Expand Down Expand Up @@ -302,7 +319,7 @@ let setup_emit_cmj_rules
@@
let open Resolve.Memo.O in
Compilation_context.requires_link cctx
>>= js_targets_of_libs sctx ~module_systems ~target_dir
>>= js_targets_of_libs ~sctx ~scope ~module_systems ~target_dir
in
Action_builder.paths deps
in
Expand Down Expand Up @@ -403,18 +420,7 @@ let modules_for_js_and_obj_dir ~sctx ~dir_contents ~scope (mel : Melange_stanzas
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules_and_obj_dir ~for_:(Melange { target = mel.target })
in
let+ modules =
let* ocaml = Context.ocaml (Super_context.context sctx) in
let version = ocaml.version in
let* preprocess =
Resolve.Memo.read_memo
(Preprocess.Per_module.with_instrumentation
mel.preprocess
~instrumentation_backend:(Lib.DB.instrumentation_backend (Scope.libs scope)))
in
let pped_map = Staged.unstage (Preprocessing.pped_modules_map preprocess version) in
Modules.map_user_written modules ~f:(fun m -> Memo.return @@ pped_map m)
in
let+ modules = modules_in_obj_dir ~sctx ~scope ~preprocess:mel.preprocess modules in
let modules_for_js =
Modules.fold_no_vlib modules ~init:[] ~f:(fun x acc ->
if Module.has x ~ml_kind:Impl then x :: acc else acc)
Expand Down Expand Up @@ -495,7 +501,11 @@ let setup_js_rules_libraries
and* local_modules =
match Lib.Local.of_lib lib with
| Some lib ->
let+ modules = Dir_contents.modules_of_local_lib sctx lib in
let* modules = Dir_contents.modules_of_local_lib sctx lib in
let+ modules =
let preprocess = Lib_info.preprocess info in
modules_in_obj_dir ~sctx ~scope ~preprocess modules
in
let obj_dir = Lib.Local.obj_dir lib in
Some (modules, obj_dir)
| None -> Memo.return None
Expand Down Expand Up @@ -540,10 +550,10 @@ let setup_js_rules_libraries
in
cmj_includes ~requires_link ~scope
in
impl_only_modules_defined_in_this_lib sctx vlib
impl_only_modules_defined_in_this_lib ~sctx ~scope vlib
>>= Memo.parallel_iter ~f:(build_js ~dir ~output ~includes ~local_modules)
in
let* source_modules = impl_only_modules_defined_in_this_lib sctx lib in
let* source_modules = impl_only_modules_defined_in_this_lib ~sctx ~scope lib in
Memo.parallel_iter source_modules ~f:(build_js ~dir ~output ~local_modules ~includes))
;;

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/module.mli
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ val visibility : t -> Visibility.t
val encode : t -> src_dir:Path.t -> Dune_lang.t list
val decode : src_dir:Path.t -> t Dune_lang.Decoder.t

(** [pped m] return [m] but with the preprocessed source paths paths *)
(** [pped m] return [m] but with the preprocessed source paths *)
val pped : t -> t

(** [ml_source m] returns [m] but with the OCaml syntax source paths *)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,11 +30,6 @@ file after any dialects have run
> let name = "Zoe"
> EOF
$ dune build @mel
Error: ocamldep returned unexpected output for _build/default/lib/foo.myd:
> lib/foo.myd.ml: Bar
-> required by _build/default/output/lib/foo.js
-> required by alias mel
[1]

Now try preprocessing too

Expand All @@ -46,12 +41,3 @@ Now try preprocessing too
> (modes melange))
> EOF
$ dune build @mel
Error: ocamldep returned unexpected output for _build/default/lib/bar.ml:
> lib/bar.pp.ml:
-> required by _build/default/output/lib/bar.js
-> required by alias mel
Error: ocamldep returned unexpected output for _build/default/lib/foo.myd.ml:
> lib/foo.pp.myd.ml: Bar
-> required by _build/default/output/lib/foo.js
-> required by alias mel
[1]

0 comments on commit 6715575

Please sign in to comment.