Skip to content

Commit 69263a9

Browse files
alainfrischdra27
authored andcommitted
Option-returning variants of stdlib functions (ocaml#885)
Provide an xxx_opt alternative for functions raising Not_found and many instances of Failure/Invalid_arg. The only exception is the rarely used Buffer.add_substitute, where the [Not_found] can really be interpreted as an error condition. Most new functions are implemented directly (instead of wrapping the raising version). This is for performance reasons and also to avoid destroying the stacktrace (if the function is used in an exception handler). One could instead implement the raising versions on top of the new functions, but there might be a small penalty.
1 parent a029589 commit 69263a9

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+784
-6
lines changed

Changes

+3
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,9 @@ Next version (4.05.0):
2525
List.compare_length_with to avoid full list length computations
2626
(Fabrice Le Fessant)
2727

28+
- GPR#885: Option-returning variants of stdlib functions
29+
(Alain Frisch, review by David Allsopp and Bart Jacobs)
30+
2831
### Tools:
2932

3033
- PR#7333: ocamldoc, use the first sentence of text file as

otherlibs/num/big_int.ml

+15
Original file line numberDiff line numberDiff line change
@@ -336,6 +336,9 @@ let int_of_big_int bi =
336336
if eq_big_int bi monster_big_int then monster_int
337337
else failwith "int_of_big_int";;
338338

339+
let int_of_big_int_opt bi =
340+
try Some (int_of_big_int bi) with Failure _ -> None
341+
339342
let big_int_of_nativeint i =
340343
if i = 0n then
341344
zero_big_int
@@ -359,6 +362,9 @@ let nativeint_of_big_int bi =
359362
then Nativeint.neg i
360363
else failwith "nativeint_of_big_int"
361364

365+
let nativeint_of_big_int_opt bi =
366+
try Some (nativeint_of_big_int bi) with Failure _ -> None
367+
362368
let big_int_of_int32 i = big_int_of_nativeint (Nativeint.of_int32 i)
363369

364370
let int32_of_big_int bi =
@@ -367,6 +373,9 @@ let int32_of_big_int bi =
367373
then Nativeint.to_int32 i
368374
else failwith "int32_of_big_int"
369375

376+
let int32_of_big_int_opt bi =
377+
try Some (int32_of_big_int bi) with Failure _ -> None
378+
370379
let big_int_of_int64 i =
371380
if Sys.word_size = 64 then
372381
big_int_of_nativeint (Int64.to_nativeint i)
@@ -406,6 +415,9 @@ let int64_of_big_int bi =
406415
else failwith "int64_of_big_int"
407416
end
408417

418+
let int64_of_big_int_opt bi =
419+
try Some (int64_of_big_int bi) with Failure _ -> None
420+
409421
(* Coercion with nat type *)
410422
let nat_of_big_int bi =
411423
if bi.sign = -1
@@ -460,6 +472,9 @@ let sys_big_int_of_string s ofs len =
460472
let big_int_of_string s =
461473
sys_big_int_of_string s 0 (String.length s)
462474

475+
let big_int_of_string_opt s =
476+
try Some (big_int_of_string s) with Failure _ -> None
477+
463478
let power_base_nat base nat off len =
464479
if base = 0 then nat_of_int 0 else
465480
if is_zero_nat nat off len || base = 1 then nat_of_int 1 else

otherlibs/num/big_int.mli

+36
Original file line numberDiff line numberDiff line change
@@ -141,6 +141,16 @@ val big_int_of_string : string -> big_int
141141
(** Convert a string to a big integer, in decimal.
142142
The string consists of an optional [-] or [+] sign,
143143
followed by one or several decimal digits. *)
144+
(* TODO: document error condition. *)
145+
146+
val big_int_of_string_opt: string -> big_int option
147+
(** Convert a string to a big integer, in decimal.
148+
The string consists of an optional [-] or [+] sign,
149+
followed by one or several decimal digits. Other the function
150+
returns [None].
151+
@since 4.05
152+
*)
153+
144154

145155
(** {6 Conversions to and from other numerical types} *)
146156

@@ -161,6 +171,13 @@ val int_of_big_int : big_int -> int
161171
Raises [Failure "int_of_big_int"] if the big integer
162172
is not representable as a small integer. *)
163173

