summaryrefslogtreecommitdiffstats
path: root/otherlibs/unix/unix.mli
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/unix/unix.mli')
-rw-r--r--otherlibs/unix/unix.mli76
1 files changed, 38 insertions, 38 deletions
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index ead724eb9..eeb5411de 100644
--- a/otherlibs/unix/unix.mli
+++ b/otherlibs/unix/unix.mli
@@ -90,7 +90,7 @@ type error =
| EOVERFLOW (** File size or position not representable *)
| EUNKNOWNERR of int (** Unknown error *)
-(** The type of error codes.
+(** The type of error codes.
Errors defined in the POSIX standard
and additional errors from UNIX98 and BSD.
All other errors are mapped to EUNKNOWNERR.
@@ -118,7 +118,7 @@ val handle_unix_error : ('a -> 'b) -> 'a -> 'b
val environment : unit -> string array
(** Return the process environment, as an array of strings
with the format ``variable=value''. *)
-
+
val getenv : string -> string
(** Return the value associated to a variable in the process
environment. Raise [Not_found] if the variable is unbound.
@@ -135,8 +135,8 @@ val putenv : string -> string -> unit
type process_status =
- WEXITED of int
- (** The process terminated normally by [exit];
+ WEXITED of int
+ (** The process terminated normally by [exit];
the argument is the return code. *)
| WSIGNALED of int
(** The process was killed by a signal;
@@ -155,9 +155,9 @@ type wait_flag =
val execv : string -> string array -> 'a
(** [execv prog args] execute the program in file [prog], with
- the arguments [args], and the current process environment.
- These [execv*] functions never return: on success, the current
- program is replaced by the new one;
+ the arguments [args], and the current process environment.
+ These [execv*] functions never return: on success, the current
+ program is replaced by the new one;
on failure, a {!Unix.Unix_error} exception is raised. *)
val execve : string -> string array -> string array -> 'a
@@ -240,7 +240,7 @@ type open_flag =
type file_perm = int
-(** The type of file access rights, e.g. [0o640] is read and write for user,
+(** The type of file access rights, e.g. [0o640] is read and write for user,
read for group, none for others *)
val openfile : string -> open_flag list -> file_perm -> file_descr
@@ -310,7 +310,7 @@ val ftruncate : file_descr -> int -> unit
to the given size. *)
-(** {6 File statistics} *)
+(** {6 File status} *)
type file_kind =
@@ -334,7 +334,7 @@ type stats =
st_size : int; (** Size in bytes *)
st_atime : float; (** Last access time *)
st_mtime : float; (** Last modification time *)
- st_ctime : float; (** Last status change time *)
+ st_ctime : float; (** Last status change time *)
}
(** The informations returned by the {!Unix.stat} calls. *)
@@ -369,7 +369,7 @@ module LargeFile :
st_size : int64; (** Size in bytes *)
st_atime : float; (** Last access time *)
st_mtime : float; (** Last modification time *)
- st_ctime : float; (** Last status change time *)
+ st_ctime : float; (** Last status change time *)
}
val stat : string -> stats
val lstat : string -> stats
@@ -569,23 +569,23 @@ val open_process_full :
and standard error of the command. *)
val close_process_in : in_channel -> process_status
-(** Close channels opened by {!Unix.open_process_in},
+(** Close channels opened by {!Unix.open_process_in},
wait for the associated command to terminate,
and return its termination status. *)
val close_process_out : out_channel -> process_status
-(** Close channels opened by {!Unix.open_process_out},
+(** Close channels opened by {!Unix.open_process_out},
wait for the associated command to terminate,
and return its termination status. *)
val close_process : in_channel * out_channel -> process_status
-(** Close channels opened by {!Unix.open_process},
+(** Close channels opened by {!Unix.open_process},
wait for the associated command to terminate,
and return its termination status. *)
val close_process_full :
in_channel * out_channel * in_channel -> process_status
-(** Close channels opened by {!Unix.open_process_full},
+(** Close channels opened by {!Unix.open_process_full},
wait for the associated command to terminate,
and return its termination status. *)
@@ -659,14 +659,14 @@ val lockf : file_descr -> lock_command -> int -> unit
(** {6 Signals}
Note: installation of signal handlers is performed via
- the functions {!Sys.signal} and {!Sys.set_signal}.
+ the functions {!Sys.signal} and {!Sys.set_signal}.
*)
val kill : int -> int -> unit
(** [kill pid sig] sends signal number [sig] to the process
with id [pid]. *)
-type sigprocmask_command =
+type sigprocmask_command =
SIG_SETMASK
| SIG_BLOCK
| SIG_UNBLOCK
@@ -700,7 +700,7 @@ type process_times =
{ tms_utime : float; (** User time for the process *)
tms_stime : float; (** System time for the process *)
tms_cutime : float; (** User time for the children processes *)
- tms_cstime : float; (** System time for the children processes *)
+ tms_cstime : float; (** System time for the children processes *)
}
(** The execution times (CPU times) of a process. *)
@@ -713,7 +713,7 @@ type tm =
tm_year : int; (** Year - 1900 *)
tm_wday : int; (** Day of week (Sunday is 0) *)
tm_yday : int; (** Day of year 0..365 *)
- tm_isdst : bool; (** Daylight time savings in effect *)
+ tm_isdst : bool; (** Daylight time savings in effect *)
}
(** The type representing wallclock time and calendar date. *)
@@ -758,7 +758,7 @@ val utimes : string -> float -> float -> unit
00:00:00 GMT, Jan. 1, 1970. *)
type interval_timer =
- ITIMER_REAL
+ ITIMER_REAL
(** decrements in real time, and sends the signal [SIGALRM] when expired.*)
| ITIMER_VIRTUAL
(** decrements in process virtual time, and sends [SIGVTALRM] when expired. *)
@@ -770,7 +770,7 @@ type interval_timer =
type interval_timer_status =
{ it_interval : float; (** Period *)
- it_value : float; (** Current value of the timer *)
+ it_value : float; (** Current value of the timer *)
}
(** The type describing the status of an interval timer *)
@@ -821,7 +821,7 @@ type passwd_entry =
pw_gid : int;
pw_gecos : string;
pw_dir : string;
- pw_shell : string
+ pw_shell : string
}
(** Structure of entries in the [passwd] database. *)
@@ -829,7 +829,7 @@ type group_entry =
{ gr_name : string;
gr_passwd : string;
gr_gid : int;
- gr_mem : string array
+ gr_mem : string array
}
(** Structure of entries in the [groups] database. *)
@@ -958,11 +958,11 @@ val getsockname : file_descr -> sockaddr
val getpeername : file_descr -> sockaddr
(** Return the address of the host connected to the given socket. *)
-type msg_flag =
+type msg_flag =
MSG_OOB
| MSG_DONTROUTE
| MSG_PEEK
-(** The flags for {!Unix.recv}, {!Unix.recvfrom},
+(** The flags for {!Unix.recv}, {!Unix.recvfrom},
{!Unix.send} and {!Unix.sendto}. *)
val recv : file_descr -> string -> int -> int -> msg_flag list -> int
@@ -1014,7 +1014,7 @@ type socket_optint_option =
(** The socket options that can be consulted with {!Unix.getsockopt_optint}
and modified with {!Unix.setsockopt_optint}. These options have a
value of type [int option], with [None] meaning ``disabled''. *)
-
+
type socket_float_option =
SO_RCVTIMEO (** Timeout for input operations *)
| SO_SNDTIMEO (** Timeout for output operations *)
@@ -1084,14 +1084,14 @@ type host_entry =
{ h_name : string;
h_aliases : string array;
h_addrtype : socket_domain;
- h_addr_list : inet_addr array
+ h_addr_list : inet_addr array
}
(** Structure of entries in the [hosts] database. *)
type protocol_entry =
- { p_name : string;
- p_aliases : string array;
- p_proto : int
+ { p_name : string;
+ p_aliases : string array;
+ p_proto : int
}
(** Structure of entries in the [protocols] database. *)
@@ -1099,7 +1099,7 @@ type service_entry =
{ s_name : string;
s_aliases : string array;
s_port : int;
- s_proto : string
+ s_proto : string
}
(** Structure of entries in the [services] database. *)
@@ -1143,7 +1143,7 @@ type getaddrinfo_option =
AI_FAMILY of socket_domain (** Impose the given socket domain *)
| AI_SOCKTYPE of socket_type (** Impose the given socket type *)
| AI_PROTOCOL of int (** Impose the given protocol *)
- | AI_NUMERICHOST (** Do not call name resolver,
+ | AI_NUMERICHOST (** Do not call name resolver,
expect numeric IP address *)
| AI_CANONNAME (** Fill the [ai_canonname] field
of the result *)
@@ -1151,7 +1151,7 @@ type getaddrinfo_option =
for use with {!Unix.bind} *)
(** Options to {!Unix.getaddrinfo}. *)
-val getaddrinfo:
+val getaddrinfo:
string -> string -> getaddrinfo_option list -> addr_info list
(** [getaddrinfo host service opts] returns a list of {!Unix.addr_info}
records describing socket parameters and addresses suitable for
@@ -1200,7 +1200,7 @@ val getnameinfo : sockaddr -> getnameinfo_option list -> name_info
complete description. *)
type terminal_io =
- {
+ {
(* input modes *)
mutable c_ignbrk : bool; (** Ignore the break condition. *)
mutable c_brkint : bool; (** Signal interrupt on break condition. *)
@@ -1245,14 +1245,14 @@ type terminal_io =
before the read request is satisfied. *)
mutable c_vtime : int; (** Maximum read wait (in 0.1s units). *)
mutable c_vstart : char; (** Start character (usually ctrl-Q). *)
- mutable c_vstop : char; (** Stop character (usually ctrl-S). *)
+ mutable c_vstop : char; (** Stop character (usually ctrl-S). *)
}
val tcgetattr : file_descr -> terminal_io
(** Return the status of the terminal referred to by the given
file descriptor. *)
-type setattr_when =
+type setattr_when =
TCSANOW
| TCSADRAIN
| TCSAFLUSH
@@ -1276,7 +1276,7 @@ val tcdrain : file_descr -> unit
(** Waits until all output written on the given file descriptor
has been transmitted. *)
-type flush_queue =
+type flush_queue =
TCIFLUSH
| TCOFLUSH
| TCIOFLUSH
@@ -1288,7 +1288,7 @@ val tcflush : file_descr -> flush_queue -> unit
[TCOFLUSH] flushes data written but not transmitted, and
[TCIOFLUSH] flushes both. *)
-type flow_action =
+type flow_action =
TCOOFF
| TCOON
| TCIOFF