Skip to content

Commit ed91231

Browse files
committed
Fix crash when evaluating mdx stanza with missing local packages
Signed-off-by: Craig Ferguson <me@craigfe.io>
1 parent 1246f5e commit ed91231

File tree

5 files changed

+24
-142
lines changed

5 files changed

+24
-142
lines changed

CHANGES.md

+3
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,9 @@ next
4949
- Insert correct extension name when editing `dune-project` files. Previously,
5050
dune would just insert the stanza name. (#3649, fixes #3624, @rgrinberg)
5151

52+
- Fix crash when evaluating an `mdx` stanza that depends on unavailable
53+
packages. (#3650, @CraigFe)
54+
5255
2.6.1 (02/07/2020)
5356
------------------
5457

src/dune/gen_rules.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -129,7 +129,7 @@ end = struct
129129
Cinaps.gen_rules sctx cinaps ~dir ~scope;
130130
empty_none
131131
| Mdx.T mdx ->
132-
Mdx.gen_rules ~sctx ~dir mdx;
132+
Mdx.gen_rules ~sctx ~dir ~expander mdx;
133133
empty_none
134134
| _ -> empty_none
135135

src/dune/mdx.ml

+7-8
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,7 @@ let files_to_mdx t ~sctx ~dir =
169169

170170
(** Generates the rules for a single [src] file covered covered by the given
171171
[stanza]. *)
172-
let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
172+
let gen_rules_for_single_file stanza ~sctx ~dir ~expander ~mdx_prog src =
173173
let loc = stanza.loc in
174174
let files = Files.from_source_file src in
175175
(* Add the rule for generating the .mdx.deps file with ocaml-mdx deps *)
@@ -180,17 +180,15 @@ let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
180180
let deps = Build.map (Deps.read files) ~f:(Deps.to_dep_set ~dir) in
181181
let dyn_deps = Build.map deps ~f:(fun d -> ((), d)) in
182182
let pkg_deps =
183-
let context = Super_context.context sctx in
184-
let packages = Super_context.packages sctx in
185183
stanza.packages
186184
|> List.map ~f:(fun pkg ->
187-
let pkg = Package.Name.Map.find_exn packages pkg in
188-
Build.alias (Build_system.Alias.package_install ~context ~pkg))
185+
Dep_conf.Package
186+
(Package.Name.to_string pkg |> String_with_vars.make_text loc))
189187
in
190188
let prelude_args =
191189
List.concat_map stanza.preludes ~f:(Prelude.to_args ~dir)
192190
in
193-
Build.(with_no_targets (all_unit pkg_deps))
191+
Build.(with_no_targets (Dep_conf_eval.unnamed ~expander pkg_deps))
194192
>>> Build.with_no_targets (Build.dyn_deps dyn_deps)
195193
>>> Command.run ~dir:(Path.build dir) mdx_prog
196194
( [ Command.Args.A "test" ] @ prelude_args
@@ -204,10 +202,11 @@ let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
204202
(Build.with_no_targets diff_action)
205203

206204
(** Generates the rules for a given mdx stanza *)
207-
let gen_rules t ~sctx ~dir =
205+
let gen_rules t ~sctx ~dir ~expander =
208206
let files_to_mdx = files_to_mdx t ~sctx ~dir in
209207
let mdx_prog =
210208
Super_context.resolve_program sctx ~dir ~loc:(Some t.loc)
211209
~hint:"opam install mdx" "ocaml-mdx"
212210
in
213-
List.iter files_to_mdx ~f:(gen_rules_for_single_file t ~sctx ~dir ~mdx_prog)
211+
List.iter files_to_mdx
212+
~f:(gen_rules_for_single_file t ~sctx ~dir ~expander ~mdx_prog)

src/dune/mdx.mli

+2-1
Original file line numberDiff line numberDiff line change
@@ -7,4 +7,5 @@ type t
77
type Stanza.t += T of t
88

99
(** Genrates the rules to handle the given mdx stanza *)
10-
val gen_rules : t -> sctx:Super_context.t -> dir:Path.Build.t -> unit
10+
val gen_rules :
11+
t -> sctx:Super_context.t -> dir:Path.Build.t -> expander:Expander.t -> unit

test/blackbox-tests/test-cases/mdx-stanza.t/run.t

+11-132
Original file line numberDiff line numberDiff line change
@@ -49,140 +49,19 @@ the stanza
4949
$ dune runtest --root local-package
5050
Entering directory 'local-package'
5151
52-
Even if the packages is unrelated:
52+
Dune should not fail if the `packages` are not available at evaluation time
53+
(regression test fixed by ocaml/dune#3650)
54+
55+
$ cd local-package-unrelated && dune build -p unrelated-package; cd ../
56+
57+
Dune will fail if the `packages` entries are not avaliable at exeuction time
5358
5459
$ cd local-package-unrelated && dune runtest -p unrelated-package; cd ../
55-
Error: exception { exn = ("Map.find_exn: failed to find key", { key = 2; keys
56-
= [ 1 ] })
57-
; backtrace =
58-
[ { ocaml =
59-
"Raised at file \"src/stdune/code_error.ml\", line 9, characters
60-
30-62\n\
61-
Called from file \"src/dune/mdx.ml\", line 187, characters
62-
23-61\n\
63-
Called from file \"list.ml\", line 103, characters 22-25\n\
64-
Called from file \"src/stdune/list.ml\", line 5, characters
65-
19-33\n\
66-
Called from file \"src/dune/mdx.ml\", line 185, characters
67-
6-196\n\
68-
Called from file \"list.ml\", line 110, characters 12-15\n\
69-
Called from file \"src/dune/gen_rules.ml\", line 128, characters
70-
6-34\n\
71-
Called from file \"src/dune/gen_rules.ml\", line 135, characters
72-
6-96\n\
73-
Called from file \"list.ml\", line 121, characters 24-34\n\
74-
Called from file \"src/dune/gen_rules.ml\", line 138, characters
75-
4-112\n\
76-
Called from file \"src/dune/gen_rules.ml\", line 218, characters
77-
4-119\n\
78-
Called from file \"src/dune/gen_rules.ml\", line 349, characters
79-
24-59\n\
80-
Called from file \"src/stdune/exn.ml\", line 12, characters
81-
8-11\n\
82-
Re-raised at file \"src/stdune/exn.ml\", line 18, characters
83-
4-11\n\
84-
Called from file \"src/memo/implicit_output.ml\", line 120,
85-
characters 4-162\n\
86-
Called from file \"src/dune/rules.ml\" (inlined), line 192,
87-
characters 20-71\n\
88-
Called from file \"src/dune/rules.ml\", line 195, characters
89-
20-33\n\
90-
Called from file \"src/dune/build_system.ml\", line 900,
91-
characters 6-76\n\
92-
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
93-
characters 8-12\n\
94-
"
95-
; memo = ("load-dir", In_build_dir "default")
96-
}
97-
; { ocaml =
98-
"Raised at file \"src/stdune/code_error.ml\", line 9, characters
99-
30-62\n\
100-
Called from file \"src/dune/mdx.ml\", line 187, characters
101-
23-61\n\
102-
Called from file \"list.ml\", line 103, characters 22-25\n\
103-
Called from file \"src/stdune/list.ml\", line 5, characters
104-
19-33\n\
105-
Called from file \"src/dune/mdx.ml\", line 185, characters
106-
6-196\n\
107-
Called from file \"list.ml\", line 110, characters 12-15\n\
108-
Called from file \"src/dune/gen_rules.ml\", line 128, characters
109-
6-34\n\
110-
Called from file \"src/dune/gen_rules.ml\", line 135, characters
111-
6-96\n\
112-
Called from file \"list.ml\", line 121, characters 24-34\n\
113-
Called from file \"src/dune/gen_rules.ml\", line 138, characters
114-
4-112\n\
115-
Called from file \"src/dune/gen_rules.ml\", line 218, characters
116-
4-119\n\
117-
Called from file \"src/dune/gen_rules.ml\", line 349, characters
118-
24-59\n\
119-
Called from file \"src/stdune/exn.ml\", line 12, characters
120-
8-11\n\
121-
Re-raised at file \"src/stdune/exn.ml\", line 18, characters
122-
4-11\n\
123-
Called from file \"src/memo/implicit_output.ml\", line 120,
124-
characters 4-162\n\
125-
Called from file \"src/dune/rules.ml\" (inlined), line 192,
126-
characters 20-71\n\
127-
Called from file \"src/dune/rules.ml\", line 195, characters
128-
20-33\n\
129-
Called from file \"src/dune/build_system.ml\", line 900,
130-
characters 6-76\n\
131-
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
132-
characters 8-12\n\
133-
Re-raised at file \"src/stdune/exn.ml\", line 36, characters
134-
27-56\n\
135-
Called from file \"src/dune/build_system.ml\", line 1046,
136-
characters 12-43\n\
137-
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
138-
characters 8-12\n\
139-
"
140-
; memo = ("load-dir", In_build_dir ".aliases/default")
141-
}
142-
]
143-
; outer_call_stack = []
144-
}
145-
Raised at file "src/stdune/code_error.ml", line 9, characters 30-62
146-
Called from file "src/dune/mdx.ml", line 187, characters 23-61
147-
Called from file "list.ml", line 103, characters 22-25
148-
Called from file "src/stdune/list.ml", line 5, characters 19-33
149-
Called from file "src/dune/mdx.ml", line 185, characters 6-196
150-
Called from file "list.ml", line 110, characters 12-15
151-
Called from file "src/dune/gen_rules.ml", line 128, characters 6-34
152-
Called from file "src/dune/gen_rules.ml", line 135, characters 6-96
153-
Called from file "list.ml", line 121, characters 24-34
154-
Called from file "src/dune/gen_rules.ml", line 138, characters 4-112
155-
Called from file "src/dune/gen_rules.ml", line 218, characters 4-119
156-
Called from file "src/dune/gen_rules.ml", line 349, characters 24-59
157-
Called from file "src/stdune/exn.ml", line 12, characters 8-11
158-
Re-raised at file "src/stdune/exn.ml", line 18, characters 4-11
159-
Called from file "src/memo/implicit_output.ml", line 120, characters 4-162
160-
Called from file "src/dune/rules.ml" (inlined), line 192, characters 20-71
161-
Called from file "src/dune/rules.ml", line 195, characters 20-33
162-
Called from file "src/dune/build_system.ml", line 900, characters 6-76
163-
Called from file "src/stdune/exn_with_backtrace.ml", line 9, characters 8-12
164-
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
165-
Called from file "src/dune/build_system.ml", line 1046, characters 12-43
166-
Called from file "src/stdune/exn_with_backtrace.ml", line 9, characters 8-12
167-
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
168-
Called from file "src/dune/build_system.ml", line 685, characters 10-23
169-
Called from file "src/dune/build_system.ml", line 682, characters 17-34
170-
Called from file "src/dune/build.ml", line 293, characters 9-22
171-
Called from file "src/dune/build.ml", line 284, characters 58-73
172-
Called from file "src/dune/build.ml", line 284, characters 42-57
173-
Called from file "src/dune/build.ml", line 284, characters 42-57
174-
Called from file "src/dune/build.ml", line 284, characters 58-73
175-
Called from file "src/dune/build_system.ml", line 1237, characters 24-39
176-
Called from file "src/dune/build_system.ml", line 1850, characters 8-97
177-
Called from file "src/fiber/fiber.ml", line 109, characters 10-15
178-
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
179-
Called from file "src/fiber/fiber.ml", line 80, characters 10-17
180-
181-
I must not crash. Uncertainty is the mind-killer. Exceptions are the
182-
little-death that brings total obliteration. I will fully express my cases.
183-
Execution will pass over me and through me. And when it has gone past, I
184-
will unwind the stack along its path. Where the cases are handled there will
185-
be nothing. Only I will remain.
60+
File "dune", line 1, characters 0-40:
61+
1 | (mdx
62+
2 | (files README.md)
63+
3 | (packages pkg))
64+
Error: Package pkg does not exist
18665
18766
You can set MDX preludes using the preludes field of the stanza
18867

0 commit comments

Comments
 (0)