~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/debugger/test/int_SUITE_data/lists1.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1998-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
%% Purpose : Basic lists processing functions.
 
22
 
 
23
-module(lists1).
 
24
 
 
25
 
 
26
-export([member/2, append/2, append/1, subtract/2, reverse/1, reverse/2,
 
27
         nth/2, nthtail/2, prefix/2, suffix/2, last/1,
 
28
         seq/2, seq/3, sum/1, duplicate/2, min/1, max/1, sublist/2, sublist/3,
 
29
         delete/2, sort/1, merge/2, concat/1,
 
30
         flatten/1, flatten/2, flat_length/1, flatlength/1,
 
31
         keymember/3, keysearch/3, keydelete/3, keyreplace/4,
 
32
         keysort/2, keymerge/3, keymap/3, keymap/4]).
 
33
 
 
34
-export([all/2,any/2,map/2,flatmap/2,foldl/3,foldr/3,filter/2,zf/2,
 
35
         mapfoldl/3,mapfoldr/3,foreach/2,takewhile/2,dropwhile/2,splitwith/2]).
 
36
-export([all/3,any/3,map/3,flatmap/3,foldl/4,foldr/4,filter/3,zf/3,
 
37
         mapfoldl/4,mapfoldr/4,foreach/3]).
 
38
 
 
39
%% member(X, L) -> (true | false)
 
40
%%  test if X is a member of the list L
 
41
 
 
42
member(X, [X|_]) -> true;
 
43
member(X, [_|Y]) ->
 
44
        member(X, Y);
 
45
member(X, []) -> false.
 
46
 
 
47
%% append(X, Y) appends lists X and Y
 
48
 
 
49
append(L1, L2) -> L1 ++ L2.
 
50
 
 
51
%% append(L) appends the list of lists L
 
52
 
 
53
append([E]) -> E;
 
54
append([H|T]) -> H ++ append(T);
 
55
append([]) -> [].
 
56
 
 
57
%% subtract(List1, List2) subtract elements in List2 form List1.
 
58
 
 
59
subtract(L1, L2) -> L1 -- L2.
 
60
 
 
61
%% reverse(L) reverse all elements in the list L
 
62
 
 
63
reverse(X) -> reverse(X, []).
 
64
 
 
65
reverse([H|T], Y) ->
 
66
    reverse(T, [H|Y]);
 
67
reverse([], X) -> X.
 
68
 
 
69
%% nth(N, L) returns the N`th element of the list L
 
70
%% nthtail(N, L) returns the N`th tail of the list L
 
71
 
 
72
nth(1, [H|T]) -> H;
 
73
nth(N, [_|T]) when N > 1 ->
 
74
    nth(N - 1, T).
 
75
 
 
76
nthtail(1, [H|T]) -> T;
 
77
nthtail(N, [H|T]) when N > 1 ->
 
78
    nthtail(N - 1, T);
 
79
nthtail(0, L) when list(L) -> L.
 
80
 
 
81
%% prefix(Prefix, List) -> (true | false)
 
82
 
 
83
prefix([X|PreTail], [X|Tail]) ->
 
84
    prefix(PreTail, Tail);
 
85
prefix([], List) -> true;
 
86
prefix(_,_) -> false.
 
87
 
 
88
 
 
89
%% suffix(Suffix, List) -> (true | false)
 
90
 
 
91
suffix(Suffix, Suffix) -> true;
 
92
suffix(Suffix, [_|Tail]) ->
 
93
    suffix(Suffix, Tail);
 
94
suffix(Suffix, []) -> false.
 
95
 
 
96
%% last(List) returns the last element in a list.
 
97
 
 
98
last([E]) -> E;
 
99
last([E|Es]) ->
 
100
    last(Es).
 
101
 
 
102
%% seq(Min, Max) -> [Min,Min+1, ..., Max]
 
103
%% seq(Min, Max, Incr) -> [Min,Min+Incr, ..., Max]
 
104
%%  returns the sequence Min..Max
 
105
%%  Min <= Max and Min and Max must be integers
 
106
 
 
107
seq(Min, Max) when integer(Min), integer(Max), Min =< Max ->
 
108
    seq(Min, Max, 1, []).
 
109
 
 
110
seq(Min, Max, Incr) ->
 
111
    seq(Min, Min + ((Max-Min) div Incr) * Incr, Incr, []).
 
