File tree Expand file tree Collapse file tree 2 files changed +22
-8
lines changed
otherlibs/configurator/src Expand file tree Collapse file tree 2 files changed +22
-8
lines changed Original file line number Diff line number Diff line change @@ -616,6 +616,7 @@ let which t prog =
616
616
module Pkg_config = struct
617
617
type nonrec t =
618
618
{ pkg_config : string
619
+ ; pkg_config_args : string list
619
620
; configurator : t
620
621
}
621
622
@@ -625,8 +626,13 @@ module Pkg_config = struct
625
626
| s -> s
626
627
| exception Not_found -> " pkg-config"
627
628
in
629
+ let pkg_config_args =
630
+ match Sys. getenv " PKG_CONFIG_ARGN" with
631
+ | s -> String. split ~on: ' ' s
632
+ | exception Not_found -> []
633
+ in
628
634
Option. map (which c pkg_config_exe_name) ~f: (fun pkg_config ->
629
- { pkg_config; configurator = c })
635
+ { pkg_config; pkg_config_args; configurator = c })
630
636
631
637
type package_conf =
632
638
{ libs : string list
@@ -688,7 +694,8 @@ module Pkg_config = struct
688
694
let run what =
689
695
match
690
696
String. trim
691
- (Process. run_capture_exn c ~dir ?env t.pkg_config [ what; package ])
697
+ (Process. run_capture_exn c ~dir ?env t.pkg_config
698
+ (t.pkg_config_args @ [ what; package ]))
692
699
with
693
700
| "" -> []
694
701
| s -> String. extract_blank_separated_words s
Original file line number Diff line number Diff line change @@ -20,12 +20,18 @@ module Query = struct
20
20
| Libs s -> sprintf " %s.libs" s
21
21
| Cflags s -> sprintf " %s.cflags" s
22
22
23
- let to_args t : _ Command.Args.t list =
23
+ let to_args t ~env : _ Command.Args. t list =
24
+ let env_args : _ Command.Args.t list =
25
+ match Env. get env " PKG_CONFIG_ARGN" with
26
+ | Some s -> [ As (String. split_on_char ~sep: ' ' s) ]
27
+ | None -> []
28
+ in
24
29
Hidden_deps Dep. (Set. singleton universe)
25
- ::
26
- (match t with
27
- | Libs lib -> [ A " --libs" ; A lib ]
28
- | Cflags lib -> [ A " --cflags" ; A lib ])
30
+ :: (env_args
31
+ @
32
+ match t with
33
+ | Libs lib -> [ A " --libs" ; A lib ]
34
+ | Cflags lib -> [ A " --cflags" ; A lib ])
29
35
30
36
let default = function
31
37
| Libs lib -> [ sprintf " -l%s" lib ]
@@ -60,8 +66,9 @@ let gen_rule sctx ~loc ~dir query =
60
66
| Error _ -> Memo. return @@ Error `Not_found
61
67
| Ok _ as bin ->
62
68
let command =
69
+ let env = Super_context. context_env sctx in
63
70
Command. run ~dir: (Path. build dir) ~stdout_to: (Query. file ~dir query) bin
64
- (Query. to_args query)
71
+ (Query. to_args ~env query)
65
72
in
66
73
let + () = Super_context. add_rule sctx ~loc ~dir command in
67
74
Ok ()
You can’t perform that action at this time.
0 commit comments