~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/queue.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1996</year>
 
8
      <year>2008</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>queue</title>
 
27
    <prepared>Joe</prepared>
 
28
    <responsible>Bjarne D&auml;cker</responsible>
 
29
    <docno>1</docno>
 
30
    <approved>Bjarne D&auml;cker</approved>
 
31
    <checked></checked>
 
32
    <date>97-01-15</date>
 
33
    <rev>B</rev>
 
34
    <file>queue.sgml</file>
 
35
  </header>
 
36
  <module>queue</module>
 
37
  <modulesummary>Abstract Data Type for FIFO Queues</modulesummary>
 
38
  <description>
 
39
    <p>This module implements (double ended) FIFO queues
 
40
      in an efficient manner.</p>
 
41
    <p>All functions fail with reason <c>badarg</c> if arguments
 
42
      are of wrong type, for example queue arguments are not
 
43
      queues, indexes are not integers, list arguments are
 
44
      not lists. Improper lists cause internal crashes.
 
45
      An index out of range for a queue also causes
 
46
      a failure with reason <c>badarg</c>.</p>
 
47
    <p>Some functions, where noted, fail with reason <c>empty</c>
 
48
      for an empty queue.</p>
 
49
    <p>All operations has an amortized O(1) running time, except
 
50
      <c>len/1</c>, <c>join/2</c>,
 
51
      <c>split/2</c> and <c>filter/2</c> that are O(n).
 
52
      To minimize the size of a queue minimizing
 
53
      the amount of garbage built by queue operations, the queues
 
54
      do not contain explicit length information, and that is
 
55
      why <c>len/1</c> is O(n). If better performance for this
 
56
      particular operation is essential, it is easy for
 
57
      the caller to keep track of the length.</p>
 
58
    <p>Queues are double ended. The mental picture of
 
59
      a queue is a line of people (items) waiting for
 
60
      their turn. The queue front is the end with the item
 
61
      that has waited the longest. The queue rear is the end
 
62
      an item enters when it starts to wait. If instead using
 
63
      the mental picture of a list, the front is called head
 
64
      and the rear is called tail.</p>
 
65
    <p>Entering at the front and exiting at the rear
 
66
      are reverse operations on the queue.</p>
 
67
    <p>The module has several sets of interface functions. The
 
68
      "Original API", the "Extended API" and the "Okasaki API".</p>
 
69
    <p>The "Original API" and the "Extended API" both use the
 
70
      mental picture of a waiting line of items. Both also 
 
71
      have reverse operations suffixed "_r".</p>
 
72
    <p>The "Original API" item removal functions return compound
 
73
      terms with both the removed item and the resulting queue.
 
74
      The "Extended API" contain alternative functions that build
 
75
      less garbage as well as functions for just inspecting the
 
76
      queue ends. Also the "Okasaki API" functions build less garbage.</p>
 
77
    <p>The "Okasaki API" is inspired by "Purely Functional Data structures"
 
78
      by Chris Okasaki. It regards queues as lists.
 
79
      The API is by many regarded as strange and avoidable.
 
80
      For example many reverse operations have lexically reversed names,
 
81
      some with more readable but perhaps less understandable aliases.</p>
 
82
  </description>
 
83
 
 
84
 
 
85
 
 
86
  <section>
 
87
    <title>Original API</title>
 
88
  </section>
 
89
 
 
90
  <funcs>
 
91
    <func>
 
92
      <name>new() -> Q</name>
 
93
      <fsummary>Create an empty queue</fsummary>
 
94
      <type>
 
95
        <v>Q = queue()</v>
 
96
      </type>
 
97
      <desc>
 
98
        <p>Returns an empty queue.</p>
 
99
      </desc>
 
100
    </func>
 
101
    <func>
 
102
      <name>is_queue(Term) -> true | false</name>
 
103
      <fsummary>Test if a term is a queue</fsummary>
 
104
      <type>
 
105
        <v>Term = term()</v>
 
106
      </type>
 
107
      <desc>
 
108
        <p>Tests if <c>Q</c> is a queue and returns <c>true</c> if so and
 
109
          <c>false</c> otherwise.</p>
 
110
      </desc>
 
111
    </func>
 
112
    <func>
 
113
      <name>is_empty(Q) -> true | false</name>
 
114
      <fsummary>Test if a queue is empty</fsummary>
 
115
      <type>
 
116
        <v>Q = queue()</v>
 
117
      </type>
 
118
      <desc>
 
119
        <p>Tests if <c>Q</c> is empty and returns <c>true</c> if so and
 
120
          <c>false</c> otherwise.</p>
 
121
      </desc>
 
122
    </func>
 
123
    <func>
 
124
      <name>len(Q) -> N</name>
 
125
      <fsummary>Get the length of a queue</fsummary>
 
126
      <type>
 
