Module Pervasives


module Pervasives = struct ... end 
Types
fpclass
= FP_normal Normal number, none of the below
| FP_subnormal Number very close to 0.0, has reduced precision
| FP_zero Number is 0.0 or -0.0
| FP_infinite Number is positive or negative infinity
| FP_nan Not a number: result of an undefined operation
in_channel Abstract
out_channel The types of input channels and output channels.
Abstract
open_flag
= Open_rdonly
| Open_wronly
| Open_append
| Open_creat
| Open_trunc
| Open_excl
| Open_binary
| Open_text
| Open_nonblock 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).
  • Open_nonblock: open in non-blocking mode.

'a ref The type of references (mutable indirection cells) containing a value of type 'a.
= {
contents
(mutable)
:  'a ;
}

Exceptions
Exit This exception is not raised by any library function. It is provided for use in your programs.

Simple values
max_int int
min_int int
The greatest and smallest representable integers.
infinity float
Positive infinity.
neg_infinity float
Negative infinity.
nan float
A special floating-point value denoting the result of an undefined operation such as 0.0 /. 0.0. Stands for ``not a number''.
stdin in_channel
stdout out_channel
stderr out_channel
The standard input, standard output, and standard error output for the process.

Functions

raise : exn -> 'b
Raise the given exception value

invalid_arg : string -> 'c
Raise exception Invalid_argument with the given string.

failwith : string -> 'd
Raise exception Failure with the given string.

= : 'e -> 'e -> bool
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.

<> : 'f -> 'f -> bool
Negation of (=).

< : 'g -> 'g -> bool

> : 'h -> 'h -> bool

<= : 'i -> 'i -> bool

>= : 'j -> 'j -> bool
Structural ordering functions. These functions coincide with the usual orderings over integers, characters, strings and floating-point numbers, and extend them to a total ordering over all types. The ordering is compatible with (=). As in the case of (=), mutable structures are compared by contents. Comparison between functional values raises Invalid_argument. Comparison between cyclic structures may not terminate.

compare : 'k -> 'k -> int
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.

min : 'l -> 'l -> 'l
Return the smaller of the two arguments.

max : 'm -> 'm -> 'm
Return the greater of the two arguments.

== : 'n -> 'n -> bool
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 (==) is implementation-dependent, except that e1 == e2 implies e1 = e2.

!= : 'o -> 'o -> bool
Negation of (==).

not : bool -> bool
The boolean negation.

&& : bool -> bool -> bool

& : bool -> bool -> bool
The boolean ``and''. Evaluation is sequential, left-to-right: in e1 && e2, e1 is evaluated first, and if it returns false, e2 is not evaluated at all.

|| : bool -> bool -> bool

or : bool -> bool -> bool
The boolean ``or''. Evaluation is sequential, left-to-right: in e1 || e2, e1 is evaluated first, and if it returns true, e2 is not evaluated at all.

~- : int -> int
Unary negation. You can also write -e instead of ~-e.

succ : int -> int
succ x is x+1.

pred : int -> int
pred x is x-1.

+ : int -> int -> int
Integer addition.

- : int -> int -> int
Integer subtraction.

* : int -> int -> int
Integer multiplication.

/ : int -> int -> int
Integer division. Raise Division_by_zero if the second argument is 0.

mod : int -> int -> int
Integer remainder. If x >= 0 and y > 0, the result of x mod y satisfies the following properties: 0 <= x mod y < y and x = (x / y) * y + x mod y. If y = 0, x mod y raises Division_by_zero. If x < 0 or y < 0, the result of x mod y is not specified and depends on the platform.

abs : int -> int
Return the absolute value of the argument.

land : int -> int -> int
Bitwise logical and.

lor : int -> int -> int
Bitwise logical or.

lxor : int -> int -> int
Bitwise logical exclusive or.

lnot : int -> int
Bitwise logical negation.

lsl : int -> int -> int
n lsl m shifts n to the left by m bits. The result is unspecified if m < 0 or m >= bitsize, where bitsize is 32 on a 32-bit platform and 64 on a 64-bit platform.

lsr : int -> int -> int
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. The result is unspecified if m < 0 or m >= bitsize.

asr : int -> int -> int
n asr m shifts n to the right by m bits. This is an arithmetic shift: the sign bit of n is replicated. The result is unspecified if m < 0 or m >= bitsize.

~- : float -> float
Unary negation. You can also write -.e instead of ~-.e.

+ : float -> float -> float
Floating-point addition

- : float -> float -> float
Floating-point subtraction

