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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/dict.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>2007</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>dict</title>
 
27
    <prepared>Robert Virding</prepared>
 
28
    <docno></docno>
 
29
    <date>1997-01-15</date>
 
30
    <rev>B</rev>
 
31
  </header>
 
32
  <module>dict</module>
 
33
  <modulesummary>Key-Value Dictionary</modulesummary>
 
34
  <description>
 
35
    <p><c>Dict</c> implements a <c>Key</c> - <c>Value</c> dictionary.
 
36
      The representation of a dictionary is not defined.</p>
 
37
    <p>This module provides exactly the same interface as the module
 
38
      <c>orddict</c>. One difference is that while this module
 
39
      considers two keys as different if they do not match (<c>=:=</c>),
 
40
      <c>orddict</c> considers two keys as different if and only if
 
41
      they do not compare equal (<c>==</c>).</p>
 
42
  </description>
 
43
 
 
44
  <section>
 
45
    <title>DATA TYPES</title>
 
46
    <code type="none">
 
47
dictionary()
 
48
  as returned by new/0</code>
 
49
  </section>
 
50
  <funcs>
 
51
    <func>
 
52
      <name>append(Key, Value, Dict1) -> Dict2</name>
 
53
      <fsummary>Append a value to keys in a dictionary</fsummary>
 
54
      <type>
 
55
        <v>Key = Value = term()</v>
 
56
        <v>Dict1 = Dict2 = dictionary()</v>
 
57
      </type>
 
58
      <desc>
 
59
        <p>This function appends a new <c>Value</c> to the current list
 
60
          of values associated with <c>Key</c>.  An exception is
 
61
          generated if the initial value associated with <c>Key</c> is
 
62
          not a list of values.</p>
 
63
      </desc>
 
64
    </func>
 
65
    <func>
 
66
      <name>append_list(Key, ValList, Dict1) -> Dict2</name>
 
67
      <fsummary>Append new values to keys in a dictionary</fsummary>
 
68
      <type>
 
69
        <v>ValList = [Value]</v>
 
70
        <v>Key = Value = term()</v>
 
71
        <v>Dict1 = Dict2 = dictionary()</v>
 
72
      </type>
 
73
      <desc>
 
74
        <p>This function appends a list of values <c>ValList</c> to
 
75
          the current list of values associated with <c>Key</c>. An
 
76
          exception is generated if the initial value associated with
 
77
          <c>Key</c> is not a list of values.</p>
 
78
      </desc>
 
79
    </func>
 
80
    <func>
 
81
      <name>erase(Key, Dict1) -> Dict2</name>
 
82
      <fsummary>Erase a key from a dictionary</fsummary>
 
83
      <type>
 
84
        <v>Key = term()</v>
 
85
        <v>Dict1 = Dict2 = dictionary()</v>
 
86
      </type>
 
87
      <desc>
 
88
        <p>This function erases all items with a given key from a
 
89
          dictionary.</p>
 
90
      </desc>
 
91
    </func>
 
92
    <func>
 
93
      <name>fetch(Key, Dict) -> Value</name>
 
94
      <fsummary>Look-up values in a dictionary</fsummary>
 
95
      <type>
 
96
        <v>Key = Value = term()</v>
 
97
        <v>Dict = dictionary()</v>
 
98
      </type>
 
99
      <desc>
 
100
        <p>This function returns the value associated with <c>Key</c>
 
101
          in the dictionary <c>Dict</c>. <c>fetch</c> assumes that
 
102
          the <c>Key</c> is present in the dictionary and an exception
 
103
          is generated if <c>Key</c> is not in the dictionary.</p>
 
104
      </desc>
 
105
    </func>
 
106
    <func>
 
107
      <name>fetch_keys(Dict) -> Keys</name>
 
108
      <fsummary>Return all keys in a dictionary</fsummary>
 
109
      <type>
 
110
        <v>Dict = dictionary()</v>
 
111
        <v>Keys = [term()]</v>
 
112
      </type>
 
113
      <desc>
 
114
        <p>This function returns a list of all keys in the dictionary.</p>
 
115
      </desc>
 
116
    </func>
 
117
    <func>
 
118
      <name>filter(Pred, Dict1) -> Dict2</name>
 
119
      <fsummary>Choose elements which satisfy a predicate</fsummary>
 
120
      <type>
 
121
        <v>Pred = fun(Key, Value) -> bool()</v>
 
122
        <v>&nbsp;Key = Value = term()</v>
 
123
        <v>Dict1 = Dict2 = dictionary()</v>
 
124
      </type>
 
125
      <desc>
 
126
        <p><c>Dict2</c> is a dictionary of all keys and values in
 
127
          <c>Dict1</c> for which <c>Pred(Key, Value)</c> is <c>true</c>.</p>
 
128
      </desc>
 
129
    </func>
 
130
    <func>
 
131
      <name>find(Key, Dict) -> {ok, Value} | error</name>
 
132
      <fsummary>Search for a key in a dictionary</fsummary>
 
133
      <type>
 
134
        <v>Key = Value = term()</v>
 
135
        <v>Dict = dictionary()</v>
 
