Skip to content

Commit

Permalink
[configurator] Return pkg-config error to clients of new query API.
Browse files Browse the repository at this point in the history
It is very convenient for configuration tools to be able to provide a
better error message to the user when pkg-config fails.

This was suggested by @garrigue.

We take advantage of the newly [undocumented] API in 1.7.2 to modify
its return type, but this could be a problem. If so, we will have to
introduce yet another function if we want this functionality.

We also update `src/configurator/dune` to include transitive
dependencies as suggested by @rgrinberg

Signed-off-by: Emilio Jesus Gallego Arias <e+git@x80.org>
  • Loading branch information
ejgallego committed Feb 27, 2019
1 parent dd7425a commit 9b4ba9a
Show file tree
Hide file tree
Showing 5 changed files with 27 additions and 12 deletions.
2 changes: 1 addition & 1 deletion src/configurator/dune
Original file line number Diff line number Diff line change
Expand Up @@ -3,5 +3,5 @@
(library
(name configurator)
(public_name dune.configurator)
(libraries stdune ocaml_config dune_lang)
(libraries stdune ocaml_config dune_lang dune_caml)
(flags (:standard -safe-string (:include flags/flags.sexp))))
18 changes: 11 additions & 7 deletions src/configurator/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -256,9 +256,6 @@ module Process = struct
let run_command_ok t ?dir ?env cmd =
(run_command t ?dir ?env cmd).exit_code = 0

let run_process_ok t ?dir ?env prog args =
(run_process t ?dir ?env prog args).exit_code = 0

let run t ?dir ?env prog args =
run_command t ?dir ?env (command_line prog args)

Expand Down Expand Up @@ -615,22 +612,29 @@ module Pkg_config = struct
end
| _ -> None
in
if Process.run_process_ok c ~dir ?env t.pkg_config [expr] then
let pc_flags = "--print-errors" in
let { Process.exit_code; stderr; _ } =
Process.run_process c ~dir ?env t.pkg_config [pc_flags; expr] in
if exit_code = 0 then
let run what =
match String.trim (Process.run_capture_exn c ~dir ?env
t.pkg_config [what; package])
with
| "" -> []
| s -> String.split s ~on:' '
in
Some
Ok
{ libs = run "--libs"
; cflags = run "--cflags"
}
else
None
Error stderr

let query t ~package =
match gen_query t ~package ~expr:None with
| Ok p -> Some p
| Error _msg -> None

let query t ~package = gen_query t ~package ~expr:None
let query_expr t ~package ~expr = gen_query t ~package ~expr:(Some expr)
end

Expand Down
9 changes: 8 additions & 1 deletion src/configurator/v1.mli
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,14 @@ module Pkg_config : sig
package may contain a version constraint. For example
"gtk+-3.0 >= 3.18". Returns [None] if [package] is not available *)

val query_expr : t -> package:string -> expr:string -> package_conf option
val query_expr : t
-> package:string
-> expr:string
-> (package_conf, string) Dune_caml.result
(** [query_expr t ~package ~expr] query pkg-config for the
[package]. [expr] may contain a version constraint, for example
"gtk+-3.0 >= 3.18". [package] should be just the name of the
package. Returns [Error error_msg] if [package] is not available *)
end with type configurator := t

module Flags : sig
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,8 @@
(* We'd like to use String.equal but that's OCaml >= 4.03 *)
let not_flag x = not ("--print-errors" = x)

let () =
let args = List.tl (Array.to_list Sys.argv) in
let args = List.filter not_flag args in
Format.printf "%a@."
(Format.pp_print_list Format.pp_print_string) args
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/pkg-config-quoting/run.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
These tests show how various pkg-config invocations get qouted:
$ dune build 2>&1 | awk '/run:.*bin\/pkg-config/{a=1}/stderr/{a=0}a'
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --print-errors gtk+-quartz-3.0
-> process exited with code 0
-> stdout:
| gtk+-quartz-3.0
Expand All @@ -14,7 +14,7 @@ These tests show how various pkg-config invocations get qouted:
-> stdout:
| --libs
| gtk+-quartz-3.0
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config 'gtk+-quartz-3.0 >= 3.18'
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --print-errors 'gtk+-quartz-3.0 >= 3.18'
-> process exited with code 0
-> stdout:
| gtk+-quartz-3.0 >= 3.18
Expand All @@ -28,7 +28,7 @@ These tests show how various pkg-config invocations get qouted:
-> stdout:
| --libs
| gtk+-quartz-3.0 >= 3.18
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config 'gtksourceview-3.0 >= 3.18'
run: $TESTCASE_ROOT/_build/install/default/bin/pkg-config --print-errors 'gtksourceview-3.0 >= 3.18'
-> process exited with code 0
-> stdout:
| gtksourceview-3.0 >= 3.18
Expand Down

0 comments on commit 9b4ba9a

Please sign in to comment.