This file is indexed.

/usr/lib/ocaml/cf/cf_seq.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
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
(*---------------------------------------------------------------------------*
  INTERFACE  cf_seq.mli

  Copyright (c) 2002-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. 
 *---------------------------------------------------------------------------*)

(** Lazily-evaluated sequences (functional streams). *)

(** {6 Overview} *)

(** This module implements a functional stream type.  It's like the built-in
    list type, but the tail of every element in the list is lazily evaluated.
    This means it is possible to represent sequences of infinite length, and
    define functions that operate on sequences in a functional, rather than
    imperative mode.  Many of the other modules in the [cf] library make
    extensive use of this type.
    
    The functions for manipulating static lists in the standard [List] library
    all have equivalents here in this module.  Additionally, there are some
    convenient functions for converting structures with imperative interfaces
    into sequences that permit functional algorithms to be applied.
*)

(** {6 Types} *)

(** A lazily-evaluated sequence. *)
type 'a t = 'a cell Lazy.t and 'a cell =
    | P of 'a * 'a t    (** Element of a sequence *)
    | Z                 (** End of sequence *)

(** {6 Exceptions} *)

(** Operation not possible on an empty list. *)
exception Empty

(** {6 Functions} *)

(** An empty sequence. *)
val nil: 'a t

(** Returns the first element in the sequence.  Raises [Empty] if the sequence
    has no elements, i.e. if the sequence is [Z].
*)
val head: 'a t -> 'a

(** Discards the first element in the sequence and returns the sequence of
    remaining elements.  Raises [Empty] if the sequence has no elements, i.e.
    if the sequence is [Z].
*)
val tail: 'a t -> 'a t

(** [concat a b] returns the sequence of all the elements in [a] followed by
    all the elements in [b].  Adds a constant cost to the evaluation of every
    element in the resulting sequence prior to the start of elements from [b],
    so it may be worth considering the use of a {!Cf_deque} object in place of
    a [Cf_seq] object to avoid cost explosion.
*)
val concat: 'a t -> 'a t -> 'a t

(** [flatten a] returns the sequence of all the elements in the sequence of
    sequences by concatenating them.
*)
val flatten: 'a t t -> 'a t

(** [limit n s] returns the sequence of all the elements in [s], up to [n]
    elements in number and no more.  Raises [Invalid_argument] if [n < 0].
    If [?x] is provided, then the exception is raised if the sequence is
    evaluated past the limit.
*)
val limit: ?x:exn -> int -> 'a t -> 'a t

(** [shift n s] returns the sequence of all the elements in [s] after the first
    [n] elements are discarded.  Returns the empty sequence if [s] has fewer
    than [n] elements.
*)
val shift: int -> 'a t -> 'a t

(** [sentinel x s] returns a sequence identical to [s] except that [x] is raised
    by evaluating to the end.  This is intended for use in incremental sequence
    processing.
*)
val sentinel: exn -> 'a t -> 'a t

(** [reverse s] evaluates the entire sequence and composes a list of the
    elements in reverse order.  Tail recursive.
*)
val reverse: 'a t -> 'a list

(** Evaluates the entire sequence and returns the number elements. *)
val length: 'a t -> int