174+
val int_of_big_int_opt: big_int -> int option
175+
(** Convert a big integer to a small integer (type [int]). Return
176+
[None] if the big integer is not representable as a small
177+
integer.
178+
@since 4.05
179+
*)
180+
164181
val big_int_of_int32 : int32 -> big_int
165182
(** Convert a 32-bit integer to a big integer. *)
166183

@@ -175,16 +192,35 @@ val int32_of_big_int : big_int -> int32
175192
Raises [Failure] if the big integer is outside the
176193
range \[-2{^31}, 2{^31}-1\]. *)
177194

195+
val int32_of_big_int_opt: big_int -> int32 option
196+
(** Convert a big integer to a 32-bit integer. Return [None] if the
197+
big integer is outside the range \[-2{^31}, 2{^31}-1\].
198+
@since 4.05
199+
*)
200+
178201
val nativeint_of_big_int : big_int -> nativeint
179202
(** Convert a big integer to a native integer.
180203
Raises [Failure] if the big integer is outside the
181204
range [[Nativeint.min_int, Nativeint.max_int]]. *)
182205

206+
val nativeint_of_big_int_opt: big_int -> nativeint option
207+
(** Convert a big integer to a native integer. Return [None] if the
208+
big integer is outside the range [[Nativeint.min_int,
209+
Nativeint.max_int]];
210+
@since 4.05
211+
*)
212+
183213
val int64_of_big_int : big_int -> int64
184214
(** Convert a big integer to a 64-bit integer.
185215
Raises [Failure] if the big integer is outside the
186216
range \[-2{^63}, 2{^63}-1\]. *)
187217

218+
val int64_of_big_int_opt: big_int -> int64 option
219+
(** Convert a big integer to a 64-bit integer. Return [None] if the
220+
big integer is outside the range \[-2{^63}, 2{^63}-1\].
221+
@since 4.05
222+
*)
223+
188224
val float_of_big_int : big_int -> float
189225
(** Returns a floating-point number approximating the
190226
given big integer. *)

otherlibs/num/num.ml

+15
Original file line numberDiff line numberDiff line change
@@ -354,6 +354,11 @@ let int_of_num = function
354354
| Big_int bi -> int_of_big_int bi
355355
| Ratio r -> int_of_ratio r
356356

357+
let int_of_num_opt = function
358+
Int i -> Some i
359+
| Big_int bi -> int_of_big_int_opt bi
360+
| Ratio r -> (try Some (int_of_ratio r) with Failure _ -> None)
361+
357362
and num_of_int i =
358363
if i = monster_int
359364
then Big_int (big_int_of_int i)
@@ -370,12 +375,18 @@ and num_of_nat nat =
370375
then Int (nth_digit_nat nat 0)
371376
else Big_int (big_int_of_nat nat)
372377

378+
let nat_of_num_opt x =
379+
try Some (nat_of_num x) with Failure _ -> None
380+
373381
(* Coercion with big_int type *)
374382
let big_int_of_num = function
375383
Int i -> big_int_of_int i
376384
| Big_int bi -> bi
377385
| Ratio r -> big_int_of_ratio r
378386

387+
let big_int_of_num_opt x =
388+
try Some (big_int_of_num x) with Failure _ -> None
389+
379390
let string_of_big_int_for_num bi =
380391
if !approx_printing_flag
381392
then approx_big_int !floating_precision bi
@@ -389,6 +400,7 @@ let string_of_normalized_num = function
389400
| Ratio r -> string_of_ratio r
390401
let string_of_num n =
391402
string_of_normalized_num (cautious_normalize_num_when_printing n)
403+
392404
let num_of_string s =
393405
try
394406
let flag = !normalize_ratio_flag in
@@ -401,6 +413,9 @@ let num_of_string s =
401413
with Failure _ ->
402414
failwith "num_of_string"
403415

