summaryrefslogtreecommitdiffstats
path: root/stdlib/scanf.ml
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2003-03-02 23:03:15 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2003-03-02 23:03:15 +0000
commit1f955eb17e76e0a4f87bbb50d48a552866b85ebc (patch)
tree6bb4e9244490d99d22f2deed72fa845a7e790d75 /stdlib/scanf.ml
parente132cd1f7a07a41dc7dbddea7453a86e6ebb5ea4 (diff)
Format %S now understands continuation newlines (\\\n).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5412 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/scanf.ml')
-rw-r--r--stdlib/scanf.ml16
1 files changed, 14 insertions, 2 deletions
diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml
index b479e9d5b..bb37064f8 100644
--- a/stdlib/scanf.ml
+++ b/stdlib/scanf.ml
@@ -475,9 +475,21 @@ let scan_String max ib =
| '"', false (* '"' helping Emacs *) ->
Scanning.next_char ib; max - 1
| '\\', false ->
- Scanning.next_char ib; loop false (scan_backslash_char (max - 1) ib)
+ Scanning.next_char ib;
+ skip_spaces true (max - 1)
+ | c, false -> loop false (Scanning.store_char ib c max)
+ | c, _ -> bad_input_char c
+ and skip_spaces s max =
+ if max = 0 || Scanning.end_of_input ib then bad_input "a string" else
+ let c = Scanning.checked_peek_char ib in
+ match c, s with
+ | '\n', true ->
+ Scanning.next_char ib;
+ skip_spaces false (max - 1)
+ | ' ', false -> skip_spaces false (max - 1)
+ | '\\', false -> loop true max
| c, false -> loop false (Scanning.store_char ib c max)
- | c, _ -> bad_input_char c in
+ | _ -> loop false (scan_backslash_char (max - 1) ib) in
loop true max;;
let scan_bool max ib =