Skip to content

Commit

Permalink
Fix crash when evaluating mdx stanza with missing local packages
Browse files Browse the repository at this point in the history
Signed-off-by: Craig Ferguson <[email protected]>
  • Loading branch information
craigfe committed Jul 28, 2020
1 parent 1246f5e commit ed91231
Show file tree
Hide file tree
Showing 5 changed files with 24 additions and 142 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,9 @@ next
- Insert correct extension name when editing `dune-project` files. Previously,
dune would just insert the stanza name. (#3649, fixes #3624, @rgrinberg)

- Fix crash when evaluating an `mdx` stanza that depends on unavailable
packages. (#3650, @CraigFe)

2.6.1 (02/07/2020)
------------------

Expand Down
2 changes: 1 addition & 1 deletion src/dune/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ end = struct
Cinaps.gen_rules sctx cinaps ~dir ~scope;
empty_none
| Mdx.T mdx ->
Mdx.gen_rules ~sctx ~dir mdx;
Mdx.gen_rules ~sctx ~dir ~expander mdx;
empty_none
| _ -> empty_none

Expand Down
15 changes: 7 additions & 8 deletions src/dune/mdx.ml
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ let files_to_mdx t ~sctx ~dir =

(** Generates the rules for a single [src] file covered covered by the given
[stanza]. *)
let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
let gen_rules_for_single_file stanza ~sctx ~dir ~expander ~mdx_prog src =
let loc = stanza.loc in
let files = Files.from_source_file src in
(* Add the rule for generating the .mdx.deps file with ocaml-mdx deps *)
Expand All @@ -180,17 +180,15 @@ let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
let deps = Build.map (Deps.read files) ~f:(Deps.to_dep_set ~dir) in
let dyn_deps = Build.map deps ~f:(fun d -> ((), d)) in
let pkg_deps =
let context = Super_context.context sctx in
let packages = Super_context.packages sctx in
stanza.packages
|> List.map ~f:(fun pkg ->
let pkg = Package.Name.Map.find_exn packages pkg in
Build.alias (Build_system.Alias.package_install ~context ~pkg))
Dep_conf.Package
(Package.Name.to_string pkg |> String_with_vars.make_text loc))
in
let prelude_args =
List.concat_map stanza.preludes ~f:(Prelude.to_args ~dir)
in
Build.(with_no_targets (all_unit pkg_deps))
Build.(with_no_targets (Dep_conf_eval.unnamed ~expander pkg_deps))
>>> Build.with_no_targets (Build.dyn_deps dyn_deps)
>>> Command.run ~dir:(Path.build dir) mdx_prog
( [ Command.Args.A "test" ] @ prelude_args
Expand All @@ -204,10 +202,11 @@ let gen_rules_for_single_file stanza ~sctx ~dir ~mdx_prog src =
(Build.with_no_targets diff_action)

(** Generates the rules for a given mdx stanza *)
let gen_rules t ~sctx ~dir =
let gen_rules t ~sctx ~dir ~expander =
let files_to_mdx = files_to_mdx t ~sctx ~dir in
let mdx_prog =
Super_context.resolve_program sctx ~dir ~loc:(Some t.loc)
~hint:"opam install mdx" "ocaml-mdx"
in
List.iter files_to_mdx ~f:(gen_rules_for_single_file t ~sctx ~dir ~mdx_prog)
List.iter files_to_mdx
~f:(gen_rules_for_single_file t ~sctx ~dir ~expander ~mdx_prog)
3 changes: 2 additions & 1 deletion src/dune/mdx.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,4 +7,5 @@ type t
type Stanza.t += T of t

(** Genrates the rules to handle the given mdx stanza *)
val gen_rules : t -> sctx:Super_context.t -> dir:Path.Build.t -> unit
val gen_rules :
t -> sctx:Super_context.t -> dir:Path.Build.t -> expander:Expander.t -> unit
143 changes: 11 additions & 132 deletions test/blackbox-tests/test-cases/mdx-stanza.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -49,140 +49,19 @@ the stanza
$ dune runtest --root local-package
Entering directory 'local-package'
Even if the packages is unrelated:
Dune should not fail if the `packages` are not available at evaluation time
(regression test fixed by ocaml/dune#3650)
$ cd local-package-unrelated && dune build -p unrelated-package; cd ../
Dune will fail if the `packages` entries are not avaliable at exeuction time
$ cd local-package-unrelated && dune runtest -p unrelated-package; cd ../
Error: exception { exn = ("Map.find_exn: failed to find key", { key = 2; keys
= [ 1 ] })
; backtrace =
[ { ocaml =
"Raised at file \"src/stdune/code_error.ml\", line 9, characters
30-62\n\
Called from file \"src/dune/mdx.ml\", line 187, characters
23-61\n\
Called from file \"list.ml\", line 103, characters 22-25\n\
Called from file \"src/stdune/list.ml\", line 5, characters
19-33\n\
Called from file \"src/dune/mdx.ml\", line 185, characters
6-196\n\
Called from file \"list.ml\", line 110, characters 12-15\n\
Called from file \"src/dune/gen_rules.ml\", line 128, characters
6-34\n\
Called from file \"src/dune/gen_rules.ml\", line 135, characters
6-96\n\
Called from file \"list.ml\", line 121, characters 24-34\n\
Called from file \"src/dune/gen_rules.ml\", line 138, characters
4-112\n\
Called from file \"src/dune/gen_rules.ml\", line 218, characters
4-119\n\
Called from file \"src/dune/gen_rules.ml\", line 349, characters
24-59\n\
Called from file \"src/stdune/exn.ml\", line 12, characters
8-11\n\
Re-raised at file \"src/stdune/exn.ml\", line 18, characters
4-11\n\
Called from file \"src/memo/implicit_output.ml\", line 120,
characters 4-162\n\
Called from file \"src/dune/rules.ml\" (inlined), line 192,
characters 20-71\n\
Called from file \"src/dune/rules.ml\", line 195, characters
20-33\n\
Called from file \"src/dune/build_system.ml\", line 900,
characters 6-76\n\
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
characters 8-12\n\
"
; memo = ("load-dir", In_build_dir "default")
}
; { ocaml =
"Raised at file \"src/stdune/code_error.ml\", line 9, characters
30-62\n\
Called from file \"src/dune/mdx.ml\", line 187, characters
23-61\n\
Called from file \"list.ml\", line 103, characters 22-25\n\
Called from file \"src/stdune/list.ml\", line 5, characters
19-33\n\
Called from file \"src/dune/mdx.ml\", line 185, characters
6-196\n\
Called from file \"list.ml\", line 110, characters 12-15\n\
Called from file \"src/dune/gen_rules.ml\", line 128, characters
6-34\n\
Called from file \"src/dune/gen_rules.ml\", line 135, characters
6-96\n\
Called from file \"list.ml\", line 121, characters 24-34\n\
Called from file \"src/dune/gen_rules.ml\", line 138, characters
4-112\n\
Called from file \"src/dune/gen_rules.ml\", line 218, characters
4-119\n\
Called from file \"src/dune/gen_rules.ml\", line 349, characters
24-59\n\
Called from file \"src/stdune/exn.ml\", line 12, characters
8-11\n\
Re-raised at file \"src/stdune/exn.ml\", line 18, characters
4-11\n\
Called from file \"src/memo/implicit_output.ml\", line 120,
characters 4-162\n\
Called from file \"src/dune/rules.ml\" (inlined), line 192,
characters 20-71\n\
Called from file \"src/dune/rules.ml\", line 195, characters
20-33\n\
Called from file \"src/dune/build_system.ml\", line 900,
characters 6-76\n\
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
characters 8-12\n\
Re-raised at file \"src/stdune/exn.ml\", line 36, characters
27-56\n\
Called from file \"src/dune/build_system.ml\", line 1046,
characters 12-43\n\
Called from file \"src/stdune/exn_with_backtrace.ml\", line 9,
characters 8-12\n\
"
; memo = ("load-dir", In_build_dir ".aliases/default")
}
]
; outer_call_stack = []
}
Raised at file "src/stdune/code_error.ml", line 9, characters 30-62
Called from file "src/dune/mdx.ml", line 187, characters 23-61
Called from file "list.ml", line 103, characters 22-25
Called from file "src/stdune/list.ml", line 5, characters 19-33
Called from file "src/dune/mdx.ml", line 185, characters 6-196
Called from file "list.ml", line 110, characters 12-15
Called from file "src/dune/gen_rules.ml", line 128, characters 6-34
Called from file "src/dune/gen_rules.ml", line 135, characters 6-96
Called from file "list.ml", line 121, characters 24-34
Called from file "src/dune/gen_rules.ml", line 138, characters 4-112
Called from file "src/dune/gen_rules.ml", line 218, characters 4-119
Called from file "src/dune/gen_rules.ml", line 349, characters 24-59
Called from file "src/stdune/exn.ml", line 12, characters 8-11
Re-raised at file "src/stdune/exn.ml", line 18, characters 4-11
Called from file "src/memo/implicit_output.ml", line 120, characters 4-162
Called from file "src/dune/rules.ml" (inlined), line 192, characters 20-71
Called from file "src/dune/rules.ml", line 195, characters 20-33
Called from file "src/dune/build_system.ml", line 900, characters 6-76
Called from file "src/stdune/exn_with_backtrace.ml", line 9, characters 8-12
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
Called from file "src/dune/build_system.ml", line 1046, characters 12-43
Called from file "src/stdune/exn_with_backtrace.ml", line 9, characters 8-12
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
Called from file "src/dune/build_system.ml", line 685, characters 10-23
Called from file "src/dune/build_system.ml", line 682, characters 17-34
Called from file "src/dune/build.ml", line 293, characters 9-22
Called from file "src/dune/build.ml", line 284, characters 58-73
Called from file "src/dune/build.ml", line 284, characters 42-57
Called from file "src/dune/build.ml", line 284, characters 42-57
Called from file "src/dune/build.ml", line 284, characters 58-73
Called from file "src/dune/build_system.ml", line 1237, characters 24-39
Called from file "src/dune/build_system.ml", line 1850, characters 8-97
Called from file "src/fiber/fiber.ml", line 109, characters 10-15
Re-raised at file "src/stdune/exn.ml", line 36, characters 27-56
Called from file "src/fiber/fiber.ml", line 80, characters 10-17

I must not crash. Uncertainty is the mind-killer. Exceptions are the
little-death that brings total obliteration. I will fully express my cases.
Execution will pass over me and through me. And when it has gone past, I
will unwind the stack along its path. Where the cases are handled there will
be nothing. Only I will remain.
File "dune", line 1, characters 0-40:
1 | (mdx
2 | (files README.md)
3 | (packages pkg))
Error: Package pkg does not exist
You can set MDX preludes using the preludes field of the stanza
Expand Down

0 comments on commit ed91231

Please sign in to comment.