~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/stdlib/src/queue.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(queue).
19
20
 
20
21
%% Creation, inspection and conversion
21
 
-export([new/0,is_queue/1,is_empty/1,len/1,to_list/1,from_list/1]).
 
22
-export([new/0,is_queue/1,is_empty/1,len/1,to_list/1,from_list/1,member/2]).
22
23
%% Original style API
23
24
-export([in/2,in_r/2,out/1,out_r/1]).
24
25
%% Less garbage style API
43
44
%% that is; the RearList is reversed.
44
45
%%
45
46
 
 
47
%% A declaration equivalent to the following is currently hard-coded
 
48
%% in erl_types.erl
 
49
%%
 
50
%% -opaque queue() :: {list(), list()}.
 
51
 
46
52
%% Creation, inspection and conversion
47
53
 
48
54
%% O(1)
 
55
-spec new() -> queue().
49
56
new() -> {[],[]}. %{RearList,FrontList}
50
57
 
51
58
%% O(1)
 
59
-spec is_queue(term()) -> bool().
52
60
is_queue({R,F}) when is_list(R), is_list(F) ->
53
61
    true;
54
62
is_queue(_) ->
55
63
    false.
56
64
 
57
65
%% O(1)
 
66
-spec is_empty(queue()) -> bool().
58
67
is_empty({[],[]}) ->
59
68
    true;
60
69
is_empty({In,Out}) when is_list(In), is_list(Out) ->
63
72
    erlang:error(badarg, [Q]).
64
73
 
65
74
%% O(len(Q))
 
75
-spec len(queue()) -> non_neg_integer().
66
76
len({R,F}) when is_list(R), is_list(F) ->
67
77
    length(R)+length(F);
68
78
len(Q) ->
69
79
    erlang:error(badarg, [Q]).
70
80
 
71
81
%% O(len(Q))
 
82
-spec to_list(queue()) -> list().
72
83
to_list({In,Out}) when is_list(In), is_list(Out) ->
73
84
    Out++lists:reverse(In, []);
74
85
to_list(Q) ->
77
88
%% Create queue from list
78
89
%%
79
90
%% O(length(L))
 
91
-spec from_list(list()) -> queue().
80
92
from_list(L) when is_list(L) ->
81
93
    f2r(L);
82
94
from_list(L) ->
83
95
    erlang:error(badarg, [L]).
84
96
 
 
97
%% Return true or false depending on if element is in queue
 
98
%% 
 
99
%% O(length(Q)) worst case
 
100
-spec member(term(), queue()) -> bool().
 
101
member(X, {R,F}) when is_list(R), is_list(F) ->
 
102
    lists:member(X, R) orelse lists:member(X, F);
 
103
member(X, Q) ->
 
104
    erlang:error(badarg, [X,Q]).
 
105
 
85
106
%%--------------------------------------------------------------------------
86
107
%% Original style API
87
108
 
89
110
%% Put at least one element in each list, if it is cheap
90
111
%%
91
112
%% O(1)
 
113
-spec in(term(), queue()) -> queue().
92
114
in(X, {[_]=In,[]}) ->
93
115
    {[X], In};
94
116
in(X, {In,Out}) when is_list(In), is_list(Out) ->
100
122
%% Put at least one element in each list, if it is cheap
101
123
%%
102
124
%% O(1)
 
125
-spec in_r(term(), queue()) -> queue().
103
126
in_r(X, {[],[_]=F}) ->
104
127
    {F,[X]};
105
128
in_r(X, {R,F}) when is_list(R), is_list(F) ->
110
133
%% Take from head/front
111
134
%%
112
135
%% O(1) amortized, O(len(Q)) worst case
 
136
-spec out(queue()) -> {'empty' | {'value',term()}, queue()}.
113
137
out({[],[]}=Q) ->
114
138
    {empty,Q};
115
139
out({[V],[]}) ->
127
151
%% Take from tail/rear
128
152
%%
129
153
%% O(1) amortized, O(len(Q)) worst case
 
154
-spec out_r(queue()) -> {'empty' | {'value',term()}, queue()}.
130
155
out_r({[],[]}=Q) ->
131
156
    {empty,Q};
132
157
out_r({[],[V]}) ->
147
172
%% Return the first element in the queue
148
173
%%
149
174
%% O(1) since the queue is supposed to be well formed
 
175
-spec get(queue()) -> term().
150
176
get({[],[]}=Q) ->
151
177
    erlang:error(empty, [Q]);
152
178
get({R,F}) when is_list(R), is_list(F) ->
154
180
get(Q) ->
155
181
    erlang:error(badarg, [Q]).
156
182
 
 
183
-spec get(list(), list()) -> term().
157
184
get(R, [H|_]) when is_list(R) ->
158
185
    H;
159
186
get([H], []) ->
161
188
get([_|R], []) -> % malformed queue -> O(len(Q))
162
189
    lists:last(R).
163
190
 
164
 
 
165
 
 
166
191
%% Return the last element in the queue
167
192
%%
168
193
%% O(1) since the queue is supposed to be well formed
 
194
-spec get_r(queue()) -> term().
169
195
get_r({[],[]}=Q) ->
170
196
    erlang:error(empty, [Q]);
171
197
get_r({[H|_],F}) when is_list(F) ->
180
206
%% Return the first element in the queue
181
207
%%
182
208
%% O(1) since the queue is supposed to be well formed
 
