diff options
author | Pierre Weis <Pierre.Weis@inria.fr> | 2002-06-12 08:31:21 +0000 |
---|---|---|
committer | Pierre Weis <Pierre.Weis@inria.fr> | 2002-06-12 08:31:21 +0000 |
commit | 0505570e3b9af853790257a9fedfc72afd30ea1e (patch) | |
tree | 611625dfc39b2018b7547d345a740f3e8ff23f69 /stdlib/scanf.ml | |
parent | 3d7002adaa2e0156afcab851f12331a27caad825 (diff) |
Introducing a specific exception for formatted input functions.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4922 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/scanf.ml')
-rw-r--r-- | stdlib/scanf.ml | 8 |
1 files changed, 5 insertions, 3 deletions
diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml index 86af010e9..648d27213 100644 --- a/stdlib/scanf.ml +++ b/stdlib/scanf.ml @@ -130,12 +130,14 @@ let from_function f = create f;; end;; (** Formatted input functions. *) +exception Scan_failure of string;; let bad_input ib s = let i = Scanning.char_count ib in - failwith - (Printf.sprintf "scanf: bad input at char number %i%s" - i (if s = "" then s else Printf.sprintf ", while scanning %s" s));; + raise + (Scan_failure + (Printf.sprintf "scanf: bad input at char number %i%s" + i (if s = "" then s else Printf.sprintf ", while scanning %s" s)));; let bad_input_buff ib = bad_input ib (Scanning.token ib);; |