127
        <v>Q = queue()</v>
 
128
        <v>N = integer()</v>
 
129
      </type>
 
130
      <desc>
 
131
        <p>Calculates and returns the length of queue <c>Q</c>.</p>
 
132
      </desc>
 
133
    </func>
 
134
 
 
135
    <func>
 
136
      <name>in(Item, Q1) -> Q2</name>
 
137
      <fsummary>Insert an item at the rear of a queue</fsummary>
 
138
      <type>
 
139
        <v>Item = term()</v>
 
140
        <v>Q1 = Q2 = queue()</v>
 
141
      </type>
 
142
      <desc>
 
143
        <p>Inserts <c>Item</c> at the rear of queue <c>Q1</c>.
 
144
          Returns the resulting queue <c>Q2</c>.</p>
 
145
      </desc>
 
146
    </func>
 
147
    <func>
 
148
      <name>in_r(Item, Q1) -> Q2</name>
 
149
      <fsummary>Insert an item at the front of a queue</fsummary>
 
150
      <type>
 
151
        <v>Item = term()</v>
 
152
        <v>Q1 = Q2 = queue()</v>
 
153
      </type>
 
154
      <desc>
 
155
        <p>Inserts <c>Item</c> at the front of queue <c>Q1</c>.
 
156
          Returns the resulting queue <c>Q2</c>.</p>
 
157
      </desc>
 
158
    </func>
 
159
    <func>
 
160
      <name>out(Q1) -> Result</name>
 
161
      <fsummary>Remove the front item from a queue</fsummary>
 
162
      <type>
 
163
        <v>Result = {{value, Item}, Q2} | {empty, Q1}</v>
 
164
        <v>Q1 = Q2 = queue()</v>
 
165
      </type>
 
166
      <desc>
 
167
        <p>Removes the item at the front of queue <c>Q1</c>. Returns the
 
168
          tuple <c>{{value, Item}, Q2}</c>, where <c>Item</c> is the
 
169
          item removed and <c>Q2</c> is the resulting queue. If <c>Q1</c> is
 
170
          empty, the tuple <c>{empty, Q1}</c> is returned.</p>
 
171
      </desc>
 
172
    </func>
 
173
    <func>
 
174
      <name>out_r(Q1) -> Result</name>
 
175
      <fsummary>Remove the rear item from a queue</fsummary>
 
176
      <type>
 
177
        <v>Result = {{value, Item}, Q2} | {empty, Q1}</v>
 
178
        <v>Q1 = Q2 = queue()</v>
 
179
      </type>
 
180
      <desc>
 
181
        <p>Removes the item at the rear of the queue <c>Q1</c>. Returns the
 
182
          tuple <c>{{value, Item}, Q2}</c>, where <c>Item</c> is the 
 
183
          item removed and <c>Q2</c> is the new queue. If <c>Q1</c> is
 
184
          empty, the tuple <c>{empty, Q1}</c> is returned.  </p>
 
185
      </desc>
 
186
    </func>
 
187
 
 
188
    <func>
 
189
      <name>from_list(L) -> queue()</name>
 
190
      <fsummary>Convert a list to a queue</fsummary>
 
191
      <type>
 
192
        <v>L = list()</v>
 
193
      </type>
 
194
      <desc>
 
195
        <p>Returns a queue containing the items in <c>L</c> in the
 
196
          same order; the head item of the list will become the front
 
197
          item of the queue.</p>
 
198
      </desc>
 
199
    </func>
 
200
    <func>
 
201
      <name>to_list(Q) -> list()</name>
 
202
      <fsummary>Convert a queue to a list</fsummary>
 
203
      <type>
 
204
        <v>Q = queue()</v>
 
205
      </type>
 
206
      <desc>
 
207
        <p>Returns a list of the items in the queue in the same order;
 
208
          the front item of the queue will become the head of the list.</p>
 
209
      </desc>
 
210
    </func>
 
211
 
 
212
    <func>
 
213
      <name>reverse(Q1) -> Q2</name>
 
214
      <fsummary>Reverse a queue</fsummary>
 
215
      <type>
 
216
        <v>Q1 = Q2 = queue()</v>
 
217
      </type>
 
218
      <desc>
 
219
        <p>Returns a queue <c>Q2</c> that contains the items of
 
220
          <c>Q1</c> in the reverse order.</p>
 
221
      </desc>
 
222
    </func>
 
223
    <func>
 
224
      <name>split(N, Q1) -> {Q2,Q3}</name>
 
225
      <fsummary>Split a queue in two</fsummary>
 
226
      <type>
 
227
        <v>N = integer()</v>
 
228
        <v>Q1 = Q2 = Q3 = queue()</v>
 
229
      </type>
 
230
      <desc>
 
231
        <p>Splits <c>Q1</c> in two. The <c>N</c> front items
 