112
 
 
113
seq(Min, Min, I, L) -> [Min|L];
 
114
seq(Min, Max, I, L) -> seq(Min, Max-I, I, [Max|L]).
 
115
 
 
116
%% sum(L) suns the sum of the elements in L
 
117
 
 
118
sum(L)          -> sum(L, 0).
 
119
sum([H|T], Sum) -> sum(T, Sum + H);
 
120
sum([], Sum)    -> Sum.
 
121
 
 
122
%% duplicate(N, X) -> [X,X,X,.....,X]  (N times)
 
123
%%   return N copies of X
 
124
 
 
125
duplicate(N, X) when integer(N), N >= 0 -> duplicate(N, X, []).
 
126
 
 
127
duplicate(0, _, L) -> L;
 
128
duplicate(N, X, L) -> duplicate(N-1, X, [X|L]).
 
129
 
 
130
 
 
131
%% min(L) -> returns the minimum element of the list L
 
132
 
 
133
min([H|T]) -> min(T, H).
 
134
 
 
135
min([H|T], Min) when H < Min -> min(T, H);
 
136
min([_|T], Min)              -> min(T, Min);
 
137
min([],    Min)              -> Min.
 
138
 
 
139
%% max(L) -> returns the maximum element of the list L
 
140
 
 
141
max([H|T]) -> max(T, H).
 
142
 
 
143
max([H|T], Max) when H > Max -> max(T, H);
 
144
max([_|T], Max)              -> max(T, Max);
 
145
max([],    Max)              -> Max.
 
146
 
 
147
%% sublist(List, Start, Length)
 
148
%%  Returns the sub-list starting at Start of length Length.
 
149
 
 
150
sublist(List, S, L) when L >= 0 ->
 
151
    sublist(nthtail(S-1, List), L).
 
152
 
 
153
sublist([H|T], L) when L > 0 ->
 
154
    [H|sublist(T, L-1)];
 
155
sublist(List, L) -> [].
 
156
 
 
157
%% delete(Item, List) -> List'
 
158
%%  Delete the first occurance of Item from the list L.
 
159
 
 
160
delete(Item, [Item|Rest]) -> Rest;
 
161
delete(Item, [H|Rest]) ->
 
162
    [H|delete(Item, Rest)];
 
163
delete(Item, []) -> [].
 
164
 
 
165
%% sort(L) -> sorts the list L
 
166
 
 
167
sort([X]) -> [X];
 
168
sort([])  -> [];
 
169
sort(X)   -> split_and_sort(X, [], []).
 
170
 
 
171
split_and_sort([A,B|T], X, Y) ->
 
172
    split_and_sort(T, [A|X], [B|Y]);
 
173
split_and_sort([H], X, Y) ->
 
174
    split_and_sort([], [H|X], Y);
 
175
split_and_sort([], X, Y) ->
 
176
    merge(sort(X), sort(Y), []).
 
177
 
 
178
%% merge(X, Y) -> L
 
179
%%  merges two sorted lists X and Y
 
180
 
 
181
merge(X, Y) -> merge(X, Y, []).
 
182
 
 
183
merge([H1|T1], [H2|T2], L) when H1 < H2 ->
 
184
    merge(T1, [H2|T2], [H1|L]);
 
185
merge(T1, [H2|T2], L) ->
 
186
    merge(T1, T2, [H2|L]);
 
187
merge([H|T], T2, L) ->
 
188
    merge(T, T2, [H|L]);
 
189
merge([], [], L) ->
 
190
    reverse(L).
 
191
 
 
192
%% concat(L) concatinate the list representation of the elements
 
193
%%  in L - the elements in L can be atoms, integers of strings.
 
194
%%  Returns a list of characters.
 
195
 
 
196
concat(List) ->
 
197
    flatmap(fun thing_to_list/1, List).
 
198
 
 
199
thing_to_list(X) when integer(X) -> integer_to_list(X);
 
200
thing_to_list(X) when float(X)   -> float_to_list(X);
 
201
thing_to_list(X) when atom(X)    -> atom_to_list(X);
 
202
thing_to_list(X) when list(X)    -> X.          %Assumed to be a string
 
203
 
 
204
%% flatten(List)
 
205
%% flatten(List, Tail)
 
206
%%  Flatten a list, adding optional tail.
 
207
 
 
208
flatten(List) ->
 
