1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Caml Special Light *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1995 Institut National de Recherche en Informatique et *)
|
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Module [Pervasives]: the initially opened module *)
|
|
|
|
|
|
|
|
(* This module provides the built-in types (numbers, booleans,
|
|
|
|
strings, exceptions, references, lists, arrays, input-output channels, ...)
|
|
|
|
and the basic operations over these types.
|
|
|
|
|
|
|
|
This module is automatically opened at the beginning of each compilation.
|
|
|
|
All components of this module can therefore be referred by their short
|
|
|
|
name, without prefixing them by [Pervasives]. *)
|
|
|
|
|
|
|
|
(*** Predefined types *)
|
|
|
|
|
|
|
|
(*- type int *)
|
|
|
|
(* The type of integer numbers. *)
|
|
|
|
(*- type char *)
|
|
|
|
(* The type of characters. *)
|
|
|
|
(*- type string *)
|
|
|
|
(* The type of character strings. *)
|
|
|
|
(*- type float *)
|
|
|
|
(* The type of floating-point numbers. *)
|
|
|
|
(*- type bool *)
|
|
|
|
(* The type of booleans (truth values). *)
|
|
|
|
(*- type unit = () *)
|
|
|
|
(* The type of the unit value. *)
|
|
|
|
(*- type exn *)
|
|
|
|
(* The type of exception values. *)
|
|
|
|
(*- type 'a array *)
|
|
|
|
(* The type of arrays whose elements have type ['a]. *)
|
|
|
|
(*- type 'a list = [] | :: of 'a * 'a list *)
|
|
|
|
(* The type of lists whose elements have type ['a]. *)
|
|
|
|
type 'a option = None | Some of 'a
|
|
|
|
(* The type of optional values. *)
|
|
|
|
(*- type ('a, 'b, 'c) format *)
|
|
|
|
(* The type of format strings. ['a] is the type of the parameters
|
|
|
|
of the format, ['c] is the result type for the [printf]-style
|
|
|
|
function, and ['b] is the type of the first argument given to
|
|
|
|
[%a] and [%t] printing functions (see module [Printf]). *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Exceptions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
external raise : exn -> 'a = "%raise"
|
|
|
|
(* Raise the given exception value *)
|
|
|
|
(*- exception Invalid_argument of string *)
|
|
|
|
(* Exception raised by library functions to signal that the given
|
|
|
|
arguments do not make sense. *)
|
|
|
|
(*- exception Failure of string *)
|
|
|
|
(* Exception raised by library functions to signal that they are
|
|
|
|
undefined on the given arguments. *)
|
|
|
|
(*- exception Not_found *)
|
|
|
|
(* Exception raised by search functions when the desired object
|
|
|
|
could not be found. *)
|
|
|
|
(*- exception Out_of_memory *)
|
|
|
|
(* Exception raised by the garbage collector
|
|
|
|
when there is insufficient memory to complete the computation. *)
|
|
|
|
(*- exception Sys_error of string *)
|
|
|
|
(* Exception raised by the input/output functions to report
|
|
|
|
an operating system error. *)
|
|
|
|
(*- exception End_of_file *)
|
|
|
|
(* Exception raised by input functions to signal that the
|
|
|
|
end of file has been reached. *)
|
|
|
|
(*- exception Division_by_zero *)
|
|
|
|
(* Exception raised by division and remainder operations
|
|
|
|
when their second argument is null. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
exception Exit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* This exception is not raised by any library function. It is
|
|
|
|
provided for use in your programs. *)
|
|
|
|
|
|
|
|
val invalid_arg: string -> 'a
|
|
|
|
(* Raise exception [Invalid_argument] with the given string. *)
|
|
|
|
val failwith: string -> 'a
|
|
|
|
(* Raise exception [Failure] with the given string. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Comparisons *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
external (=) : 'a -> 'a -> bool = "%equal"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [e1 = e2] tests for structural equality of [e1] and [e2].
|
|
|
|
Mutable structures (e.g. references and arrays) are equal
|
|
|
|
if and only if their current contents are structurally equal,
|
|
|
|
even if the two mutable objects are not the same physical object.
|
|
|
|
Equality between functional values raises [Invalid_argument].
|
|
|
|
Equality between cyclic data structures may not terminate. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (<>) : 'a -> 'a -> bool = "%notequal"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Negation of [prefix =]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (<) : 'a -> 'a -> bool = "%lessthan"
|
|
|
|
external (>) : 'a -> 'a -> bool = "%greaterthan"
|
|
|
|
external (<=) : 'a -> 'a -> bool = "%lessequal"
|
|
|
|
external (>=) : 'a -> 'a -> bool = "%greaterequal"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Structural ordering functions. These functions coincide with
|
|
|
|
the usual orderings over integer, string and floating-point
|
|
|
|
numbers, and extend them to a total ordering over all types.
|
|
|
|
The ordering is compatible with [prefix =]. As in the case
|
|
|
|
of [prefix =], mutable structures are compared by contents.
|
|
|
|
Comparison between functional values raises [Invalid_argument].
|
|
|
|
Comparison between cyclic structures may not terminate. *)
|
1995-07-25 04:39:02 -07:00
|
|
|
external compare: 'a -> 'a -> int = "compare" "noalloc"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [compare x y] returns [0] if [x=y], a negative integer if
|
|
|
|
[x<y], and a positive integer if [x>y]. The same restrictions
|
|
|
|
as for [=] apply. [compare] can be used as the comparison function
|
|
|
|
required by the [Set] and [Map] modules. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val min: 'a -> 'a -> 'a
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the smaller of the two arguments. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val max: 'a -> 'a -> 'a
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the greater of the two arguments. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (==) : 'a -> 'a -> bool = "%eq"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [e1 == e2] tests for physical equality of [e1] and [e2].
|
|
|
|
On integers and characters, it is the same as structural
|
|
|
|
equality. On mutable structures, [e1 == e2] is true if and only if
|
|
|
|
physical modification of [e1] also affects [e2].
|
|
|
|
On non-mutable structures, the behavior of [prefix ==] is
|
|
|
|
implementation-dependent, except that [e1 == e2] implies
|
|
|
|
[e1 = e2]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (!=) : 'a -> 'a -> bool = "%noteq"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Negation of [prefix ==]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Boolean operations *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
external not : bool -> bool = "%boolnot"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The boolean negation. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (&) : bool -> bool -> bool = "%sequand"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The boolean ``and''. Evaluation is sequential, left-to-right:
|
|
|
|
in [e1 & e2], [e1] is eavaluated first, and if it returns [false],
|
|
|
|
[e2] is not evaluated at all. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (or) : bool -> bool -> bool = "%sequor"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The boolean ``or''. Evaluation is sequential, left-to-right:
|
|
|
|
in [e1 or e2], [e1] is eavaluated first, and if it returns [true],
|
|
|
|
[e2] is not evaluated at all. *)
|
|
|
|
|
|
|
|
(*** Integer arithmetic *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Integers are 31 bits wide (or 63 bits on 64-bit processors).
|
|
|
|
All operations are taken modulo $2^{31}$ (or $2^{63}$).
|
|
|
|
They do not fail on overflow. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
external (~-) : int -> int = "%negint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Unary negation. You can also write [-e] instead of [~-e]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external succ : int -> int = "%succint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [succ x] is [x+1]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external pred : int -> int = "%predint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [pred x] is [x-1]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (+) : int -> int -> int = "%addint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Integer addition. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (-) : int -> int -> int = "%subint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Integer subtraction. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external ( * ) : int -> int -> int = "%mulint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Integer multiplication. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (/) : int -> int -> int = "%divint"
|
|
|
|
external (mod) : int -> int -> int = "%modint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Integer division and remainder.
|
|
|
|
Raise [Division_by_zero] if the second argument is 0.
|
|
|
|
If one of the arguments is negative, the result is
|
|
|
|
platform-dependent. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val abs : int -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the absolute value of the argument. *)
|
|
|
|
|
|
|
|
(** Bitwise operations *)
|
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
external (land) : int -> int -> int = "%andint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Bitwise logical and. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (lor) : int -> int -> int = "%orint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Bitwise logical or. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (lxor) : int -> int -> int = "%xorint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Bitwise logical exclusive or. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val lnot: int -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Bitwise logical negation. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (lsl) : int -> int -> int = "%lslint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [n lsl m] shifts [n] to the left by [m] bits. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (lsr) : int -> int -> int = "%lsrint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [n lsr m] shifts [n] to the right by [m] bits.
|
|
|
|
This is a logical shift: zeroes are inserted regardless of
|
|
|
|
the sign of [n].*)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (asr) : int -> int -> int = "%asrint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [n asr m] shifts [n] to the right by [m] bits.
|
|
|
|
This is an arithmetic shift: the sign bit of [n] is replicated. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Floating-point arithmetic *)
|
|
|
|
|
|
|
|
(* On most platforms, Caml's floating-point numbers follow the
|
|
|
|
IEEE 754 standard, using double precision (64 bits) numbers.
|
|
|
|
Floating-point operations do not fail on overflow or underflow,
|
|
|
|
but return denormal numbers. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-07-02 09:46:44 -07:00
|
|
|
external (~-.) : float -> float = "%negfloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Unary negation. You can also write [-.e] instead of [~-.e]. *)
|
1995-07-02 09:46:44 -07:00
|
|
|
external (+.) : float -> float -> float = "%addfloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Floating-point addition *)
|
1995-07-02 09:46:44 -07:00
|
|
|
external (-.) : float -> float -> float = "%subfloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Floating-point subtraction *)
|
1995-07-02 09:46:44 -07:00
|
|
|
external ( *. ) : float -> float -> float = "%mulfloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Floating-point multiplication *)
|
1995-07-02 09:46:44 -07:00
|
|
|
external (/.) : float -> float -> float = "%divfloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Floating-point division. Raise [Division_by_zero] if second
|
|
|
|
argument is null. *)
|
1995-07-27 10:44:04 -07:00
|
|
|
external ( ** ) : float -> float -> float = "power_float" "pow" "float"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Exponentiation *)
|
1995-07-27 10:44:04 -07:00
|
|
|
external exp : float -> float = "exp_float" "exp" "float"
|
|
|
|
external log : float -> float = "log_float" "log" "float"
|
|
|
|
external sqrt : float -> float = "sqrt_float" "sqrt" "float"
|
|
|
|
external sin : float -> float = "sin_float" "sin" "float"
|
|
|
|
external cos : float -> float = "cos_float" "cos" "float"
|
|
|
|
external tan : float -> float = "tan_float" "tan" "float"
|
|
|
|
external asin : float -> float = "asin_float" "asin" "float"
|
|
|
|
external acos : float -> float = "acos_float" "acos" "float"
|
|
|
|
external atan : float -> float = "atan_float" "atan" "float"
|
|
|
|
external atan2 : float -> float -> float = "atan2_float" "atan2" "float"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Usual transcendental functions on floating-point numbers. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val abs_float : float -> float
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the absolute value of the argument. *)
|
1995-07-11 01:54:13 -07:00
|
|
|
external float : int -> float = "%floatofint"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Convert an integer to floating-point. *)
|
1995-07-11 01:54:13 -07:00
|
|
|
external truncate : float -> int = "%intoffloat"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Truncate the given floating-point number to an integer.
|
|
|
|
The result is unspecified if it falls outside the
|
|
|
|
range of representable integers. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** String operations *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* More string operations are provided in module [String]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
val (^) : string -> string -> string
|
|
|
|
(* String concatenation. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** String conversion functions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val string_of_bool : bool -> string
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the string representation of a boolean. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val string_of_int : int -> string
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the string representation of an integer, in decimal. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external int_of_string : string -> int = "int_of_string"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Convert the given string to an integer.
|
|
|
|
The string is read in decimal (by default) or in hexadecimal,
|
|
|
|
octal or binary if the string begins with [0x], [0o] or [0b]
|
|
|
|
respectively.
|
|
|
|
Raise [Failure "int_of_string"] if the given string is not
|
|
|
|
a valid representation of an integer. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val string_of_float : float -> string
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the string representation of a floating-point number. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external float_of_string : string -> float = "float_of_string"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Convert the given string to a float.
|
|
|
|
The result is unspecified if the given string is not
|
|
|
|
a valid representation of a float. *)
|
|
|
|
|
|
|
|
(*** Pair operations *)
|
|
|
|
|
|
|
|
external fst : 'a * 'b -> 'a = "%field0"
|
|
|
|
(* Return the first component of a pair. *)
|
|
|
|
external snd : 'a * 'b -> 'b = "%field1"
|
|
|
|
(* Return the second component of a pair. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** List operations *)
|
|
|
|
|
|
|
|
(* More list operations are provided in module [List]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val (@) : 'a list -> 'a list -> 'a list
|
1995-08-09 06:15:01 -07:00
|
|
|
(* List concatenation. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Input/output *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type in_channel
|
|
|
|
type out_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The types of input channels and output channels. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val stdin : in_channel
|
|
|
|
val stdout : out_channel
|
|
|
|
val stderr : out_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The standard input, standard output, and standard error output
|
|
|
|
for the process. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(** Output functions on standard output *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val print_char : char -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a character on standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val print_string : string -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a string on standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val print_int : int -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print an integer, in decimal, on standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val print_float : float -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a floating-point number, in decimal, on standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val print_endline : string -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a string, followed by a newline character, on
|
|
|
|
standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val print_newline : unit -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a newline character on standard output, and flush
|
|
|
|
standard output. This can be used to simulate line
|
|
|
|
buffering of standard output. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(** Output functions on standard error *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val prerr_char : char -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a character on standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val prerr_string : string -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a string on standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val prerr_int : int -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print an integer, in decimal, on standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val prerr_float : float -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a floating-point number, in decimal, on standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val prerr_endline : string -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a string, followed by a newline character on standard error
|
|
|
|
and flush standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val prerr_newline : unit -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Print a newline character on standard error, and flush
|
|
|
|
standard error. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(** Input functions on standard input *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val read_line : unit -> string
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Flush standard output, then read characters from standard input
|
|
|
|
until a newline character is encountered. Return the string of
|
|
|
|
all characters read, without the newline character at the end. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val read_int : unit -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Flush standard output, then read one line from standard input
|
|
|
|
and convert it to an integer. Raise [Failure "int_of_string"]
|
|
|
|
if the line read is not a valid representation of an integer. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val read_float : unit -> float
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Flush standard output, then read one line from standard input
|
|
|
|
and convert it to a floating-point number.
|
|
|
|
The result is unspecified if the line read is not a valid
|
|
|
|
representation of a floating-point number. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(** General output functions *)
|
1995-05-04 05:48:07 -07:00
|
|
|
|
|
|
|
type open_flag =
|
1995-08-10 05:18:40 -07:00
|
|
|
Open_rdonly | Open_wronly | Open_append
|
|
|
|
| Open_creat | Open_trunc | Open_excl
|
1995-05-04 05:48:07 -07:00
|
|
|
| Open_binary | Open_text
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Opening modes for [open_out_gen] and [open_in_gen].
|
|
|
|
- [Open_rdonly]: open for reading.
|
|
|
|
- [Open_wronly]: open for writing.
|
|
|
|
- [Open_append]: open for appending.
|
|
|
|
- [Open_creat]: create the file if it does not exist.
|
|
|
|
- [Open_trunc]: empty the file if it already exists.
|
|
|
|
- [Open_excl]: fail if the file already exists.
|
|
|
|
- [Open_binary]: open in binary mode (no conversion).
|
|
|
|
- [Open_text]: open in text mode (may perform conversions). *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val open_out : string -> out_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Open the named file for writing, and return a new output channel
|
|
|
|
on that file, positionned at the beginning of the file. The
|
|
|
|
file is truncated to zero length if it already exists. It
|
|
|
|
is created if it does not already exists.
|
|
|
|
Raise [Sys_error] if the file could not be opened. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val open_out_bin : string -> out_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Same as [open_out], but the file is opened in binary mode,
|
|
|
|
so that no translation takes place during writes. On operating
|
|
|
|
systems that do not distinguish between text mode and binary
|
|
|
|
mode, this function behaves like [open_out]. *)
|
1995-05-04 05:48:07 -07:00
|
|
|
val open_out_gen : open_flag list -> int -> string -> out_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [open_out_gen mode rights filename] opens the file named
|
|
|
|
[filename] for writing, as above. The extra argument [mode]
|
|
|
|
specify the opening mode. The extra argument [rights] specifies
|
|
|
|
the file permissions, in case the file must be created.
|
|
|
|
[open_out] and [open_out_bin] are special cases of this function. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external flush : out_channel -> unit = "flush"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Flush the buffer associated with the given output channel,
|
|
|
|
performing all pending writes on that channel.
|
|
|
|
Interactive programs must be careful about flushing standard
|
|
|
|
output and standard error at the right time. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external output_char : out_channel -> char -> unit = "output_char"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Write the character on the given output channel. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val output_string : out_channel -> string -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Write the string on the given output channel. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val output : out_channel -> string -> int -> int -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [output chan buff ofs len] writes [len] characters from string
|
|
|
|
[buff], starting at offset [ofs], to the output channel [chan].
|
|
|
|
Raise [Invalid_argument "output"] if [ofs] and [len] do not
|
|
|
|
designate a valid substring of [buff]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external output_byte : out_channel -> int -> unit = "output_char"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Write one 8-bit integer (as the single character with that code)
|
|
|
|
on the given output channel. The given integer is taken modulo
|
|
|
|
256. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external output_binary_int : out_channel -> int -> unit = "output_int"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Write one integer in binary format on the given output channel.
|
|
|
|
The only reliable way to read it back is through the
|
|
|
|
[input_binary_int] function. The format is compatible across
|
|
|
|
all machines for a given version of Caml Light. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external output_value : out_channel -> 'a -> unit = "output_value"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Write the representation of a structured value of any type
|
|
|
|
to a channel. Circularities and sharing inside the value
|
|
|
|
are detected and preserved. The object can be read back,
|
|
|
|
by the function [input_value]. The format is compatible across
|
|
|
|
all machines for a given version of Caml Light. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external seek_out : out_channel -> int -> unit = "seek_out"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [seek_out chan pos] sets the current writing position to [pos]
|
|
|
|
for channel [chan]. This works only for regular files. On
|
|
|
|
files of other kinds (such as terminals, pipes and sockets),
|
|
|
|
the behavior is unspecified. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external pos_out : out_channel -> int = "pos_out"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the current writing position for the given channel. *)
|
|
|
|
external out_channel_length : out_channel -> int = "channel_size"
|
|
|
|
(* Return the total length (number of characters) of the
|
|
|
|
given channel. This works only for regular files. On files of
|
|
|
|
other kinds, the result is meaningless. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external close_out : out_channel -> unit = "close_out"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Close the given channel, flushing all buffered write operations.
|
|
|
|
The behavior is unspecified if any of the functions above is
|
|
|
|
called on a closed channel. *)
|
|
|
|
|
|
|
|
(** General input functions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val open_in : string -> in_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Open the named file for reading, and return a new input channel
|
|
|
|
on that file, positionned at the beginning of the file.
|
|
|
|
Raise [Sys_error] if the file could not be opened. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val open_in_bin : string -> in_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Same as [open_in], but the file is opened in binary mode,
|
|
|
|
so that no translation takes place during reads. On operating
|
|
|
|
systems that do not distinguish between text mode and binary
|
|
|
|
mode, this function behaves like [open_in]. *)
|
1995-05-04 05:48:07 -07:00
|
|
|
val open_in_gen : open_flag list -> int -> string -> in_channel
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [open_in_gen mode rights filename] opens the file named
|
|
|
|
[filename] for reading, as above. The extra arguments
|
|
|
|
[mode] and [rights] specify the opening mode and file permissions.
|
|
|
|
[open_in] and [open_in_bin] are special cases of this function. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external input_char : in_channel -> char = "input_char"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Read one character from the given input channel.
|
|
|
|
Raise [End_of_file] if there are no more characters to read. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val input_line : in_channel -> string
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Read characters from the given input channel, until a
|
|
|
|
newline character is encountered. Return the string of
|
|
|
|
all characters read, without the newline character at the end.
|
|
|
|
Raise [End_of_file] if the end of the file is reached
|
|
|
|
at the beginning of line. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val input : in_channel -> string -> int -> int -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [input chan buff ofs len] attempts to read [len] characters
|
|
|
|
from channel [chan], storing them in string [buff], starting at
|
|
|
|
character number [ofs]. It returns the actual number of characters
|
|
|
|
read, between 0 and [len] (inclusive).
|
|
|
|
A return value of 0 means that the end of file was reached.
|
|
|
|
A return value between 0 and [len] exclusive means that
|
|
|
|
no more characters were available at that time; [input] must be
|
|
|
|
called again to read the remaining characters, if desired.
|
|
|
|
Exception [Invalid_argument "input"] is raised if [ofs] and [len]
|
|
|
|
do not designate a valid substring of [buff]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val really_input : in_channel -> string -> int -> int -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [really_input chan buff ofs len] reads [len] characters
|
|
|
|
from channel [chan], storing them in string [buff], starting at
|
|
|
|
character number [ofs]. Raise [End_of_file] if
|
|
|
|
the end of file is reached before [len] characters have been read.
|
|
|
|
Raise [Invalid_argument "really_input"] if
|
|
|
|
[ofs] and [len] do not designate a valid substring of [buff]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external input_byte : in_channel -> int = "input_char"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Same as [input_char], but return the 8-bit integer representing
|
|
|
|
the character.
|
|
|
|
Raise [End_of_file] if an end of file was reached. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external input_binary_int : in_channel -> int = "input_int"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Read an integer encoded in binary format from the given input
|
|
|
|
channel. See [output_binary_int].
|
|
|
|
Raise [End_of_file] if an end of file was reached while reading the
|
|
|
|
integer. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external input_value : in_channel -> 'a = "input_value"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Read the representation of a structured value, as produced
|
|
|
|
by [output_value] or [output_compact_value], and return
|
|
|
|
the corresponding value.
|
|
|
|
This is not type-safe. The type of the returned object is
|
|
|
|
not ['a] properly speaking: the returned object has one
|
|
|
|
unique type, which cannot be determined at compile-time.
|
|
|
|
The programmer should explicitly give the expected type of the
|
|
|
|
returned value, using the following syntax:
|
|
|
|
[(input_value chan : type)].
|
|
|
|
The behavior is unspecified if the object in the file does not
|
|
|
|
belong to the given type. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external seek_in : in_channel -> int -> unit = "seek_in"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [seek_in chan pos] sets the current reading position to [pos]
|
|
|
|
for channel [chan]. This works only for regular files. On
|
|
|
|
files of other kinds, the behavior is unspecified. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external pos_in : in_channel -> int = "pos_in"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the current reading position for the given channel. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external in_channel_length : in_channel -> int = "channel_size"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the total length (number of characters) of the
|
|
|
|
given channel. This works only for regular files. On files of
|
|
|
|
other kinds, the result is meaningless. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external close_in : in_channel -> unit = "close_in"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Close the given channel. Anything can happen if any of the
|
|
|
|
functions above is called on a closed channel. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** References *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type 'a ref = { mutable contents: 'a }
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The type of references (mutable indirection cells) containing
|
|
|
|
a value of type ['a]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external ref: 'a -> 'a ref = "%makeblock"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return a fresh reference containing the given value. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (!): 'a ref -> 'a = "%field0"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [!r] returns the current contents of reference [r].
|
|
|
|
Could be defined as [fun r -> r.contents]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external (:=): 'a ref -> 'a -> unit = "%setfield0"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [r := a] stores the value of [a] in reference [r].
|
|
|
|
Could be defined as [fun r v -> r.contents <- v]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external incr: int ref -> unit = "%incr"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Increment the integer contained in the given reference.
|
|
|
|
Could be defined as [fun r -> r := succ !r]. *)
|
1995-05-05 03:05:18 -07:00
|
|
|
external decr: int ref -> unit = "%decr"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Decrement the integer contained in the given reference.
|
|
|
|
Could be defined as [fun r -> r := pred !r]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(*** Program termination *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val exit : int -> 'a
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Flush all pending writes on [stdout] and [stderr],
|
|
|
|
and terminate the process, returning the given status code
|
|
|
|
to the operating system (usually 0 to indicate no errors,
|
|
|
|
and a small positive integer to indicate failure.)
|
|
|
|
This function should be called at
|
|
|
|
the end of all standalone programs that output results on
|
|
|
|
[stdout] or [stderr]; otherwise, the program may appear
|
|
|
|
to produce no output, or its output may be truncated. *)
|
|
|
|
|
|
|
|
(*--*)
|
|
|
|
|
|
|
|
(*** For system use only, not for the casual user *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val unsafe_really_input: in_channel -> string -> int -> int -> unit
|