/usr/lib/ocaml/cf/cf_pqueue.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 | (*---------------------------------------------------------------------------*
INTERFACE cf_pqueue.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.
*---------------------------------------------------------------------------*)
(** A module type for functional priority queue implementations. *)
(** {6 Module Type} *)
(**
This module defines the common interface to functional priority queues in
the {!Cf} library.
*)
module type T = sig
(** The priority queue type *)
type +'a t
(** A module defining the type of the key. Some map implementations may
define more functions in this module for disambiguating keys from one
another.
*)
module Key: sig type t end
(** The empty priority queue. *)
val nil: 'a t
(** Use [empty q] to test whether the priority queue [q] is empty. *)
val empty: 'a t -> bool
(** Use [size q] to count the number of elements in the priority queue [q].
*)
val size: 'a t -> int
(** Use [head q] to obtain the element on the top of the priority queue
[q]. Raises [Not_found] if the queue is empty.
*)
val head: 'a t -> (Key.t * 'a)
(** Use [tail q] to obtain the heap produced by discarding the element on
the top of the priority queue [q]. If [q] is the empty queue, then the
empty queue is returned.
*)
val tail: 'a t -> 'a t
(** Use [pop q] to obtain the head and the tail of a priority queue [q] in
one operation. Returns [None] if the queue [q] is empty.
*)
val pop: 'a t -> ((Key.t * 'a) * 'a t) option
(** Use [put e q] to obtain a new priority queue that is the result of
inserting the element [e] into the queue [q].
*)
val put: (Key.t * 'a) -> 'a t -> 'a t
(** Use [merge q1 q2] to obtain a new priority queue that is the result of
merging all the elements of [q1] and [q2] into a single heap.
*)
val merge: 'a t -> 'a t -> 'a t
(** Use [iterate f q] to apply [f] to every element in the priority queue
[q] in an arbitrary order (not top to bottom).
*)
val iterate: ((Key.t * 'a) -> unit) -> 'a t -> unit
(** Use [predicate f q] to test whether all the elements in priority queue
[q] satisfy the predicate function [f]. Visits the elements in the
queue in arbitrary order (not top to bottom).
*)
val predicate: ((Key.t * 'a) -> bool) -> 'a t -> bool
(** Use [fold f s q] to produce the result of folding a value [s] into
the elements of priority queue [q] with the folding function [f] in an
arbitrary order (not top to bottom).
*)
val fold: ('b -> (Key.t * 'a) -> 'b) -> 'b -> 'a t -> 'b
(** Use [filter f q] to apply [f] to each element in the priority queue [q]
in an arbitrary order (not to top bottom), and produce a new heap that
contains only those elements for which [f pair] returned [true].
*)
val filter: ((Key.t * 'a) -> bool) -> 'a t -> 'a t
(** Use [map f q] to obtain a new heap by applying the mapping function [f]
to the key and the value of every element in the priority queue [q] to
obtain a mapped element with the same key and a new value. The
elements of [q] are visited in an arbitrary order (not top to bottom).
*)
val map: ((Key.t * 'a) -> 'b) -> 'a t -> 'b t
(** Use [optmap f q] to obtain a new heap by applying the mapping function
[f] to the key and the value of every element in priority queue [q] to
obtain a mapped element with the same key and a new value. The
elements of [q] are visited in an arbitrary order (not top to bottom).
When [f] returns [None] for a given key, that key will not be present
in the new queue.
*)
val optmap: ((Key.t * 'a) -> 'b option) -> 'a t -> 'b t
(** Use [partition f q] to obtain a pair of new priority queues that are
the result of applying the partitioning function [f] to each element in
the queue [q] in an arbitrary order (not top to bottom). The first
queue returned will contain all the elements for which [f pair]
returned true, and the second queue will return all the remaining
elements.
*)
val partition: ((Key.t * 'a) -> bool) -> 'a t -> 'a t * 'a t
(** Use [of_seq z] to construct a priority queue from a sequence of
elements. Evaluates the whole sequence.
*)
val of_seq: (Key.t * 'a) Cf_seq.t -> 'a t
(** Use [of_list s] to construct a priority queue from a list of elements.
*)
val of_list: (Key.t * 'a) list -> 'a t
(** Use [to_seq q] to produce a sequence of elements in top to bottom order
from the priority queue [q].
*)
val to_seq: 'a t -> (Key.t * 'a) Cf_seq.t
(** Use [to_seq2 q] to produce a sequence of elements from the priority
queue [q], where the first element of each pair is a key-value pair
obtained from the head of the queue, and the second element of the
pair is the corresponding tail of the queue.
*)
val to_seq2: 'a t -> ((Key.t * 'a) * 'a t) Cf_seq.t
end
(*--- End of File [ cf_pqueue.mli ] ---*)
|