Skip to content

Commit

Permalink
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 44e4d21 commit 2deca02
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 8 deletions.
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
19 changes: 13 additions & 6 deletions src/dune_rules/pkg_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,18 @@ 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 list =
match Env.get env "PKG_CONFIG_ARGN" with
| Some s -> [ As (String.split_on_char ~sep:' ' s) ]
| None -> []
in
Hidden_deps Dep.(Set.singleton universe)
::
(match t with
| Libs lib -> [ A "--libs"; A lib ]
| Cflags lib -> [ A "--cflags"; A lib ])
:: (env_args
@
match t with
| Libs lib -> [ A "--libs"; A lib ]
| Cflags lib -> [ A "--cflags"; A lib ])

let default = function
| Libs lib -> [ sprintf "-l%s" lib ]
Expand Down Expand Up @@ -60,8 +66,9 @@ let gen_rule sctx ~loc ~dir query =
| Error _ -> Memo.return @@ Error `Not_found
| Ok _ as bin ->
let command =
let env = Super_context.context_env sctx 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 2deca02

Please sign in to comment.