* add pi constant to pervasives
[ocaml.git] / stdlib / pervasives.mli
blobdc5a639f6b69e1a9b272100e988949cdcc542da9
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** The initially opened module.
18 This module provides the basic operations over the built-in types
19 (numbers, booleans, strings, exceptions, references, lists, arrays,
20 input-output channels, ...)
22 This module is automatically opened at the beginning of each compilation.
23 All components of this module can therefore be referred by their short
24 name, without prefixing them by [Pervasives].
27 (** {6 Exceptions} *)
29 external raise : exn -> 'a = "%raise"
30 (** Raise the given exception value *)
32 val invalid_arg : string -> 'a
33 (** Raise exception [Invalid_argument] with the given string. *)
35 val failwith : string -> 'a
36 (** Raise exception [Failure] with the given string. *)
38 exception Exit
39 (** The [Exit] exception is not raised by any library function. It is
40 provided for use in your programs.*)
43 (** {6 Comparisons} *)
46 external ( = ) : 'a -> 'a -> bool = "%equal"
47 (** [e1 = e2] tests for structural equality of [e1] and [e2].
48 Mutable structures (e.g. references and arrays) are equal
49 if and only if their current contents are structurally equal,
50 even if the two mutable objects are not the same physical object.
51 Equality between functional values raises [Invalid_argument].
52 Equality between cyclic data structures does not terminate. *)
54 external ( <> ) : 'a -> 'a -> bool = "%notequal"
55 (** Negation of {!Pervasives.(=)}. *)
57 external ( < ) : 'a -> 'a -> bool = "%lessthan"
58 (** See {!Pervasives.(>=)}. *)
60 external ( > ) : 'a -> 'a -> bool = "%greaterthan"
61 (** See {!Pervasives.(>=)}. *)
63 external ( <= ) : 'a -> 'a -> bool = "%lessequal"
64 (** See {!Pervasives.(>=)}. *)
66 external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
67 (** Structural ordering functions. These functions coincide with
68 the usual orderings over integers, characters, strings
69 and floating-point numbers, and extend them to a
70 total ordering over all types.
71 The ordering is compatible with [(=)]. As in the case
72 of [(=)], mutable structures are compared by contents.
73 Comparison between functional values raises [Invalid_argument].
74 Comparison between cyclic structures does not terminate. *)
76 external compare : 'a -> 'a -> int = "%compare"
77 (** [compare x y] returns [0] if [x] is equal to [y],
78 a negative integer if [x] is less than [y], and a positive integer
79 if [x] is greater than [y]. The ordering implemented by [compare]
80 is compatible with the comparison predicates [=], [<] and [>]
81 defined above, with one difference on the treatment of the float value
82 {!Pervasives.nan}. Namely, the comparison predicates treat [nan]
83 as different from any other float value, including itself;
84 while [compare] treats [nan] as equal to itself and less than any
85 other float value. This treatment of [nan] ensures that [compare]
86 defines a total ordering relation.
88 [compare] applied to functional values may raise [Invalid_argument].
89 [compare] applied to cyclic structures may not terminate.
91 The [compare] function can be used as the comparison function
92 required by the {!Set.Make} and {!Map.Make} functors, as well as
93 the {!List.sort} and {!Array.sort} functions. *)
95 val min : 'a -> 'a -> 'a
96 (** Return the smaller of the two arguments. *)
98 val max : 'a -> 'a -> 'a
99 (** Return the greater of the two arguments. *)
101 external ( == ) : 'a -> 'a -> bool = "%eq"
102 (** [e1 == e2] tests for physical equality of [e1] and [e2].
103 On integers and characters, physical equality is identical to structural
104 equality. On mutable structures, [e1 == e2] is true if and only if
105 physical modification of [e1] also affects [e2].
106 On non-mutable structures, the behavior of [(==)] is
107 implementation-dependent; however, it is guaranteed that
108 [e1 == e2] implies [compare e1 e2 = 0]. *)
110 external ( != ) : 'a -> 'a -> bool = "%noteq"
111 (** Negation of {!Pervasives.(==)}. *)
114 (** {6 Boolean operations} *)
117 external not : bool -> bool = "%boolnot"
118 (** The boolean negation. *)
120 external ( && ) : bool -> bool -> bool = "%sequand"
121 (** The boolean ``and''. Evaluation is sequential, left-to-right:
122 in [e1 && e2], [e1] is evaluated first, and if it returns [false],
123 [e2] is not evaluated at all. *)
125 external ( & ) : bool -> bool -> bool = "%sequand"
126 (** @deprecated {!Pervasives.(&&)} should be used instead. *)
128 external ( || ) : bool -> bool -> bool = "%sequor"
129 (** The boolean ``or''. Evaluation is sequential, left-to-right:
130 in [e1 || e2], [e1] is evaluated first, and if it returns [true],
131 [e2] is not evaluated at all. *)
133 external ( or ) : bool -> bool -> bool = "%sequor"
134 (** @deprecated {!Pervasives.(||)} should be used instead.*)
137 (** {6 Integer arithmetic} *)
139 (** Integers are 31 bits wide (or 63 bits on 64-bit processors).
140 All operations are taken modulo 2{^31} (or 2{^63}).
141 They do not fail on overflow. *)
143 external ( ~- ) : int -> int = "%negint"
144 (** Unary negation. You can also write [-e] instead of [~-e]. *)
146 external succ : int -> int = "%succint"
147 (** [succ x] is [x+1]. *)
149 external pred : int -> int = "%predint"
150 (** [pred x] is [x-1]. *)
152 external ( + ) : int -> int -> int = "%addint"
153 (** Integer addition. *)
155 external ( - ) : int -> int -> int = "%subint"
156 (** Integer subtraction. *)
158 external ( * ) : int -> int -> int = "%mulint"
159 (** Integer multiplication. *)
161 external ( / ) : int -> int -> int = "%divint"
162 (** Integer division.
163 Raise [Division_by_zero] if the second argument is 0.
164 Integer division rounds the real quotient of its arguments towards zero.
165 More precisely, if [x >= 0] and [y > 0], [x / y] is the greatest integer
166 less than or equal to the real quotient of [x] by [y]. Moreover,
167 [(-x) / y = x / (-y) = -(x / y)]. *)
169 external ( mod ) : int -> int -> int = "%modint"
170 (** Integer remainder. If [y] is not zero, the result
171 of [x mod y] satisfies the following properties:
172 [x = (x / y) * y + x mod y] and
173 [abs(x mod y) <= abs(y)-1].
174 If [y = 0], [x mod y] raises [Division_by_zero].
175 Notice that [x mod y] is nonpositive if and only if [x < 0].
176 Raise [Division_by_zero] if [y] is zero. *)
178 val abs : int -> int
179 (** Return the absolute value of the argument. Note that this may be
180 negative if the argument is [min_int]. *)
182 val max_int : int
183 (** The greatest representable integer. *)
185 val min_int : int
186 (** The smallest representable integer. *)
190 (** {7 Bitwise operations} *)
193 external ( land ) : int -> int -> int = "%andint"
194 (** Bitwise logical and. *)
196 external ( lor ) : int -> int -> int = "%orint"
197 (** Bitwise logical or. *)
199 external ( lxor ) : int -> int -> int = "%xorint"
200 (** Bitwise logical exclusive or. *)
202 val lnot : int -> int
203 (** Bitwise logical negation. *)
205 external ( lsl ) : int -> int -> int = "%lslint"
206 (** [n lsl m] shifts [n] to the left by [m] bits.
207 The result is unspecified if [m < 0] or [m >= bitsize],
208 where [bitsize] is [32] on a 32-bit platform and
209 [64] on a 64-bit platform. *)
211 external ( lsr ) : int -> int -> int = "%lsrint"
212 (** [n lsr m] shifts [n] to the right by [m] bits.
213 This is a logical shift: zeroes are inserted regardless of
214 the sign of [n].
215 The result is unspecified if [m < 0] or [m >= bitsize]. *)
217 external ( asr ) : int -> int -> int = "%asrint"
218 (** [n asr m] shifts [n] to the right by [m] bits.
219 This is an arithmetic shift: the sign bit of [n] is replicated.
220 The result is unspecified if [m < 0] or [m >= bitsize]. *)
223 (** {6 Floating-point arithmetic}
225 Caml's floating-point numbers follow the
226 IEEE 754 standard, using double precision (64 bits) numbers.
227 Floating-point operations never raise an exception on overflow,
228 underflow, division by zero, etc. Instead, special IEEE numbers
229 are returned as appropriate, such as [infinity] for [1.0 /. 0.0],
230 [neg_infinity] for [-1.0 /. 0.0], and [nan] (``not a number'')
231 for [0.0 /. 0.0]. These special numbers then propagate through
232 floating-point computations as expected: for instance,
233 [1.0 /. infinity] is [0.0], and any operation with [nan] as
234 argument returns [nan] as result.
237 external ( ~-. ) : float -> float = "%negfloat"
238 (** Unary negation. You can also write [-.e] instead of [~-.e]. *)
240 external ( +. ) : float -> float -> float = "%addfloat"
241 (** Floating-point addition *)
243 external ( -. ) : float -> float -> float = "%subfloat"
244 (** Floating-point subtraction *)
246 external ( *. ) : float -> float -> float = "%mulfloat"
247 (** Floating-point multiplication *)
249 external ( /. ) : float -> float -> float = "%divfloat"
250 (** Floating-point division. *)
252 external ( ** ) : float -> float -> float = "caml_power_float" "pow" "float"
253 (** Exponentiation *)
255 external sqrt : float -> float = "caml_sqrt_float" "sqrt" "float"
256 (** Square root *)
258 external exp : float -> float = "caml_exp_float" "exp" "float"
259 (** Exponential. *)
261 external log : float -> float = "caml_log_float" "log" "float"
262 (** Natural logarithm. *)
264 external log10 : float -> float = "caml_log10_float" "log10" "float"
265 (** Base 10 logarithm. *)
267 external cos : float -> float = "caml_cos_float" "cos" "float"
268 (** See {!Pervasives.atan2}. *)
270 external sin : float -> float = "caml_sin_float" "sin" "float"
271 (** See {!Pervasives.atan2}. *)
273 external tan : float -> float = "caml_tan_float" "tan" "float"
274 (** See {!Pervasives.atan2}. *)
276 external acos : float -> float = "caml_acos_float" "acos" "float"
277 (** See {!Pervasives.atan2}. *)
279 external asin : float -> float = "caml_asin_float" "asin" "float"
280 (** See {!Pervasives.atan2}. *)
282 external atan : float -> float = "caml_atan_float" "atan" "float"
283 (** See {!Pervasives.atan2}. *)
285 external atan2 : float -> float -> float = "caml_atan2_float" "atan2" "float"
286 (** The usual trigonometric functions. *)
288 external cosh : float -> float = "caml_cosh_float" "cosh" "float"
289 (** See {!Pervasives.tanh}. *)
291 external sinh : float -> float = "caml_sinh_float" "sinh" "float"
292 (** See {!Pervasives.tanh}. *)
294 external tanh : float -> float = "caml_tanh_float" "tanh" "float"
295 (** The usual hyperbolic trigonometric functions. *)
297 external ceil : float -> float = "caml_ceil_float" "ceil" "float"
298 (** See {!Pervasives.floor}. *)
300 external floor : float -> float = "caml_floor_float" "floor" "float"
301 (** Round the given float to an integer value.
302 [floor f] returns the greatest integer value less than or
303 equal to [f].
304 [ceil f] returns the least integer value greater than or
305 equal to [f]. *)
307 external abs_float : float -> float = "%absfloat"
308 (** Return the absolute value of the argument. *)
310 external mod_float : float -> float -> float = "caml_fmod_float" "fmod" "float"
311 (** [mod_float a b] returns the remainder of [a] with respect to
312 [b]. The returned value is [a -. n *. b], where [n]
313 is the quotient [a /. b] rounded towards zero to an integer. *)
315 external frexp : float -> float * int = "caml_frexp_float"
316 (** [frexp f] returns the pair of the significant
317 and the exponent of [f]. When [f] is zero, the
318 significant [x] and the exponent [n] of [f] are equal to
319 zero. When [f] is non-zero, they are defined by
320 [f = x *. 2 ** n] and [0.5 <= x < 1.0]. *)
322 external ldexp : float -> int -> float = "caml_ldexp_float"
323 (** [ldexp x n] returns [x *. 2 ** n]. *)
325 external modf : float -> float * float = "caml_modf_float"
326 (** [modf f] returns the pair of the fractional and integral
327 part of [f]. *)
329 external float : int -> float = "%floatofint"
330 (** Same as {!Pervasives.float_of_int}. *)
332 external float_of_int : int -> float = "%floatofint"
333 (** Convert an integer to floating-point. *)
335 external truncate : float -> int = "%intoffloat"
336 (** Same as {!Pervasives.int_of_float}. *)
338 external int_of_float : float -> int = "%intoffloat"
339 (** Truncate the given floating-point number to an integer.
340 The result is unspecified if the argument is [nan] or falls outside the
341 range of representable integers. *)
343 val infinity : float
344 (** Positive infinity. *)
346 val neg_infinity : float
347 (** Negative infinity. *)
349 val nan : float
350 (** A special floating-point value denoting the result of an
351 undefined operation such as [0.0 /. 0.0]. Stands for
352 ``not a number''. Any floating-point operation with [nan] as
353 argument returns [nan] as result. As for floating-point comparisons,
354 [=], [<], [<=], [>] and [>=] return [false] and [<>] returns [true]
355 if one or both of their arguments is [nan]. *)
357 val max_float : float
358 (** The largest positive finite value of type [float]. *)
360 val min_float : float
361 (** The smallest positive, non-zero, non-denormalized value of type [float]. *)
363 val epsilon_float : float
364 (** The smallest positive float [x] such that [1.0 +. x <> 1.0]. *)
366 val pi : float
367 (** The constant pi (3.14159...) *)
369 type fpclass =
370 FP_normal (** Normal number, none of the below *)
371 | FP_subnormal (** Number very close to 0.0, has reduced precision *)
372 | FP_zero (** Number is 0.0 or -0.0 *)
373 | FP_infinite (** Number is positive or negative infinity *)
374 | FP_nan (** Not a number: result of an undefined operation *)
375 (** The five classes of floating-point numbers, as determined by
376 the {!Pervasives.classify_float} function. *)
378 external classify_float : float -> fpclass = "caml_classify_float"
379 (** Return the class of the given floating-point number:
380 normal, subnormal, zero, infinite, or not a number. *)
383 (** {6 String operations}
385 More string operations are provided in module {!String}.
388 val ( ^ ) : string -> string -> string
389 (** String concatenation. *)
392 (** {6 Character operations}
394 More character operations are provided in module {!Char}.
397 external int_of_char : char -> int = "%identity"
398 (** Return the ASCII code of the argument. *)
400 val char_of_int : int -> char
401 (** Return the character with the given ASCII code.
402 Raise [Invalid_argument "char_of_int"] if the argument is
403 outside the range 0--255. *)
406 (** {6 Unit operations} *)
408 external ignore : 'a -> unit = "%ignore"
409 (** Discard the value of its argument and return [()].
410 For instance, [ignore(f x)] discards the result of
411 the side-effecting function [f]. It is equivalent to
412 [f x; ()], except that the latter may generate a
413 compiler warning; writing [ignore(f x)] instead
414 avoids the warning. *)
417 (** {6 String conversion functions} *)
419 val string_of_bool : bool -> string
420 (** Return the string representation of a boolean. *)
422 val bool_of_string : string -> bool
423 (** Convert the given string to a boolean.
424 Raise [Invalid_argument "bool_of_string"] if the string is not
425 ["true"] or ["false"]. *)
427 val string_of_int : int -> string
428 (** Return the string representation of an integer, in decimal. *)
430 external int_of_string : string -> int = "caml_int_of_string"
431 (** Convert the given string to an integer.
432 The string is read in decimal (by default) or in hexadecimal (if it
433 begins with [0x] or [0X]), octal (if it begins with [0o] or [0O]),
434 or binary (if it begins with [0b] or [0B]).
435 Raise [Failure "int_of_string"] if the given string is not
436 a valid representation of an integer, or if the integer represented
437 exceeds the range of integers representable in type [int]. *)
439 val string_of_float : float -> string
440 (** Return the string representation of a floating-point number. *)
442 external float_of_string : string -> float = "caml_float_of_string"
443 (** Convert the given string to a float. Raise [Failure "float_of_string"]
444 if the given string is not a valid representation of a float. *)
448 (** {6 Pair operations} *)
450 external fst : 'a * 'b -> 'a = "%field0"
451 (** Return the first component of a pair. *)
453 external snd : 'a * 'b -> 'b = "%field1"
454 (** Return the second component of a pair. *)
457 (** {6 List operations}
459 More list operations are provided in module {!List}.
462 val ( @ ) : 'a list -> 'a list -> 'a list
463 (** List concatenation. *)
466 (** {6 Input/output} *)
468 type in_channel
469 (** The type of input channel. *)
471 type out_channel
472 (** The type of output channel. *)
474 val stdin : in_channel
475 (** The standard input for the process. *)
477 val stdout : out_channel
478 (** The standard output for the process. *)
480 val stderr : out_channel
481 (** The standard error ouput for the process. *)
484 (** {7 Output functions on standard output} *)
486 val print_char : char -> unit
487 (** Print a character on standard output. *)
489 val print_string : string -> unit
490 (** Print a string on standard output. *)
492 val print_int : int -> unit
493 (** Print an integer, in decimal, on standard output. *)
495 val print_float : float -> unit
496 (** Print a floating-point number, in decimal, on standard output. *)
498 val print_endline : string -> unit
499 (** Print a string, followed by a newline character, on
500 standard output and flush standard output. *)
502 val print_newline : unit -> unit
503 (** Print a newline character on standard output, and flush
504 standard output. This can be used to simulate line
505 buffering of standard output. *)
508 (** {7 Output functions on standard error} *)
510 val prerr_char : char -> unit
511 (** Print a character on standard error. *)
513 val prerr_string : string -> unit
514 (** Print a string on standard error. *)
516 val prerr_int : int -> unit
517 (** Print an integer, in decimal, on standard error. *)
519 val prerr_float : float -> unit
520 (** Print a floating-point number, in decimal, on standard error. *)
522 val prerr_endline : string -> unit
523 (** Print a string, followed by a newline character on standard error
524 and flush standard error. *)
526 val prerr_newline : unit -> unit
527 (** Print a newline character on standard error, and flush
528 standard error. *)
531 (** {7 Input functions on standard input} *)
533 val read_line : unit -> string
534 (** Flush standard output, then read characters from standard input
535 until a newline character is encountered. Return the string of
536 all characters read, without the newline character at the end. *)
538 val read_int : unit -> int
539 (** Flush standard output, then read one line from standard input
540 and convert it to an integer. Raise [Failure "int_of_string"]
541 if the line read is not a valid representation of an integer. *)
543 val read_float : unit -> float
544 (** Flush standard output, then read one line from standard input
545 and convert it to a floating-point number.
546 The result is unspecified if the line read is not a valid
547 representation of a floating-point number. *)
549 (** {7 General output functions} *)
552 type open_flag =
553 Open_rdonly (** open for reading. *)
554 | Open_wronly (** open for writing. *)
555 | Open_append (** open for appending: always write at end of file. *)
556 | Open_creat (** create the file if it does not exist. *)
557 | Open_trunc (** empty the file if it already exists. *)
558 | Open_excl (** fail if Open_creat and the file already exists. *)
559 | Open_binary (** open in binary mode (no conversion). *)
560 | Open_text (** open in text mode (may perform conversions). *)
561 | Open_nonblock (** open in non-blocking mode. *)
562 (** Opening modes for {!Pervasives.open_out_gen} and
563 {!Pervasives.open_in_gen}. *)
565 val open_out : string -> out_channel
566 (** Open the named file for writing, and return a new output channel
567 on that file, positionned at the beginning of the file. The
568 file is truncated to zero length if it already exists. It
569 is created if it does not already exists.
570 Raise [Sys_error] if the file could not be opened. *)
572 val open_out_bin : string -> out_channel
573 (** Same as {!Pervasives.open_out}, but the file is opened in binary mode,
574 so that no translation takes place during writes. On operating
575 systems that do not distinguish between text mode and binary
576 mode, this function behaves like {!Pervasives.open_out}. *)
578 val open_out_gen : open_flag list -> int -> string -> out_channel
579 (** [open_out_gen mode perm filename] opens the named file for writing,
580 as described above. The extra argument [mode]
581 specify the opening mode. The extra argument [perm] specifies
582 the file permissions, in case the file must be created.
583 {!Pervasives.open_out} and {!Pervasives.open_out_bin} are special
584 cases of this function. *)
586 val flush : out_channel -> unit
587 (** Flush the buffer associated with the given output channel,
588 performing all pending writes on that channel.
589 Interactive programs must be careful about flushing standard
590 output and standard error at the right time. *)
592 val flush_all : unit -> unit
593 (** Flush all open output channels; ignore errors. *)
595 val output_char : out_channel -> char -> unit
596 (** Write the character on the given output channel. *)
598 val output_string : out_channel -> string -> unit
599 (** Write the string on the given output channel. *)
601 val output : out_channel -> string -> int -> int -> unit
602 (** [output oc buf pos len] writes [len] characters from string [buf],
603 starting at offset [pos], to the given output channel [oc].
604 Raise [Invalid_argument "output"] if [pos] and [len] do not
605 designate a valid substring of [buf]. *)
607 val output_byte : out_channel -> int -> unit
608 (** Write one 8-bit integer (as the single character with that code)
609 on the given output channel. The given integer is taken modulo
610 256. *)
612 val output_binary_int : out_channel -> int -> unit
613 (** Write one integer in binary format (4 bytes, big-endian)
614 on the given output channel.
615 The given integer is taken modulo 2{^32}.
616 The only reliable way to read it back is through the
617 {!Pervasives.input_binary_int} function. The format is compatible across
618 all machines for a given version of Objective Caml. *)
620 val output_value : out_channel -> 'a -> unit
621 (** Write the representation of a structured value of any type
622 to a channel. Circularities and sharing inside the value
623 are detected and preserved. The object can be read back,
624 by the function {!Pervasives.input_value}. See the description of module
625 {!Marshal} for more information. {!Pervasives.output_value} is equivalent
626 to {!Marshal.to_channel} with an empty list of flags. *)
628 val seek_out : out_channel -> int -> unit
629 (** [seek_out chan pos] sets the current writing position to [pos]
630 for channel [chan]. This works only for regular files. On
631 files of other kinds (such as terminals, pipes and sockets),
632 the behavior is unspecified. *)
634 val pos_out : out_channel -> int
635 (** Return the current writing position for the given channel. Does
636 not work on channels opened with the [Open_append] flag (returns
637 unspecified results). *)
639 val out_channel_length : out_channel -> int
640 (** Return the size (number of characters) of the regular file
641 on which the given channel is opened. If the channel is opened
642 on a file that is not a regular file, the result is meaningless. *)
644 val close_out : out_channel -> unit
645 (** Close the given channel, flushing all buffered write operations.
646 Output functions raise a [Sys_error] exception when they are
647 applied to a closed output channel, except [close_out] and [flush],
648 which do nothing when applied to an already closed channel.
649 Note that [close_out] may raise [Sys_error] if the operating
650 system signals an error when flushing or closing. *)
652 val close_out_noerr : out_channel -> unit
653 (** Same as [close_out], but ignore all errors. *)
655 val set_binary_mode_out : out_channel -> bool -> unit
656 (** [set_binary_mode_out oc true] sets the channel [oc] to binary
657 mode: no translations take place during output.
658 [set_binary_mode_out oc false] sets the channel [oc] to text
659 mode: depending on the operating system, some translations
660 may take place during output. For instance, under Windows,
661 end-of-lines will be translated from [\n] to [\r\n].
662 This function has no effect under operating systems that
663 do not distinguish between text mode and binary mode. *)
666 (** {7 General input functions} *)
668 val open_in : string -> in_channel
669 (** Open the named file for reading, and return a new input channel
670 on that file, positionned at the beginning of the file.
671 Raise [Sys_error] if the file could not be opened. *)
673 val open_in_bin : string -> in_channel
674 (** Same as {!Pervasives.open_in}, but the file is opened in binary mode,
675 so that no translation takes place during reads. On operating
676 systems that do not distinguish between text mode and binary
677 mode, this function behaves like {!Pervasives.open_in}. *)
679 val open_in_gen : open_flag list -> int -> string -> in_channel
680 (** [open_in mode perm filename] opens the named file for reading,
681 as described above. The extra arguments
682 [mode] and [perm] specify the opening mode and file permissions.
683 {!Pervasives.open_in} and {!Pervasives.open_in_bin} are special
684 cases of this function. *)
686 val input_char : in_channel -> char
687 (** Read one character from the given input channel.
688 Raise [End_of_file] if there are no more characters to read. *)
690 val input_line : in_channel -> string
691 (** Read characters from the given input channel, until a
692 newline character is encountered. Return the string of
693 all characters read, without the newline character at the end.
694 Raise [End_of_file] if the end of the file is reached
695 at the beginning of line. *)
697 val input : in_channel -> string -> int -> int -> int
698 (** [input ic buf pos len] reads up to [len] characters from
699 the given channel [ic], storing them in string [buf], starting at
700 character number [pos].
701 It returns the actual number of characters read, between 0 and
702 [len] (inclusive).
703 A return value of 0 means that the end of file was reached.
704 A return value between 0 and [len] exclusive means that
705 not all requested [len] characters were read, either because
706 no more characters were available at that time, or because
707 the implementation found it convenient to do a partial read;
708 [input] must be called again to read the remaining characters,
709 if desired. (See also {!Pervasives.really_input} for reading
710 exactly [len] characters.)
711 Exception [Invalid_argument "input"] is raised if [pos] and [len]
712 do not designate a valid substring of [buf]. *)
714 val really_input : in_channel -> string -> int -> int -> unit
715 (** [really_input ic buf pos len] reads [len] characters from channel [ic],
716 storing them in string [buf], starting at character number [pos].
717 Raise [End_of_file] if the end of file is reached before [len]
718 characters have been read.
719 Raise [Invalid_argument "really_input"] if
720 [pos] and [len] do not designate a valid substring of [buf]. *)
722 val input_byte : in_channel -> int
723 (** Same as {!Pervasives.input_char}, but return the 8-bit integer representing
724 the character.
725 Raise [End_of_file] if an end of file was reached. *)
727 val input_binary_int : in_channel -> int
728 (** Read an integer encoded in binary format (4 bytes, big-endian)
729 from the given input channel. See {!Pervasives.output_binary_int}.
730 Raise [End_of_file] if an end of file was reached while reading the
731 integer. *)
733 val input_value : in_channel -> 'a
734 (** Read the representation of a structured value, as produced
735 by {!Pervasives.output_value}, and return the corresponding value.
736 This function is identical to {!Marshal.from_channel};
737 see the description of module {!Marshal} for more information,
738 in particular concerning the lack of type safety. *)
740 val seek_in : in_channel -> int -> unit
741 (** [seek_in chan pos] sets the current reading position to [pos]
742 for channel [chan]. This works only for regular files. On
743 files of other kinds, the behavior is unspecified. *)
745 val pos_in : in_channel -> int
746 (** Return the current reading position for the given channel. *)
748 val in_channel_length : in_channel -> int
749 (** Return the size (number of characters) of the regular file
750 on which the given channel is opened. If the channel is opened
751 on a file that is not a regular file, the result is meaningless.
752 The returned size does not take into account the end-of-line
753 translations that can be performed when reading from a channel
754 opened in text mode. *)
756 val close_in : in_channel -> unit
757 (** Close the given channel. Input functions raise a [Sys_error]
758 exception when they are applied to a closed input channel,
759 except [close_in], which does nothing when applied to an already
760 closed channel. Note that [close_in] may raise [Sys_error] if
761 the operating system signals an error. *)
763 val close_in_noerr : in_channel -> unit
764 (** Same as [close_in], but ignore all errors. *)
766 val set_binary_mode_in : in_channel -> bool -> unit
767 (** [set_binary_mode_in ic true] sets the channel [ic] to binary
768 mode: no translations take place during input.
769 [set_binary_mode_out ic false] sets the channel [ic] to text
770 mode: depending on the operating system, some translations
771 may take place during input. For instance, under Windows,
772 end-of-lines will be translated from [\r\n] to [\n].
773 This function has no effect under operating systems that
774 do not distinguish between text mode and binary mode. *)
776 (** {7 Operations on large files} *)
778 module LargeFile :
780 val seek_out : out_channel -> int64 -> unit
781 val pos_out : out_channel -> int64
782 val out_channel_length : out_channel -> int64
783 val seek_in : in_channel -> int64 -> unit
784 val pos_in : in_channel -> int64
785 val in_channel_length : in_channel -> int64
787 (** Operations on large files.
788 This sub-module provides 64-bit variants of the channel functions
789 that manipulate file positions and file sizes. By representing
790 positions and sizes by 64-bit integers (type [int64]) instead of
791 regular integers (type [int]), these alternate functions allow
792 operating on files whose sizes are greater than [max_int]. *)
794 (** {6 References} *)
796 type 'a ref = { mutable contents : 'a }
797 (** The type of references (mutable indirection cells) containing
798 a value of type ['a]. *)
800 external ref : 'a -> 'a ref = "%makemutable"
801 (** Return a fresh reference containing the given value. *)
803 external ( ! ) : 'a ref -> 'a = "%field0"
804 (** [!r] returns the current contents of reference [r].
805 Equivalent to [fun r -> r.contents]. *)
807 external ( := ) : 'a ref -> 'a -> unit = "%setfield0"
808 (** [r := a] stores the value of [a] in reference [r].
809 Equivalent to [fun r v -> r.contents <- v]. *)
811 external incr : int ref -> unit = "%incr"
812 (** Increment the integer contained in the given reference.
813 Equivalent to [fun r -> r := succ !r]. *)
815 external decr : int ref -> unit = "%decr"
816 (** Decrement the integer contained in the given reference.
817 Equivalent to [fun r -> r := pred !r]. *)
820 (** {6 Operations on format strings} *)
822 (** See modules {!Printf} and {!Scanf} for more operations on
823 format strings. *)
824 type ('a, 'b, 'c, 'd) format4 = ('a, 'b, 'c, 'c, 'c, 'd) format6
826 type ('a, 'b, 'c) format = ('a, 'b, 'c, 'c) format4
827 (** Simplified type for format strings, included for backward compatibility
828 with earlier releases of Objective Caml.
829 ['a] is the type of the parameters of the format,
830 ['c] is the result type for the "printf"-style function,
831 and ['b] is the type of the first argument given to
832 [%a] and [%t] printing functions. *)
834 val string_of_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
835 (** Converts a format string into a string. *)
837 external format_of_string :
838 ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
839 ('a, 'b, 'c, 'd, 'e, 'f) format6 = "%identity"
840 (** [format_of_string s] returns a format string read from the string
841 literal [s]. *)
843 val ( ^^ ) :
844 ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
845 ('f, 'b, 'c, 'e, 'g, 'h) format6 ->
846 ('a, 'b, 'c, 'd, 'g, 'h) format6
847 (** [f1 ^^ f2] catenates formats [f1] and [f2]. The result is a format
848 that accepts arguments from [f1], then arguments from [f2]. *)
851 (** {6 Program termination} *)
854 val exit : int -> 'a
855 (** Terminate the process, returning the given status code
856 to the operating system: usually 0 to indicate no errors,
857 and a small positive integer to indicate failure.
858 All open output channels are flushed with flush_all.
859 An implicit [exit 0] is performed each time a program
860 terminates normally. An implicit [exit 2] is performed if the program
861 terminates early because of an uncaught exception. *)
863 val at_exit : (unit -> unit) -> unit
864 (** Register the given function to be called at program
865 termination time. The functions registered with [at_exit]
866 will be called when the program executes {!Pervasives.exit},
867 or terminates, either normally or because of an uncaught exception.
868 The functions are called in ``last in, first out'' order:
869 the function most recently added with [at_exit] is called first. *)
872 (**/**)
874 (** {6 For system use only, not for the casual user} *)
876 val valid_float_lexem : string -> string
878 val unsafe_really_input : in_channel -> string -> int -> int -> unit
880 val do_at_exit : unit -> unit