]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/otherlibs/threads/thread.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / otherlibs / threads / thread.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: thread.mli 6553 2004-07-13 12:25:21Z xleroy $ *)
15
16 (** Lightweight threads. *)
17
18 type t
19 (** The type of thread handles. *)
20
21
22 (** {6 Thread creation and termination} *)
23
24 val create : ('a -> 'b) -> 'a -> t
25 (** [Thread.create funct arg] creates a new thread of control,
26    in which the function application [funct arg]
27    is executed concurrently with the other threads of the program.
28    The application of [Thread.create]
29    returns the handle of the newly created thread.
30    The new thread terminates when the application [funct arg]
31    returns, either normally or by raising an uncaught exception.
32    In the latter case, the exception is printed on standard error,
33    but not propagated back to the parent thread. Similarly, the
34    result of the application [funct arg] is discarded and not
35    directly accessible to the parent thread. *)
36
37 val self : unit -> t
38 (** Return the thread currently executing. *)
39
40 external id : t -> int = "thread_id"
41 (** Return the identifier of the given thread. A thread identifier
42    is an integer that identifies uniquely the thread.
43    It can be used to build data structures indexed by threads. *)
44
45 val exit : unit -> unit
46 (** Terminate prematurely the currently executing thread. *)
47
48 val kill : t -> unit
49 (** Terminate prematurely the thread whose handle is given.
50    This functionality is available only with bytecode-level threads. *)
51
52 (** {6 Suspending threads} *)
53
54 val delay : float -> unit
55 (** [delay d] suspends the execution of the calling thread for
56    [d] seconds. The other program threads continue to run during
57    this time. *)
58
59 val join : t -> unit
60 (** [join th] suspends the execution of the calling thread
61    until the thread [th] has terminated. *)
62
63 val wait_read : Unix.file_descr -> unit
64 (** See {!Thread.wait_write}.*)
65
66 val wait_write : Unix.file_descr -> unit
67 (** Suspend the execution of the calling thread until at least
68    one character is available for reading ({!Thread.wait_read}) or
69    one character can be written without blocking ([wait_write])
70    on the given Unix file descriptor. *)
71
72 val wait_timed_read : Unix.file_descr -> float -> bool
73 (** See {!Thread.wait_timed_write}.*)
74
75 val wait_timed_write : Unix.file_descr -> float -> bool
76 (** Same as {!Thread.wait_read} and {!Thread.wait_write}, but wait for at most
77    the amount of time given as second argument (in seconds).
78    Return [true] if the file descriptor is ready for input/output
79    and [false] if the timeout expired. *)
80
81 val select :
82   Unix.file_descr list -> Unix.file_descr list -> Unix.file_descr list ->
83     float ->
84     Unix.file_descr list * Unix.file_descr list * Unix.file_descr list
85 (** Suspend the execution of the calling thead until input/output
86    becomes possible on the given Unix file descriptors.
87    The arguments and results have the same meaning as for
88    {!Unix.select}. *)
89
90 val wait_pid : int -> int * Unix.process_status
91 (** [wait_pid p] suspends the execution of the calling thread
92    until the Unix process specified by the process identifier [p]
93    terminates. A pid [p] of [-1] means wait for any child.
94    A pid of [0] means wait for any child in the same process group
95    as the current process. Negative pid arguments represent
96    process groups. Returns the pid of the child caught and
97    its termination status, as per {!Unix.wait}. *)
98
99 val wait_signal : int list -> int
100 (** [wait_signal sigs] suspends the execution of the calling thread
101    until the process receives one of the signals specified in the
102    list [sigs].  It then returns the number of the signal received.
103    Signal handlers attached to the signals in [sigs] will not
104    be invoked.  Do not call [wait_signal] concurrently 
105    from several threads on the same signals. *)
106
107 val yield : unit -> unit
108 (** Re-schedule the calling thread without suspending it.
109    This function can be used to give scheduling hints,
110    telling the scheduler that now is a good time to
111    switch to other threads. *)
112
113 (**/**)
114
115 (** {6 Synchronization primitives}
116
117    The following primitives provide the basis for implementing 
118    synchronization functions between threads. Their direct use is
119    discouraged, as they are very low-level and prone to race conditions
120    and deadlocks. The modules {!Mutex}, {!Condition} and {!Event}
121    provide higher-level synchronization primitives. *)
122
123 val critical_section : bool ref
124 (** Setting this reference to [true] deactivate thread preemption
125    (the timer interrupt that transfers control from thread to thread),
126    causing the current thread to run uninterrupted until
127    [critical_section] is reset to [false] or the current thread
128    explicitely relinquishes control using [sleep], [delay],
129    [wait_inchan] or [wait_descr]. *)
130
131 val sleep : unit -> unit
132 (** Suspend the calling thread until another thread reactivates it
133    using {!Thread.wakeup}. Just before suspending the thread,
134    {!Thread.critical_section} is reset to [false]. Resetting
135    {!Thread.critical_section} and suspending the calling thread is an
136    atomic operation. *)
137
138 val wakeup : t -> unit
139 (** Reactivate the given thread. After the call to [wakeup],
140    the suspended thread will resume execution at some future time. *)
141