* : float -> float -> float
Floating-point multiplication

/ : float -> float -> float
Floating-point division.

** : float -> float -> float
Exponentiation

sqrt : float -> float
Square root

exp : float -> float

log : float -> float

log10 : float -> float
Exponential, natural logarithm, base 10 logarithm.

cos : float -> float

sin : float -> float

tan : float -> float

acos : float -> float

asin : float -> float

atan : float -> float

atan2 : float -> float -> float
The usual trigonometric functions

cosh : float -> float

sinh : float -> float

tanh : float -> float
The usual hyperbolic trigonometric functions

ceil : float -> float

floor : float -> float
Round the given float to an integer value. floor f returns the greatest integer value less than or equal to f. ceil f returns the least integer value greater than or equal to f.

abs_float : float -> float
Return the absolute value of the argument.

mod_float : float -> float -> float
mod_float a b returns the remainder of a with respect to b. The returned value is a -. n *. b, where n is the quotient a /. b rounded towards zero to an integer.

frexp : float -> float * int
frexp f returns the pair of the significant and the exponent of f. When f is zero, the significant x and the exponent n of f are equal to zero. When f is non-zero, they are defined by f = x *. 2 ** n and 0.5 <= x < 1.0.

ldexp : float -> int -> float
ldexp x n returns x *. 2 ** n.

modf : float -> float * float
modf f returns the pair of the fractional and integral part of f.

float : int -> float

float_of_int : int -> float
Convert an integer to floating-point.

truncate : float -> int

int_of_float : float -> int
Truncate the given floating-point number to an integer. The result is unspecified if it falls outside the range of representable integers.

classify_float : float -> fpclass
Return the class of the given floating-point number: normal, subnormal, zero, infinite, or not a number.

^ : string -> string -> string
String concatenation.

int_of_char : char -> int
Return the ASCII code of the argument.

char_of_int : int -> char
Return the character with the given ASCII code. Raise Invalid_argument "char_of_int" if the argument is outside the range 0--255.

ignore : 'p -> unit
Discard the value of its argument and return (). For instance, ignore(f x) discards the result of the side-effecting function f. It is equivalent to f x; (), except that the latter may generate a compiler warning; writing ignore(f x) instead avoids the warning.

string_of_bool : bool -> string
Return the string representation of a boolean.

bool_of_string : string -> bool
Convert the given string to a boolean. Raise Invalid_argument "bool_of_string" if the string is not "true" or "false".

string_of_int : int -> string
Return the string representation of an integer, in decimal.

int_of_string : string -> int
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.

string_of_float : float -> string
Return the string representation of a floating-point number.

float_of_string : string -> float
Convert the given string to a float. The result is unspecified if the given string is not a valid representation of a float.

fst : 'q * 'r -> 'q
Return the first component of a pair.

snd : 's * 't -> 't
Return the second component of a pair.

@ : 'u list -> 'u list -> 'u list
List concatenation.

print_char : char -> unit
Print a character on standard output.

print_string : string -> unit
Print a string on standard output.

print_int : int -> unit
Print an integer, in decimal, on standard output.

print_float : float -> unit
Print a floating-point number, in decimal, on standard output.

print_endline : string -> unit
Print a string, followed by a newline character, on standard output.

print_newline : unit -> unit
Print a newline character on standard output, and flush standard output. This can be used to simulate line buffering of standard output.

prerr_char : char -> unit
Print a character on standard error.

prerr_string : string -> unit
Print a string on standard error.

prerr_int : int -> unit
Print an integer, in decimal, on standard error.

prerr_float : float -> unit
Print a floating-point number, in decimal, on standard error.

prerr_endline : string -> unit
Print a string, followed by a newline character on standard error and flush standard error.

prerr_newline : unit -> unit
Print a newline character on standard error, and flush standard error.

read_line : unit -> string
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.

read_int : unit -> int
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.

read_float : unit -> float
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.

open_out : string -> out_channel
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.

open_out_bin : string -> out_channel
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.

open_out_gen : mode:open_flag list ->
perm:int -> string -> out_channel

Open the named file for writing, as above. The extra argument mode specify the opening mode. The extra argument perm specifies the file permissions, in case the file must be created. open_out and open_out_bin are special cases of this function.

flush : out_channel -> unit
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.

output_char : out_channel -> char -> unit
Write the character on the given output channel.

output_string : out_channel -> string -> unit
Write the string on the given output channel.

