Skip to content

Commit

Permalink
Add variables %{lib-private} and %{libexec-private} (#2901)
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <[email protected]>
  • Loading branch information
snowleopard authored Nov 21, 2019
1 parent 2fa81d6 commit 75826d1
Show file tree
Hide file tree
Showing 7 changed files with 320 additions and 28 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
2.1.0 (unreleased)
------------------

- Add variables `%{lib-private...}` and `%{libexec-private...}` for finding
build paths of files in public and private libraries within the same
project. (#2901, @snowleopard)

2.0.0 (unreleased)
------------------

Expand Down
16 changes: 11 additions & 5 deletions doc/concepts.rst
Original file line number Diff line number Diff line change
Expand Up @@ -197,13 +197,19 @@ In addition, ``(action ...)`` fields support the following special variables:
%{bin:program} ...)`` and ``(run program ...)`` behave in the same
way. ``%{bin:...}`` is only necessary when you are using ``(bash
...)`` or ``(system ...)``
- ``lib:<public-library-name>:<file>`` expands to a path to file ``<file>`` of
library ``<public-library-name>``. If ``<public-library-name>`` is available
in the current workspace, the local file will be used, otherwise the one from
the installed world will be used
- ``lib:<public-library-name>:<file>`` expands to the installation path of
the file ``<file>`` in the library ``<public-library-name>``. If
``<public-library-name>`` is available in the current workspace, the local
file will be used, otherwise the one from the installed world will be used.
- ``lib-private:<library-name>:<file>`` expands to the build path of the file
``<file>`` in the library ``<library-name>``. Both public and private library
names are allowed as long as they refer to libraries within the same project.
- ``libexec:<public-library-name>:<file>`` is the same as ``lib:...`` except
when cross-compiling, in which case it will expand to the file from the host
build context
build context.
- ``libexec-private:<library-name>:<file>`` is the same as ``lib-private:...``
except when cross-compiling, in which case it will expand to the file from the
host build context.
- ``lib-available:<library-name>`` expands to ``true`` or ``false`` depending on
whether the library is available or not. A library is available iff at least
one of the following condition holds:
Expand Down
69 changes: 54 additions & 15 deletions src/dune/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -371,23 +371,44 @@ let expand_and_record acc ~map_exe ~dep_kind ~expansion_kind
match resolve_binary ~loc:(Some loc) t ~prog:s with
| Error fail -> add_fail acc fail
| Ok path -> Some (path_exp path) )
| Macro (Lib, s) -> (
let lib_dep, file = parse_lib_file ~loc s in
Resolved_forms.add_lib_dep acc lib_dep dep_kind;
| Macro (Lib { lib_exec; lib_private }, s) -> (
let lib, file = parse_lib_file ~loc s in
Resolved_forms.add_lib_dep acc lib dep_kind;
match
Artifacts.Public_libs.file_of_lib t.lib_artifacts ~loc ~lib:lib_dep ~file
with
| Ok path -> Some (path_exp path)
| Error e -> add_fail acc { fail = (fun () -> raise e) } )
| Macro (Libexec, s) -> (
let lib_dep, file = parse_lib_file ~loc s in
Resolved_forms.add_lib_dep acc lib_dep dep_kind;
match
Artifacts.Public_libs.file_of_lib t.lib_artifacts ~loc ~lib:lib_dep ~file
if lib_private then
let open Result.O in
let* lib = Lib.DB.resolve (Scope.libs t.scope) (loc, lib) in
let current_project_name = Scope.name t.scope
and referenced_project_name =
Lib.info lib |> Lib_info.status |> Lib_info.Status.project_name
in
if
Option.equal Dune_project.Name.equal (Some current_project_name)
referenced_project_name
then
Ok (Path.relative (Lib_info.src_dir (Lib.info lib)) file)
else
Error
(User_error.E
(User_error.make ~loc
[ Pp.textf
"The variable \"lib-private\" can only refer to \
libraries within the same project. The current \
project's name is %S, but the reference is to %s."
(Dune_project.Name.to_string_hum current_project_name)
( match referenced_project_name with
| Some name ->
"\"" ^ Dune_project.Name.to_string_hum name ^ "\""
| None -> "an external library" )
]))
else
Artifacts.Public_libs.file_of_lib t.lib_artifacts ~loc ~lib ~file
with
| Error e -> add_fail acc { fail = (fun () -> raise e) }
| Ok path ->
if (not Sys.win32) || Filename.extension s = ".exe" then
(* TODO: The [exec = true] case is currently not handled correctly and
does not match the documentation. *)
if (not lib_exec) || (not Sys.win32) || Filename.extension s = ".exe"
then
Some (path_exp path)
else
let path_exe = Path.extend_basename path ~suffix:".exe" in
Expand All @@ -400,7 +421,25 @@ let expand_and_record acc ~map_exe ~dep_kind ~expansion_kind
(let+ () = Build.path path in
path_exp path)
in
add_ddep dep )
add_ddep dep
| Error e -> (
match lib_private with
| true -> add_fail acc { fail = (fun () -> raise e) }
| false ->
if Lib.DB.available (Scope.libs t.scope) lib then
let fail () =
raise
(User_error.raise ~loc
[ Pp.textf
"The library %S is not public. The variable \"lib\" \
expands to the file's installation path which is not \
defined for private libraries."
(Lib_name.to_string lib)
])
in
add_fail acc { fail }
else
add_fail acc { fail = (fun () -> raise e) } ) )
| Macro (Lib_available, s) ->
let lib = Lib_name.of_string_exn ~loc:(Some loc) s in
Resolved_forms.add_lib_dep acc lib Optional;
Expand Down
23 changes: 17 additions & 6 deletions src/dune/pform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,10 @@ module Macro = struct
| Exe
| Dep
| Bin
| Lib
| Libexec
| Lib of
{ lib_exec : bool
; lib_private : bool
}
| Lib_available
| Version
| Read
Expand All @@ -70,8 +72,11 @@ module Macro = struct
| Exe -> string "Exe"
| Dep -> string "Dep"
| Bin -> string "Bin"
| Lib -> string "Lib"
| Libexec -> string "Libexec"
| Lib { lib_private; lib_exec } ->
constr "Lib"
[ record
[ ("lib_exec", bool lib_exec); ("lib_private", bool lib_private) ]
]
| Lib_available -> string "Lib_available"
| Version -> string "Version"
| Read -> string "Read"
Expand Down Expand Up @@ -164,8 +169,14 @@ module Map = struct
String.Map.of_list_exn
( [ ("exe", macro Exe)
; ("bin", macro Bin)
; ("lib", macro Lib)
; ("libexec", macro Libexec)
; ("lib", macro (Lib { lib_exec = false; lib_private = false }))
; ("libexec", macro (Lib { lib_exec = true; lib_private = false }))
; ( "lib-private"
, since ~version:(2, 1)
(Macro.Lib { lib_exec = false; lib_private = true }) )
; ( "libexec-private"
, since ~version:(2, 1)
(Macro.Lib { lib_exec = true; lib_private = true }) )
; ("lib-available", macro Lib_available)
; ("version", macro Version)
; ("read", macro Read)
Expand Down
8 changes: 6 additions & 2 deletions src/dune/pform.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,12 @@ module Macro : sig
| Exe
| Dep
| Bin
| Lib
| Libexec
(* All four combinations are allowed and correspond to variables [lib],
[libexec], [lib-private], and [libexec-private]. *)
| Lib of
{ lib_exec : bool
; lib_private : bool
}
| Lib_available
| Version
| Read
Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -1149,6 +1149,14 @@
test-cases/js_of_ocaml
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected))))))

(rule
(alias lib)
(deps (package dune) (source_tree test-cases/lib))
(action
(chdir
test-cases/lib
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(rule
(alias lib-available)
(deps (package dune) (source_tree test-cases/lib-available))
Expand Down Expand Up @@ -2058,6 +2066,7 @@
(alias install-with-var)
(alias installable-dup-private-libs)
(alias intf-only)
(alias lib)
(alias lib-available)
(alias lib-errors)
(alias link-deps)
Expand Down Expand Up @@ -2277,6 +2286,7 @@
(alias install-with-var)
(alias installable-dup-private-libs)
(alias intf-only)
(alias lib)
(alias lib-available)
(alias lib-errors)
(alias link-deps)
Expand Down
Loading

0 comments on commit 75826d1

Please sign in to comment.