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

« back to all changes in this revision

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