209
    flatten(List, [], []).
 
210
 
 
211
flatten(List, Tail) ->
 
212
    flatten(List, [], Tail).
 
213
 
 
214
flatten([H|T], Cont, Tail) when list(H) ->
 
215
    flatten(H, [T|Cont], Tail);
 
216
flatten([H|T], Cont, Tail) ->
 
217
    [H|flatten(T, Cont, Tail)];
 
218
flatten([], [H|Cont], Tail) ->
 
219
    flatten(H, Cont, Tail);
 
220
flatten([], [], Tail) ->
 
221
    Tail.
 
222
 
 
223
%% flat_length(List) (undocumented can be rmove later)
 
224
%%  Calculate the length of a list of lists.
 
225
 
 
226
flat_length(List) -> flatlength(List).
 
227
 
 
228
%% flatlength(List)
 
229
%%  Calculate the length of a list of lists.
 
230
 
 
231
flatlength(List) ->
 
232
    flatlength(List, 0).
 
233
 
 
234
flatlength([H|T], L) when list(H) ->
 
235
    flatlength(H, flatlength(T, L));
 
236
flatlength([H|T], L) ->
 
237
    flatlength(T, L + 1);
 
238
flatlength([], L) -> L.
 
239
 
 
240
%% keymember(Key, Index, [Tuple])
 
241
%% keysearch(Key, Index, [Tuple])
 
242
%% keydelete(Key, Index, [Tuple])
 
243
%% keyreplace(Key, Index, [Tuple], NewTuple)
 
244
%% keysort(Index, [Tuple])
 
245
%% keymerge(Index, [Tuple], [Tuple])
 
246
%% keymap(Function, Index, [Tuple])
 
247
%% keymap(Function, ExtraArgs, Index, [Tuple])
 
248
 
 
249
keymember(Key, N, [T|Ts]) when element(N, T) == Key -> true;
 
250
keymember(Key, N, [T|Ts]) ->
 
251
    keymember(Key, N, Ts);
 
252
keymember(Key, N, []) -> false.
 
253
 
 
254
keysearch(Key, N, [H|T]) when element(N, H) == Key ->
 
255
    {value, H};
 
256
keysearch(Key, N, [H|T]) ->
 
257
    keysearch(Key, N, T);
 
258
keysearch(Key, N, []) -> false.
 
259
 
 
260
keydelete(Key, N, [H|T]) when element(N, H) == Key -> T;
 
261
keydelete(Key, N, [H|T]) ->
 
262
    [H|keydelete(Key, N, T)];
 
263
keydelete(Key, N, []) -> [].
 
264
 
 
265
keyreplace(Key, Pos, [Tup|Tail], New) when element(Pos, Tup) == Key ->
 
266
    [New|Tail];
 
267
keyreplace(Key, Pos, [H|T], New) ->
 
268
    [H|keyreplace(Key, Pos, T, New)];
 
269
keyreplace(Key, Pos, [], New) -> [].
 
270
 
 
271
keysort(Index, [X]) -> [X];
 
272
keysort(Index, [])  -> [];
 
273
keysort(Index, X)   -> split_and_keysort(X, [], [], Index).
 
274
 
 
275
split_and_keysort([A,B|T], X, Y, Index) ->
 
276
    split_and_keysort(T, [A|X], [B|Y], Index);
 
277
split_and_keysort([H], X, Y, Index) ->
 
278
    split_and_keysort([], [H|X], Y, Index);
 
279
split_and_keysort([], X, Y, Index) ->
 
280
    keymerge(Index, keysort(Index, X), keysort(Index, Y), []).
 
281
 
 
282
keymerge(Index, X, Y) -> keymerge(Index, X, Y, []).
 
283
 
 
284
keymerge(I, [H1|T1], [H2|T2], L) when element(I, H1) < element(I, H2) ->
 
285
    keymerge(I, T1, [H2|T2], [H1|L]);
 
286
keymerge(Index, T1, [H2|T2], L) ->
 
287
    keymerge(Index,T1, T2, [H2|L]);
 
288
keymerge(Index,[H|T], T2, L) ->
 
289
    keymerge(Index,T, T2, [H|L]);
 
290
keymerge(Index, [], [], L) ->
 
291
    reverse(L).
 
292
 
 
293
keymap(Fun, Index, [Tup|Tail]) ->
 