136
      </type>
 
137
      <desc>
 
138
        <p>This function searches for a key in a dictionary. Returns
 
139
          <c>{ok, Value}</c> where <c>Value</c> is the value associated
 
140
          with <c>Key</c>, or <c>error</c> if the key is not present in
 
141
          the dictionary.</p>
 
142
      </desc>
 
143
    </func>
 
144
    <func>
 
145
      <name>fold(Fun, Acc0, Dict) -> Acc1</name>
 
146
      <fsummary>Fold a function over a dictionary</fsummary>
 
147
      <type>
 
148
        <v>Fun = fun(Key, Value, AccIn) -> AccOut</v>
 
149
        <v>Key = Value = term()</v>
 
150
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
 
151
        <v>Dict = dictionary()</v>
 
152
      </type>
 
153
      <desc>
 
154
        <p>Calls <c>Fun</c> on successive keys and values of
 
155
          <c>Dict</c> together with an extra argument <c>Acc</c>
 
156
          (short for accumulator). <c>Fun</c> must return a new
 
157
          accumulator which is passed to the next call. <c>Acc0</c> is
 
158
          returned if the list is empty. The evaluation order is
 
159
          undefined.</p>
 
160
      </desc>
 
161
    </func>
 
162
    <func>
 
163
      <name>from_list(List) -> Dict</name>
 
164
      <fsummary>Convert a list of pairs to a dictionary</fsummary>
 
165
      <type>
 
166
        <v>List = [{Key, Value}]</v>
 
167
        <v>Dict = dictionary()</v>
 
168
      </type>
 
169
      <desc>
 
170
        <p>This function converts the key/value list <c>List</c> to a 
 
171
          dictionary.</p>
 
172
      </desc>
 
173
    </func>
 
174
    <func>
 
175
      <name>is_key(Key, Dict) -> bool()</name>
 
176
      <fsummary>Test if a key is in a dictionary</fsummary>
 
177
      <type>
 
178
        <v>Key = term()</v>
 
179
        <v>Dict = dictionary()</v>
 
180
      </type>
 
181
      <desc>
 
182
        <p>This function tests if <c>Key</c> is contained in
 
183
          the dictionary <c>Dict</c>.</p>
 
184
      </desc>
 
185
    </func>
 
186
    <func>
 
187
      <name>map(Fun, Dict1) -> Dict2</name>
 
188
      <fsummary>Map a function over a dictionary</fsummary>
 
189
      <type>
 
190
        <v>Fun = fun(Key, Value1) -> Value2</v>
 
191
        <v>&nbsp;Key = Value1 = Value2 = term()</v>
 
192
        <v>Dict1 = Dict2 = dictionary()</v>
 
193
      </type>
 
194
      <desc>
 
195
        <p><c>map</c> calls <c>Func</c> on successive keys and values
 
196
          of <c>Dict</c> to return a new value for each key.
 
197
          The evaluation order is undefined.</p>
 
198
      </desc>
 
199
    </func>
 
200
    <func>
 
201
      <name>merge(Fun, Dict1, Dict2) -> Dict3</name>
 
202
      <fsummary>Merge two dictionaries</fsummary>
 
203
      <type>
 
204
        <v>Fun = fun(Key, Value1, Value2) -> Value</v>
 
205
        <v>&nbsp;Key = Value1 = Value2 = Value3 = term()</v>
 
206
        <v>Dict1 = Dict2 = Dict3 = dictionary()</v>
 
207
      </type>
 
208
      <desc>
 
209
        <p><c>merge</c> merges two dictionaries, <c>Dict1</c> and
 
210
          <c>Dict2</c>, to create a new dictionary.  All the <c>Key</c>
 
211
          - <c>Value</c> pairs from both dictionaries are included in
 
212
          the new dictionary.  If a key occurs in both dictionaries then
 
213
          <c>Fun</c> is called with the key and both values to return a
 
214
          new value. <c>merge</c> could be defined as:</p>
 
215
        <code type="none">
 
216
merge(Fun, D1, D2) ->
 
217
    fold(fun (K, V1, D) ->
 
218
                 update(K, fun (V2) -> Fun(K, V1, V2) end, V1, D)
 
219
         end, D2, D1).</code>
 
220
        <p>but is faster.</p>
 
221
      </desc>
 
222
    </func>
 
223
    <func>
 
224
      <name>new() -> dictionary()</name>
 
225
      <fsummary>Create a dictionary</fsummary>
 
226
      <desc>
 
227
        <p>This function creates a new dictionary.</p>
 
228
      </desc>
 
229
    </func>
 
230
    <func>
 
231
      <name>size(Dict) -> int()</name>
 
232
      <fsummary>Return the number of elements in a dictionary</fsummary>
 
233
      <type>
 
234
        <v>Dict = dictionary()</v>
 
235
      </type>
 
236
      <desc>
 
237
        <p>Returns the number of elements in a <c>Dict</c>.</p>
 
238
      </desc>
 
239
    </func>
 
240
    <func>
 
241
      <name>store(Key, Value, Dict1) -> Dict2</name>
 
