Skip to content

Commit 8114ac4

Browse files
committed
fix(module_compilation): add dep to original source file
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
1 parent e1ea3b4 commit 8114ac4

File tree

4 files changed

+14
-0
lines changed

4 files changed

+14
-0
lines changed

src/dune_rules/module.ml

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -336,6 +336,15 @@ let sources_without_pp t =
336336
~f:(Option.map ~f:(fun (x : File.t) -> x.original_path))
337337
;;
338338

339+
let source_without_pp ~ml_kind t =
340+
let source =
341+
match (ml_kind : Ml_kind.t) with
342+
| Impl -> t.source.files.impl
343+
| Intf -> t.source.files.intf
344+
in
345+
Option.map source ~f:(fun (x : File.t) -> x.original_path)
346+
;;
347+
339348
module Obj_map = struct
340349
include Map.Make (struct
341350
type nonrec t = t

src/dune_rules/module.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,7 @@ end
8888

8989
val sources : t -> Path.t list
9090
val sources_without_pp : t -> Path.t list
91+
val source_without_pp : ml_kind:Ml_kind.t -> t -> Path.t option
9192
val visibility : t -> Visibility.t
9293
val encode : t -> src_dir:Path.t -> Dune_lang.t list
9394
val decode : src_dir:Path.t -> t Dune_lang.Decoder.t

src/dune_rules/module_compilation.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -158,6 +158,7 @@ let build_cm
158158
let* compiler = compiler in
159159
let ml_kind = Lib_mode.Cm_kind.source cm_kind in
160160
let+ src = Module.file m ~ml_kind in
161+
let original = Module.source_without_pp m ~ml_kind in
161162
let dst = Obj_dir.Module.cm_file_exn obj_dir m ~kind:cm_kind in
162163
let obj =
163164
Obj_dir.Module.obj_file obj_dir m ~kind:(Ocaml Cmx) ~ext:ocaml.lib_config.ext_obj
@@ -324,6 +325,7 @@ let build_cm
324325
; A "-c"
325326
; Command.Ml_kind.flag ml_kind
326327
; Dep src
328+
; Hidden_deps (Dep.Set.of_files (Option.to_list original))
327329
; other_targets
328330
]
329331
>>| Action.Full.add_sandbox sandbox))

test/blackbox-tests/test-cases/melange/ppx-preview.t

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,8 @@ Show PPX snippet preview is shown in Dune
2525
$ export DUNE_SANDBOX=symlink
2626
$ dune build @melange
2727
File "lib/the_lib.ml", line 1, characters 7-11:
28+
1 | let x: nope = "hello"
29+
^^^^
2830
Error: Unbound type constructor nope
2931
[1]
3032

0 commit comments

Comments
 (0)