Skip to content

Commit

Permalink
feat(pkg-config): allow reading PKG_CONFIG_ARGN
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro committed May 16, 2023
1 parent 23ec454 commit 8850129
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 9 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
Unreleased
----------

- Read `pkg-config` arguments from the `PKG_CONFIG_ARGN` environment variable
(#1492, #7734, @anmonteiro)

- Correctly set `MANPATH` in `dune exec`. Previously, we would use the `bin/`
directory of the context. (#7655, @rgrinberg)

Expand Down
11 changes: 9 additions & 2 deletions otherlibs/configurator/src/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -616,6 +616,7 @@ let which t prog =
module Pkg_config = struct
type nonrec t =
{ pkg_config : string
; pkg_config_args : string list
; configurator : t
}

Expand All @@ -625,8 +626,13 @@ module Pkg_config = struct
| s -> s
| exception Not_found -> "pkg-config"
in
let pkg_config_args =
match Sys.getenv "PKG_CONFIG_ARGN" with
| s -> String.split ~on:' ' s
| exception Not_found -> []
in
Option.map (which c pkg_config_exe_name) ~f:(fun pkg_config ->
{ pkg_config; configurator = c })
{ pkg_config; pkg_config_args; configurator = c })

type package_conf =
{ libs : string list
Expand Down Expand Up @@ -688,7 +694,8 @@ module Pkg_config = struct
let run what =
match
String.trim
(Process.run_capture_exn c ~dir ?env t.pkg_config [ what; package ])
(Process.run_capture_exn c ~dir ?env t.pkg_config
(t.pkg_config_args @ [ what; package ]))
with
| "" -> []
| s -> String.extract_blank_separated_words s
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@ These tests show that setting `PKG_CONFIG_ARGN` passes extra args to `pkg-config
-> process exited with code 0
-> stdout:
| gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --cflags gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --static --cflags gtk+-quartz-3.0
-> process exited with code 0
-> stdout:
| --cflags
| --static--cflags
| gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --libs gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --static --libs gtk+-quartz-3.0
-> process exited with code 0
-> stdout:
| --libs
| --static--libs
| gtk+-quartz-3.0
22 changes: 19 additions & 3 deletions src/dune_rules/pkg_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,14 @@ module Query = struct
| Libs s -> sprintf "%s.libs" s
| Cflags s -> sprintf "%s.cflags" s

let to_args t : _ Command.Args.t list =
let to_args t ~env : _ Command.Args.t list =
let env_args : _ Command.Args.t =
match Env.get env "PKG_CONFIG_ARGN" with
| Some s -> As (String.split_on_char ~sep:' ' s)
| None -> Command.Args.empty
in
Hidden_deps Dep.(Set.singleton universe)
:: env_args
::
(match t with
| Libs lib -> [ A "--libs"; A lib ]
Expand Down Expand Up @@ -59,9 +65,19 @@ let gen_rule sctx ~loc ~dir query =
match bin with
| Error _ -> Memo.return @@ Error `Not_found
| Ok _ as bin ->
let command =
let* command =
let+ env =
let* dune_version =
let+ expander = Super_context.expander sctx ~dir in
expander |> Expander.scope |> Scope.project
|> Dune_project.dune_version
in
let* env_node = Super_context.env_node sctx ~dir in
if dune_version >= (3, 8) then Env_node.external_env env_node
else Memo.return Env.empty
in
Command.run ~dir:(Path.build dir) ~stdout_to:(Query.file ~dir query) bin
(Query.to_args query)
(Query.to_args ~env query)
in
let+ () = Super_context.add_rule sctx ~loc ~dir command in
Ok ()
Expand Down

0 comments on commit 8850129

Please sign in to comment.