Skip to content

Commit

Permalink
feature: introduce public_headers
Browse files Browse the repository at this point in the history
This field works like install_c_headers except it allows full file names
and allows to customize the destination paths

Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: cf542cda-1684-4719-bffd-fdb6a8bc2d63 -->
  • Loading branch information
rgrinberg committed Apr 8, 2023
1 parent fd93c4a commit 666553c
Show file tree
Hide file tree
Showing 5 changed files with 79 additions and 8 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
Unreleased
----------

- Introduce a `public_headers` field on libraries. This field is like
`install_c_headers`, but it allows to choose the extension and choose the
paths for the installed headers. (#7512, @rgrinberg)

- Load the host context `findlib.conf` when cross-compiling (#7428, fixes
#1701, @rgrinberg, @anmonteiro)

Expand Down
7 changes: 7 additions & 0 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -562,6 +562,7 @@ module Library = struct
; visibility : visibility
; synopsis : string option
; install_c_headers : string list
; public_headers : Install_entry.File.t list
; ppx_runtime_libraries : (Loc.t * Lib_name.t) list
; modes : Mode_conf.Lib.Set.t
; kind : Lib_kind.t
Expand Down Expand Up @@ -599,6 +600,11 @@ module Library = struct
and+ synopsis = field_o "synopsis" string
and+ install_c_headers =
field "install_c_headers" (repeat string) ~default:[]
and+ public_headers =
field "public_headers"
(Dune_lang.Syntax.since Stanza.syntax (3, 8)
>>> repeat Install_entry.File.decode)
~default:[]
and+ ppx_runtime_libraries =
field "ppx_runtime_libraries"
(repeat (located Lib_name.decode))
Expand Down Expand Up @@ -734,6 +740,7 @@ module Library = struct
; visibility
; synopsis
; install_c_headers
; public_headers
; ppx_runtime_libraries
; modes
; kind
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,7 @@ module Library : sig
; visibility : visibility
; synopsis : string option
; install_c_headers : string list
; public_headers : Install_entry.File.t list
; ppx_runtime_libraries : (Loc.t * Lib_name.t) list
; modes : Mode_conf.Lib.Set.t
; kind : Lib_kind.t
Expand Down
28 changes: 20 additions & 8 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -95,14 +95,14 @@ end = struct
&& ctx.dynamically_linked_foreign_archives)
(Lib_info.foreign_dll_files lib)

let lib_install_files sctx ~scope ~dir_contents ~dir ~sub_dir:lib_subdir
(lib : Library.t) =
let lib_install_files sctx ~expander ~scope ~dir_contents ~dir
~sub_dir:lib_subdir (lib : Library.t) =
let loc = lib.buildable.loc in
let ctx = Super_context.context sctx in
let lib_config = ctx.lib_config in
let* info = Dune_file.Library.to_lib_info lib ~dir ~lib_config in
let obj_dir = Lib_info.obj_dir info in
let make_entry section ?sub_dir ?dst fn =
let make_entry section ?(loc = loc) ?sub_dir ?dst fn =
let entry =
Install.Entry.make section fn ~kind:`File
~dst:
Expand Down Expand Up @@ -272,15 +272,25 @@ end = struct
in
modules
in
let install_c_headers =
List.map lib.install_c_headers ~f:(fun base ->
Path.Build.relative dir (base ^ Foreign_language.header_extension))
in
let* lib_files, dll_files =
let+ lib_files = lib_files ~dir ~dir_contents ~lib_config info in
let dll_files = dll_files ~modes:ocaml ~dynlink:lib.dynlink ~ctx info in
(lib_files, dll_files)
in
let+ execs = lib_ppxs ctx ~scope ~lib in
let install_c_headers =
List.map lib.install_c_headers ~f:(fun base ->
Path.Build.relative dir (base ^ Foreign_language.header_extension))
let* execs = lib_ppxs ctx ~scope ~lib in
let+ public_headers =
Install_entry.File.to_file_bindings_expanded lib.public_headers
~expand_str:(Expander.No_deps.expand_str expander)
~dir
>>| List.map ~f:(fun fb ->
let loc = File_binding.Expanded.src_loc fb in
let src = File_binding.Expanded.src fb in
let dst = File_binding.Expanded.dst fb in
make_entry ~loc Lib ?dst src)
in
List.concat
[ sources
Expand All @@ -293,6 +303,7 @@ end = struct
let entry = Install.Entry.make ~kind:`File Stublibs a in
Install.Entry.Sourced.create ~loc entry)
; List.map ~f:(make_entry Lib) install_c_headers
; public_headers
]

let keep_if expander ~scope stanza =
Expand Down Expand Up @@ -402,7 +413,8 @@ end = struct
| Library lib ->
let sub_dir = Dune_file.Library.sub_dir lib in
let* dir_contents = Dir_contents.get sctx ~dir in
lib_install_files sctx ~scope ~dir ~sub_dir lib ~dir_contents
lib_install_files sctx ~expander ~scope ~dir ~sub_dir lib
~dir_contents
| Coq_stanza.Theory.T coqlib ->
Coq_rules.install_rules ~sctx ~dir coqlib
| Documentation d ->
Expand Down
47 changes: 47 additions & 0 deletions test/blackbox-tests/test-cases/foreign-stubs/public-headers.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,47 @@
Headers with the same filename cannot be installed together:

$ cat >dune-project <<EOF
> (lang dune 3.8)
> (package (name mypkg))
> EOF

$ mkdir inc

$ cat >dune <<EOF
> (library
> (public_name mypkg)
> (public_headers foo.h (inc/foo.h as inc/foo.h)))
> EOF

$ touch foo.h inc/foo.h

$ dune build mypkg.install && cat _build/default/mypkg.install | grep ".h"
"_build/install/default/lib/mypkg/foo.h"
"_build/install/default/lib/mypkg/inc/foo.h" {"inc/foo.h"}

Now we try to use the installed headers:

$ dune install --prefix _install mypkg
$ export OCAMLPATH=$PWD/_install/lib:$OCAMLPATH

$ mkdir subdir
$ cd subdir

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

$ cat >dune <<EOF
> (executable
> (name bar)
> (foreign_stubs
> (language c)
> (include_dirs (lib mypkg))
> (names foo)))
> EOF
$ touch bar.ml
$ cat >foo.c <<EOF
> #include <foo.h>
> #include <inc/foo.h>
> EOF
$ dune build bar.exe

0 comments on commit 666553c

Please sign in to comment.