Skip to content

Commit

Permalink
fix(ctypes): only function descriptions have stubs (#9302)
Browse files Browse the repository at this point in the history
Fixes #9300

Signed-off-by: Etienne Millon <[email protected]>
  • Loading branch information
emillon authored Nov 30, 2023
1 parent 5489f6f commit 55143f3
Show file tree
Hide file tree
Showing 6 changed files with 19 additions and 28 deletions.
3 changes: 3 additions & 0 deletions doc/changes/ctypes-no-stubs.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
- ctypes: fix an error where `(ctypes)` with no `(function_description)` would
cause an error trying refer to a nonexistent `_stubs.a` dependency
(#9302, fix #9300, @emillon)
6 changes: 6 additions & 0 deletions src/dune_rules/ctypes/ctypes_field.ml
Original file line number Diff line number Diff line change
Expand Up @@ -276,3 +276,9 @@ let generated_ml_and_c_files ctypes =
in
ml_files @ c_files
;;

let has_stubs = function
| None -> false
| Some { function_description = []; _ } -> false
| _ -> true
;;
1 change: 1 addition & 0 deletions src/dune_rules/ctypes/ctypes_field.mli
Original file line number Diff line number Diff line change
Expand Up @@ -73,3 +73,4 @@ val c_generated_types_module : t -> Module_name.t
val type_gen_script : t -> string
val c_generated_functions_cout_c : t -> Function_description.t -> string
val function_gen_script : t -> Function_description.t -> string
val has_stubs : t option -> bool
10 changes: 7 additions & 3 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,10 @@ module Buildable = struct
let has_mode_dependent_foreign_stubs t =
List.exists ~f:Foreign.Stubs.is_mode_dependent t.foreign_stubs
;;

let has_foreign_stubs t =
List.is_non_empty t.foreign_stubs || Ctypes_field.has_stubs t.ctypes
;;
end

module Public_lib = struct
Expand Down Expand Up @@ -823,9 +827,9 @@ module Library = struct
let has_foreign_cxx t = Buildable.has_foreign_cxx t.buildable

let stubs_archive t =
if List.is_empty t.buildable.foreign_stubs && Option.is_none t.buildable.ctypes
then None
else Some (Foreign.Archive.stubs (Lib_name.Local.to_string (snd t.name)))
if Buildable.has_foreign_stubs t.buildable
then Some (Foreign.Archive.stubs (Lib_name.Local.to_string (snd t.name)))
else None
;;

let foreign_archives t = List.map ~f:snd t.buildable.foreign_archives
Expand Down
11 changes: 0 additions & 11 deletions test/blackbox-tests/test-cases/ctypes/github-5561-name-mangle.t
Original file line number Diff line number Diff line change
Expand Up @@ -20,15 +20,4 @@
3 | (module Type_description.Types)
^^^^^^^^^^^^^^^^^^^^^^
Error: Unbound module Type_description
File "dune", line 1, characters 0-211:
1 | (library
2 | (name foo)
3 | (ctypes
4 | (external_library_name fooBar)
5 | (build_flags_resolver vendored)
6 | (generated_entry_point Types_generated2)
7 | (type_description
8 | (instance Type)
9 | (functor Type_description))))
Error: No rule found for libfoo_stubs.a
[1]
16 changes: 2 additions & 14 deletions test/blackbox-tests/test-cases/ctypes/types-only.t
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
When a ctypes description has just a type description, Dune does not setup a
rule for a stubs file it tries to use.
When a ctypes description has just a type description, if should be possible to
build the library.
See #9300.

$ cat > dune-project << EOF
Expand All @@ -24,15 +24,3 @@ See #9300.
> EOF

$ dune build
File "dune", line 1, characters 0-185:
1 | (library
2 | (name l)
3 | (ctypes
4 | (external_library_name none)
5 | (build_flags_resolver vendored)
6 | (type_description
7 | (functor bindings)
8 | (instance types))
9 | (generated_entry_point c)))
Error: No rule found for libl_stubs.a
[1]

0 comments on commit 55143f3

Please sign in to comment.