416+
let num_of_string_opt s =
417+
try Some (num_of_string s) with Failure _ -> None
418+
404419
(* Coercion with float type *)
405420
let float_of_num = function
406421
Int i -> float i

otherlibs/num/num.mli

+13
Original file line numberDiff line numberDiff line change
@@ -159,14 +159,27 @@ val num_of_string : string -> num
159159
Raise [Failure "num_of_string"] if the given string is not
160160
a valid representation of an integer *)
161161

162+
val num_of_string_opt: string -> num option
163+
(** Convert a string to a number.
164+
Return [None] if the given string is not
165+
a valid representation of an integer.
166+
167+
@since 4.05
168+
*)
169+
162170
(** {6 Coercions between numerical types} *)
163171

172+
(* TODO: document the functions below (truncating behavior and error conditions). *)
173+
164174
val int_of_num : num -> int
175+
val int_of_num_opt: num -> int option
165176
val num_of_int : int -> num
166177
val nat_of_num : num -> nat
178+
val nat_of_num_opt: num -> nat option
167179
val num_of_nat : nat -> num
168180
val num_of_big_int : big_int -> num
169181
val big_int_of_num : num -> big_int
182+
val big_int_of_num_opt: num -> big_int option
170183
val ratio_of_num : num -> ratio
171184
val num_of_ratio : ratio -> num
172185
val float_of_num : num -> float

otherlibs/threads/pervasives.ml

+18
Original file line numberDiff line numberDiff line change
@@ -246,10 +246,21 @@ let bool_of_string = function
246246
| "false" -> false
247247
| _ -> invalid_arg "bool_of_string"
248248

249+
let bool_of_string_opt = function
250+
| "true" -> Some true
251+
| "false" -> Some false
252+
| _ -> None
253+
249254
let string_of_int n =
250255
format_int "%d" n
251256

252257
external int_of_string : string -> int = "caml_int_of_string"
258+
259+
let int_of_string_opt s =
260+
(* TODO: provide this directly as a non-raising primitive. *)
261+
try Some (int_of_string s)
262+
with Failure _ -> None
263+
253264
external string_get : string -> int -> char = "%string_safe_get"
254265

255266
let valid_float_lexem s =
@@ -267,6 +278,11 @@ let string_of_float f = valid_float_lexem (format_float "%.12g" f);;
267278

268279
external float_of_string : string -> float = "caml_float_of_string"
269280

281+
let float_of_string_opt s =
282+
(* TODO: provide this directly as a non-raising primitive. *)
283+
try Some (float_of_string s)
284+
with Failure _ -> None
285+
270286
(* List operations -- more in module List *)
271287

272288
let rec ( @ ) l1 l2 =
@@ -563,7 +579,9 @@ let prerr_newline () = output_char stderr '\n'; flush stderr
563579

564580
let read_line () = flush stdout; input_line stdin
565581
let read_int () = int_of_string(read_line())
582+
let read_int_opt () = int_of_string_opt(read_line())
566583
let read_float () = float_of_string(read_line())
584+
let read_float_opt () = float_of_string_opt(read_line())
567585

568586
(* Operations on large files *)
569587

stdlib/bytes.ml

+24-1
Original file line numberDiff line numberDiff line change
@@ -116,7 +116,7 @@ let rec unsafe_blits dst pos sep seplen = function
116116
let concat sep = function
117117
[] -> empty
118118
| l -> let seplen = length sep in
119-
unsafe_blits
119+
unsafe_blits
120120
(create (sum_lengths 0 seplen l))
121121
0 sep seplen l
122122

@@ -226,11 +226,22 @@ let rec index_rec s lim i c =
226226

227227
let index s c = index_rec s (length s) 0 c
228228

229+
let rec index_rec_opt s lim i c =
230+
if i >= lim then None else
231+
if unsafe_get s i = c then Some i else index_rec_opt s lim (i + 1) c
232+
233+
let index_opt s c = index_rec_opt s (length s) 0 c
234+
229235
let index_from s i c =
230236
let l = length s in
231237
if i < 0 || i > l then invalid_arg "String.index_from / Bytes.index_from" else
232238
index_rec s l i c
233239

