1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
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
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
(** System interface. *)
|
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. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external file_exists : string -> bool = "sys_file_exists"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Test if a file with the given name exists. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external remove : string -> unit = "sys_remove"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Remove the given file name from the file system. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external rename : string -> string -> unit = "sys_rename"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Rename a file. The first argument is the old name and the
|
|
|
|
second is the new name. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external getenv : string -> string = "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. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external command : string -> int = "sys_system_command"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Execute the given shell command and return its exit code. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external time : unit -> float = "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. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external chdir : string -> unit = "sys_chdir"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Change the current working directory of the process. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
external getcwd : unit -> string = "sys_getcwd"
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Return the current working directory of the process. *)
|
|
|
|
|
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
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Operating system currently executing the Caml program.
|
|
|
|
One of ["Unix"], ["Win32"], ["Cygwin"] or ["MacOS"]. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val word_size : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Size of one word on the machine currently executing the Caml
|
|
|
|
program, in bits: 32 or 64. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val max_string_length : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Maximum length of a string. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val max_array_length : int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Maximum length of an array. *)
|
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
|
|
|
|
| Signal_ignore
|
|
|
|
| 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 :
|
|
|
|
int -> signal_behavior -> signal_behavior = "install_signal_handler"
|
2001-10-26 16:33:00 -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. *)
|
|
|
|
|
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
|
|
|
|
2001-12-28 15:14:14 -08: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 *)
|
|
|
|
|
|
|
|
|
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)
|
|
|
|
terminates the program or raises the [Break] exception.
|
|
|
|
Call [catch_break true] to enable raising [Break],
|
|
|
|
and [catch_break false] to let the system
|
|
|
|
terminate the program on user interrupt. *)
|