232
          are put in <c>Q2</c> and the rest in <c>Q3</c></p>
 
233
      </desc>
 
234
    </func>
 
235
    <func>
 
236
      <name>join(Q1, Q2) -> Q3</name>
 
237
      <fsummary>Join two queues</fsummary>
 
238
      <type>
 
239
        <v>Q1 = Q2 = Q3 = queue()</v>
 
240
      </type>
 
241
      <desc>
 
242
        <p>Returns a queue <c>Q3</c> that is the result of joining
 
243
          <c>Q1</c> and <c>Q2</c> with <c>Q1</c> in front of
 
244
          <c>Q2</c>.</p>
 
245
      </desc>
 
246
    </func>
 
247
    <func>
 
248
      <name>filter(Fun, Q1) -> Q2</name>
 
249
      <fsummary>Filter a queue</fsummary>
 
250
      <type>
 
251
        <v>Fun = fun(Item) -> bool() | list()</v>
 
252
        <v>Q1 = Q2 = queue()</v>
 
253
      </type>
 
254
      <desc>
 
255
        <p>Returns a queue <c>Q2</c> that is the result of calling
 
256
          <c>Fun(Item)</c> on all items in <c>Q1</c>,
 
257
          in order from front to rear.</p>
 
258
        <p>If <c>Fun(Item)</c> returns <c>true</c>, <c>Item</c>
 
259
          is copied to the result queue. If it returns <c>false</c>,
 
260
          <c>Item</c> is not copied. If it returns a list
 
261
          the list elements are inserted instead of <c>Item</c> in the
 
262
          result queue.</p>
 
263
        <p>So, <c>Fun(Item)</c> returning <c>[Item]</c> is thereby
 
264
          semantically equivalent to returning <c>true</c>, just
 
265
          as returning <c>[]</c> is semantically equivalent to
 
266
          returning <c>false</c>. But returning a list builds
 
267
          more garbage than returning an atom.</p>
 
268
      </desc>
 
269
    </func>
 
270
  </funcs>
 
271
 
 
272
 
 
273
 
 
274
  <section>
 
275
    <title>Extended API</title>
 
276
  </section>
 
277
 
 
278
  <funcs>
 
279
    <func>
 
280
      <name>get(Q) -> Item</name>
 
281
      <fsummary>Return the front item of a queue</fsummary>
 
282
      <type>
 
283
        <v>Item = term()</v>
 
284
        <v>Q = queue()</v>
 
285
      </type>
 
286
      <desc>
 
287
        <p>Returns <c>Item</c> at the front of queue <c>Q</c>.</p>
 
288
        <p>Fails with reason <c>empty</c> if <c>Q</c> is empty.</p>
 
289
      </desc>
 
290
    </func>
 
291
    <func>
 
292
      <name>get_r(Q) -> Item</name>
 
293
      <fsummary>Return the rear item of a queue</fsummary>
 
294
      <type>
 
295
        <v>Item = term()</v>
 
296
        <v>Q = queue()</v>
 
297
      </type>
 
298
      <desc>
 
299
        <p>Returns <c>Item</c> at the rear of queue <c>Q</c>.</p>
 
300
        <p>Fails with reason <c>empty</c> if <c>Q</c> is empty.</p>
 
301
      </desc>
 
302
    </func>
 
303
    <func>
 
304
      <name>drop(Q1) -> Q2</name>
 
305
      <fsummary>Remove the front item from a queue</fsummary>
 
306
      <type>
 
307
        <v>Item = term()</v>
 
308
        <v>Q1 = Q2 = queue()</v>
 
309
      </type>
 
310
      <desc>
 
311
        <p>Returns a queue <c>Q2</c> that is the result of removing
 
312
          the front item from <c>Q1</c>.</p>
 
313
        <p>Fails with reason <c>empty</c> if <c>Q1</c> is empty.</p>
 
314
      </desc>
 
315
    </func>
 
316
    <func>
 
317
      <name>drop_r(Q1) -> Q2</name>
 
318
      <fsummary>Remove the rear item from a queue</fsummary>
 
319
      <type>
 
320
        <v>Item = term()</v>
 
321
        <v>Q1 = Q2 = queue()</v>
 
322
      </type>
 
323
      <desc>
 
324
        <p>Returns a queue <c>Q2</c> that is the result of removing
 
325
          the rear item from <c>Q1</c>.</p>
 
326
        <p>Fails with reason <c>empty</c> if <c>Q1</c> is empty.</p>
 
327
      </desc>
 
328
    </func>
 
329
    <func>
 
330
      <name>peek(Q) -> {value,Item} | empty</name>
 
331
      <fsummary>Return the front item of a queue</fsummary>
 
332
      <type>
 
333
        <v>Item = term()</v>
 
334
        <v>Q = queue()</v>
 
335
      </type>
 
