/usr/lib/ocaml/cf/cf_deque.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 | (*---------------------------------------------------------------------------*
INTERFACE cf_deque.mli
Copyright (c) 2003-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.
*---------------------------------------------------------------------------*)
(** A functional persistent double-ended catenable deque, with O{_ avg}(1) cost
for every operation. Internally, this is a recursive data structure with
height O(log N).
*)
(** The abstract type of a deque. *)
type +'a t
(** The empty deque. *)
val nil: 'a t
(** Returns [true] if the deque is the empty deque. *)
val empty: 'a t -> bool
(** Functions for operations on one of the two ends of a deque. *)
module type Direction_T = sig
(** [push x d] adds the element [x] to the end of the deque [d]. The
average cost is constant. Worst-case running time is O(log N), which
happens once in every N operations. Not tail-recursive.
*)
val push: 'a -> 'a t -> 'a t
(** [pop d] returns [None] if [d] is the empty deque, otherwise it returns
[Some (x, d')] where [x] is the element on the end of the deque, and
[d'] is the remainder of [d] with the element [x] removed. The average
cost is constant. Worst-case running time is O(log N), which happens
once in every N operations. Not tail-recursive.
*)
val pop: 'a t -> ('a * 'a t) option
(** [head d] returns the element at the end of the deque [d]. Raises
[Not_found] if the deque is empty. Not tail-recursive.
*)
val head: 'a t -> 'a
(** [tail d] is discards the element at the end of the deque [d]. Raises
[Not_found] if the deque is empty. Not tail-recursive.
*)
val tail: 'a t -> 'a t
(** [fold f a0 d] is [f (... (f (f a0 e0) e1) ...) en] when [e0..en] are
the elements of the deque [d]. Not tail recursive.
*)
val fold: ('b -> 'a -> 'b) -> 'b -> 'a t -> 'b
(** Use [of_list s] to construct a deque from a list of elements. Th
resulting elements begin at the head of the deque.
*)
val of_list: 'a list -> 'a t
(** Use [of_seq z] to construct a deque from a sequence of elements.
Evaluates the whole sequence and the resulting elements begin at the
head of the deque..
*)
val of_seq: 'a Cf_seq.t -> 'a t
(** [to_list d] returns the elements in the deque in the order they would
appear by successive calls of [pop d].
*)
val to_list: 'a t -> 'a list
(** [to_seq d] returns a lazily evaluated sequence of the elements in the
deque in the order they would appear by successive calls of [pop d].
*)
val to_seq: 'a t -> 'a Cf_seq.t
(** [to_seq2 d] returns a lazily evaluated sequence of the pairs [(hd, tl)]
obtained by successively calling of [pop d].
*)
val to_seq2: 'a t -> ('a * 'a t) Cf_seq.t
end
module A: Direction_T (** Operations on the left end of a deque. *)
module B: Direction_T (** Operations on the right end of a deque. *)
(** [iterate f d] applies [f] to every element in [d] in left-to-right
order. Not tail recursive.
*)
val iterate: ('a -> unit) -> 'a t -> unit
(** [predicate f d] returns [true] if the result of applying [f] to every
element in the deque [d] is [true], or if [d] is the empty deque. The
order in which elements are applied is left to right. If [f] returns
[false], then no more elements from [d] will be applied and the result
will be returned immediately. Not tail recursive.
*)
val predicate: ('a -> bool) -> 'a t -> bool
(** [filter f d] returns a new deque composed by applying [f] to every element
in [d], including only those elements for which the result is [true]. The
function is applied to the elements in the deque in left-to-right order.
Not tail recursive.
*)
val filter: ('a -> bool) -> 'a t -> 'a t
(** [map f d] returns a new deque composed by applying [f] to every element in
[d] in left-to-right order. Not tail recursive.
*)
val map: ('a -> 'b) -> 'a t -> 'b t
(** [optmap f d] returns a new deque composed by applying [f] to every element
in [d] in left-to-right order, including only those elements of [d]
for which [f] returns [Some] value. Not tail recursive.
*)
val optmap: ('a -> 'b option) -> 'a t -> 'b t
(** [listmap f d] returns a new deque composed by applying [f] to every element
in [d] in left-to-right order, taking all the resulting lists of
elements in order. Not tail recursive.
*)
val listmap: ('a -> 'b list) -> 'a t -> 'b t
(** [seqmap f d] returns a new deque composed by applying [f] to every element
in [d] in left-to-right order, taking all the resulting sequences of
elements in order. Not tail recursive.
*)
val seqmap: ('a -> 'b Cf_seq.t) -> 'a t -> 'b t
(** [partition f s] returns two deques. The first is the deque of
elements in [d] for which applying [f] results in [true], and the second
is the deque of elements for which applying [f] results in [false]. The
elements are applied in left-to-right order.
*)
val partition: ('a -> bool) -> 'a t -> 'a t * 'a t
(** [length d] computes the number elements contained in the deque [d]. Not
tail recursive.
*)
val length: 'a t -> int
(** [catenate d1 d2] returns a new deque composed by joining the right end of
[d1] to the left end of [d2]. The average cost is constant. Not
tail-recursive.
*)
val catenate: 'a t -> 'a t -> 'a t
(*--- End of File [ cf_deque.mli ] ---*)
|