209
-spec peek(queue()) -> 'empty' | {'value',term()}.
183
210
peek({[],[]}) ->
184
211
    empty;
185
212
peek({R,[H|_]}) when is_list(R) ->
194
221
%% Return the last element in the queue
195
222
%%
196
223
%% O(1) since the queue is supposed to be well formed
 
224
-spec peek_r(queue()) -> 'empty' | {'value',term()}.
197
225
peek_r({[],[]}) ->
198
226
    empty;
199
227
peek_r({[H|_],F}) when is_list(F) ->
208
236
%% Remove the first element and return resulting queue
209
237
%%
210
238
%% O(1) amortized
 
239
-spec drop(queue()) -> queue().
211
240
drop({[],[]}=Q) ->
212
241
    erlang:error(empty, [Q]);
213
242
drop({[_],[]}) ->
225
254
%% Remove the last element and return resulting queue
226
255
%%
227
256
%% O(1) amortized
 
257
-spec drop_r(queue()) -> queue().
228
258
drop_r({[],[]}=Q) ->
229
259
    erlang:error(empty, [Q]);
230
260
drop_r({[],[_]}) ->
245
275
%% Return reversed queue
246
276
%%
247
277
%% O(1)
 
278
-spec reverse(queue()) -> queue().
248
279
reverse({R,F}) when is_list(R), is_list(F) ->
249
280
    {F,R};
250
281
reverse(Q) ->
254
285
%%
255
286
%% Q2 empty: O(1)
256
287
%% else:     O(len(Q1))
 
288
-spec join(queue(), queue()) -> queue().
257
289
join({R,F}=Q, {[],[]}) when is_list(R), is_list(F) ->
258
290
    Q;
259
291
join({[],[]}, {R,F}=Q) when is_list(R), is_list(F) ->
267
299
%%
268
300
%% N = 0..len(Q)
269
301
%% O(max(N, len(Q)))
 
302
-spec split(non_neg_integer(), queue()) -> {queue(),queue()}.
270
303
split(0, {R,F}=Q) when is_list(R), is_list(F) ->
271
304
    {{[],[]},Q};
272
305
split(N, {R,F}=Q) when is_integer(N), N >= 1, is_list(R), is_list(F) ->
273
306
    Lf = erlang:length(F),
274
307
    if  N < Lf -> % Lf >= 2
275
308
            [X|F1] = F,
276
 
            split_f1_to_r2(N-1,
277
 
                           R,  F1,
278
 
                           [], [X]);
 
309
            split_f1_to_r2(N-1, R, F1, [], [X]);
279
310
        N > Lf ->
280
311
            Lr = length(R),
281
312
            M = Lr - (N-Lf),
283
314
                    erlang:error(badarg, [N,Q]);
284
315
                M > 0 ->
285
316
                    [X|R1] = R,
286
 
                    split_r1_to_f2(M-1,
287
 
                                   R1,  F,
288
 
                                   [X], []);
 
317
                    split_r1_to_f2(M-1, R1, F, [X], []);
289
318
                true -> % M == 0
290
319
                    {Q,{[],[]}}
291
320
            end;
311
340
%% 
312
341
%% Fun(_) -> List: O(length(List) * len(Q))
313
342
%% else:           O(len(Q)
 
343
-spec filter(fun((term()) -> bool() | list()), queue()) -> queue().
314
344
filter(Fun, {R0,F0}) when is_function(Fun, 1), is_list(R0), is_list(F0) ->
315
345
    F = filter_f(Fun, F0),
316
346
    R = filter_r(Fun, R0),
386
416
 
387
417
%% Cons to head
388
418
%%
 
419
-spec cons(term(), queue()) -> queue().
389
420
cons(X, Q) ->
390
421
    in_r(X, Q).
391
422
 
394
425
%% Return the first element in the queue
395
426
%%
396
427
%% O(1) since the queue is supposed to be well formed
 
428
-spec head(queue()) -> term().
397
429
head({[],[]}=Q) ->
398
430
    erlang:error(empty, [Q]);
399
431
head({R,F}) when is_list(R), is_list(F) ->
403
435
 
404
436
%% Remove head element and return resulting queue
405
437
%%
 
438
-spec tail(queue()) -> queue().
406
439
tail(Q) ->
407
440
    drop(Q).
408
441
 
410
443
 
411
444
%% Cons to tail
412
445
%%
 
446
-spec snoc(queue(), term()) -> queue().
413
447
snoc(Q, X) ->
414
448
    in(X, Q).
415
449
 
416
450
%% Return last element
 
451
-spec daeh(queue()) -> term().
417
452
daeh(Q) -> get_r(Q).
 
453
-spec last(queue()) -> term().
418
454
last(Q) -> get_r(Q).
419
455
 
420
456
%% Remove last element and return resulting queue
 
457
-spec liat(queue()) -> queue().
421
458
liat(Q) -> drop_r(Q).
422
 
lait(Q) -> drop_r(Q). %% Oops, miss-spelled 'tail' reversed. Forget this one.
 
459
-spec lait(queue()) -> queue().
 
460
lait(Q) -> drop_r(Q). %% Oops, mis-spelled 'tail' reversed. Forget this one.
 
461
-spec init(queue()) -> queue().
423
462
init(Q) -> drop_r(Q).
424
463
 
425
464
%%--------------------------------------------------------------------------