~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/dict.xml

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
4
4
<erlref>
5
5
  <header>
6
6
    <copyright>
7
 
      <year>1996</year><year>2009</year>
 
7
      <year>1996</year><year>2011</year>
8
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
9
9
    </copyright>
10
10
    <legalnotice>
39
39
      they do not compare equal (<c>==</c>).</p>
40
40
  </description>
41
41
 
42
 
  <section>
43
 
    <title>DATA TYPES</title>
44
 
    <code type="none">
45
 
dictionary()
46
 
  as returned by new/0</code>
47
 
  </section>
 
42
  <datatypes>
 
43
    <datatype>
 
44
      <name><marker id="type-dict">dict()</marker></name>
 
45
      <desc><p>Dictionary as returned by <c>new/0</c>.</p></desc>
 
46
    </datatype>
 
47
  </datatypes>
48
48
  <funcs>
49
49
    <func>
50
 
      <name>append(Key, Value, Dict1) -> Dict2</name>
 
50
      <name name="append" arity="3"/>
51
51
      <fsummary>Append a value to keys in a dictionary</fsummary>
52
 
      <type>
53
 
        <v>Key = Value = term()</v>
54
 
        <v>Dict1 = Dict2 = dictionary()</v>
55
 
      </type>
56
52
      <desc>
57
 
        <p>This function appends a new <c>Value</c> to the current list
58
 
          of values associated with <c>Key</c>.  An exception is
59
 
          generated if the initial value associated with <c>Key</c> is
60
 
          not a list of values.</p>
 
53
        <p>This function appends a new <c><anno>Value</anno></c> to the current list
 
54
          of values associated with <c><anno>Key</anno></c>.</p>
61
55
      </desc>
62
56
    </func>
63
57
    <func>
64
 
      <name>append_list(Key, ValList, Dict1) -> Dict2</name>
 
58
      <name name="append_list" arity="3"/>
65
59
      <fsummary>Append new values to keys in a dictionary</fsummary>
66
 
      <type>
67
 
        <v>ValList = [Value]</v>
68
 
        <v>Key = Value = term()</v>
69
 
        <v>Dict1 = Dict2 = dictionary()</v>
70
 
      </type>
71
60
      <desc>
72
 
        <p>This function appends a list of values <c>ValList</c> to
73
 
          the current list of values associated with <c>Key</c>. An
 
61
        <p>This function appends a list of values <c><anno>ValList</anno></c> to
 
62
          the current list of values associated with <c><anno>Key</anno></c>. An
74
63
          exception is generated if the initial value associated with
75
 
          <c>Key</c> is not a list of values.</p>
 
64
          <c><anno>Key</anno></c> is not a list of values.</p>
76
65
      </desc>
77
66
    </func>
78
67
    <func>
79
 
      <name>erase(Key, Dict1) -> Dict2</name>
 
68
      <name name="erase" arity="2"/>
80
69
      <fsummary>Erase a key from a dictionary</fsummary>
81
 
      <type>
82
 
        <v>Key = term()</v>
83
 
        <v>Dict1 = Dict2 = dictionary()</v>
84
 
      </type>
85
70
      <desc>
86
71
        <p>This function erases all items with a given key from a
87
72
          dictionary.</p>
88
73
      </desc>
89
74
    </func>
90
75
    <func>
91
 
      <name>fetch(Key, Dict) -> Value</name>
 
76
      <name name="fetch" arity="2"/>
92
77
      <fsummary>Look-up values in a dictionary</fsummary>
93
 
      <type>
94
 
        <v>Key = Value = term()</v>
95
 
        <v>Dict = dictionary()</v>
96
 
      </type>
97
78
      <desc>
98
 
        <p>This function returns the value associated with <c>Key</c>
99
 
          in the dictionary <c>Dict</c>. <c>fetch</c> assumes that
100
 
          the <c>Key</c> is present in the dictionary and an exception
101
 
          is generated if <c>Key</c> is not in the dictionary.</p>
 
79
        <p>This function returns the value associated with <c><anno>Key</anno></c>
 
80
          in the dictionary <c><anno>Dict</anno></c>. <c>fetch</c> assumes that
 
81
          the <c><anno>Key</anno></c> is present in the dictionary and an exception
 
82
          is generated if <c><anno>Key</anno></c> is not in the dictionary.</p>
102
83
      </desc>
103
84
    </func>
104
85
    <func>
105
 
      <name>fetch_keys(Dict) -> Keys</name>
 
