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

« back to all changes in this revision

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

  • 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:
45
45
         delete/2, substitute_aliases/2, substitute_negations/2,
46
46
         expand/2, normalize/2, split/2]).
47
47
 
 
48
%% ---------------------------------------------------------------------
 
49
 
 
50
-type property()   :: atom() | tuple().
 
51
 
 
52
-type aliases()    :: [{any(), any()}].
 
53
-type negations()  :: [{any(), any()}].
 
54
-type expansions() :: [{property(), [any()]}].
 
55
 
 
56
%% ---------------------------------------------------------------------
48
57
 
49
58
%% @spec property(P::property()) -> property()
50
59
%%
55
64
%%
56
65
%% @see property/2
57
66
 
 
67
-spec property(property()) -> property().
 
68
 
58
69
property({Key, true}) when is_atom(Key) ->
59
70
    Key;
60
71
property(Property) ->
70
81
%%
71
82
%% @see property/1
72
83
 
 
84
-spec property(Key::any(), Value::any()) -> atom() | {any(), any()}.
 
85
 
73
86
property(Key, true) when is_atom(Key) ->
74
87
    Key;
75
88
property(Key, Value) ->
85
98
%%
86
99
%% @see compact/1
87
100
 
 
101
-spec unfold(List::[any()]) -> [any()].
 
102
 
88
103
unfold([P | Ps]) ->
89
104
    if is_atom(P) ->
90
105
            [{P, true} | unfold(Ps)];
102
117
%% @see unfold/1
103
118
%% @see property/1
104
119
 
 
120
-spec compact(List::[property()]) -> [property()].
 
121
 
105
122
compact(List) ->
106
123
    [property(P) || P <- List].
107
124
 
119
136
%% @see get_value/2
120
137
%% @see get_bool/2
121
138
 
 
139
-spec lookup(Key::any(), List::[any()]) -> 'none' | tuple().
 
140
 
122
141
lookup(Key, [P | Ps]) ->
123
142
    if is_atom(P), P =:= Key ->
124
143
            {Key, true};
139
158
%%
140
159
%% @see lookup/2
141
160
 
 
161
-spec lookup_all(Key::any(), List::[any()]) -> [tuple()].
 
162
 
142
163
lookup_all(Key, [P | Ps]) ->
143
164
    if is_atom(P), P =:= Key ->
144
165
            [{Key, true} | lookup_all(Key, Ps)];
159
180
%% one entry associated with <code>Key</code>, otherwise
160
181
%% <code>false</code> is returned.
161
182
 
 
183
-spec is_defined(Key::any(), List::[any()]) -> bool().
 
184
 
162
185
is_defined(Key, [P | Ps]) ->
163
186
    if is_atom(P), P =:= Key ->
164
187
            true;
176
199
%% @spec get_value(Key::term(), List::[term()]) -> term()
177
200
%% @equiv get_value(Key, List, undefined)
178
201
 
 
202
-spec get_value(Key::any(), List::[any()]) -> any().
 
203
 
179
204
get_value(Key, List) ->
180
205
    get_value(Key, List, undefined).
181
206
 
188
213
%% <code>Value</code>, otherwise <code>Default</code> is returned.
189
214
%%
190
215
%% @see lookup/2
191
 
%% @see get_value/1
 
216
%% @see get_value/2
192
217
%% @see get_all_values/2
193
218
%% @see get_bool/2
194
219
 
 
220
-spec get_value(Key::any(), List::[any()], Default::any()) -> any().
 
221
 
195
222
get_value(Key, [P | Ps], Default) ->
196
223
    if is_atom(P), P =:= Key ->
197
224
            true;
218
245
%%
219
246
%% @see get_value/2
220
247
 
 
248
-spec get_all_values(Key::any(), List::[any()]) -> [any()].
 
249
 
221
250
get_all_values(Key, [P | Ps]) ->
222
251
    if is_atom(P), P =:= Key ->
