summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2006-01-12 10:18:18 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2006-01-12 10:18:18 +0000
commitdc068cdbe1b43493b81cfbdf25a6e54608f51558 (patch)
treef096129e93aa5a832e8d5c6689b06b4aca8c4219
parent400095d7e7fea8d8d27d860eb9eef89e0bb634e5 (diff)
Sscanf_format gets a type consistent with the type of sscanf.
Adding a function scan_format that scan a string to directely return a format4 value. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7324 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--stdlib/scanf.ml23
-rw-r--r--stdlib/scanf.mli8
2 files changed, 18 insertions, 13 deletions
diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml
index 95b925563..030075ba3 100644
--- a/stdlib/scanf.ml
+++ b/stdlib/scanf.ml
@@ -958,17 +958,22 @@ let kscanf ib ef fmt f =
| 'B' | 'b' ->
let _x = scan_bool max ib in
scan_fmt (stack f (token_bool ib)) (i + 1)
- | 'l' | 'n' | 'L' as typ ->
+ | 'l' | 'n' | 'L' as conv ->
let i = i + 1 in
- if i > lim then scan_fmt (stack f (get_count typ ib)) i else begin
+ if i > lim then scan_fmt (stack f (get_count conv ib)) i else begin
match fmt.[i] with
+ (* This is in fact an integer conversion (e.g. %ld, %ni, or %Lo). *)
| 'd' | 'i' | 'o' | 'u' | 'x' | 'X' as conv ->
let _x = scan_int_conv conv max ib in
- begin match typ with
+ (* Look back to the character that triggered the integer conversion
+ (this character is either 'l', 'n' or 'L'), to find the
+ conversion to apply to the integer token read. *)
+ begin match fmt.[i - 1] with
| 'l' -> scan_fmt (stack f (token_int32 conv ib)) (i + 1)
| 'n' -> scan_fmt (stack f (token_nativeint conv ib)) (i + 1)
| _ -> scan_fmt (stack f (token_int64 conv ib)) (i + 1) end
- | _ -> scan_fmt (stack f (get_count typ ib)) i end
+ (* This is not an integer conversion, but a regular %l, %n or %L. *)
+ | _ -> scan_fmt (stack f (get_count conv ib)) i end
| 'N' as conv ->
scan_fmt (stack f (get_count conv ib)) (i + 1)
| '!' ->
@@ -1037,10 +1042,6 @@ let bscanf_format ib fmt f =
let fresh_fmt1 = String.copy fmt1 in
f (string_to_format fresh_fmt1);;
-let sscanf_format s fmt =
- let fmt = format_to_string fmt in
- let fmt1 = s in
- if not (compatible_format_type fmt1 fmt) then
- bad_input (format_mismatch_err fmt1 fmt) else
- let fresh_fmt1 = String.copy fmt1 in
- string_to_format fresh_fmt1;;
+let sscanf_format s fmt f = bscanf_format (Scanning.from_string s) fmt f;;
+
+let scan_format s fmt = sscanf_format s fmt (fun x -> x);;
diff --git a/stdlib/scanf.mli b/stdlib/scanf.mli
index adf700d1a..646fcccdb 100644
--- a/stdlib/scanf.mli
+++ b/stdlib/scanf.mli
@@ -258,7 +258,6 @@ val kscanf :
val bscanf_format :
Scanning.scanbuf -> ('a, 'b, 'c, 'd) format4 ->
(('a, 'b, 'c, 'd) format4 -> 'e) -> 'e;;
-
(** [bscanf_format ib fmt f] reads a format string token in buffer [ib],
according to the format string [fmt], and applies the function [f] to the
resulting format string value.
@@ -266,6 +265,11 @@ val bscanf_format :
as [fmt]. *)
val sscanf_format :
+ string -> ('a, 'b, 'c, 'd) format4 ->
+ (('a, 'b, 'c, 'd) format4 -> 'e) -> 'e;;
+(** Same as {!Scanf.bscanf}, but inputs from the given string. *)
+
+val scan_format :
string -> ('a, 'b, 'c, 'd) format4 -> ('a, 'b, 'c, 'd) format4;;
-(** Same as {!Scanf.bscanf_format}, but converts the given string to a format
+(** Same as {!Scanf.sscanf_format}, but converts the given string to a format
string. *)