1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2014-08-22 06:45:02 -07:00
|
|
|
(** System interface.
|
|
|
|
|
|
|
|
Every function in this module raises [Sys_error] with an
|
|
|
|
informative message when the underlying system call signal
|
|
|
|
an error.
|
|
|
|
*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val argv : string array
|
2001-10-26 16:33:00 -07:00
|
|
|
(** The command line arguments given to the process.
|
|
|
|
The first element is the command name used to invoke the program.
|
|
|
|
The following elements are the command-line arguments
|
|
|
|
given to the program. *)
|
|
|
|
|
2002-02-11 05:51:40 -08:00
|
|
|
val executable_name : string
|
|
|
|
(** The name of the file containing the executable currently running. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external file_exists : string -> bool = "caml_sys_file_exists"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Test if a file with the given name exists. *)
|
|
|
|
|
2007-02-26 06:21:57 -08:00
|
|
|
external is_directory : string -> bool = "caml_sys_is_directory"
|
|
|
|
(** Returns [true] if the given name refers to a directory,
|
|
|
|
[false] if it refers to another kind of file.
|
2010-05-21 11:30:12 -07:00
|
|
|
Raise [Sys_error] if no file exists with the given name.
|
2011-07-20 02:17:07 -07:00
|
|
|
@since 3.10.0
|
2010-05-21 11:30:12 -07:00
|
|
|
*)
|
2007-02-26 06:21:57 -08:00
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external remove : string -> unit = "caml_sys_remove"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Remove the given file name from the file system. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external rename : string -> string -> unit = "caml_sys_rename"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Rename a file. The first argument is the old name and the
|
2004-04-13 10:11:55 -07:00
|
|
|
second is the new name. If there is already another file
|
|
|
|
under the new name, [rename] may replace it, or raise an
|
|
|
|
exception, depending on your operating system. *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external getenv : string -> string = "caml_sys_getenv"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Return the value associated to a variable in the process
|
|
|
|
environment. Raise [Not_found] if the variable is unbound. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external command : string -> int = "caml_sys_system_command"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Execute the given shell command and return its exit code. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external time : unit -> float = "caml_sys_time"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Return the processor time, in seconds, used by the program
|
|
|
|
since the beginning of execution. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external chdir : string -> unit = "caml_sys_chdir"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Change the current working directory of the process. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external getcwd : unit -> string = "caml_sys_getcwd"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Return the current working directory of the process. *)
|
|
|
|
|
2003-12-16 10:09:44 -08:00
|
|
|
external readdir : string -> string array = "caml_sys_read_directory"
|
2003-03-03 09:16:15 -08:00
|
|
|
(** Return the names of all files present in the given directory.
|
|
|
|
Names denoting the current directory and the parent directory
|
|
|
|
(["."] and [".."] in Unix) are not returned. Each string in the
|
|
|
|
result is a file name rather than a complete path. There is no
|
|
|
|
guarantee that the name strings in the resulting array will appear
|
|
|
|
in any specific order; they are not, in particular, guaranteed to
|
|
|
|
appear in alphabetical order. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val interactive : bool ref
|
2001-10-26 16:33:00 -07:00
|
|
|
(** This reference is initially set to [false] in standalone
|
|
|
|
programs and to [true] if the code is being executed under
|
|
|
|
the interactive toplevel system [ocaml]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val os_type : string
|
2011-12-21 07:37:54 -08:00
|
|
|
(** Operating system currently executing the OCaml program. One of
|
2003-03-03 09:16:15 -08:00
|
|
|
- ["Unix"] (for all Unix versions, including Linux and Mac OS X),
|
|
|
|
- ["Win32"] (for MS-Windows, OCaml compiled with MSVC++ or Mingw),
|
2004-01-16 07:24:03 -08:00
|
|
|
- ["Cygwin"] (for MS-Windows, OCaml compiled with Cygwin). *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2012-11-29 01:55:00 -08:00
|
|
|
val unix : bool
|
|
|
|
(** True if [Sys.os_type = "Unix"].
|
2013-01-08 05:23:49 -08:00
|
|
|
@since 4.01.0 *)
|
2012-11-29 01:55:00 -08:00
|
|
|
|
|
|
|
val win32 : bool
|
|
|
|
(** True if [Sys.os_type = "Win32"].
|
2013-01-08 05:23:49 -08:00
|
|
|
@since 4.01.0 *)
|
2012-11-29 01:55:00 -08:00
|
|
|
|
|
|
|
val cygwin : bool
|
|
|
|
(** True if [Sys.os_type = "Cygwin"].
|
2013-01-08 05:23:49 -08:00
|
|
|
@since 4.01.0 *)
|
2012-11-29 01:55:00 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val word_size : int
|
2011-12-21 07:37:54 -08:00
|
|
|
(** Size of one word on the machine currently executing the OCaml
|
2001-10-26 16:33:00 -07:00
|
|
|
program, in bits: 32 or 64. *)
|
|
|
|
|
2014-11-17 04:21:46 -08:00
|
|
|
val int_size : int
|
2014-11-17 04:21:48 -08:00
|
|
|
(** Size of an int. It is 31 bits (resp. 63 bits) when using the
|
|
|
|
OCaml compiler on a 32 bits (resp. 64 bits) platform. It may
|
|
|
|
differ for other compilers, e.g. it is 32 bits when compiling to
|
2015-04-10 07:50:30 -07:00
|
|
|
JavaScript.
|
|
|
|
@since 4.03.0 *)
|
2014-11-17 04:21:46 -08:00
|
|
|
|
2012-03-08 11:52:03 -08:00
|
|
|
val big_endian : bool
|
2012-03-08 14:27:57 -08:00
|
|
|
(** Whether the machine currently executing the Caml program is big-endian.
|
|
|
|
@since 4.00.0 *)
|
2012-03-08 11:52:03 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val max_string_length : int
|
2014-04-29 04:56:17 -07:00
|
|
|
(** Maximum length of strings and byte sequences. *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val max_array_length : int
|
2005-08-13 13:59:37 -07:00
|
|
|
(** Maximum length of a normal array. The maximum length of a float
|
|
|
|
array is [max_array_length/2] on 32-bit machines and
|
|
|
|
[max_array_length] on 64-bit machines. *)
|
1996-11-07 03:00:19 -08:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-12-28 15:14:14 -08:00
|
|
|
(** {6 Signal handling} *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
type signal_behavior =
|
|
|
|
Signal_default
|
2005-08-13 13:59:37 -07:00
|
|
|
| Signal_ignore
|
2013-01-03 08:01:13 -08:00
|
|
|
| Signal_handle of (int -> unit) (** *)
|
2001-10-26 16:33:00 -07:00
|
|
|
(** What to do when receiving a signal:
|
|
|
|
- [Signal_default]: take the default behavior
|
|
|
|
(usually: abort the program)
|
|
|
|
- [Signal_ignore]: ignore the signal
|
|
|
|
- [Signal_handle f]: call function [f], giving it the signal
|
|
|
|
number as argument. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external signal :
|
2004-01-01 08:42:43 -08:00
|
|
|
int -> signal_behavior -> signal_behavior = "caml_install_signal_handler"
|
2004-05-04 04:51:13 -07:00
|
|
|
(** Set the behavior of the system on receipt of a given signal. The
|
|
|
|
first argument is the signal number. Return the behavior
|
|
|
|
previously associated with the signal. If the signal number is
|
|
|
|
invalid (or not available on your system), an [Invalid_argument]
|
|
|
|
exception is raised. *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val set_signal : int -> signal_behavior -> unit
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Same as {!Sys.signal} but return value is ignored. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2005-10-25 11:34:07 -07:00
|
|
|
(** {7 Signal numbers for the standard POSIX signals.} *)
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val sigabrt : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Abnormal termination *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigalrm : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Timeout *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigfpe : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Arithmetic exception *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sighup : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Hangup on controlling terminal *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigill : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Invalid hardware instruction *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigint : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Interactive interrupt (ctrl-C) *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigkill : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Termination (cannot be ignored) *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigpipe : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Broken pipe *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigquit : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Interactive termination *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigsegv : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Invalid memory reference *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigterm : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Termination *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigusr1 : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Application-defined signal 1 *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigusr2 : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Application-defined signal 2 *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigchld : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Child process terminated *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigcont : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Continue *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigstop : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Stop *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigtstp : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Interactive stop *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigttin : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Terminal read from background process *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigttou : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Terminal write from background process *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigvtalrm : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Timeout in virtual time *)
|
2001-12-03 14:16:03 -08:00
|
|
|
|
|
|
|
val sigprof : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Profiling interrupt *)
|
|
|
|
|
2015-08-02 06:05:45 -07:00
|
|
|
val sigbus : int
|
|
|
|
(** Bus error
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigpoll : int
|
|
|
|
(** Pollable event
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigsys : int
|
|
|
|
(** Bad argument to routine
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigtrap : int
|
|
|
|
(** Trace/breakpoint trap
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigurg : int
|
|
|
|
(** Urgent condition on socket
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigxcpu : int
|
|
|
|
(** Timeout in cpu time
|
|
|
|
@since 4.03 *)
|
|
|
|
|
|
|
|
val sigxfsz : int
|
|
|
|
(** File size limit exceeded
|
|
|
|
@since 4.03 *)
|
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
exception Break
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Exception raised on interactive interrupt if {!Sys.catch_break}
|
|
|
|
is on. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val catch_break : bool -> unit
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [catch_break] governs whether interactive interrupt (ctrl-C)
|
2005-10-25 11:34:07 -07:00
|
|
|
terminates the program or raises the [Break] exception.
|
2001-10-26 16:33:00 -07:00
|
|
|
Call [catch_break true] to enable raising [Break],
|
|
|
|
and [catch_break false] to let the system
|
|
|
|
terminate the program on user interrupt. *)
|
2002-02-05 09:11:33 -08:00
|
|
|
|
|
|
|
|
|
|
|
val ocaml_version : string;;
|
2011-07-27 07:17:02 -07:00
|
|
|
(** [ocaml_version] is the version of OCaml.
|
2006-12-19 12:30:53 -08:00
|
|
|
It is a string of the form ["major.minor[.patchlevel][+additional-info]"],
|
|
|
|
where [major], [minor], and [patchlevel] are integers, and
|
|
|
|
[additional-info] is an arbitrary string. The [[.patchlevel]] and
|
2003-12-31 06:20:40 -08:00
|
|
|
[[+additional-info]] parts may be absent. *)
|
2015-07-24 06:11:26 -07:00
|
|
|
|
|
|
|
|
|
|
|
val enable_runtime_warnings: bool -> unit
|
|
|
|
(** Control whether the OCaml runtime system can emit warnings
|
|
|
|
on stderr. Currently, the only supported warning is triggered
|
|
|
|
when a channel created by [open_*] functions is finalized without
|
|
|
|
being closed. Runtime warnings are enabled by default. *)
|
|
|
|
|
|
|
|
val runtime_warnings_enabled: unit -> bool
|
|
|
|
(** Return whether runtime warnings are currently enabled. *)
|