86
      <name name="fetch_keys" arity="1"/>
106
87
      <fsummary>Return all keys in a dictionary</fsummary>
107
 
      <type>
108
 
        <v>Dict = dictionary()</v>
109
 
        <v>Keys = [term()]</v>
110
 
      </type>
111
88
      <desc>
112
89
        <p>This function returns a list of all keys in the dictionary.</p>
113
90
      </desc>
114
91
    </func>
115
92
    <func>
116
 
      <name>filter(Pred, Dict1) -> Dict2</name>
 
93
      <name name="filter" arity="2"/>
117
94
      <fsummary>Choose elements which satisfy a predicate</fsummary>
118
 
      <type>
119
 
        <v>Pred = fun(Key, Value) -> bool()</v>
120
 
        <v>&nbsp;Key = Value = term()</v>
121
 
        <v>Dict1 = Dict2 = dictionary()</v>
122
 
      </type>
123
95
      <desc>
124
 
        <p><c>Dict2</c> is a dictionary of all keys and values in
125
 
          <c>Dict1</c> for which <c>Pred(Key, Value)</c> is <c>true</c>.</p>
 
96
        <p><c><anno>Dict2</anno></c> is a dictionary of all keys and values in
 
97
          <c><anno>Dict1</anno></c> for which <c><anno>Pred</anno>(<anno>Key</anno>, <anno>Value</anno>)</c> is <c>true</c>.</p>
126
98
      </desc>
127
99
    </func>
128
100
    <func>
129
 
      <name>find(Key, Dict) -> {ok, Value} | error</name>
 
101
      <name name="find" arity="2"/>
130
102
      <fsummary>Search for a key in a dictionary</fsummary>
131
 
      <type>
132
 
        <v>Key = Value = term()</v>
133
 
        <v>Dict = dictionary()</v>
134
 
      </type>
135
103
      <desc>
136
104
        <p>This function searches for a key in a dictionary. Returns
137
 
          <c>{ok, Value}</c> where <c>Value</c> is the value associated
138
 
          with <c>Key</c>, or <c>error</c> if the key is not present in
 
105
          <c>{ok, <anno>Value</anno>}</c> where <c><anno>Value</anno></c> is the value associated
 
106
          with <c><anno>Key</anno></c>, or <c>error</c> if the key is not present in
139
107
          the dictionary.</p>
140
108
      </desc>
141
109
    </func>
142
110
    <func>
143
 
      <name>fold(Fun, Acc0, Dict) -> Acc1</name>
 
111
      <name name="fold" arity="3"/>
144
112
      <fsummary>Fold a function over a dictionary</fsummary>
145
 
      <type>
146
 
        <v>Fun = fun(Key, Value, AccIn) -> AccOut</v>
147
 
        <v>Key = Value = term()</v>
148
 
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
149
 
        <v>Dict = dictionary()</v>
150
 
      </type>
151
113
      <desc>
152
 
        <p>Calls <c>Fun</c> on successive keys and values of
153
 
          <c>Dict</c> together with an extra argument <c>Acc</c>
154
 
          (short for accumulator). <c>Fun</c> must return a new
155
 
          accumulator which is passed to the next call. <c>Acc0</c> is
 
114
        <p>Calls <c><anno>Fun</anno></c> on successive keys and values of
 
115
          <c><anno>Dict</anno></c> together with an extra argument <c>Acc</c>
 
116
          (short for accumulator). <c><anno>Fun</anno></c> must return a new
 
117
          accumulator which is passed to the next call. <c><anno>Acc0</anno></c> is
156
118
          returned if the list is empty. The evaluation order is
157
119
          undefined.</p>
158
120
      </desc>
159
121
    </func>
160
122
    <func>
161
 
      <name>from_list(List) -> Dict</name>
 
123
      <name name="from_list" arity="1"/>
162
124
      <fsummary>Convert a list of pairs to a dictionary</fsummary>
163
 
      <type>
164
 
        <v>List = [{Key, Value}]</v>
165
 
        <v>Dict = dictionary()</v>
166
 
      </type>
167
125
      <desc>
168
 
        <p>This function converts the key/value list <c>List</c> to a 
169
 
          dictionary.</p>
 
126
        <p>This function converts the <c><anno>Key</anno></c> - <c><anno>Value</anno></c> list
 
127
          <c><anno>List</anno></c> to a dictionary.</p>
170
128
      </desc>
171
129
    </func>
172
130
    <func>
