Skip to content

Commit

Permalink
fix(mdx): link mdx binary with byte_complete (#10586)
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
Signed-off-by: Etienne Millon <[email protected]>
Co-authored-by: Etienne Millon <[email protected]>
  • Loading branch information
anmonteiro and emillon authored May 31, 2024
1 parent e3f0357 commit 034e352
Show file tree
Hide file tree
Showing 4 changed files with 9 additions and 19 deletions.
2 changes: 2 additions & 0 deletions doc/changes/10586.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- mdx: link mdx binary with `byte_complete`. This fixes `(libraries)` with foreign archives on Linux.
(#10586, fixes #10582, @anmonteiro)
18 changes: 7 additions & 11 deletions src/dune_rules/mdx.ml
Original file line number Diff line number Diff line change
Expand Up @@ -411,25 +411,21 @@ let name = "mdx_gen"

let mdx_prog_gen t ~sctx ~dir ~scope ~mdx_prog =
let loc = t.loc in
let open Memo.O in
let* ocaml_toolchain = Context.ocaml (Super_context.context sctx) in
(* Libs from the libraries field should have their include directories sent to
mdx *)
let action =
let open Resolve.Memo.O in
let directory_args =
let* libs_to_include =
let+ libs_to_include =
Resolve.Memo.List.filter_map t.libraries ~f:(function
| Direct lib | Re_export lib ->
let+ lib = Lib.DB.resolve (Scope.libs scope) lib in
Some lib
| _ -> Resolve.Memo.return None)
in
let+ mode =
let open Memo.O in
Super_context.context sctx
|> Context.ocaml
>>| Ocaml_toolchain.best_mode
|> Resolve.Memo.lift_memo
in
let mode = ocaml_toolchain |> Ocaml_toolchain.best_mode in
let open Command.Args in
S
(Lib_flags.L.include_paths libs_to_include (Ocaml mode)
Expand All @@ -449,7 +445,6 @@ let mdx_prog_gen t ~sctx ~dir ~scope ~mdx_prog =
; Lazy.force color_always
]
in
let open Memo.O in
let* () = Super_context.add_rule sctx ~loc ~dir action in
(* We build the generated executable linking in the libs from the libraries
field *)
Expand Down Expand Up @@ -492,15 +487,16 @@ let mdx_prog_gen t ~sctx ~dir ~scope ~mdx_prog =
~package:None
()
in
let ext = ".bc.exe" in
let+ (_ : Exe.dep_graphs) =
Exe.build_and_link
cctx
~program:{ name; main_module_name; loc }
~link_args:(Action_builder.return (Command.Args.A "-linkall"))
~linkages:[ Exe.Linkage.byte ]
~linkages:[ Exe.Linkage.custom_with_ext ~ext ocaml_toolchain.version ]
~promote:None
in
Path.Build.relative dir (name ^ ".bc")
Path.Build.relative dir (name ^ ext)
;;

(** Generates the rules for a given mdx stanza *)
Expand Down
2 changes: 0 additions & 2 deletions test/blackbox-tests/test-cases/mdx-stanza/dune
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,6 @@

(cram
(applies_to shared-libraries)
(enabled_if
(= %{system} linux))
(deps
%{bin:gcc}
%{bin:ar}
Expand Down
6 changes: 0 additions & 6 deletions test/blackbox-tests/test-cases/mdx-stanza/shared-libraries.t
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,3 @@ See #10582.
> EOF

$ dune runtest
File "dune", lines 14-15, characters 0-29:
14 | (mdx
15 | (libraries public_lib))
Fatal error: cannot load shared library dlltest
Reason: dlltest.so: cannot open shared object file: No such file or directory
[1]

0 comments on commit 034e352

Please sign in to comment.