240+
let index_from_opt s i c =
241+
let l = length s in
242+
if i < 0 || i > l then invalid_arg "String.index_from_opt / Bytes.index_from_opt" else
243+
index_rec_opt s l i c
244+
234245
let rec rindex_rec s i c =
235246
if i < 0 then raise Not_found else
236247
if unsafe_get s i = c then i else rindex_rec s (i - 1) c
@@ -243,6 +254,18 @@ let rindex_from s i c =
243254
else
244255
rindex_rec s i c
245256

257+
let rec rindex_rec_opt s i c =
258+
if i < 0 then None else
259+
if unsafe_get s i = c then Some i else rindex_rec_opt s (i - 1) c
260+
261+
let rindex_opt s c = rindex_rec_opt s (length s - 1) c
262+
263+
let rindex_from_opt s i c =
264+
if i < -1 || i >= length s then
265+
invalid_arg "String.rindex_from_opt / Bytes.rindex_from_opt"
266+
else
267+
rindex_rec_opt s i c
268+
246269

247270
let contains_from s i c =
248271
let l = length s in

stdlib/bytes.mli

+27
Original file line numberDiff line numberDiff line change
@@ -193,12 +193,22 @@ val index : bytes -> char -> int
193193
194194
Raise [Not_found] if [c] does not occur in [s]. *)
195195

196+
val index_opt: bytes -> char -> int option
197+
(** [index_opt s c] returns the index of the first occurrence of byte [c]
198+
in [s] or [None] if [c] does not occur in [s].
199+
@since 4.05 *)
200+
196201
val rindex : bytes -> char -> int
197202
(** [rindex s c] returns the index of the last occurrence of byte [c]
198203
in [s].
199204
200205
Raise [Not_found] if [c] does not occur in [s]. *)
201206

207+
val rindex_opt: bytes -> char -> int option
208+
(** [rindex_opt s c] returns the index of the last occurrence of byte [c]
209+
in [s] or [None] if [c] does not occur in [s].
210+
@since 4.05 *)
211+
202212
val index_from : bytes -> int -> char -> int
203213
(** [index_from s i c] returns the index of the first occurrence of
204214
byte [c] in [s] after position [i]. [Bytes.index s c] is
@@ -207,6 +217,14 @@ val index_from : bytes -> int -> char -> int
207217
Raise [Invalid_argument] if [i] is not a valid position in [s].
208218
Raise [Not_found] if [c] does not occur in [s] after position [i]. *)
209219

220+
val index_from_opt: bytes -> int -> char -> int option
221+
(** [index_from _opts i c] returns the index of the first occurrence of
222+
byte [c] in [s] after position [i] or [None] if [c] does not occur in [s] after position [i].
223+
[Bytes.index_opt s c] is equivalent to [Bytes.index_from_opt s 0 c].
224+
225+
Raise [Invalid_argument] if [i] is not a valid position in [s].
226+
@since 4.05 *)
227+
210228
val rindex_from : bytes -> int -> char -> int
211229
(** [rindex_from s i c] returns the index of the last occurrence of
212230
byte [c] in [s] before position [i+1]. [rindex s c] is equivalent
@@ -215,6 +233,15 @@ val rindex_from : bytes -> int -> char -> int
215233
Raise [Invalid_argument] if [i+1] is not a valid position in [s].
216234
Raise [Not_found] if [c] does not occur in [s] before position [i+1]. *)
217235

236+
val rindex_from_opt: bytes -> int -> char -> int option
237+
(** [rindex_from_opt s i c] returns the index of the last occurrence
238+
of byte [c] in [s] before position [i+1] or [None] if [c] does not
239+
occur in [s] before position [i+1]. [rindex_opt s c] is equivalent to
240+
[rindex_from s (Bytes.length s - 1) c].
241+
242+
Raise [Invalid_argument] if [i+1] is not a valid position in [s].
243+
@since 4.05 *)
244+
218245
val contains : bytes -> char -> bool
219246
(** [contains s c] tests if byte [c] appears in [s]. *)
220247

0 commit comments

Comments
 (0)