summaryrefslogtreecommitdiff
path: root/stdlib/queue.mli
blob: 83dd83a9c7ae67c975f44b82b82e89e4b48c0146 (plain)
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
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           *)
(*                                                                        *)
(*   Copyright 1996 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(** First-in first-out queues.

   This module implements queues (FIFOs), with in-place modification.
   See {{!examples} the example section} below.
*)

(** {b Unsynchronized accesses} *)

[@@@alert unsynchronized_access
    "Unsynchronized accesses to queues are a programming error."
]

(**
    Unsynchronized accesses to a queue may lead to an invalid queue state.
    Thus, concurrent accesses to queues must be synchronized (for instance
    with a {!Mutex.t}).
*)

type !'a t
(** The type of queues containing elements of type ['a]. *)


exception Empty
(** Raised when {!Queue.take} or {!Queue.peek} is applied to an empty queue. *)


val create : unit -> 'a t
(** Return a new queue, initially empty. *)

val add : 'a -> 'a t -> unit
(** [add x q] adds the element [x] at the end of the queue [q]. *)

val push : 'a -> 'a t -> unit
(** [push] is a synonym for [add]. *)

val take : 'a t -> 'a
(** [take q] removes and returns the first element in queue [q],
   or raises {!Empty} if the queue is empty. *)

val take_opt : 'a t -> 'a option
(** [take_opt q] removes and returns the first element in queue [q],
   or returns [None] if the queue is empty.
   @since 4.08 *)

val pop : 'a t -> 'a
(** [pop] is a synonym for [take]. *)

val peek : 'a t -> 'a
(** [peek q] returns the first element in queue [q], without removing
   it from the queue, or raises {!Empty} if the queue is empty. *)

val peek_opt : 'a t -> 'a option
(** [peek_opt q] returns the first element in queue [q], without removing
   it from the queue, or returns [None] if the queue is empty.
   @since 4.08 *)

val top : 'a t -> 'a
(** [top] is a synonym for [peek]. *)

val clear : 'a t -> unit
(** Discard all elements from a queue. *)

val copy : 'a t -> 'a t
(** Return a copy of the given queue. *)

val is_empty : 'a t -> bool
(** Return [true] if the given queue is empty, [false] otherwise. *)

val length : 'a t -> int
(** Return the number of elements in a queue. *)

val iter : ('a -> unit) -> 'a t -> unit
(** [iter f q] applies [f] in turn to all elements of [q],
   from the least recently entered to the most recently entered.
   The queue itself is unchanged. *)

val fold : ('acc -> 'a -> 'acc) -> 'acc -> 'a t -> 'acc
(** [fold f accu q] is equivalent to [List.fold_left f accu l],
   where [l] is the list of [q]'s elements. The queue remains
   unchanged. *)

val transfer : 'a t -> 'a t -> unit
(** [transfer q1 q2] adds all of [q1]'s elements at the end of
   the queue [q2], then clears [q1]. It is equivalent to the
   sequence [iter (fun x -> add x q2) q1; clear q1], but runs
   in constant time. *)

(** {1 Iterators} *)

val to_seq : 'a t -> 'a Seq.t
(** Iterate on the queue, in front-to-back order.
    The behavior is not specified if the queue is modified
    during the iteration.
    @since 4.07 *)

val add_seq : 'a t -> 'a Seq.t -> unit
(** Add the elements from a sequence to the end of the queue.
    @since 4.07 *)

val of_seq : 'a Seq.t -> 'a t
(** Create a queue from a sequence.
    @since 4.07 *)

(** {1:examples Examples}

  {2 Basic Example}

   A basic example:
    {[
    # let q = Queue.create ()
    val q : '_weak1 Queue.t = <abstr>


    # Queue.push 1 q; Queue.push 2 q; Queue.push 3 q
    - : unit = ()

    # Queue.length q
    - : int = 3

    # Queue.pop q
    - : int = 1

    # Queue.pop q
    - : int = 2

    # Queue.pop q
    - : int = 3

    # Queue.pop q
    Exception: Stdlib.Queue.Empty.
    ]}

  {2 Search Through a Graph}

   For a more elaborate example, a classic algorithmic use of queues
   is to implement a BFS (breadth-first search) through a graph.

   {[
     type graph = {
       edges: (int, int list) Hashtbl.t
     }

    (* Search in graph [g] using BFS, starting from node [start].
       It returns the first node that satisfies [p], or [None] if
       no node reachable from [start] satisfies [p].
    *)
    let search_for ~(g:graph) ~(start:int) (p:int -> bool) : int option =
      let to_explore = Queue.create() in
      let explored = Hashtbl.create 16 in

      Queue.push start to_explore;
      let rec loop () =
        if Queue.is_empty to_explore then None
        else
          (* node to explore *)
          let node = Queue.pop to_explore in
          explore_node node

      and explore_node node =
        if not (Hashtbl.mem explored node) then (
          if p node then Some node (* found *)
          else (
            Hashtbl.add explored node ();
            let children =
              Hashtbl.find_opt g.edges node
              |> Option.value ~default:[]
            in
            List.iter (fun child -> Queue.push child to_explore) children;
            loop()
          )
        ) else loop()
      in
      loop()

    (* a sample graph *)
    let my_graph: graph =
      let edges =
        List.to_seq [
          1, [2;3];
          2, [10; 11];
          3, [4;5];
          5, [100];
          11, [0; 20];
        ]
        |> Hashtbl.of_seq
      in {edges}

    # search_for ~g:my_graph ~start:1 (fun x -> x = 30)
    - : int option = None

    # search_for ~g:my_graph ~start:1 (fun x -> x >= 15)
    - : int option = Some 20

    # search_for ~g:my_graph ~start:1 (fun x -> x >= 50)
    - : int option = Some 100
   ]}
   *)