diff options
-rw-r--r-- | stdlib/scanf.ml | 24 | ||||
-rw-r--r-- | stdlib/scanf.mli | 9 |
2 files changed, 19 insertions, 14 deletions
diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml index a738cdd37..f27d80808 100644 --- a/stdlib/scanf.ml +++ b/stdlib/scanf.ml @@ -135,15 +135,16 @@ end;; exception Scan_failure of string;; let bad_input s = raise (Scan_failure s);; -let bad_input_eof () = bad_input "eof";; let bad_input_char c = bad_input (String.make 1 c);; let bad_input_escape c = bad_input (Printf.sprintf "illegal escape character %c" c);; -let scanf_bad_input ib s = - let i = Scanning.char_count ib in - bad_input (Printf.sprintf "scanf: bad input at char number %i: %s" i s);; +let scanf_bad_input ib = function + | Scan_failure s | Failure s -> + let i = Scanning.char_count ib in + bad_input (Printf.sprintf "scanf: bad input at char number %i: %s" i s) + | x -> raise x;; let bad_format fmt i fc = invalid_arg @@ -479,7 +480,7 @@ external string_of_format : ('a, 'b, 'c) format -> string = "%identity";; tokens as specified by the format. When it founds one token, it converts it as specified, remembers the converted value as a future argument to the function [f], and continues scanning. - If the scanning or some convertion fail, the scanning function + If the scanning or some convertion fails, the scanning function aborts and applies the scanning buffer and a string that explains the error to the error continuation [ef]. *) let kscanf ib (fmt : ('a, 'b, 'c) format) f ef = @@ -493,22 +494,21 @@ let kscanf ib (fmt : ('a, 'b, 'c) format) f ef = let rec scan f i = if i > lim then f else match fmt.[i] with + | c when Scanning.end_of_input ib -> raise End_of_file | '%' -> scan_width f (i + 1) | '@' as t -> let i = i + 1 in if i > lim then bad_format fmt (i - 1) t else begin match fmt.[i] with - | c when Scanning.end_of_input ib -> bad_input_eof () | '@' as c when Scanning.peek_char ib = c -> Scanning.next_char ib; scan f (i + 1) | c when Scanning.peek_char ib = c -> Scanning.next_char ib; scan f (i + 1) - | c -> bad_input_char c end + | c -> bad_input_char (Scanning.peek_char ib) end | ' ' | '\r' | '\t' | '\n' -> skip_whites ib; scan f (i + 1) - | c when Scanning.end_of_input ib -> bad_input_eof () | c when Scanning.peek_char ib = c -> Scanning.next_char ib; scan f (i + 1) - | c -> bad_input_char c + | c -> bad_input_char (Scanning.peek_char ib) and scan_width f i = if i > lim then bad_format fmt i '%' else @@ -528,11 +528,11 @@ let kscanf ib (fmt : ('a, 'b, 'c) format) f ef = and scan_conversion max f i = if i > lim then bad_format fmt i fmt.[lim - 1] else match fmt.[i] with + | c when Scanning.end_of_input ib -> raise End_of_file | 'c' | 'C' as conv -> let x = if conv = 'c' then scan_char max ib else scan_Char max ib in scan (stack f (token_char ib)) (i + 1) - | c when Scanning.end_of_input ib -> bad_input_eof () | '%' as fc when Scanning.peek_char ib = fc -> Scanning.next_char ib; scan f (i + 1) | '%' -> bad_input_char (Scanning.peek_char ib) @@ -584,9 +584,11 @@ let kscanf ib (fmt : ('a, 'b, 'c) format) f ef = | _ -> i - 1, [] in Scanning.reset_token ib; + let v = try scan (fun () -> f) 0 with - | Scan_failure s | Failure s -> stack (delay ef ib) s in + | (Scan_failure _ | Failure _ | End_of_file) as exc -> + stack (delay ef ib) exc in return v;; let bscanf ib fmt f = kscanf ib fmt f scanf_bad_input;; diff --git a/stdlib/scanf.mli b/stdlib/scanf.mli index 49c6d9965..b8d46ac0e 100644 --- a/stdlib/scanf.mli +++ b/stdlib/scanf.mli @@ -57,10 +57,13 @@ val bscanf : Raise [Scanf.Scan_failure] if the given input does not match the format. + Raise [End_of_file] if the end of input is encountered while scanning + and the input matches the given format so far. + The format is a character string which contains three types of objects: - plain characters, which are simply matched with the - input channel, + characters of the input, - conversion specifications, each of which causes reading and conversion of one argument for [f], - scanning indications to specify boundaries of tokens and the @@ -132,9 +135,9 @@ val scanf : ('a, Scanning.scanbuf, 'b) format -> 'a -> 'b;; val kscanf : Scanning.scanbuf -> ('a, 'b, 'c) format -> 'a -> - (Scanning.scanbuf -> string -> 'c) -> 'c;; + (Scanning.scanbuf -> exn -> 'c) -> 'c;; (** Same as {!Scanf.bscanf}, but takes an additional function argument [ef] that is called in case of error: if the scanning process or some convertion fails, the scanning function aborts and applies the - scanning buffer and a string that explains the error to the error + scanning buffer and the exception that aborted evaluation to the error continuation [ef]. *) |