Skip to content

Commit 7d1d881

Browse files
committed
code review
1 parent 069d6a0 commit 7d1d881

File tree

4 files changed

+55
-15
lines changed

4 files changed

+55
-15
lines changed

driver/compenv.ml

+11-3
Original file line numberDiff line numberDiff line change
@@ -206,9 +206,17 @@ let read_OCAMLPARAM ppf position =
206206

207207
(* inlining *)
208208
| "inline" ->
209-
Float_arg_helper.parse v
210-
"Bad syntax in OCAMLPARAM for 'inline'"
211-
inline_threshold
209+
let module F = Float_arg_helper in
210+
begin match F.parse_no_error v inline_threshold with
211+
| F.Ok -> ()
212+
| F.Parse_failed exn ->
213+
let error =
214+
Printf.sprintf "bad syntax for \"inline\": %s"
215+
(Printexc.to_string exn)
216+
in
217+
Location.print_warning Location.none ppf
218+
(Warnings.Bad_env_variable ("OCAMLPARAM", error))
219+
end
212220

213221
(* color output *)
214222
| "color" ->

utils/arg_helper.ml

+25-11
Original file line numberDiff line numberDiff line change
@@ -42,45 +42,59 @@ end) = struct
4242
| exception Not_found -> true
4343
| _index -> false
4444

45-
let parse str ~help_text ~update =
45+
exception Parse_failure of exn
46+
47+
let parse_exn str ~update =
4648
let values = Misc.Stdlib.String.split str ~on:',' in
4749
let parsed =
4850
List.fold_left (fun acc value ->
4951
match String.index value '=' with
5052
| exception Not_found ->
5153
begin match S.Value.of_string value with
5254
| value -> { acc with default = value }
53-
| exception exn ->
54-
fatal (Printf.sprintf "%s: %s" (Printexc.to_string exn) help_text)
55+
| exception exn -> raise (Parse_failure exn)
5556
end
5657
| equals ->
5758
let key_value_pair = value in
5859
let length = String.length key_value_pair in
59-
if equals <= 0 || equals >= length - 1 then begin
60-
fatal help_text
60+
assert (equals >= 0 && equals < length);
61+
if equals = 0 then begin
62+
raise (Parse_failure (
63+
Failure "Missing key in argument specification"))
6164
end;
6265
let key =
6366
let key = String.sub key_value_pair 0 equals in
6467
try S.Key.of_string key
65-
with exn ->
66-
fatal (Printf.sprintf "%s: %s"
67-
(Printexc.to_string exn) help_text)
68+
with exn -> raise (Parse_failure exn)
6869
in
6970
let value =
7071
let value =
7172
String.sub key_value_pair (equals + 1) (length - equals - 1)
7273
in
7374
try S.Value.of_string value
74-
with exn ->
75-
fatal (Printf.sprintf "%s: %s"
76-
(Printexc.to_string exn) help_text)
75+
with exn -> raise (Parse_failure exn)
7776
in
7877
{ acc with override = S.Key.Map.add key value acc.override })
7978
!update
8079
values
8180
in
8281
update := parsed
8382

83+
let parse str ~help_text ~update =
84+
match parse_exn str ~update with
85+
| () -> ()
86+
| exception (Parse_failure exn) ->
87+
fatal (Printf.sprintf "%s: %s" (Printexc.to_string exn) help_text)
88+
89+
type parse_result =
90+
| Ok
91+
| Parse_failed of exn
92+
93+
let parse_no_error str ~update =
94+
match parse_exn str ~update with
95+
| () -> Ok
96+
| exception (Parse_failure exn) -> Parse_failed exn
97+
8498
let get ~key parsed =
8599
match S.Key.Map.find key parsed.override with
86100
| provided -> provided

utils/arg_helper.mli

+7-1
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ module Make (S : sig
3333
module Value : sig
3434
type t
3535

36-
(** The textual representation of a value must not contain '=' or ','. *)
36+
(** The textual representation of a value must not contain ','. *)
3737
val of_string : string -> t
3838
end
3939
end) : sig
@@ -46,5 +46,11 @@ end) : sig
4646

4747
val parse : string -> help_text:string -> update:parsed ref -> unit
4848

49+
type parse_result =
50+
| Ok
51+
| Parse_failed of exn
52+
53+
val parse_no_error : string -> update:parsed ref -> parse_result
54+
4955
val get : key:S.Key.t -> parsed -> S.Value.t
5056
end

utils/clflags.mli

+12
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,12 @@ module Int_arg_helper : sig
1818
}
1919

2020
val parse : string -> help_text:string -> update:parsed ref -> unit
21+
22+
type parse_result =
23+
| Ok
24+
| Parse_failed of exn
25+
val parse_no_error : string -> update:parsed ref -> parse_result
26+
2127
val get : key:int -> parsed -> int
2228
end
2329

@@ -29,6 +35,12 @@ module Float_arg_helper : sig
2935
}
3036

3137
val parse : string -> help_text:string -> update:parsed ref -> unit
38+
39+
type parse_result =
40+
| Ok
41+
| Parse_failed of exn
42+
val parse_no_error : string -> update:parsed ref -> parse_result
43+
3244
val get : key:int -> parsed -> float
3345
end
3446

0 commit comments

Comments
 (0)