Module Stdlib.Scanf

Introduction

Functional input with format strings

A simple example

Formatted input as a functional feature

Formatted input channel

module Scanning : sig ... end

Type of formatted input functions

type ('a, 'b, 'c, 'd) scanner = ('aScanning.in_channel'b'c'a -> 'd'd) Stdlib.format6 -> 'c

The type of formatted input scanners: ('a, 'b, 'c, 'd) scanner is the type of a formatted input function that reads from some formatted input channel according to some format string; more precisely, if scan is some formatted input function, then scan ic fmt f applies f to all the arguments specified by format string fmt, when scan has read those arguments from the Scanning.in_channel formatted input channel ic.

For instance, the Scanf.scanf function below has type ('a, 'b, 'c, 'd) scanner, since it is a formatted input function that reads from Scanning.stdin: scanf fmt f applies f to the arguments specified by fmt, reading those arguments from Stdlib.stdin as expected.

If the format fmt has some %r indications, the corresponding formatted input functions must be provided before receiver function f. For instance, if read_elem is an input function for values of type t, then bscanf ic "%r;" read_elem f reads a value v of type t followed by a ';' character, and returns f v.

since
3.10.0
exception Scan_failure of string

When the input can not be read according to the format string specification, formatted input functions typically raise exception Scan_failure.

The general formatted input function

val bscanf : Scanning.in_channel -> ('a'b'c'd) scanner

Format string description

The space character in format strings

Conversion specifications in format strings

Scanning indications in format strings

Exceptions during scanning

Specialised formatted input functions

val sscanf : string -> ('a'b'c'd) scanner

Same as Scanf.bscanf, but reads from the given string.

val scanf : ('a'b'c'd) scanner

Same as Scanf.bscanf, but reads from the predefined formatted input channel Scanf.Scanning.stdin that is connected to Stdlib.stdin.

val kscanf : Scanning.in_channel -> (Scanning.in_channel -> exn -> 'd) -> ('a'b'c'd) scanner

Same as Scanf.bscanf, but takes an additional function argument ef that is called in case of error: if the scanning process or some conversion fails, the scanning function aborts and calls the error handling function ef with the formatted input channel and the exception that aborted the scanning process as arguments.

val ksscanf : string -> (Scanning.in_channel -> exn -> 'd) -> ('a'b'c'd) scanner

Same as Scanf.kscanf but reads from the given string.

since
4.02.0

Reading format strings from input

val bscanf_format : Scanning.in_channel -> ('a'b'c'd'e'f) Stdlib.format6 -> (('a'b'c'd'e'f) Stdlib.format6 -> 'g) -> 'g

bscanf_format ic fmt f reads a format string token from the formatted input channel ic, according to the given format string fmt, and applies f to the resulting format string value. Raise Scan_failure if the format string value read does not have the same type as fmt.

since
3.09.0
val sscanf_format : string -> ('a'b'c'd'e'f) Stdlib.format6 -> (('a'b'c'd'e'f) Stdlib.format6 -> 'g) -> 'g

Same as Scanf.bscanf_format, but reads from the given string.

since
3.09.0
val format_from_string : string -> ('a'b'c'd'e'f) Stdlib.format6 -> ('a'b'c'd'e'f) Stdlib.format6

format_from_string s fmt converts a string argument to a format string, according to the given format string fmt. Raise Scan_failure if s, considered as a format string, does not have the same type as fmt.

since
3.10.0
val unescaped : string -> string

unescaped s return a copy of s with escape sequences (according to the lexical conventions of OCaml) replaced by their corresponding special characters. More precisely, Scanf.unescaped has the following property: for all string s, Scanf.unescaped (String.escaped s) = s.

Always return a copy of the argument, even if there is no escape sequence in the argument. Raise Scan_failure if s is not properly escaped (i.e. s has invalid escape sequences or special characters that are not properly escaped). For instance, Scanf.unescaped "\"" will fail.

since
4.00.0

Deprecated

val fscanf : Stdlib.in_channel -> ('a'b'c'd) scanner
deprecated

Scanf.fscanf is error prone and deprecated since 4.03.0.

This function violates the following invariant of the Scanf module: To preserve scanning semantics, all scanning functions defined in Scanf must read from a user defined Scanning.in_channel formatted input channel.

If you need to read from a Stdlib.in_channel input channel ic, simply define a Scanning.in_channel formatted input channel as in let ib = Scanning.from_channel ic, then use Scanf.bscanf ib as usual.

val kfscanf : Stdlib.in_channel -> (Scanning.in_channel -> exn -> 'd) -> ('a'b'c'd) scanner
deprecated

Scanf.kfscanf is error prone and deprecated since 4.03.0.