(** [unfold f a] returns the sequence composed of the results of applying [f]
    according to the following rule: the first application of [f] is with [a]
    as the argument; if the result is [None] then the empty sequence is
    returned; else, the result is [Some (hd, tl)] and the sequence returned is
    composed of an element [hd] followed by the sequence produced by looping
    through applications of [f tl] until [None] is returned to signal the end
    of the sequence.
    
    The function is defined as follows:
    {[
    let rec unfold f s =
        match f s with
        | Some (hd, tl) -> P (hd, lazy (unfold f tl))
        | None -> Z
    ]}
*)
val unfold: ('b -> ('a * 'b) option) -> 'b -> 'a t

(** [unfold2 f a] is like [unfold f a] above, except that the sequence returned
    has elements which are pairs of output values and the input values that
    correspond to them.
    
    The function is defined as follows:
    {[    
    let rec unfold2 f s =
        match f s with
        | Some (hd, tl) -> P ((hd, s), lazy (unfold2 f tl))
        | None -> Z
    ]}
*)
val unfold2: ('b -> ('a * 'b) option) -> 'b -> ('a * 'b) t

(** [iterate f s] evaluates the entire sequence [s], applying [f] to each
    element in order until the end of the sequence is reached.  Tail recursive.
*)
val iterate: ('a -> unit) -> 'a t -> unit

(** [predicate f s] evaluates as much of the sequence [s] as necessary to
    determine that every element satisfy the predicate function [f].  If any
    element produces a [false] result, then [false] is returned and the
    remainder of the sequence is not evaluated.  Otherwise, the entire sequence
    is evaluated and [true] is returned.  Tail recursive.
*)
val predicate: ('a -> bool) -> 'a t -> bool

(** [constrain f s] evaluates the sequence [s] by applying [f] to each element
    while the result is [true].  The returned sequence is all the elements of
    [s] before the first element for which [f] returns false.  Tail recursive.
*)
val constrain: ('a -> bool) -> 'a t -> 'a t

(** [search f s] evaluates the sequence [s] until the result of applying [f] is
    [true] and returns the number of elements applied that resulted in a
    [false] result.  Tail recursive.
*)
val search: ('a -> bool) -> 'a t -> int

(** [fold f a s] is like [List.fold_left] and is the result of applying [f] to
    the elements in sequence, i.e. [f (... (f (f a b1) b2) ...) bn], where
    [b1], [b2] ... [bn] are the elements of the sequence.  Evaluates the
    entire sequence [s] in a tail recursive loop.
*)
val fold: ('b -> 'a -> 'b) -> 'b -> 'a t -> 'b

(** [filter f s] returns the sequence produced by applying [f] to every element
    of [s] and taking all the elements for which the result is [true].  The
    sequence returned evaluates [s] on demand.
*)
val filter: ('a -> bool) -> 'a t -> 'a t

(** [map f s] returns the sequence produced by transforming every element in
    [s] by applying it to [f].  The sequence returned evaluates [s] on demand.
*)
val map: ('a -> 'b) -> 'a t -> 'b t

(** [optmap f s] returns the sequence produced by applying [f] to every element
    of [s] and taking all the [Some a] results in order.  The sequence returned
    evaluates [s] on demand.
*)
val optmap: ('a -> 'b option) -> 'a t -> 'b t

(** [listmap f s] returns the sequence produced by applying [f] to every
    element of [s] and taking all the resulting lists of elements in order.
    The sequence returned evaluates [s] on demand.
*)
val listmap: ('a -> 'b list) -> 'a t -> 'b t

(** [seqmap f s] returns the sequence produced by applying [f] to every element
    of [s] and taking all the resulting sequences of elements in order.  The
    sequence returned evaluates [s] on demand.
*)
val seqmap: ('a -> 'b t) -> 'a t -> 'b t

(** [partition f s] returns two sequences.  The first is the sequence of
    elements in [s] for which applying [f] results in [true], and the second
    is the sequence of elements for which applying [f] results in [false].
*)
val partition: ('a -> bool) -> 'a t -> 'a t * 'a t

(** [fcmp f a b] compares two sequences by applying [f] to the elements of
    each sequence in turn until the result is non-zero, or the end of one
    or both sequences is reached.  If the result of [f] is non-zero, then
    that is the value returned; otherwise, the value returned is an indication
    of which sequences have ended.  If [a] ends while [b] continues, then the
    result is [1].  If [b] ends while [a] continues, then the result is [(-1)].
    If both sequences end at the same place, then [0] is returned.
    
    The function is defined as follows:
    {[
    let rec fcmp f s0 s1 =
        match s0, s1 with
        | P (x0, y0), P (x1, y1) ->
            let d = f x0 x1 in
            if d <> 0 then d else fcmp f (Lazy.force y0) (Lazy.force y1)
        | P _, Z -> 1
        | Z, P _ -> -1
        | Z, Z -> 0
    ]}
*)
val fcmp: ('a -> 'a -> int) -> 'a t -> 'a t -> int

(** [cmp a b] is the same as [fcmp Pervasives.compare a b]. *)
val cmp: 'a t -> 'a t -> int

(** [equal a b] returns [true], if every element in both sequences [a] and [b]
    are logically equivalent, as with the built-in [(=)] comparison operator.
    Both sequences are evaluated until one of the sequences reaches the end, or
    the elements in each are found to be inequivalent.
*)
val equal: 'a t -> 'a t -> bool

(** [first s] returns the sequence of elements composed by taking only the
    first object in an element pair.  Evaluates [s] on demand.
*)
val first: ('a * 'b) t -> 'a t

(** [second s] returns the sequence of elements composed by taking only the
    second object in an element pair.  Evaluates [s] on demand.
*)
val second: ('a * 'b) t -> 'b t

(** [split s] is equivalent to [(first s, second s)]. *)
val split: ('a * 'b) t -> 'a t * 'b t

(** [combine a b] returns the sequence composed of the pairs of elements
    produced by combining each element from [a] and the corresponding element
    from [b] in a pair [(a, b)] until all the elements from one or both
    sequences are exhausted.  The sequences [a] and [b] are evaluated on
    demand.  The resulting sequence is only as long as the shorter of the two
    input sequences.
*)
val combine: 'a t -> 'b t -> ('a * 'b) t

(** [iterate2 f a b] is like [iterate f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val iterate2: ('a -> 'b -> unit) -> 'a t -> 'b t -> unit

(** [predicate2 f a b] is like [predicate f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.  If
    the sequences are not the same length, then the result is always [false].
*)
val predicate2: ('a -> 'b -> bool) -> 'a t -> 'b t -> bool

(** [constrain2 f a b] is like [constrain f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end or
    the constrain returns [false].
*)
val constrain2: ('a -> 'b -> bool) -> 'a t -> 'b t -> ('a * 'b) t

(** [fold2 f a s1 s2] is like [fold f a s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val fold2: ('c -> 'a -> 'b -> 'c) -> 'c -> 'a t -> 'b t -> 'c

(** [filter2 f a b] is like [filter f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val filter2: ('a -> 'b -> bool) -> 'a t -> 'b t -> ('a * 'b) t

(** [map2 f a b] is like [map f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val map2: ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t

(** [optmap2 f a b] is like [optmap f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val optmap2: ('a -> 'b -> 'c option) -> 'a t -> 'b t -> 'c t

(** [listmap2 f a b] is like [listmap f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val listmap2: ('a -> 'b -> 'c list) -> 'a t -> 'b t -> 'c t

(** [seqmap2 f a b] is like [seqmap f s], except it operates on a pair of
    sequences simultaneously, until one or both sequences reaches its end.
*)
val seqmap2: ('a -> 'b -> 'c t) -> 'a t -> 'b t -> 'c t

(** [of_channel c] returns the sequence of characters produced by reading them
    on demand from the channel [c].  (Note: this means that dueling [char t]
    sequences reading from the same [in_channel] object may interfere with one
    another.)  The sequence returned ends when [EOF] happens on the channel.
*)
val of_channel: in_channel -> char t

(** [of_string s] returns the sequence of characters produced by extracting
    them on demand from the string [s] with [String.unsafe_get].  Since the
    contents of strings are mutable, be advised that the character extracted
    from the string is determined at the time the position in the sequence is
    evaluated, and that subsequent changes to the string will not be reflected
    in the sequence.
*)
val of_string: string -> char t

(** [of_substring s pos] returns the sequence of characters produced by
    extracting them on demand from the string [s] with [String.unsafe_get].
    Returns [Invalid_argument] if [pos < 0] or [pos >= String.length s].
    The sequence ends when the end of the string is reached.  If a shorter
    substring is desired, use the [limit] function in conjunction.
*)
val of_substring: string -> int -> char t

(** [of_array v] is like [of_string s], except that it operates on an
    ['a array] value instead of a [string] value.
*)
val of_array: 'a array -> 'a t

(** [of_subarray v pos] is like [of_substring s pos], except that it operates
    on an ['a array] value instead of a [string] value.
*)
val of_subarray: 'a array -> int -> 'a t

(** [of_list s] converts a ['a list] value into a sequence. *)
val of_list: 'a list -> 'a t

(** [of_function f] returns a sequence produced by applying [f ()] repeatedly
    until [Not_found] is raised.
*)
val of_function: (unit -> 'a) -> 'a t

(** [to_channel s c] evaluates the entire character sequence [s] and puts each
    character produced into the [out_channel] object in a tail-recursive loop.
*)
val to_channel: char t -> out_channel -> unit

(** [to_string s] evaluates the entire character sequence [s] and composes a
    [string] value containing the characters in order.  Tail-recursive.
*)
val to_string: char t -> string

(** [to_substring s str pos len] overwrites the substring of [str] starting at
    [pos] and running for [len] characters, with the first [len] characters
    from the sequence [s].  If the sequence is shorter than [len] characters,
    then the rest of the substring is not overwritten.  If [pos] and [len] do
    not describe a valid substring of [str], then [Invalid_argument] is raised.
    The unused portion of the character sequence is returned.
*)
val to_substring: char t -> string -> int -> int -> char t

(** [to_array v] is like [to_string s], except that it constructs an ['a array]
    value instead of a [string] value.
*)
val to_array: 'a t -> 'a array

(** [to_subarray s v pos len] is like [to_substring s str pos len], except that
    it overwrites an ['a array] value instead of a [string] value.
*)
val to_subarray: 'a t -> 'a array -> int -> int -> 'a t

(** [to_list s] is the same as [List.rev (reverse s)]. *)
val to_list: 'a t -> 'a list

(** [to_buffer s b] is like [to_channel s c] except that characters are output
    to a [Buffer] object, instead of an [out_channel] object.
*)
val to_buffer: char t -> Buffer.t -> unit

(** [to_function s] returns a function that evaluates the next value in the
    sequence each time it's called.  When the sequence completes, [End_of_file]
    is raised.
*)
val to_function: 'a t -> (unit -> 'a)

(** {6 Monad Functions} *)

(** Use [write x] to compose a continuation monad that puts [x] into the
    sequence produced by evaluation and returns the unit value.
*)
val writeC: 'x -> ('x t, unit) Cf_cmonad.t

(** Use [evalC m] to evaluate the continuation monad [m] to compute the
    sequence it encapsulates.
*)
val evalC: ('x t, unit) Cf_cmonad.t -> 'x t

(** Use [writeSC x] to compose a state-continuation monad that puts [x] into
    the sequence produced by evaluation and returns the unit value.
*)
val writeSC: 'x -> ('s, 'x t, unit) Cf_scmonad.t

(** Use [evalSC m s] to evaluate the state-continuation monad [m] with the
    initial state [s], computing the encapsulated sequence.
*)
val evalSC: ('s, 'x t, unit) Cf_scmonad.t -> 's -> 'x t

(** The module containing the [sequence] and [accumulate] functions for the
    state monad.
*)
module S: sig

    (** Use [sequence z] to compose a monad that binds all of the monads in the
        sequence [z] in the order specified.  Returns the unit value.
    *)
    val sequence: ('x, unit) Cf_smonad.t t -> ('x, unit) Cf_smonad.t
    
    (** Use [accumulate z] to compose a monad that binds all of the monads in
        the sequence [z] in the order specified, accumulating all of the values
        returned into a list.
    *)
    val accumulate: ('x, 'a) Cf_smonad.t t -> ('x, 'a list) Cf_smonad.t
end

(** The module containing the [sequence] and [accumulate] functions for the
    continuation monad.
*)
module C: sig

    (** Use [sequence z] to compose a monad that binds all of the monads in the
        sequence [z] in the order specified.  Returns the unit value.
    *)
    val sequence: ('x, unit) Cf_cmonad.t t -> ('x, unit) Cf_cmonad.t
    
    (** Use [accumulate z] to compose a monad that binds all of the monads in
        the sequence [z] in the order specified, accumulating all of the values
        returned into a list.
    *)
    val accumulate: ('x, 'a) Cf_cmonad.t t -> ('x, 'a list) Cf_cmonad.t
end

(** The module containing the [sequence] and [accumulate] functions for the
    state-continuation monad.
*)
module SC: sig

    (** Use [sequence z] to compose a monad that binds all of the monads in the
        sequence [z] in the order specified.  Returns the unit value.
    *)
    val sequence: ('s, 'x, unit) Cf_scmonad.t t -> ('s, 'x, unit) Cf_scmonad.t
    
    (** Use [accumulate z] to compose a monad that binds all of the monads in
        the sequence [z] in the order specified, accumulating all of the values
        returned into a list.
    *)
    val accumulate:
        ('s, 'x, 'a) Cf_scmonad.t t -> ('s, 'x, 'a list) Cf_scmonad.t
end

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