]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/otherlibs/threads/threadUnix.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / otherlibs / threads / threadUnix.mli
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 (***********************************************************************)
13
14 (* $Id: threadUnix.mli 6553 2004-07-13 12:25:21Z xleroy $ *)
15
16 (** Thread-compatible system calls.
17
18    @deprecated The functionality of this module has been merged back into
19    the {!Unix} module.  Threaded programs can now call the functions
20    from module {!Unix} directly, and still get the correct behavior
21    (block the calling thread, if required, but do not block all threads
22    in the process).  *)
23
24 (** {6 Process handling} *)
25
26 val execv : string -> string array -> unit
27 val execve : string -> string array -> string array -> unit
28 val execvp : string -> string array -> unit
29 val wait : unit -> int * Unix.process_status
30 val waitpid : Unix.wait_flag list -> int -> int * Unix.process_status
31 val system : string -> Unix.process_status
32
33 (** {6 Basic input/output} *)
34
35 val read : Unix.file_descr -> string -> int -> int -> int
36 val write : Unix.file_descr -> string -> int -> int -> int
37 val single_write : Unix.file_descr -> string -> int -> int -> int
38
39 (** {6 Input/output with timeout} *)
40
41 val timed_read : Unix.file_descr -> string -> int -> int -> float -> int
42 (** See {!ThreadUnix.timed_write}. *)
43
44 val timed_write : Unix.file_descr -> string -> int -> int -> float -> int
45 (** Behave as {!ThreadUnix.read} and {!ThreadUnix.write}, except that
46    [Unix_error(ETIMEDOUT,_,_)] is raised if no data is
47    available for reading or ready for writing after [d] seconds.
48    The delay [d] is given in the fifth argument, in seconds. *)
49
50 (** {6 Polling} *)
51
52 val select :
53   Unix.file_descr list -> Unix.file_descr list -> Unix.file_descr list ->
54     float ->
55     Unix.file_descr list * Unix.file_descr list * Unix.file_descr list
56
57 (** {6 Pipes and redirections} *)
58
59 val pipe : unit -> Unix.file_descr * Unix.file_descr
60 val open_process_in : string -> in_channel
61 val open_process_out : string -> out_channel
62 val open_process : string -> in_channel * out_channel
63 val open_process_full :
64   string -> string array -> in_channel * out_channel * in_channel
65
66 (** {6 Time} *)
67
68 val sleep : int -> unit
69
70 (** {6 Sockets} *)
71
72 val socket : Unix.socket_domain -> Unix.socket_type -> int -> Unix.file_descr
73 val socketpair :
74   Unix.socket_domain -> Unix.socket_type -> int ->
75     Unix.file_descr * Unix.file_descr
76 val accept : Unix.file_descr -> Unix.file_descr * Unix.sockaddr
77 val connect : Unix.file_descr -> Unix.sockaddr -> unit
78 val recv :
79   Unix.file_descr -> string -> int -> int -> Unix.msg_flag list -> int
80 val recvfrom :
81   Unix.file_descr -> string -> int -> int -> Unix.msg_flag list ->
82     int * Unix.sockaddr
83 val send :
84   Unix.file_descr -> string -> int -> int -> Unix.msg_flag list -> int
85 val sendto :
86   Unix.file_descr -> string -> int -> int -> Unix.msg_flag list ->
87     Unix.sockaddr -> int
88 val open_connection : Unix.sockaddr -> in_channel * out_channel
89 val establish_server :
90   (in_channel -> out_channel -> unit) -> Unix.sockaddr -> unit