output : out_channel -> buf:string -> pos:int -> len:int -> unit
Write len characters from string buf, starting at offset pos, to the given output channel. Raise Invalid_argument "output" if pos and len do not designate a valid substring of buf.

output_byte : out_channel -> int -> unit
Write one 8-bit integer (as the single character with that code) on the given output channel. The given integer is taken modulo 256.

output_binary_int : out_channel -> int -> unit
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 Objective Caml.

output_value : out_channel -> 'v -> unit
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. See the description of module Marshal for more information. output_value is equivalent to Marshal.to_channel with an empty list of flags.

seek_out : out_channel -> int -> unit
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.

pos_out : out_channel -> int
Return the current writing position for the given channel.

out_channel_length : out_channel -> int
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.

close_out : out_channel -> unit
Close the given channel, flushing all buffered write operations. A Sys_error exception is raised if any of the functions above is called on a closed channel.

set_binary_mode_out : out_channel -> bool -> unit
set_binary_mode_out oc true sets the channel oc to binary mode: no translations take place during output. set_binary_mode_out oc false sets the channel oc to text mode: depending on the operating system, some translations may take place during output. For instance, under Windows, end-of-lines will be translated from \n to \r\n. This function has no effect under operating systems that do not distinguish between text mode and binary mode.

open_in : string -> in_channel
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.

open_in_bin : string -> in_channel
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.

open_in_gen : mode:open_flag list -> perm:int -> string -> in_channel
Open the named file for reading, as above. The extra arguments mode and perm specify the opening mode and file permissions. open_in and open_in_bin are special cases of this function.

input_char : in_channel -> char
Read one character from the given input channel. Raise End_of_file if there are no more characters to read.

input_line : in_channel -> string
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.

input : in_channel -> buf:string -> pos:int -> len:int -> int
Read up to len characters from the given channel, storing them in string buf, starting at character number pos. 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 not all requested len characters were read, either because no more characters were available at that time, or because the implementation found it convenient to do a partial read; input must be called again to read the remaining characters, if desired. (See also Pervasives.really_input for reading exactly len characters.) Exception Invalid_argument "input" is raised if pos and len do not designate a valid substring of buf.

really_input : in_channel -> buf:string -> pos:int -> len:int -> unit
Read len characters from the given channel, storing them in string buf, starting at character number pos. Raise End_of_file if the end of file is reached before len characters have been read. Raise Invalid_argument "really_input" if pos and len do not designate a valid substring of buf.

input_byte : in_channel -> int
Same as input_char, but return the 8-bit integer representing the character. Raise End_of_file if an end of file was reached.

input_binary_int : in_channel -> int
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.

input_value : in_channel -> 'w
Read the representation of a structured value, as produced by output_value, and return the corresponding value. This function is identical to Marshal.from_channel; see the description of module Marshal for more information, in particular concerning the lack of type safety.

seek_in : in_channel -> int -> unit
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.

pos_in : in_channel -> int
Return the current reading position for the given channel.

in_channel_length : in_channel -> int
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.

close_in : in_channel -> unit
Close the given channel. A Sys_error exception is raised if any of the functions above is called on a closed channel.

set_binary_mode_in : in_channel -> bool -> unit
set_binary_mode_in ic true sets the channel ic to binary mode: no translations take place during input. set_binary_mode_out ic false sets the channel ic to text mode: depending on the operating system, some translations may take place during input. For instance, under Windows, end-of-lines will be translated from \r\n to \n. This function has no effect under operating systems that do not distinguish between text mode and binary mode.

ref : 'x -> 'x ref
Return a fresh reference containing the given value.

! : 'y ref -> 'y
!r returns the current contents of reference r. Equivalent to fun r -> r.contents.

:= : 'z ref -> 'z -> unit
r := a stores the value of a in reference r. Equivalent to fun r v -> r.contents <- v.

incr : int ref -> unit
Increment the integer contained in the given reference. Equivalent to fun r -> r := succ !r.

decr : int ref -> unit
Decrement the integer contained in the given reference. Equivalent to fun r -> r := pred !r.

exit : int -> 'a1
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.) An implicit exit 0 is performed each time a program terminates normally (but not if it terminates because of an uncaught exception).

at_exit : (unit -> unit) -> unit
Register the given function to be called at program termination time. The functions registered with at_exit will be called when the program executes exit. They will not be called if the program terminates because of an uncaught exception. The functions are called in ``last in, first out'' order: the function most recently added with at_exit is called first.

unsafe_really_input : in_channel -> string -> int -> int -> unit

do_at_exit : unit -> unit