This file is indexed.

/usr/lib/ocaml/cf/cf_gadget.mli is in libcf-ocaml-dev 0.10-4build1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  1
  2
  3
  4
  5
  6
  7
  8
  9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
(*---------------------------------------------------------------------------*
  INTERFACE  cf_gadget.mli

  Copyright (c) 2004-2006, James H. Woodyatt
  All rights reserved.

  Redistribution and use in source and binary forms, with or without
  modification, are permitted provided that the following conditions
  are met:

    Redistributions of source code must retain the above copyright
    notice, this list of conditions and the following disclaimer.

    Redistributions in binary form must reproduce the above copyright
    notice, this list of conditions and the following disclaimer in
    the documentation and/or other materials provided with the
    distribution

  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
  FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
  COPYRIGHT HOLDERS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT,
  INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
  (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
  SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
  HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
  STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
  ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
  OF THE POSSIBILITY OF SUCH DAMAGE. 
 *---------------------------------------------------------------------------*)


(** Monadic composition of complex stream processors.  An experimental
    interface for constructing interactive functional systems in a single
    thread of control.
*)

(** {6 Overview}

    This module implements a marginally more general version of the Gadget
    system described in Chapter 30 of Magnus Carlsson's and Thomas Hallgren's
    joint {{:http://www.cs.chalmers.se/~hallgren/Thesis/}Ph.D. thesis}.
    
    In the context of this module, a "gadget" is a monad that evaluates into
    a {!Cf_flow} object, capable of alternately reading from a source of input
    values and writing to a sink of output values.  The continuation monad is
    specialized over an abstract "work" monad type, and a scheduler handles
    the calls and jumps between multiple simultaneous work units, communicating
    with one another over a very lightweight message passing abstraction called
    a "wire".
    
    The abstract work monad is a kind of state-continuation monad for
    operations over the internal {!Cf_flow} value.  The operations it supports
    are lifted into the gadget monad, and they are summarized as follows:
    
    {ul
        {- {i start}: launch a new gadget in the scheduler.}
        {- {i wire}: create a new message wire.}
        {- {i put}: send a message on a wire.}
        {- {i get}: create a gate for receiving messages on a wire.}
        {- {i guard}: receive a message from one of several gates.}
        {- {i read}: read a new value from the external input.}
        {- {i write}: write a new value to the external output.}
    }
    
    A wire is logically composed of a receiver and a transmitter, with weak
    mutual references between them.  When either end of the wire is reclaimed
    by the memory allocator, the other end is automatically rendered into a
    null wire, i.e. receivers never get messages and transmitters put messages
    by discarding them.
    
    A pair of classes are provided to represent the receiver and the
    transmitter on a wire.  Objects of the [rx] class define a [get] method for
    creating a "gate" that can receive a message.  Objects of the [tx] class
    define a [put] method for transmitting a message.  Both objects can be
    constructed with a wire object, and a convenience operators are defined for
    creating a new wire and construction a pair of associated [rx] and [tx]
    objects.
    
    Any gadget may read from the internal input stream or write to the
    external output stream.  Conventionally, it is often simpler to define a
    a reader gadget and a writer gadget to localize these effects.
    
    {b Note}: see Magnus Carlsson's and Thomas Hallgren's joint
    {{:http://www.cs.chalmers.se/~hallgren/Thesis/}Ph.D. thesis} for a complete
    dissertation on the nature of the system of concepts behind this module.
*)

(** {6 Types} *)

(** An functionally compositional work unit in a gadget, encapsulating the
    state-continuation monad for the underlying {!Cf_flow} object.
*)
type ('i, 'o) work

(** A gating sequence for receiving messages using the [guard] function. *)
type ('i, 'o) gate

(** An object capable of delivering messages of type ['x] from a sender to a
    a receiver in a [('i, 'o) work] continuation.
*)
type ('x, 'i, 'o) wire

(** A guard for receiving a message from one or more sources. *)
type ('i, 'o, 'a) guard = (('i, 'o) gate, 'a) Cf_cmonad.t

(** A continuation monad parameterized by work unit type. *)
type ('i, 'o, 'a) t = (('i, 'o) work, 'a) Cf_cmonad.t

(** {6 Functions} *)

(** Use [eval y] to obtain a new flow by evaluating the gadget monad [y]. *)
val eval: ('i, 'o, unit) t -> ('i, 'o) Cf_flow.t

(** Use [start y] to start a new gadget evaluating the gadget [y]. *)
val start: ('i, 'o, unit) t -> ('i, 'o, unit) t

(** Use [guard m] to receive the next message guarded by [m].  The continuation
    bound to the result is discarded and control passes to the scheduler.
*)
val guard: ('i, 'o, unit) guard -> ('i, 'o, 'a) t

(** Use [abort] to abort gadgeting and return to the scheduler.  This is a
    convenient shortcut for [guard Cf_cmonad.nil].
*)
val abort: ('i, 'o, 'a) t

(** Use [wire] to return a new wire for carrying messages of type ['x]. *)
val wire: ('i, 'o, ('x, 'i, 'o) wire) t

(** Use [wirepair] to return a pair of new wires for carrying messages of type
    ['x] and ['y].
*)
val wirepair: ('i, 'o, ('x, 'i, 'o) wire * ('y, 'i, 'o) wire) t

(** Use [null] to construct a wire that discards every message transmitted
    without ever delivering it.  Such wires can be useful for default arguments
    to some gadget functions.
*)
val null: ('i, 'o, ('x, 'i, 'o) wire) t

(** Bind [read] to get the next input value from the external stream. *)
val read: ('i, 'o, 'i) t

(** Bind the result of [write obj] to put the next output value into the
    external stream.
*)
val write: 'o -> ('i, 'o, unit) t

(** {6 Classes} *)

(** The class type of connector objects. *)
class type connector =
    object
        (** Returns a string representation of the wire end identifier. *)
        method id: string

        (** Returns [true] if the other end of the wire has not yet been
            reclaimed by the garbage collector.
        *)
        method check: bool
        
        (** Cut the connection between the receiver and the transmitter. *)
        (* method cut: unit *)
    end

(** The class of receiver objects. *)
class ['x, 'i, 'o] rx:
    ('x, 'i, 'o) wire -> (** A wire carrying messages of type ['x]. *)
    object
        inherit connector
        
        (** Use [rx#get f] to produce a guard that receives a message on the
            associated wire by applying the function [f] to it.
        *)
        method get: ('x -> ('i, 'o, unit) t) -> ('i, 'o, unit) guard
    end

(** The class of transmitter objects. *)
class ['x, 'i, 'o] tx:
    ('x, 'i, 'o) wire -> (** A wire carrying messages of type ['x]. *)
    object
        inherit connector
        
        (** Use [tx#put obj] to schedule the message obj for deliver on the
            associated wire.
        *)
        method put: 'x -> ('i, 'o, unit) t
    end

(** {6 Miscellaneous} *)

(** Use [connect m] to construct a new matching pair of [rx] and [tx] objects
    from the wire returned by [m].
*)
val connect:
    ('i, 'o, ('x, 'i, 'o) wire) t ->
    ('i, 'o, ('x, 'i, 'o) rx * ('x, 'i, 'o) tx) t

(** Use [simplex] to construct a new matching pair of [rx] and [tx] objects.
    This is a convenient abbreviation of [connect wire].
*)
val simplex: ('i, 'o, ('x, 'i, 'o) rx * ('x, 'i, 'o) tx) t

(** A pair of convenience types for representing each end of a bundle of two
    wires used for duplex communication.  By convention, a [pad] comprises a
    receiver for control events and a transmitter for notification events, and
    a [fix] comprises the transmitter for control events and the receiver for
    notification events
*)
type ('x, 'y, 'i, 'o) pad = ('x, 'i, 'o) rx * ('y, 'i, 'o) tx
type ('x, 'y, 'i, 'o) fix = ('y, 'i, 'o) rx * ('x, 'i, 'o) tx

(** Use [connectpair m] to construct a new duplex communication channel,
    composed with the wire pair returned by [m].  A matching [fix] and [pad] of
    the channel are returned.
*)
val connectpair:
    ('i, 'o, ('x, 'i, 'o) wire * ('y, 'i, 'o) wire) t ->
    ('i, 'o, ('x, 'y, 'i, 'o) fix * ('x, 'y, 'i, 'o) pad) t

(** Use [duplex] to construct a new duplex communication channel, composed of
    two wires each in opposite flow.  A matching [fix] and [pad] for each
    channel are returned.  This is a convenient abbreviation of
    [connectpair wirepair].
*)
val duplex: ('i, 'o, ('x, 'y, 'i, 'o) fix * ('x, 'y, 'i, 'o) pad) t

(** Use [wrap rx tx w] to start a new gadget that wraps the flow [w], so that
    it reads output from the flow (copying it to [tx] object) and writes input
    to the flow (copying it from the [rx] object).
*)
val wrap:
    ('x, 'i, 'o) #rx -> ('y, 'i, 'o) #tx -> ('x, 'y) Cf_flow.t ->
    ('i, 'o, unit) t

(** Use [inherit \['i, 'o\] next] to derive a class that implements an
    intermediate state in a machine.
*)
class virtual ['i, 'o] next:
    object('self)        
        (** The guard evaluated by this state of the machine. *)
        method virtual private guard: ('i, 'o, unit) guard

        (** Use [obj#next] to transition the state of the gadget by applying
            {!Cf_state_gadget.guard} [self#guard].
        *)
        method next: 'a. ('i, 'o, 'a) t
    end

(** Use [inherit \['i, 'o\] start] to derive a class to represent the
    initial state of a machine.  It's [start] method initiates the machine
    with the virtual private [guard] method.
*)
class virtual ['i, 'o] start:
    object('self)
        (** The first guard evaluationed by the machine after starting. *)
        method virtual private guard: ('i, 'o, unit) guard
        
        (** Starts a new gadget, i.e. [start (guard self#guard)]. *)
        method start: ('i, 'o, unit) t
    end

(** Use [create f] to create a duplex channel, and apply [f] to the resulting
    [pad] to obtain the initial state of a machine.  The machine is started and
    the corresponding [fix] is returned.
*)
val create:
    (('c, 'n, 'i, 'o) pad -> ('i, 'o) #start) ->
    ('i, 'o, ('c, 'n, 'i, 'o) fix) t

(** Use [createM f] to create a duplex channel, and apply [f] to the resulting
    [pad] to obtain a continuation monad that evaluates to the initial state of
    a machine.  The machine is started and the corresponding [fix] is returned.
*)
val createM:
    (('c, 'n, 'i, 'o) pad -> ('i, 'o, ('i, 'o) #start) t) ->
    ('i, 'o, ('c, 'n, 'i, 'o) fix) t

(*--- End of File [ cf_gadget.mli ] ---*)