Skip to content

Commit

Permalink
[configurator] more flexible #define parsing
Browse files Browse the repository at this point in the history
Allow duplicate values for the same key as long as they are interpreted
as the same value.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Aug 25, 2020
1 parent 6a0725a commit 239e3ad
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 19 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
Unreleased
----------

- configurator: More flexible probing of `#define`. We allow duplicate values in
the object file, as long as they are the same after parsing. (#3739,
@rgrinberg)

2.7.0 (13/08/2020)
------------------

Expand Down
2 changes: 2 additions & 0 deletions otherlibs/configurator/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,8 @@ module Option = struct
else
None

let some x = Some x

let try_with f =
match f () with
| exception _ -> None
Expand Down
50 changes: 31 additions & 19 deletions otherlibs/configurator/src/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -466,10 +466,6 @@ module C_define = struct
| Switch of bool
| Int of int
| String of string

let switch b = Switch b

let int i = Int i
end

let extract_program ?prelude includes vars =
Expand Down Expand Up @@ -532,28 +528,44 @@ const char *s%i = "BEGIN-%i-false-END";
let extract_values obj_file vars =
let values =
Io.with_lexbuf_from_file obj_file ~f:(Extract_obj.extract [])
|> Int.Map.of_list_exn
|> List.fold_left ~init:Int.Map.empty ~f:(fun acc (key, v) ->
Int.Map.update acc ~key ~f:(function
| None -> Some [ v ]
| Some vs -> Some (v :: vs)))
in
List.mapi vars ~f:(fun i (name, t) ->
let raw_val =
let raw_vals =
match Int.Map.find values i with
| None -> die "Unable to get value for %s" name
| Some v -> v
| None -> die "Unable to get value for %s" name
in
let value =
match t with
| Type.Switch -> Bool.of_string raw_val |> Option.map ~f:Value.switch
| Int -> Int.of_string raw_val |> Option.map ~f:Value.int
| String -> Some (String raw_val)
let parse_val_or_exn f =
let f x =
match f x with
| Some s -> s
| None ->
die
"Unable to read variable %S of type %s. Invalid value %S in %s \
found"
name (Type.name t) x obj_file
in
let vs =
List.map ~f:(fun x -> (x, f x)) raw_vals
|> List.sort_uniq ~cmp:(fun (_, x) (_, y) -> compare x y)
in
match vs with
| [] -> assert false
| [ (_, v) ] -> v
| vs ->
let vs = List.map ~f:fst vs in
die "Duplicate values for %s:\n%s" name
(vs |> List.map ~f:(sprintf "- %s") |> String.concat ~sep:"\n")
in
let value =
match value with
| Some v -> v
| None ->
die
"Unable to read variable %S of type %s. Invalid value %S in %s \
found"
name (Type.name t) raw_val obj_file
match t with
| Type.Switch -> Value.Switch (parse_val_or_exn Bool.of_string)
| Int -> Value.Int (parse_val_or_exn Int.of_string)
| String -> String (parse_val_or_exn Option.some)
in
(name, value))

Expand Down

0 comments on commit 239e3ad

Please sign in to comment.