336
      <desc>
 
337
        <p>Returns the tuple <c>{value, Item}</c> where <c>Item</c> is the
 
338
          front item of <c>Q</c>, or <c>empty</c> if <c>Q1</c> is empty.</p>
 
339
      </desc>
 
340
    </func>
 
341
    <func>
 
342
      <name>peek_r(Q) -> {value,Item} | empty</name>
 
343
      <fsummary>Return the rear item of a queue</fsummary>
 
344
      <type>
 
345
        <v>Item = term()</v>
 
346
        <v>Q = queue()</v>
 
347
      </type>
 
348
      <desc>
 
349
        <p>Returns the tuple <c>{value, Item}</c> where <c>Item</c> is the
 
350
          rear item of <c>Q</c>, or <c>empty</c> if <c>Q1</c> is empty.</p>
 
351
      </desc>
 
352
    </func>
 
353
  </funcs>
 
354
 
 
355
 
 
356
  <section>
 
357
    <title>Okasaki API</title>
 
358
  </section>
 
359
 
 
360
  <funcs>
 
361
    <func>
 
362
      <name>cons(Item, Q1) -> Q2</name>
 
363
      <fsummary>Insert an item at the head of a queue</fsummary>
 
364
      <type>
 
365
        <v>Item = term()</v>
 
366
        <v>Q1 = Q2 = queue()</v>
 
367
      </type>
 
368
      <desc>
 
369
        <p>Inserts <c>Item</c> at the head of queue <c>Q1</c>. Returns
 
370
          the new queue <c>Q2</c>.</p>
 
371
      </desc>
 
372
    </func>
 
373
    <func>
 
374
      <name>head(Q) -> Item</name>
 
375
      <fsummary>Return the item at the head of a queue</fsummary>
 
376
      <type>
 
377
        <v>Item = term()</v>
 
378
        <v>Q = queue()</v>
 
379
      </type>
 
380
      <desc>
 
381
        <p>Returns <c>Item</c> from the head of queue <c>Q</c>.</p>
 
382
        <p>Fails with reason <c>empty</c> if <c>Q</c> is empty.</p>
 
383
      </desc>
 
384
    </func>
 
385
    <func>
 
386
      <name>tail(Q1) -> Q2</name>
 
387
      <fsummary>Remove the head item from a queue</fsummary>
 
388
      <type>
 
389
        <v>Item = term()</v>
 
390
        <v>Q1 = Q2 = queue()</v>
 
391
      </type>
 
392
      <desc>
 
393
        <p>Returns a queue <c>Q2</c> that is the result of removing
 
394
          the head item from <c>Q1</c>.</p>
 
395
        <p>Fails with reason <c>empty</c> if <c>Q1</c> is empty.</p>
 
396
      </desc>
 
397
    </func>
 
398
    <func>
 
399
      <name>snoc(Q1, Item) -> Q2</name>
 
400
      <fsummary>Insert an item at the tail of a queue</fsummary>
 
401
      <type>
 
402
        <v>Item = term()</v>
 
403
        <v>Q1 = Q2 = queue()</v>
 
404
      </type>
 
405
      <desc>
 
406
        <p>Inserts <c>Item</c> as the tail item of queue <c>Q1</c>. Returns
 
407
          the new queue <c>Q2</c>.</p>
 
408
      </desc>
 
409
    </func>
 
410
    <func>
 
411
      <name>daeh(Q) -> Item</name>
 
412
      <name>last(Q) -> Item</name>
 
413
      <fsummary>Return the tail item of a queue</fsummary>
 
414
      <type>
 
415
        <v>Item = term()</v>
 
416
        <v>Q = queue()</v>
 
417
      </type>
 
418
      <desc>
 
419
        <p>Returns the tail item of queue <c>Q</c>.</p>
 
420
        <p>Fails with reason <c>empty</c> if <c>Q</c> is empty.</p>
 
421
      </desc>
 
422
    </func>
 
423
    <func>
 
424
      <name>liat(Q1) -> Q2</name>
 
425
      <name>init(Q1) -> Q2</name>
 
426
      <name>lait(Q1) -> Q2</name>
 
427
      <fsummary>Remove the tail item from a queue</fsummary>
 
428
      <type>
 
429
        <v>Item = term()</v>
 
430
        <v>Q1 = Q2 = queue()</v>
 
431
      </type>
 
432
      <desc>
 
433
        <p>Returns a queue <c>Q2</c> that is the result of removing
 
434
          the tail item from <c>Q1</c>.</p>
 
435
        <p>Fails with reason <c>empty</c> if <c>Q1</c> is empty.</p>
 
436
        <p>The name <c>lait/1</c> is a misspelling - do not use it anymore.</p>
 
437
      </desc>
 
438
    </func>
 
439
  </funcs>
 
440
 
 
441
</erlref>