Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 9 additions & 0 deletions src/dune_rules/module.ml
Original file line number Diff line number Diff line change
Expand Up @@ -336,6 +336,15 @@ let sources_without_pp t =
~f:(Option.map ~f:(fun (x : File.t) -> x.original_path))
;;

let source_without_pp ~ml_kind t =
let source =
match (ml_kind : Ml_kind.t) with
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think this might need an adjustment for sources without mli's. That is, when ml_kind = Intf but there's not t.source.files.intf we should fall back to the .impl.

Would be great to have a test for this as well if you have the time.

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thanks, will have a look.

| Impl -> t.source.files.impl
| Intf -> t.source.files.intf
in
Option.map source ~f:(fun (x : File.t) -> x.original_path)
;;

module Obj_map = struct
include Map.Make (struct
type nonrec t = t
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/module.mli
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ end

val sources : t -> Path.t list
val sources_without_pp : t -> Path.t list
val source_without_pp : ml_kind:Ml_kind.t -> t -> Path.t option
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
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -158,6 +158,7 @@ let build_cm
let* compiler = compiler in
let ml_kind = Lib_mode.Cm_kind.source cm_kind in
let+ src = Module.file m ~ml_kind in
let original = Module.source_without_pp m ~ml_kind in
let dst = Obj_dir.Module.cm_file_exn obj_dir m ~kind:cm_kind in
let obj =
Obj_dir.Module.obj_file obj_dir m ~kind:(Ocaml Cmx) ~ext:ocaml.lib_config.ext_obj
Expand Down Expand Up @@ -324,6 +325,7 @@ let build_cm
; A "-c"
; Command.Ml_kind.flag ml_kind
; Dep src
; Hidden_deps (Dep.Set.of_files (Option.to_list original))
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Would be nice to leave a comment why we need the source file here. It is in fact only needed for sandboxed builds as far as I can tell.

; other_targets
]
>>| Action.Full.add_sandbox sandbox))
Expand Down
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/melange/ppx-preview.t
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,8 @@ Show PPX snippet preview is shown in Dune
$ export DUNE_SANDBOX=symlink
$ dune build @melange
File "lib/the_lib.ml", line 1, characters 7-11:
1 | let x: nope = "hello"
^^^^
Error: Unbound type constructor nope
[1]

Expand Down