File tree Expand file tree Collapse file tree 4 files changed +39
-9
lines changed
test/blackbox-tests/test-cases/melange Expand file tree Collapse file tree 4 files changed +39
-9
lines changed Original file line number Diff line number Diff 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+
339348module Obj_map = struct
340349 include Map. Make (struct
341350 type nonrec t = t
Original file line number Diff line number Diff line change 8888
8989val sources : t -> Path .t list
9090val sources_without_pp : t -> Path .t list
91+ val source_without_pp : ml_kind :Ml_kind .t -> t -> Path .t option
9192val visibility : t -> Visibility .t
9293val encode : t -> src_dir :Path .t -> Dune_lang .t list
9394val decode : src_dir :Path .t -> t Dune_lang.Decoder .t
Original file line number Diff line number Diff 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,10 @@ let build_cm
324325 ; A " -c"
325326 ; Command.Ml_kind. flag ml_kind
326327 ; Dep src
328+ ; (* We add a hidden dependency on the original, pre-PPX source
329+ file, which the compiler wants to find to display error
330+ location snippets. *)
331+ Hidden_deps (Dep.Set. of_files (Option. to_list original))
327332 ; other_targets
328333 ]
329334 >> | Action.Full. add_sandbox sandbox))
Original file line number Diff line number Diff line change @@ -15,26 +15,41 @@ Show PPX snippet preview is shown in Dune
1515 > let x : nope = " hello"
1616 > EOF
1717
18- $ cat > dune << EOF
19- > (melange. emit
20- > (target output)
21- > (libraries the_lib)
22- > (emit_stdlib false))
23- > EOF
24-
2518 $ export DUNE_SANDBOX= symlink
26- $ dune build @ melange
19+ $ dune build @ all
2720 File " lib/the_lib.ml" , line 1 , characters 7 -11:
21+ 1 | let x : nope = " hello"
22+ ^^^^
2823 Error: Unbound type constructor nope
2924 [1 ]
3025
3126Works if the sandbox is disabled
3227
3328 $ export DUNE_SANDBOX= none
34- $ dune build @ melange
29+ $ dune build @ all
3530 File " lib/the_lib.ml" , line 1 , characters 7 -11:
3631 1 | let x : nope = " hello"
3732 ^^^^
3833 Error: Unbound type constructor nope
3934 [1 ]
4035
36+ $ cat > lib / the_lib. mli << EOF
37+ > val x : nope
38+ > EOF
39+
40+ $ export DUNE_SANDBOX= symlink
41+ $ dune build @ all
42+ File " lib/the_lib.mli" , line 1 , characters 7 -11:
43+ 1 | val x : nope
44+ ^^^^
45+ Error: Unbound type constructor nope
46+ [1 ]
47+
48+ $ export DUNE_SANDBOX= none
49+ $ dune build @ all
50+ File " lib/the_lib.mli" , line 1 , characters 7 -11:
51+ 1 | val x : nope
52+ ^^^^
53+ Error: Unbound type constructor nope
54+ [1 ]
55+
You can’t perform that action at this time.
0 commit comments