173
 
      <name>is_key(Key, Dict) -> bool()</name>
 
131
      <name name="is_key" arity="2"/>
174
132
      <fsummary>Test if a key is in a dictionary</fsummary>
175
 
      <type>
176
 
        <v>Key = term()</v>
177
 
        <v>Dict = dictionary()</v>
178
 
      </type>
179
133
      <desc>
180
 
        <p>This function tests if <c>Key</c> is contained in
181
 
          the dictionary <c>Dict</c>.</p>
 
134
        <p>This function tests if <c><anno>Key</anno></c> is contained in
 
135
          the dictionary <c><anno>Dict</anno></c>.</p>
182
136
      </desc>
183
137
    </func>
184
138
    <func>
185
 
      <name>map(Fun, Dict1) -> Dict2</name>
 
139
      <name name="map" arity="2"/>
186
140
      <fsummary>Map a function over a dictionary</fsummary>
187
 
      <type>
188
 
        <v>Fun = fun(Key, Value1) -> Value2</v>
189
 
        <v>&nbsp;Key = Value1 = Value2 = term()</v>
190
 
        <v>Dict1 = Dict2 = dictionary()</v>
191
 
      </type>
192
141
      <desc>
193
 
        <p><c>map</c> calls <c>Func</c> on successive keys and values
194
 
          of <c>Dict</c> to return a new value for each key.
 
142
        <p><c>map</c> calls <c><anno>Fun</anno></c> on successive keys and values
 
143
          of <c><anno>Dict1</anno></c> to return a new value for each key.
195
144
          The evaluation order is undefined.</p>
196
145
      </desc>
197
146
    </func>
198
147
    <func>
199
 
      <name>merge(Fun, Dict1, Dict2) -> Dict3</name>
 
148
      <name name="merge" arity="3"/>
200
149
      <fsummary>Merge two dictionaries</fsummary>
201
 
      <type>
202
 
        <v>Fun = fun(Key, Value1, Value2) -> Value</v>
203
 
        <v>&nbsp;Key = Value1 = Value2 = Value3 = term()</v>
204
 
        <v>Dict1 = Dict2 = Dict3 = dictionary()</v>
205
 
      </type>
206
150
      <desc>
207
 
        <p><c>merge</c> merges two dictionaries, <c>Dict1</c> and
208
 
          <c>Dict2</c>, to create a new dictionary.  All the <c>Key</c>
209
 
          - <c>Value</c> pairs from both dictionaries are included in
 
151
        <p><c>merge</c> merges two dictionaries, <c><anno>Dict1</anno></c> and
 
152
          <c><anno>Dict2</anno></c>, to create a new dictionary.  All the <c><anno>Key</anno></c>
 
153
          - <c><anno>Value</anno></c> pairs from both dictionaries are included in
210
154
          the new dictionary.  If a key occurs in both dictionaries then
211
 
          <c>Fun</c> is called with the key and both values to return a
 
155
          <c><anno>Fun</anno></c> is called with the key and both values to return a
212
156
          new value. <c>merge</c> could be defined as:</p>
213
157
        <code type="none">
214
158
merge(Fun, D1, D2) ->
219
163
      </desc>
220
164
    </func>
221
165
    <func>
222
 
      <name>new() -> dictionary()</name>
 
166
      <name name="new" arity="0"/>
223
167
      <fsummary>Create a dictionary</fsummary>
224
168
      <desc>
225
169
        <p>This function creates a new dictionary.</p>
226
170
      </desc>
227
171
    </func>
228
172
    <func>
229
 
      <name>size(Dict) -> int()</name>
 
173
      <name name="size" arity="1"/>
230
174
      <fsummary>Return the number of elements in a dictionary</fsummary>
231
 
      <type>
232
 
        <v>Dict = dictionary()</v>
233
 
      </type>
234
175
      <desc>
235
 
        <p>Returns the number of elements in a <c>Dict</c>.</p>
 
176
        <p>Returns the number of elements in a <c><anno>Dict</anno></c>.</p>
236
177
      </desc>
237
178
    </func>
238
179
    <func>
239
 
      <name>store(Key, Value, Dict1) -> Dict2</name>
 
180
      <name name="store" arity="3"/>
240
181
      <fsummary>Store a value in a dictionary</fsummary>
241
 
      <type>
242
 
        <v>Key = Value = term()</v>
243
 
        <v>Dict1 = Dict2 = dictionary()</v>
244
 
      </type>
