]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/otherlibs/threads/event.mli
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / otherlibs / threads / event.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*  David Nowak and 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: event.mli 7322 2006-01-12 03:24:56Z garrigue $ *)
15
16 (** First-class synchronous communication.
17
18    This module implements synchronous inter-thread communications over
19    channels. As in John Reppy's Concurrent ML system, the communication 
20    events are first-class values: they can be built and combined
21    independently before being offered for communication. 
22 *)
23
24 type 'a channel
25 (** The type of communication channels carrying values of type ['a]. *)
26
27 val new_channel : unit -> 'a channel
28 (** Return a new channel. *)
29
30 type +'a event
31 (** The type of communication events returning a result of type ['a]. *)
32
33 (** [send ch v] returns the event consisting in sending the value [v]
34    over the channel [ch]. The result value of this event is [()]. *) 
35 val send : 'a channel -> 'a -> unit event
36
37 (** [receive ch] returns the event consisting in receiving a value
38    from the channel [ch]. The result value of this event is the
39    value received. *) 
40 val receive : 'a channel -> 'a event
41
42 val always : 'a -> 'a event
43 (** [always v] returns an event that is always ready for
44    synchronization.  The result value of this event is [v]. *)
45
46 val choose : 'a event list -> 'a event
47 (** [choose evl] returns the event that is the alternative of
48    all the events in the list [evl]. *)
49
50 val wrap : 'a event -> ('a -> 'b) -> 'b event
51 (** [wrap ev fn] returns the event that performs the same communications
52    as [ev], then applies the post-processing function [fn]
53    on the return value. *)
54
55 val wrap_abort : 'a event -> (unit -> unit) -> 'a event
56 (** [wrap_abort ev fn] returns the event that performs
57    the same communications as [ev], but if it is not selected
58    the function [fn] is called after the synchronization. *)
59
60 val guard : (unit -> 'a event) -> 'a event
61 (** [guard fn] returns the event that, when synchronized, computes
62    [fn()] and behaves as the resulting event. This allows to
63    compute events with side-effects at the time of the synchronization
64    operation. *)
65
66 val sync : 'a event -> 'a
67 (** ``Synchronize'' on an event: offer all the communication 
68    possibilities specified in the event to the outside world,
69    and block until one of the communications succeed. The result
70    value of that communication is returned. *)
71
72 val select : 'a event list -> 'a
73 (** ``Synchronize'' on an alternative of events.
74    [select evl] is shorthand for [sync(choose evl)]. *)
75
76 val poll : 'a event -> 'a option
77 (** Non-blocking version of {!Event.sync}: offer all the communication 
78    possibilities specified in the event to the outside world,
79    and if one can take place immediately, perform it and return
80    [Some r] where [r] is the result value of that communication.
81    Otherwise, return [None] without blocking. *)
82