294
   [setelement(Index, Tup, Fun(element(Index, Tup)))|keymap(Fun, Index, Tail)];
 
295
keymap( _, _ , []) -> [].
 
296
 
 
297
keymap(Fun, ExtraArgs, Index, [Tup|Tail]) ->
 
298
   [setelement(Index, Tup, apply(Fun, [element(Index, Tup)|ExtraArgs]))|
 
299
    keymap(Fun, ExtraArgs, Index, Tail)];
 
300
keymap( _, _ , _, []) -> [].
 
301
 
 
302
%% all(Predicate, List)
 
303
%% any(Predicate, List)
 
304
%% map(Function, List)
 
305
%% flatmap(Function, List)
 
306
%% foldl(Function, First, List)
 
307
%% foldr(Function, Last, List)
 
308
%% filter(Predicate, List)
 
309
%% zf(Function, List)
 
310
%% mapfoldl(Function, First, List)
 
311
%% mapfoldr(Function, Last, List)
 
312
%% foreach(Function, List)
 
313
%% takewhile(Predicate, List)
 
314
%% dropwhile(Predicate, List)
 
315
%% splitwith(Predicate, List)
 
316
%%  for list programming. Function here is either a 'fun' or a tuple
 
317
%%  {Module,Name} and we use apply/2 to evaluate. The name zf is a joke!
 
318
%%
 
319
%%  N.B. Unless where the functions actually needs it only foreach/2/3,
 
320
%%  which is meant to be used for its side effects, has a defined order
 
321
%%  of evaluation.
 
322
%%
 
323
%%  There are also versions with an extra argument, ExtraArgs, which is a
 
324
%%  list of extra arguments to each call.
 
325
 
 
326
all(Pred, [Hd|Tail]) ->
 
327
    case Pred(Hd) of
 
328
        true -> all(Pred, Tail);
 
329
        false -> false
 
330
    end;
 
331
all(Pred, []) -> true.
 
332
 
 
333
any(Pred, [Hd|Tail]) ->
 
334
    case Pred(Hd) of
 
335
        true -> true;
 
336
        false -> any(Pred, Tail)
 
337
    end;
 
338
any(Pred, []) -> false.
 
339
 
 
340
map(F, List) -> [ F(E) || E <- List ].
 
341
 
 
342
flatmap(F, [Hd|Tail]) ->
 
343
    F(Hd) ++ flatmap(F, Tail);
 
344
flatmap(F, []) -> [].
 
345
 
 
346
foldl(F, Accu, [Hd|Tail]) ->
 
347
    foldl(F, F(Hd, Accu), Tail);
 
348
foldl(F, Accu, []) -> Accu.
 
349
 
 
350
foldr(F, Accu, [Hd|Tail]) ->
 
351
    F(Hd, foldr(F, Accu, Tail));
 
352
foldr(F, Accu, []) -> Accu.
 
353
 
 
354
filter(Pred, List) -> [ E || E <- List, Pred(E) ].
 
355
 
 
356
zf(F, [Hd|Tail]) ->
 
357
    case F(Hd) of
 
358
        true ->
 
359
            [Hd|zf(F, Tail)];
 
360
        {true,Val} ->
 
361
            [Val|zf(F, Tail)];
 
362
        false ->
 
363
            zf(F, Tail)
 
364
    end;
 
365
zf(F, []) -> [].
 
366
 
 
367
foreach(F, [Hd|Tail]) ->
 
368
    F(Hd),
 
369
    foreach(F, Tail);
 
370
foreach(F, []) -> ok.
 
371
 
 
372
mapfoldl(F, Accu0, [Hd|Tail]) ->
 
373
    {R,Accu1} = F(Hd, Accu0),
 
374
    {Rs,Accu2} = mapfoldl(F, Accu1, Tail),
 
375
    {[R|Rs],Accu2};
 
376
mapfoldl(F, Accu, []) -> {[],Accu}.
 
377
 
 
378
mapfoldr(F, Accu0, [Hd|Tail]) ->
 
379
    {Rs,Accu1} = mapfoldr(F, Accu0, Tail),
 
380
    {R,Accu2} = F(Hd, Accu1),
 
381
    {[R|Rs],Accu2};
 
382
mapfoldr(F, Accu, []) -> {[],Accu}.
 
383
 
 
384
takewhile(Pred, [Hd|Tail]) ->
 
385
    case Pred(Hd) of
 