245
182
      <desc>
246
 
        <p>This function stores a <c>Key</c> - <c>Value</c> pair in a
247
 
          dictionary. If the <c>Key</c> already exists in <c>Dict1</c>,
248
 
          the associated value is replaced by <c>Value</c>.</p>
 
183
        <p>This function stores a <c><anno>Key</anno></c> - <c><anno>Value</anno></c> pair in a
 
184
          dictionary. If the <c><anno>Key</anno></c> already exists in <c><anno>Dict1</anno></c>,
 
185
          the associated value is replaced by <c><anno>Value</anno></c>.</p>
249
186
      </desc>
250
187
    </func>
251
188
    <func>
252
 
      <name>to_list(Dict) -> List</name>
 
189
      <name name="to_list" arity="1"/>
253
190
      <fsummary>Convert a dictionary to a list of pairs</fsummary>
254
 
      <type>
255
 
        <v>Dict = dictionary()</v>
256
 
        <v>List = [{Key, Value}]</v>
257
 
      </type>
258
191
      <desc>
259
192
        <p>This function converts the dictionary to a list
260
193
          representation.</p>
261
194
      </desc>
262
195
    </func>
263
196
    <func>
264
 
      <name>update(Key, Fun, Dict1) -> Dict2</name>
 
197
      <name name="update" arity="3"/>
265
198
      <fsummary>Update a value in a dictionary</fsummary>
266
 
      <type>
267
 
        <v>Key = term()</v>
268
 
        <v>Fun = fun(Value1) -> Value2</v>
269
 
        <v>&nbsp;Value1 = Value2 = term()</v>
270
 
        <v>Dict1 = Dict2 = dictionary()</v>
271
 
      </type>
272
199
      <desc>
273
 
        <p>Update the a value in a dictionary by calling <c>Fun</c> on
 
200
        <p>Update a value in a dictionary by calling <c><anno>Fun</anno></c> on
274
201
          the value to get a new value.  An exception is generated if
275
 
          <c>Key</c> is not present in the dictionary.</p>
 
202
          <c><anno>Key</anno></c> is not present in the dictionary.</p>
276
203
      </desc>
277
204
    </func>
278
205
    <func>
279
 
      <name>update(Key, Fun, Initial, Dict1) -> Dict2</name>
 
206
      <name name="update" arity="4"/>
280
207
      <fsummary>Update a value in a dictionary</fsummary>
281
 
      <type>
282
 
        <v>Key = Initial = term()</v>
283
 
        <v>Fun = fun(Value1) -> Value2</v>
284
 
        <v>&nbsp;Value1 = Value2 = term()</v>
285
 
        <v>Dict1 = Dict2 = dictionary()</v>
286
 
      </type>
287
208
      <desc>
288
 
        <p>Update the a value in a dictionary by calling <c>Fun</c> on
289
 
          the value to get a new value.  If <c>Key</c> is not present
290
 
          in the dictionary then <c>Initial</c> will be stored as
 
209
        <p>Update a value in a dictionary by calling <c><anno>Fun</anno></c> on
 
210
          the value to get a new value.  If <c><anno>Key</anno></c> is not present
 
211
          in the dictionary then <c><anno>Initial</anno></c> will be stored as
291
212
          the first value. For example <c>append/3</c> could be defined
292
213
          as:</p>
293
214
        <code type="none">
296
217
      </desc>
297
218
    </func>
298
219
    <func>
299
 
      <name>update_counter(Key, Increment, Dict1) -> Dict2</name>
 
220
      <name name="update_counter" arity="3"/>
300
221
      <fsummary>Increment a value in a dictionary</fsummary>
301
 
      <type>
302
 
        <v>Key = term()</v>
303
 
        <v>Increment = number()</v>
304
 
        <v>Dict1 = Dict2 = dictionary()</v>
305
 
      </type>
306
222
      <desc>
307
 
        <p>Add <c>Increment</c> to the value associated with <c>Key</c>
308
 
          and store this value.  If <c>Key</c> is not present in
309
 
          the dictionary then <c>Increment</c> will be stored as
 
223
        <p>Add <c><anno>Increment</anno></c> to the value associated with <c><anno>Key</anno></c>
 
224
          and store this value.  If <c><anno>Key</anno></c> is not present in
 
225
          the dictionary then <c><anno>Increment</anno></c> will be stored as
310
226
          the first value.</p>
311
227
        <p>This could be defined as:</p>
312
228
        <code type="none">