Skip to content
Merged
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
2 changes: 2 additions & 0 deletions doc/changes/11707.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- fix: Evaluate `enabled_if` when computing the stubs for stanzas such as
`foreign_library` (#11707, @Alizter, @rgrinberg)
4 changes: 2 additions & 2 deletions src/dune_rules/dir_contents.ml
Original file line number Diff line number Diff line change
Expand Up @@ -292,7 +292,7 @@ end = struct
; foreign_sources =
Memo.lazy_ (fun () ->
let dune_version = Dune_project.dune_version project in
stanzas >>| Foreign_sources.make ~dune_version ~dirs)
stanzas >>= Foreign_sources.make ~dir ~dune_version ~dirs)
; coq =
Memo.lazy_ (fun () ->
stanzas >>| Coq_sources.of_dir ~dir ~include_subdirs ~dirs)
Expand Down Expand Up @@ -370,7 +370,7 @@ end = struct
let foreign_sources =
Memo.lazy_ (fun () ->
let dune_version = Dune_project.dune_version project in
stanzas >>| Foreign_sources.make ~dune_version ~dirs)
stanzas >>= Foreign_sources.make ~dir ~dune_version ~dirs)
in
let coq =
Memo.lazy_ (fun () ->
Expand Down
34 changes: 27 additions & 7 deletions src/dune_rules/foreign_sources.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
open Import
open Memo.O

type t =
{ libraries : Foreign.Sources.t Lib_name.Map.t
Expand Down Expand Up @@ -215,24 +216,23 @@ let make stanzas ~(sources : Unresolved.t) ~dune_version =
List.fold_left
stanzas
~init:([], [], [])
~f:(fun ((libs, foreign_libs, exes) as acc) stanza ->
match Stanza.repr stanza with
| Library.T lib ->
~f:(fun (libs, foreign_libs, exes) stanza ->
match stanza with
| `Library (lib : Library.t) ->
let all =
eval_foreign_stubs lib.buildable.foreign_stubs lib.buildable.ctypes
in
(lib, all) :: libs, foreign_libs, exes
| Foreign_library.T library ->
| `Foreign_library (library : Foreign_library.t) ->
let all = eval_foreign_stubs [ library.stubs ] None in
( libs
, (library.archive_name, (library.archive_name_loc, all)) :: foreign_libs
, exes )
| Executables.T exe | Tests.T { exes = exe; _ } ->
| `Executables exe | `Tests { Tests.exes = exe; _ } ->
let all =
eval_foreign_stubs exe.buildable.foreign_stubs exe.buildable.ctypes
in
libs, foreign_libs, (exe, all) :: exes
| _ -> acc)
libs, foreign_libs, (exe, all) :: exes)
in
List.(rev libs, rev foreign_libs, rev exes)
in
Expand Down Expand Up @@ -337,3 +337,23 @@ let make stanzas ~dune_version ~dirs =
let sources = Unresolved.load_dirs ~dune_version dirs in
make stanzas ~dune_version ~sources
;;

let make stanzas ~dir ~dune_version ~dirs =
let+ stanzas =
List.filter_map stanzas ~f:(fun stanza ->
match Stanza.repr stanza with
| Library.T lib -> Some (`Library lib, lib.enabled_if)
| Foreign_library.T lib -> Some (`Foreign_library lib, lib.enabled_if)
| Executables.T exe -> Some (`Executables exe, exe.enabled_if)
| Tests.T ({ exes = exe; _ } as tests) -> Some (`Tests tests, exe.enabled_if)
| _ -> None)
|> Memo.parallel_map ~f:(fun (stanza, enabled_if) ->
let* expander = Expander0.get ~dir in
Expander0.eval_blang expander enabled_if
>>| function
| false -> None
| true -> Some stanza)
>>| List.filter_opt
in
make stanzas ~dune_version ~dirs
;;
3 changes: 2 additions & 1 deletion src/dune_rules/foreign_sources.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ val for_exes : t -> first_exe:string -> Foreign.Sources.t

val make
: Stanza.t list
-> dir:Path.Build.t
-> dune_version:Syntax.Version.t
-> dirs:Source_file_dir.t list
-> t
-> t Memo.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
Interaction of the foreign_library stanza and the enabled_if field.

$ cat > dune-project <<EOF
> (lang dune 3.18)
> EOF

We should allow multiple foreign libraries to define the same archive if only
one of them is enabled:

$ cat > dune <<EOF
> (foreign_library
> (enabled_if true)
> (language c)
> (archive_name a)
> (names a))
>
> (foreign_library
> (enabled_if false)
> (language c)
> (archive_name a)
> (names a))
>
> (foreign_library
> (enabled_if false)
> (language c)
> (archive_name a)
> (names a))
> EOF
$ cat > a.c
$ dune build


Repeat the test, but now two of the libraries are indeed enabled which is
illegal:

$ cat > dune <<EOF
> (foreign_library
> (enabled_if true)
> (language c)
> (archive_name a)
> (names a))
>
> (foreign_library
> (enabled_if true)
> (language c)
> (archive_name a)
> (names a))
>
> (foreign_library
> (enabled_if false)
> (language c)
> (archive_name a)
> (names a))
> EOF
$ cat > a.c
$ dune build
File "dune", line 5, characters 8-9:
5 | (names a))
^
Error: Multiple definitions for the same object file "a". See another
definition at dune:11.
Hint: You can avoid the name clash by renaming one of the objects, or by
placing it into a different directory.
[1]
5 changes: 0 additions & 5 deletions test/blackbox-tests/test-cases/foreign-stubs/github10675.t
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,3 @@ stubs, dune should not crash. See #10675.
$ touch startup.c main.ml

$ dune build
File "dune", line 3, characters 7-11:
3 | (name main))
^^^^
Error: Executables with same name "main" use different foreign sources
[1]
Loading