386
        true -> [Hd|takewhile(Pred, Tail)];
 
387
        false -> []
 
388
    end;
 
389
takewhile(Pred, []) -> [].
 
390
 
 
391
dropwhile(Pred, [Hd|Tail]) ->
 
392
    case Pred(Hd) of
 
393
        true -> dropwhile(Pred, Tail);
 
394
        false -> [Hd|Tail]
 
395
    end;
 
396
dropwhile(Pred, []) -> [].
 
397
 
 
398
splitwith(Pred, List) -> splitwith(Pred, List, []).
 
399
 
 
400
splitwith(Pred, [Hd|Tail], Taken) ->
 
401
    case Pred(Hd) of
 
402
        true -> splitwith(Pred, Tail, [Hd|Taken]);
 
403
        false -> {reverse(Taken), [Hd|Tail]}
 
404
    end;
 
405
splitwith(Pred, [], Taken) -> {reverse(Taken),[]}.
 
406
 
 
407
%% Versions of the above functions with extra arguments.
 
408
 
 
409
all(Pred, Eas, [Hd|Tail]) ->
 
410
    case apply(Pred, [Hd|Eas]) of
 
411
        true -> all(Pred, Eas, Tail);
 
412
        false -> false
 
413
    end;
 
414
all(Pred, Eas, []) -> true.
 
415
 
 
416
any(Pred, Eas, [Hd|Tail]) ->
 
417
    case apply(Pred, [Hd|Eas]) of
 
418
        true -> true;
 
419
        false -> any(Pred, Eas, Tail)
 
420
    end;
 
421
any(Pred, Eas, []) -> false.
 
422
 
 
423
map(F, Eas, List) -> [ apply(F, [E|Eas]) || E <- List ].
 
424
 
 
425
flatmap(F, Eas, [Hd|Tail]) ->
 
426
    apply(F, [Hd|Eas]) ++ flatmap(F, Eas, Tail);
 
427
flatmap(F, Eas, []) -> [].
 
428
 
 
429
foldl(F, Eas, Accu, [Hd|Tail]) ->
 
430
    foldl(F, Eas, apply(F, [Hd,Accu|Eas]), Tail);
 
431
foldl(F, Eas, Accu, []) -> Accu.
 
432
 
 
433
foldr(F, Eas, Accu, [Hd|Tail]) ->
 
434
    apply(F, [Hd,foldr(F, Eas, Accu, Tail)|Eas]);
 
435
foldr(F, Eas, Accu, []) ->
 
436
    Accu.
 
437
 
 
438
filter(Pred, Eas, List) -> [ E || E <- List, apply(Pred, [E|Eas]) ].
 
439
 
 
440
zf(F, Eas, [Hd|Tail]) ->
 
441
    case apply(F, [Hd|Eas]) of
 
442
        true ->
 
443
            [Hd|zf(F, Eas, Tail)];
 
444
        {true,Val} ->
 
445
            [Val|zf(F, Eas, Tail)];
 
446
        false ->
 
447
            zf(F, Eas, Tail)
 
448
    end;
 
449
zf(F, Eas, []) -> [].
 
450
 
 
451
foreach(F, Eas, [Hd|Tail]) ->
 
452
    apply(F, [Hd|Eas]),
 
453
    foreach(F, Eas, Tail);
 
454
foreach(F, Eas, []) -> ok.
 
455
 
 
456
mapfoldl(F, Eas, Accu0, [Hd|Tail]) ->
 
457
    {R,Accu1} = apply(F, [Hd,Accu0|Eas]),
 
458
    {Rs,Accu2} = mapfoldl(F, Eas, Accu1, Tail),
 
459
    {[R|Rs],Accu2};
 
460
mapfoldl(F, Eas, Accu, []) -> {[],Accu}.
 
461
 
 
462
mapfoldr(F, Eas, Accu0, [Hd|Tail]) ->
 
463
    {Rs,Accu1} = mapfoldr(F, Eas, Accu0, Tail),
 
464
    {R,Accu2} = apply(F, [Hd,Accu1|Eas]),
 
465
    {[R|Rs],Accu2};
 
466
mapfoldr(F, Eas, Accu, []) -> {[],Accu}.
 
467
 
 
468
%% takewhile/2, dropwhile/2 and splitwith/2 do not have versions with
 
469
%% extra arguments as this going to be discontinued.