Skip to content

Commit

Permalink
dune-configurator: respect $PKG_CONFIG
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro committed Apr 3, 2023
1 parent e70afff commit e2745eb
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 3 deletions.
7 changes: 6 additions & 1 deletion otherlibs/configurator/src/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -620,7 +620,12 @@ module Pkg_config = struct
}

let get c =
Option.map (which c "pkg-config") ~f:(fun pkg_config ->
let pkg_config_exe_name =
match Sys.getenv "PKG_CONFIG" with
| s -> s
| exception Not_found -> "pkg-config"
in
Option.map (which c pkg_config_exe_name) ~f:(fun pkg_config ->
{ pkg_config; configurator = c })

type package_conf =
Expand Down
12 changes: 10 additions & 2 deletions src/dune_rules/pkg_config.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
open Import

let pkg_config_binary sctx =
let env = Super_context.context_env sctx in
match Env.get env "PKG_CONFIG" with
| None -> "pkg-config"
| Some s -> s

module Query = struct
type t =
| Libs of string
Expand Down Expand Up @@ -27,8 +33,9 @@ module Query = struct
let read t sctx ~dir =
let open Action_builder.O in
let* bin =
let pkg_config = pkg_config_binary sctx in
Action_builder.of_memo
@@ Super_context.resolve_program sctx ~loc:None ~dir "pkg-config"
@@ Super_context.resolve_program sctx ~loc:None ~dir pkg_config
in
match bin with
| Error _ -> Action_builder.return (default t)
Expand All @@ -42,7 +49,8 @@ end
let gen_rule sctx ~loc ~dir query =
let open Memo.O in
let* bin =
Super_context.resolve_program sctx ~loc:(Some loc) ~dir "pkg-config"
let pkg_config = pkg_config_binary sctx in
Super_context.resolve_program sctx ~loc:(Some loc) ~dir pkg_config
in
match bin with
| Error _ -> Memo.return @@ Error `Not_found
Expand Down

0 comments on commit e2745eb

Please sign in to comment.