Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / pervasives.mli
blob07c48220eefa7844e3360e3f9b758df0e0a4adae
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 val finally : (unit -> unit) -> ('a -> 'b) -> 'a -> 'b
39 (** [finally fend f x] calls [f x] and then [fend()] even if [f x] raised
40 an exception. *)
42 exception Exit
43 (** The [Exit] exception is not raised by any library function. It is
44 provided for use in your programs.*)
47 (** {6 Comparisons} *)
50 external ( = ) : 'a -> 'a -> bool = "%equal"
51 (** [e1 = e2] tests for structural equality of [e1] and [e2].
52 Mutable structures (e.g. references and arrays) are equal
53 if and only if their current contents are structurally equal,
54 even if the two mutable objects are not the same physical object.
55 Equality between functional values raises [Invalid_argument].
56 Equality between cyclic data structures does not terminate. *)
58 external ( <> ) : 'a -> 'a -> bool = "%notequal"
59 (** Negation of {!Pervasives.(=)}. *)
61 external ( < ) : 'a -> 'a -> bool = "%lessthan"
62 (** See {!Pervasives.(>=)}. *)
64 external ( > ) : 'a -> 'a -> bool = "%greaterthan"
65 (** See {!Pervasives.(>=)}. *)
67 external ( <= ) : 'a -> 'a -> bool = "%lessequal"
68 (** See {!Pervasives.(>=)}. *)
70 external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
71 (** Structural ordering functions. These functions coincide with
72 the usual orderings over integers, characters, strings
73 and floating-point numbers, and extend them to a
74 total ordering over all types.
75 The ordering is compatible with [(=)]. As in the case
76 of [(=)], mutable structures are compared by contents.
77 Comparison between functional values raises [Invalid_argument].
78 Comparison between cyclic structures does not terminate. *)
80 external compare : 'a -> 'a -> int = "%compare"
81 (** [compare x y] returns [0] if [x] is equal to [y],
82 a negative integer if [x] is less than [y], and a positive integer
83 if [x] is greater than [y]. The ordering implemented by [compare]
84 is compatible with the comparison predicates [=], [<] and [>]
85 defined above, with one difference on the treatment of the float value
86 {!Pervasives.nan}. Namely, the comparison predicates treat [nan]
87 as different from any other float value, including itself;
88 while [compare] treats [nan] as equal to itself and less than any
89 other float value. This treatment of [nan] ensures that [compare]
90 defines a total ordering relation.
92 [compare] applied to functional values may raise [Invalid_argument].
93 [compare] applied to cyclic structures may not terminate.
95 The [compare] function can be used as the comparison function
96 required by the {!Set.Make} and {!Map.Make} functors, as well as
97 the {!List.sort} and {!Array.sort} functions. *)
99 val min : 'a -> 'a -> 'a
100 (** Return the smaller of the two arguments. *)
102 val max : 'a -> 'a -> 'a
103 (** Return the greater of the two arguments. *)
105 external ( == ) : 'a -> 'a -> bool = "%eq"
106 (** [e1 == e2] tests for physical equality of [e1] and [e2].
107 On integers and characters, physical equality is identical to structural
108 equality. On mutable structures, [e1 == e2] is true if and only if
109 physical modification of [e1] also affects [e2].
110 On non-mutable structures, the behavior of [(==)] is
111 implementation-dependent; however, it is guaranteed that
112 [e1 == e2] implies [compare e1 e2 = 0]. *)
114 external ( != ) : 'a -> 'a -> bool = "%noteq"
115 (** Negation of {!Pervasives.(==)}. *)
118 (** {6 Boolean operations} *)
121 external not : bool -> bool = "%boolnot"
122 (** The boolean negation. *)
124 external ( && ) : bool -> bool -> bool = "%sequand"
125 (** The boolean ``and''. Evaluation is sequential, left-to-right:
126 in [e1 && e2], [e1] is evaluated first, and if it returns [false],
127 [e2] is not evaluated at all. *)
129 external ( & ) : bool -> bool -> bool = "%sequand"
130 (** @deprecated {!Pervasives.(&&)} should be used instead. *)
132 external ( || ) : bool -> bool -> bool = "%sequor"
133 (** The boolean ``or''. Evaluation is sequential, left-to-right:
134 in [e1 || e2], [e1] is evaluated first, and if it returns [true],
135 [e2] is not evaluated at all. *)
137 external ( or ) : bool -> bool -> bool = "%sequor"
138 (** @deprecated {!Pervasives.(||)} should be used instead.*)
141 (** {6 Integer arithmetic} *)
143 (** Integers are 31 bits wide (or 63 bits on 64-bit processors).
144 All operations are taken modulo 2{^31} (or 2{^63}).
145 They do not fail on overflow. *)
147 external ( ~- ) : int -> int = "%negint"
148 (** Unary negation. You can also write [-e] instead of [~-e]. *)
150 external succ : int -> int = "%succint"
151 (** [succ x] is [x+1]. *)
153 external pred : int -> int = "%predint"
154 (** [pred x] is [x-1]. *)
156 external ( + ) : int -> int -> int = "%addint"
157 (** Integer addition. *)
159 external ( - ) : int -> int -> int = "%subint"
160 (** Integer subtraction. *)
162 external ( * ) : int -> int -> int = "%mulint"
163 (** Integer multiplication. *)
165 external ( / ) : int -> int -> int = "%divint"
166 (** Integer division.
167 Raise [Division_by_zero] if the second argument is 0.
168 Integer division rounds the real quotient of its arguments towards zero.
169 More precisely, if [x >= 0] and [y > 0], [x / y] is the greatest integer
170 less than or equal to the real quotient of [x] by [y]. Moreover,
171 [(-x) / y = x / (-y) = -(x / y)]. *)
173 external ( mod ) : int -> int -> int = "%modint"
174 (** Integer remainder. If [y] is not zero, the result
175 of [x mod y] satisfies the following properties:
176 [x = (x / y) * y + x mod y] and
177 [abs(x mod y) <= abs(y)-1].
178 If [y = 0], [x mod y] raises [Division_by_zero].
179 Notice that [x mod y] is nonpositive if and only if [x < 0].
180 Raise [Division_by_zero] if [y] is zero. *)
182 val abs : int -> int
183 (** Return the absolute value of the argument. Note that this may be
184 negative if the argument is [min_int]. *)
186 val max_int : int
187 (** The greatest representable integer. *)
189 val min_int : int
190 (** The smallest representable integer. *)
194 (** {7 Bitwise operations} *)
197 external ( land ) : int -> int -> int = "%andint"
198 (** Bitwise logical and. *)
200 external ( lor ) : int -> int -> int = "%orint"
201 (** Bitwise logical or. *)
203 external ( lxor ) : int -> int -> int = "%xorint"
204 (** Bitwise logical exclusive or. *)
206 val lnot : int -> int
207 (** Bitwise logical negation. *)
209 external ( lsl ) : int -> int -> int = "%lslint"
210 (** [n lsl m] shifts [n] to the left by [m] bits.
211 The result is unspecified if [m < 0] or [m >= bitsize],
212 where [bitsize] is [32] on a 32-bit platform and
213 [64] on a 64-bit platform. *)
215 external ( lsr ) : int -> int -> int = "%lsrint"
216 (** [n lsr m] shifts [n] to the right by [m] bits.
217 This is a logical shift: zeroes are inserted regardless of
218 the sign of [n].
219 The result is unspecified if [m < 0] or [m >= bitsize]. *)
221 external ( asr ) : int -> int -> int = "%asrint"
222 (** [n asr m] shifts [n] to the right by [m] bits.
223 This is an arithmetic shift: the sign bit of [n] is replicated.
224 The result is unspecified if [m < 0] or [m >= bitsize]. *)
227 (** {6 Floating-point arithmetic}
229 Caml's floating-point numbers follow the
230 IEEE 754 standard, using double precision (64 bits) numbers.
231 Floating-point operations never raise an exception on overflow,
232 underflow, division by zero, etc. Instead, special IEEE numbers
233 are returned as appropriate, such as [infinity] for [1.0 /. 0.0],
234 [neg_infinity] for [-1.0 /. 0.0], and [nan] (``not a number'')
235 for [0.0 /. 0.0]. These special numbers then propagate through
236 floating-point computations as expected: for instance,
237 [1.0 /. infinity] is [0.0], and any operation with [nan] as
238 argument returns [nan] as result.
241 external ( ~-. ) : float -> float = "%negfloat"
242 (** Unary negation. You can also write [-.e] instead of [~-.e]. *)
244 external ( +. ) : float -> float -> float = "%addfloat"
245 (** Floating-point addition *)
247 external ( -. ) : float -> float -> float = "%subfloat"
248 (** Floating-point subtraction *)
250 external ( *. ) : float -> float -> float = "%mulfloat"
251 (** Floating-point multiplication *)
253 external ( /. ) : float -> float -> float = "%divfloat"
254 (** Floating-point division. *)
256 external ( ** ) : float -> float -> float = "caml_power_float" "pow" "float"
257 (** Exponentiation *)
259 external sqrt : float -> float = "caml_sqrt_float" "sqrt" "float"
260 (** Square root *)
262 external exp : float -> float = "caml_exp_float" "exp" "float"
263 (** Exponential. *)
265 external log : float -> float = "caml_log_float" "log" "float"
266 (** Natural logarithm. *)
268 external log10 : float -> float = "caml_log10_float" "log10" "float"
269 (** Base 10 logarithm. *)
271 external cos : float -> float = "caml_cos_float" "cos" "float"
272 (** See {!Pervasives.atan2}. *)
274 external sin : float -> float = "caml_sin_float" "sin" "float"
275 (** See {!Pervasives.atan2}. *)
277 external tan : float -> float = "caml_tan_float" "tan" "float"
278 (** See {!Pervasives.atan2}. *)
280 external acos : float -> float = "caml_acos_float" "acos" "float"
281 (** See {!Pervasives.atan2}. *)
283 external asin : float -> float = "caml_asin_float" "asin" "float"
284 (** See {!Pervasives.atan2}. *)
286 external atan : float -> float = "caml_atan_float" "atan" "float"
287 (** See {!Pervasives.atan2}. *)
289 external atan2 : float -> float -> float = "caml_atan2_float" "atan2" "float"
290 (** The usual trigonometric functions. *)
292 external cosh : float -> float = "caml_cosh_float" "cosh" "float"
293 (** See {!Pervasives.tanh}. *)
295 external sinh : float -> float = "caml_sinh_float" "sinh" "float"
296 (** See {!Pervasives.tanh}. *)
298 external tanh : float -> float = "caml_tanh_float" "tanh" "float"
299 (** The usual hyperbolic trigonometric functions. *)
301 external ceil : float -> float = "caml_ceil_float" "ceil" "float"
302 (** See {!Pervasives.floor}. *)
304 external floor : float -> float = "caml_floor_float" "floor" "float"
305 (** Round the given float to an integer value.
306 [floor f] returns the greatest integer value less than or
307 equal to [f].
308 [ceil f] returns the least integer value greater than or
309 equal to [f]. *)
311 external abs_float : float -> float = "%absfloat"
312 (** Return the absolute value of the argument. *)
314 external mod_float : float -> float -> float = "caml_fmod_float" "fmod" "float"
315 (** [mod_float a b] returns the remainder of [a] with respect to
316 [b]. The returned value is [a -. n *. b], where [n]
317 is the quotient [a /. b] rounded towards zero to an integer. *)
319 external frexp : float -> float * int = "caml_frexp_float"
320 (** [frexp f] returns the pair of the significant
321 and the exponent of [f]. When [f] is zero, the
322 significant [x] and the exponent [n] of [f] are equal to
323 zero. When [f] is non-zero, they are defined by
324 [f = x *. 2 ** n] and [0.5 <= x < 1.0]. *)
326 external ldexp : float -> int -> float = "caml_ldexp_float"
327 (** [ldexp x n] returns [x *. 2 ** n]. *)
329 external modf : float -> float * float = "caml_modf_float"
330 (** [modf f] returns the pair of the fractional and integral
331 part of [f]. *)
333 external float : int -> float = "%floatofint"
334 (** Same as {!Pervasives.float_of_int}. *)
336 external float_of_int : int -> float = "%floatofint"
337 (** Convert an integer to floating-point. *)
339 external truncate : float -> int = "%intoffloat"
340 (** Same as {!Pervasives.int_of_float}. *)
342 external int_of_float : float -> int = "%intoffloat"
343 (** Truncate the given floating-point number to an integer.
344 The result is unspecified if the argument is [nan] or falls outside the
345 range of representable integers. *)
347 val infinity : float
348 (** Positive infinity. *)
350 val neg_infinity : float
351 (** Negative infinity. *)
353 val nan : float
354 (** A special floating-point value denoting the result of an
355 undefined operation such as [0.0 /. 0.0]. Stands for
356 ``not a number''. Any floating-point operation with [nan] as
357 argument returns [nan] as result. As for floating-point comparisons,
358 [=], [<], [<=], [>] and [>=] return [false] and [<>] returns [true]
359 if one or both of their arguments is [nan]. *)
361 val max_float : float
362 (** The largest positive finite value of type [float]. *)
364 val min_float : float
365 (** The smallest positive, non-zero, non-denormalized value of type [float]. *)
367 val epsilon_float : float
368 (** The smallest positive float [x] such that [1.0 +. x <> 1.0]. *)
370 val pi : float
371 (** The constant pi (3.14159...) *)
373 type fpclass =
374 FP_normal (** Normal number, none of the below *)
375 | FP_subnormal (** Number very close to 0.0, has reduced precision *)
376 | FP_zero (** Number is 0.0 or -0.0 *)
377 | FP_infinite (** Number is positive or negative infinity *)
378 | FP_nan (** Not a number: result of an undefined operation *)
379 (** The five classes of floating-point numbers, as determined by
380 the {!Pervasives.classify_float} function. *)
382 external classify_float : float -> fpclass = "caml_classify_float"
383 (** Return the class of the given floating-point number:
384 normal, subnormal, zero, infinite, or not a number. *)
387 (** {6 String operations}
389 More string operations are provided in module {!String}.
392 val ( ^ ) : string -> string -> string
393 (** String concatenation. *)
396 (** {6 Character operations}
398 More character operations are provided in module {!Char}.
401 external int_of_char : char -> int = "%identity"
402 (** Return the ASCII code of the argument. *)
404 val char_of_int : int -> char
405 (** Return the character with the given ASCII code.
406 Raise [Invalid_argument "char_of_int"] if the argument is
407 outside the range 0--255. *)
410 (** {6 Unit operations} *)
412 external ignore : 'a -> unit = "%ignore"
413 (** Discard the value of its argument and return [()].
414 For instance, [ignore(f x)] discards the result of
415 the side-effecting function [f]. It is equivalent to
416 [f x; ()], except that the latter may generate a
417 compiler warning; writing [ignore(f x)] instead
418 avoids the warning. *)
421 (** {6 String conversion functions} *)
423 val string_of_bool : bool -> string
424 (** Return the string representation of a boolean. *)
426 val bool_of_string : string -> bool
427 (** Convert the given string to a boolean.
428 Raise [Invalid_argument "bool_of_string"] if the string is not
429 ["true"] or ["false"]. *)
431 val string_of_int : int -> string
432 (** Return the string representation of an integer, in decimal. *)
434 external int_of_string : string -> int = "caml_int_of_string"
435 (** Convert the given string to an integer.
436 The string is read in decimal (by default) or in hexadecimal (if it
437 begins with [0x] or [0X]), octal (if it begins with [0o] or [0O]),
438 or binary (if it begins with [0b] or [0B]).
439 Raise [Failure "int_of_string"] if the given string is not
440 a valid representation of an integer, or if the integer represented
441 exceeds the range of integers representable in type [int]. *)
443 val string_of_float : float -> string
444 (** Return the string representation of a floating-point number. *)
446 external float_of_string : string -> float = "caml_float_of_string"
447 (** Convert the given string to a float. Raise [Failure "float_of_string"]
448 if the given string is not a valid representation of a float. *)
452 (** {6 Pair operations} *)
454 external fst : 'a * 'b -> 'a = "%field0"
455 (** Return the first component of a pair. *)
457 external snd : 'a * 'b -> 'b = "%field1"
458 (** Return the second component of a pair. *)
461 (** {6 List operations}
463 More list operations are provided in module {!List}.
466 val ( @ ) : 'a list -> 'a list -> 'a list
467 (** List concatenation. *)
470 (** {6 Input/output} *)
472 type in_channel
473 (** The type of input channel. *)
475 type out_channel
476 (** The type of output channel. *)
478 val stdin : in_channel
479 (** The standard input for the process. *)
481 val stdout : out_channel
482 (** The standard output for the process. *)
484 val stderr : out_channel
485 (** The standard error ouput for the process. *)
488 (** {7 Output functions on standard output} *)
490 val print_char : char -> unit
491 (** Print a character on standard output. *)
493 val print_string : string -> unit
494 (** Print a string on standard output. *)
496 val print_int : int -> unit
497 (** Print an integer, in decimal, on standard output. *)
499 val print_float : float -> unit
500 (** Print a floating-point number, in decimal, on standard output. *)
502 val print_endline : string -> unit
503 (** Print a string, followed by a newline character, on
504 standard output and flush standard output. *)
506 val print_newline : unit -> unit
507 (** Print a newline character on standard output, and flush
508 standard output. This can be used to simulate line
509 buffering of standard output. *)
512 (** {7 Output functions on standard error} *)
514 val prerr_char : char -> unit
515 (** Print a character on standard error. *)
517 val prerr_string : string -> unit
518 (** Print a string on standard error. *)
520 val prerr_int : int -> unit
521 (** Print an integer, in decimal, on standard error. *)
523 val prerr_float : float -> unit
524 (** Print a floating-point number, in decimal, on standard error. *)
526 val prerr_endline : string -> unit
527 (** Print a string, followed by a newline character on standard error
528 and flush standard error. *)
530 val prerr_newline : unit -> unit
531 (** Print a newline character on standard error, and flush
532 standard error. *)
535 (** {7 Input functions on standard input} *)
537 val read_line : unit -> string
538 (** Flush standard output, then read characters from standard input
539 until a newline character is encountered. Return the string of
540 all characters read, without the newline character at the end. *)
542 val read_int : unit -> int
543 (** Flush standard output, then read one line from standard input
544 and convert it to an integer. Raise [Failure "int_of_string"]
545 if the line read is not a valid representation of an integer. *)
547 val read_float : unit -> float
548 (** Flush standard output, then read one line from standard input
549 and convert it to a floating-point number.
550 The result is unspecified if the line read is not a valid
551 representation of a floating-point number. *)
553 (** {7 General output functions} *)
556 type open_flag =
557 Open_rdonly (** open for reading. *)
558 | Open_wronly (** open for writing. *)
559 | Open_append (** open for appending: always write at end of file. *)
560 | Open_creat (** create the file if it does not exist. *)
561 | Open_trunc (** empty the file if it already exists. *)
562 | Open_excl (** fail if Open_creat and the file already exists. *)
563 | Open_binary (** open in binary mode (no conversion). *)
564 | Open_text (** open in text mode (may perform conversions). *)
565 | Open_nonblock (** open in non-blocking mode. *)
566 (** Opening modes for {!Pervasives.open_out_gen} and
567 {!Pervasives.open_in_gen}. *)
569 val open_out : string -> out_channel
570 (** Open the named file for writing, and return a new output channel
571 on that file, positionned at the beginning of the file. The
572 file is truncated to zero length if it already exists. It
573 is created if it does not already exists.
574 Raise [Sys_error] if the file could not be opened. *)
576 val open_out_bin : string -> out_channel
577 (** Same as {!Pervasives.open_out}, but the file is opened in binary mode,
578 so that no translation takes place during writes. On operating
579 systems that do not distinguish between text mode and binary
580 mode, this function behaves like {!Pervasives.open_out}. *)
582 val open_out_gen : open_flag list -> int -> string -> out_channel
583 (** [open_out_gen mode perm filename] opens the named file for writing,
584 as described above. The extra argument [mode]
585 specify the opening mode. The extra argument [perm] specifies
586 the file permissions, in case the file must be created.
587 {!Pervasives.open_out} and {!Pervasives.open_out_bin} are special
588 cases of this function. *)
590 val flush : out_channel -> unit
591 (** Flush the buffer associated with the given output channel,
592 performing all pending writes on that channel.
593 Interactive programs must be careful about flushing standard
594 output and standard error at the right time. *)
596 val flush_all : unit -> unit
597 (** Flush all open output channels; ignore errors. *)
599 val output_char : out_channel -> char -> unit
600 (** Write the character on the given output channel. *)
602 val output_string : out_channel -> string -> unit
603 (** Write the string on the given output channel. *)
605 val output : out_channel -> string -> int -> int -> unit
606 (** [output oc buf pos len] writes [len] characters from string [buf],
607 starting at offset [pos], to the given output channel [oc].
608 Raise [Invalid_argument "output"] if [pos] and [len] do not
609 designate a valid substring of [buf]. *)
611 val output_byte : out_channel -> int -> unit
612 (** Write one 8-bit integer (as the single character with that code)
613 on the given output channel. The given integer is taken modulo
614 256. *)
616 val output_binary_int : out_channel -> int -> unit
617 (** Write one integer in binary format (4 bytes, big-endian)
618 on the given output channel.
619 The given integer is taken modulo 2{^32}.
620 The only reliable way to read it back is through the
621 {!Pervasives.input_binary_int} function. The format is compatible across
622 all machines for a given version of Objective Caml. *)
624 val output_value : out_channel -> 'a -> unit
625 (** Write the representation of a structured value of any type
626 to a channel. Circularities and sharing inside the value
627 are detected and preserved. The object can be read back,
628 by the function {!Pervasives.input_value}. See the description of module
629 {!Marshal} for more information. {!Pervasives.output_value} is equivalent
630 to {!Marshal.to_channel} with an empty list of flags. *)
632 val seek_out : out_channel -> int -> unit
633 (** [seek_out chan pos] sets the current writing position to [pos]
634 for channel [chan]. This works only for regular files. On
635 files of other kinds (such as terminals, pipes and sockets),
636 the behavior is unspecified. *)
638 val pos_out : out_channel -> int
639 (** Return the current writing position for the given channel. Does
640 not work on channels opened with the [Open_append] flag (returns
641 unspecified results). *)
643 val out_channel_length : out_channel -> int
644 (** Return the size (number of characters) of the regular file
645 on which the given channel is opened. If the channel is opened
646 on a file that is not a regular file, the result is meaningless. *)
648 val close_out : out_channel -> unit
649 (** Close the given channel, flushing all buffered write operations.
650 Output functions raise a [Sys_error] exception when they are
651 applied to a closed output channel, except [close_out] and [flush],
652 which do nothing when applied to an already closed channel.
653 Note that [close_out] may raise [Sys_error] if the operating
654 system signals an error when flushing or closing. *)
656 val close_out_noerr : out_channel -> unit
657 (** Same as [close_out], but ignore all errors. *)
659 val set_binary_mode_out : out_channel -> bool -> unit
660 (** [set_binary_mode_out oc true] sets the channel [oc] to binary
661 mode: no translations take place during output.
662 [set_binary_mode_out oc false] sets the channel [oc] to text
663 mode: depending on the operating system, some translations
664 may take place during output. For instance, under Windows,
665 end-of-lines will be translated from [\n] to [\r\n].
666 This function has no effect under operating systems that
667 do not distinguish between text mode and binary mode. *)
670 (** {7 General input functions} *)
672 val open_in : string -> in_channel
673 (** Open the named file for reading, and return a new input channel
674 on that file, positionned at the beginning of the file.
675 Raise [Sys_error] if the file could not be opened. *)
677 val open_in_bin : string -> in_channel
678 (** Same as {!Pervasives.open_in}, but the file is opened in binary mode,
679 so that no translation takes place during reads. On operating
680 systems that do not distinguish between text mode and binary
681 mode, this function behaves like {!Pervasives.open_in}. *)
683 val open_in_gen : open_flag list -> int -> string -> in_channel
684 (** [open_in mode perm filename] opens the named file for reading,
685 as described above. The extra arguments
686 [mode] and [perm] specify the opening mode and file permissions.
687 {!Pervasives.open_in} and {!Pervasives.open_in_bin} are special
688 cases of this function. *)
690 val input_char : in_channel -> char
691 (** Read one character from the given input channel.
692 Raise [End_of_file] if there are no more characters to read. *)
694 val input_line : in_channel -> string
695 (** Read characters from the given input channel, until a
696 newline character is encountered. Return the string of
697 all characters read, without the newline character at the end.
698 Raise [End_of_file] if the end of the file is reached
699 at the beginning of line. *)
701 val input : in_channel -> string -> int -> int -> int
702 (** [input ic buf pos len] reads up to [len] characters from
703 the given channel [ic], storing them in string [buf], starting at
704 character number [pos].
705 It returns the actual number of characters read, between 0 and
706 [len] (inclusive).
707 A return value of 0 means that the end of file was reached.
708 A return value between 0 and [len] exclusive means that
709 not all requested [len] characters were read, either because
710 no more characters were available at that time, or because
711 the implementation found it convenient to do a partial read;
712 [input] must be called again to read the remaining characters,
713 if desired. (See also {!Pervasives.really_input} for reading
714 exactly [len] characters.)
715 Exception [Invalid_argument "input"] is raised if [pos] and [len]
716 do not designate a valid substring of [buf]. *)
718 val really_input : in_channel -> string -> int -> int -> unit
719 (** [really_input ic buf pos len] reads [len] characters from channel [ic],
720 storing them in string [buf], starting at character number [pos].
721 Raise [End_of_file] if the end of file is reached before [len]
722 characters have been read.
723 Raise [Invalid_argument "really_input"] if
724 [pos] and [len] do not designate a valid substring of [buf]. *)
726 val input_byte : in_channel -> int
727 (** Same as {!Pervasives.input_char}, but return the 8-bit integer representing
728 the character.
729 Raise [End_of_file] if an end of file was reached. *)
731 val input_binary_int : in_channel -> int
732 (** Read an integer encoded in binary format (4 bytes, big-endian)
733 from the given input channel. See {!Pervasives.output_binary_int}.
734 Raise [End_of_file] if an end of file was reached while reading the
735 integer. *)
737 val input_value : in_channel -> 'a
738 (** Read the representation of a structured value, as produced
739 by {!Pervasives.output_value}, and return the corresponding value.
740 This function is identical to {!Marshal.from_channel};
741 see the description of module {!Marshal} for more information,
742 in particular concerning the lack of type safety. *)
744 val seek_in : in_channel -> int -> unit
745 (** [seek_in chan pos] sets the current reading position to [pos]
746 for channel [chan]. This works only for regular files. On
747 files of other kinds, the behavior is unspecified. *)
749 val pos_in : in_channel -> int
750 (** Return the current reading position for the given channel. *)
752 val in_channel_length : in_channel -> int
753 (** Return the size (number of characters) of the regular file
754 on which the given channel is opened. If the channel is opened
755 on a file that is not a regular file, the result is meaningless.
756 The returned size does not take into account the end-of-line
757 translations that can be performed when reading from a channel
758 opened in text mode. *)
760 val close_in : in_channel -> unit
761 (** Close the given channel. Input functions raise a [Sys_error]
762 exception when they are applied to a closed input channel,
763 except [close_in], which does nothing when applied to an already
764 closed channel. Note that [close_in] may raise [Sys_error] if
765 the operating system signals an error. *)
767 val close_in_noerr : in_channel -> unit
768 (** Same as [close_in], but ignore all errors. *)
770 val set_binary_mode_in : in_channel -> bool -> unit
771 (** [set_binary_mode_in ic true] sets the channel [ic] to binary
772 mode: no translations take place during input.
773 [set_binary_mode_out ic false] sets the channel [ic] to text
774 mode: depending on the operating system, some translations
775 may take place during input. For instance, under Windows,
776 end-of-lines will be translated from [\r\n] to [\n].
777 This function has no effect under operating systems that
778 do not distinguish between text mode and binary mode. *)
780 (** {7 Operations on large files} *)
782 module LargeFile :
784 val seek_out : out_channel -> int64 -> unit
785 val pos_out : out_channel -> int64
786 val out_channel_length : out_channel -> int64
787 val seek_in : in_channel -> int64 -> unit
788 val pos_in : in_channel -> int64
789 val in_channel_length : in_channel -> int64
791 (** Operations on large files.
792 This sub-module provides 64-bit variants of the channel functions
793 that manipulate file positions and file sizes. By representing
794 positions and sizes by 64-bit integers (type [int64]) instead of
795 regular integers (type [int]), these alternate functions allow
796 operating on files whose sizes are greater than [max_int]. *)
798 (** {6 References} *)
800 type 'a ref = { mutable contents : 'a }
801 (** The type of references (mutable indirection cells) containing
802 a value of type ['a]. *)
804 external ref : 'a -> 'a ref = "%makemutable"
805 (** Return a fresh reference containing the given value. *)
807 external ( ! ) : 'a ref -> 'a = "%field0"
808 (** [!r] returns the current contents of reference [r].
809 Equivalent to [fun r -> r.contents]. *)
811 external ( := ) : 'a ref -> 'a -> unit = "%setfield0"
812 (** [r := a] stores the value of [a] in reference [r].
813 Equivalent to [fun r v -> r.contents <- v]. *)
815 external incr : int ref -> unit = "%incr"
816 (** Increment the integer contained in the given reference.
817 Equivalent to [fun r -> r := succ !r]. *)
819 external decr : int ref -> unit = "%decr"
820 (** Decrement the integer contained in the given reference.
821 Equivalent to [fun r -> r := pred !r]. *)
824 (** {6 Operations on format strings} *)
826 (** See modules {!Printf} and {!Scanf} for more operations on
827 format strings. *)
828 type ('a, 'b, 'c, 'd) format4 = ('a, 'b, 'c, 'c, 'c, 'd) format6
830 type ('a, 'b, 'c) format = ('a, 'b, 'c, 'c) format4
831 (** Simplified type for format strings, included for backward compatibility
832 with earlier releases of Objective Caml.
833 ['a] is the type of the parameters of the format,
834 ['c] is the result type for the "printf"-style function,
835 and ['b] is the type of the first argument given to
836 [%a] and [%t] printing functions. *)
838 val string_of_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
839 (** Converts a format string into a string. *)
841 external format_of_string :
842 ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
843 ('a, 'b, 'c, 'd, 'e, 'f) format6 = "%identity"
844 (** [format_of_string s] returns a format string read from the string
845 literal [s]. *)
847 val ( ^^ ) :
848 ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
849 ('f, 'b, 'c, 'e, 'g, 'h) format6 ->
850 ('a, 'b, 'c, 'd, 'g, 'h) format6
851 (** [f1 ^^ f2] catenates formats [f1] and [f2]. The result is a format
852 that accepts arguments from [f1], then arguments from [f2]. *)
855 (** {6 Program termination} *)
858 val exit : int -> 'a
859 (** Terminate the process, returning the given status code
860 to the operating system: usually 0 to indicate no errors,
861 and a small positive integer to indicate failure.
862 All open output channels are flushed with flush_all.
863 An implicit [exit 0] is performed each time a program
864 terminates normally. An implicit [exit 2] is performed if the program
865 terminates early because of an uncaught exception. *)
867 val at_exit : (unit -> unit) -> unit
868 (** Register the given function to be called at program
869 termination time. The functions registered with [at_exit]
870 will be called when the program executes {!Pervasives.exit},
871 or terminates, either normally or because of an uncaught exception.
872 The functions are called in ``last in, first out'' order:
873 the function most recently added with [at_exit] is called first. *)
876 (**/**)
878 (** {6 For system use only, not for the casual user} *)
880 val valid_float_lexem : string -> string
882 val unsafe_really_input : in_channel -> string -> int -> int -> unit
884 val do_at_exit : unit -> unit