242
      <fsummary>Store a value in a dictionary</fsummary>
 
243
      <type>
 
244
        <v>Key = Value = term()</v>
 
245
        <v>Dict1 = Dict2 = dictionary()</v>
 
246
      </type>
 
247
      <desc>
 
248
        <p>This function stores a <c>Key</c> - <c>Value</c> pair in a
 
249
          dictionary. If the <c>Key</c> already exists in <c>Dict1</c>,
 
250
          the associated value is replaced by <c>Value</c>.</p>
 
251
      </desc>
 
252
    </func>
 
253
    <func>
 
254
      <name>to_list(Dict) -> List</name>
 
255
      <fsummary>Convert a dictionary to a list of pairs</fsummary>
 
256
      <type>
 
257
        <v>Dict = dictionary()</v>
 
258
        <v>List = [{Key, Value}]</v>
 
259
      </type>
 
260
      <desc>
 
261
        <p>This function converts the dictionary to a list
 
262
          representation.</p>
 
263
      </desc>
 
264
    </func>
 
265
    <func>
 
266
      <name>update(Key, Fun, Dict1) -> Dict2</name>
 
267
      <fsummary>Update a value in a dictionary</fsummary>
 
268
      <type>
 
269
        <v>Key = term()</v>
 
270
        <v>Fun = fun(Value1) -> Value2</v>
 
271
        <v>&nbsp;Value1 = Value2 = term()</v>
 
272
        <v>Dict1 = Dict2 = dictionary()</v>
 
273
      </type>
 
274
      <desc>
 
275
        <p>Update the a value in a dictionary by calling <c>Fun</c> on
 
276
          the value to get a new value.  An exception is generated if
 
277
          <c>Key</c> is not present in the dictionary.</p>
 
278
      </desc>
 
279
    </func>
 
280
    <func>
 
281
      <name>update(Key, Fun, Initial, Dict1) -> Dict2</name>
 
282
      <fsummary>Update a value in a dictionary</fsummary>
 
283
      <type>
 
284
        <v>Key = Initial = term()</v>
 
285
        <v>Fun = fun(Value1) -> Value2</v>
 
286
        <v>&nbsp;Value1 = Value2 = term()</v>
 
287
        <v>Dict1 = Dict2 = dictionary()</v>
 
288
      </type>
 
289
      <desc>
 
290
        <p>Update the a value in a dictionary by calling <c>Fun</c> on
 
291
          the value to get a new value.  If <c>Key</c> is not present
 
292
          in the dictionary then <c>Initial</c> will be stored as
 
293
          the first value. For example <c>append/3</c> could be defined
 
294
          as:</p>
 
295
        <code type="none">
 
296
append(Key, Val, D) ->
 
297
    update(Key, fun (Old) -> Old ++ [Val] end, [Val], D).</code>
 
298
      </desc>
 
299
    </func>
 
300
    <func>
 
301
      <name>update_counter(Key, Increment, Dict1) -> Dict2</name>
 
302
      <fsummary>Increment a value in a dictionary</fsummary>
 
303
      <type>
 
304
        <v>Key = term()</v>
 
305
        <v>Increment = number()</v>
 
306
        <v>Dict1 = Dict2 = dictionary()</v>
 
307
      </type>
 
308
      <desc>
 
309
        <p>Add <c>Increment</c> to the value associated with <c>Key</c>
 
310
          and store this value.  If <c>Key</c> is not present in
 
311
          the dictionary then <c>Increment</c> will be stored as
 
312
          the first value.</p>
 
313
        <p>This could be defined as:</p>
 
314
        <code type="none">
 
315
update_counter(Key, Incr, D) ->
 
316
    update(Key, fun (Old) -> Old + Incr end, Incr, D).</code>
 
317
        <p>but is faster.</p>
 
318
      </desc>
 
319
    </func>
 
320
  </funcs>
 
321
 
 
322
  <section>
 
323
    <title>Notes</title>
 
324
    <p>The functions <c>append</c> and <c>append_list</c> are included
 
325
      so we can store keyed values in a list <em>accumulator</em>. For
 
326
      example:</p>
 
327
    <pre>
 
328
> D0 = dict:new(),
 
329
  D1 = dict:store(files, [], D0),
 
330
  D2 = dict:append(files, f1, D1),
 
331
  D3 = dict:append(files, f2, D2),
 
332
  D4 = dict:append(files, f3, D3),
 
333
  dict:fetch(files, D4).
 
334
[f1,f2,f3]    </pre>
 
335
    <p>This saves the trouble of first fetching a keyed value,
 
336
      appending a new value to the list of stored values, and storing
 
337
      the result.
 
338
      </p>
 
339
    <p>The function <c>fetch</c> should be used if the key is known to
 
340
      be in the dictionary, otherwise <c>find</c>.</p>
 
341
  </section>
 
342
 
 
343
  <section>
 
344
    <title>See Also</title>
 
345
    <p><seealso marker="gb_trees">gb_trees(3)</seealso>, 
 
346
      <seealso marker="orddict">orddict(3)</seealso></p>
 
347
  </section>
 
348
</erlref>
 
349