223
252
            [true | get_all_values(Key, Ps)];
245
274
%%
246
275
%% @see get_all_values/2
247
276
 
 
277
-spec append_values(Key::any(), List::[any()]) -> [any()].
 
278
 
248
279
append_values(Key, [P | Ps]) ->
249
280
    if is_atom(P), P =:= Key ->
250
281
            [true | append_values(Key, Ps)];
276
307
%% @see lookup/2
277
308
%% @see get_value/2
278
309
 
 
310
-spec get_bool(Key::any(), List::[any()]) -> bool().
 
311
 
279
312
get_bool(Key, [P | Ps]) ->
280
313
    if is_atom(P), P =:= Key ->
281
314
            true;
296
329
 
297
330
%% ---------------------------------------------------------------------
298
331
 
299
 
%% @spec get_keys(List::term()) -> [term()]
 
332
%% @spec get_keys(List::[term()]) -> [term()]
300
333
%%
301
334
%% @doc Returns an unordered list of the keys used in <code>List</code>,
302
335
%% not containing duplicates.
303
336
 
 
337
-spec get_keys(List::[any()]) -> [any()].
 
338
 
304
339
get_keys(Ps) ->
305
340
    sets:to_list(get_keys(Ps, sets:new())).
306
341
 
320
355
 
321
356
%% @spec delete(Key::term(), List::[term()]) -> [term()]
322
357
%%
323
 
%%
324
358
%% @doc Deletes all entries associated with <code>Key</code> from
325
359
%% <code>List</code>.
326
360
 
 
361
-spec delete(Key::any(), List::[any()]) -> [any()].
 
362
 
327
363
delete(Key, [P | Ps]) ->
328
364
    if is_atom(P), P =:= Key ->
329
365
            delete(Key, Ps);
358
394
%% @see substitute_negations/2
359
395
%% @see normalize/2
360
396
 
 
397
-spec substitute_aliases(aliases(), List::[any()]) -> [any()].
 
398
 
361
399
substitute_aliases(As, Props) ->
362
400
    [substitute_aliases_1(As, P) || P <- Props].
363
401
 
401
439
%% @see substitute_aliases/2
402
440
%% @see normalize/2
403
441
 
 
442
-spec substitute_negations(negations(), List::[any()]) -> [any()].
 
443
 
404
444
substitute_negations(As, Props) ->
405
445
    [substitute_negations_1(As, P) || P <- Props].
406
446
 
466
506
%%
467
507
%% @see normalize/2
468
508
 
 
509
-spec expand(Expansions::expansions(), [any()]) -> [any()].
 
510
 
469
511
expand(Es, Ps) when is_list(Ps) ->
470
512
    Es1 = [{property(P), V} || {P, V} <- Es],
471
513
    flatten(expand_0(key_uniq(Es1), Ps)).
573
615
%% @see expand/2
574
616
%% @see compact/1
575
617
 
 
618
-type operation() :: {'aliases', aliases()}
 
619
                   | {'negations', negations()}
 
620
                   | {'expand', expansions()}.
 
621
 
 
622
-spec normalize(List::[any()], Stages::[operation()]) -> [any()].
 
623
 
576
624
normalize(L, [{aliases, As} | Xs]) ->
577
625
    normalize(substitute_aliases(As, L), Xs);
578
626
normalize(L, [{expand, Es} | Xs]) ->
602
650
%% {[[a], [{b, 5}, b],[{c, 2}, {c, 3, 4}]], [{e, 1}, d]}</pre>
603
651
%% </p>
604
652
 
 
653
-spec split(List::[any()], Keys::[any()]) -> {[[any()]], [any()]}.
 
654
 
605
655
split(List, Keys) ->
606
656
    {Store, Rest} = split(List, dict:from_list([{K, []} || K <- Keys]), []),
607
657
    {[lists:reverse(dict:fetch(K, Store)) || K <- Keys],