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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/file_sorter.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>2001</year><year>2010</year>
 
7
      <year>2001</year><year>2011</year>
8
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
9
9
    </copyright>
10
10
    <legalnotice>
89
89
       considerably. The <c>keysort</c>, <c>keymerge</c> and
90
90
       <c>keycheck</c> functions do not accept ordering functions.
91
91
      </item>
92
 
      <item><c>{unique, bool()}</c>. When sorting or merging files,
 
92
      <item><c>{unique, boolean()}</c>. When sorting or merging files,
93
93
       only the first of a sequence of terms that compare equal (<c>==</c>)
94
94
       is output if this option is set to <c>true</c>. The default
95
95
       value is <c>false</c> which implies that all terms that
112
112
       overwritten. Temporary files are deleted unless some
113
113
       uncaught EXIT signal occurs.
114
114
      </item>
115
 
      <item><c>{compressed, bool()}</c>. Temporary files and the
 
115
      <item><c>{compressed, boolean()}</c>. Temporary files and the
116
116
       output file may be compressed. The default value
117
117
      <c>false</c> implies that written files are not
118
118
       compressed. Regardless of the value of the <c>compressed</c>
128
128
       merged at a time. This option should rarely be needed.
129
129
      </item>
130
130
    </list>
131
 
    <p>To summarize, here is the syntax of the options:</p>
132
 
    <list type="bulleted">
133
 
      <item>
134
 
        <p><c>Options = [Option] | Option</c></p>
135
 
      </item>
136
 
      <item>
137
 
        <p><c>Option = {header, HeaderLength} | {format, Format} | {order, Order} | {unique, bool()} | {tmpdir, TempDirectory} | {compressed, bool()} | {size, Size} | {no_files, NoFiles}</c></p>
138
 
      </item>
139
 
      <item>
140
 
        <p><c>HeaderLength = int() > 0</c></p>
141
 
      </item>
142
 
      <item>
143
 
        <p><c>Format = binary_term | term | binary | FormatFun</c></p>
144
 
      </item>
145
 
      <item>
146
 
        <p><c>FormatFun = fun(Binary) -> Term</c></p>
147
 
      </item>
148
 
      <item>
149
 
        <p><c>Order = ascending | descending | OrderFun</c></p>
150
 
      </item>
151
 
      <item>
152
 
        <p><c>OrderFun = fun(Term, Term) -> bool()</c></p>
153
 
      </item>
154
 
      <item>
155
 
        <p><c>TempDirectory = "" | file_name()</c></p>
156
 
      </item>
157
 
      <item>
158
 
        <p><c>Size = int() >= 0</c></p>
159
 
      </item>
160
 
      <item>
161
 
        <p><c>NoFiles = int() > 1</c></p>
162
 
      </item>
163
 
    </list>
164
131
    <p>As an alternative to sorting files, a function of one argument
165
132
      can be given as input. When called with the argument <c>read</c>
166
133
      the function is assumed to return <c>end_of_input</c> or
234
201
      occurs are:</p>
235
202
    <list type="bulleted">
236
203
      <item>
237
 
        <p><c>bad_object</c>, <c>{bad_object, FileName}</c>. 
238
 
          Applying the format function failed for some binary, 
 
204
        <p><c>bad_object</c>, <c>{bad_object, FileName}</c>.
 
205
          Applying the format function failed for some binary,
239
206
          or the key(s) could not be extracted from some term.</p>
240
207
      </item>
241
208
      <item>
243
210
          to read some term.</p>
244
211
      </item>
245
212
      <item>
246
 
        <p><c>{file_error, FileName, Reason2}</c>. See
247
 
          <c>file(3)</c> for an explanation of <c>Reason2</c>.</p>
 
213
        <p><c>{file_error, FileName, file:posix()}</c>. See
 
214
          <c>file(3)</c> for an explanation of <c>file:posix()</c>.</p>
248
215
      </item>
249
216
      <item>
250
 
        <p><c>{premature_eof, FileName}</c>. End-of-file was 
 
217
        <p><c>{premature_eof, FileName}</c>. End-of-file was
251
218
          encountered inside some binary term.</p>
252
219
      </item>
253
220
    </list>
254
 
    <p><em>Types</em></p>
255
 
    <pre>
256
 
Binary = binary()
257
 
FileName = file_name()
258
 
FileNames = [FileName]
259
 
ICommand = read | close
260
 
IReply = end_of_input | {end_of_input, Value} | {[Object], Infun} | InputReply
261
 
Infun = fun(ICommand) -> IReply
262
 
Input = FileNames | Infun
263
 
InputReply = Term
264
 
KeyPos = int() > 0 | [int() > 0]
265
 
OCommand = {value, Value} | [Object] | close
266
 
OReply = Outfun | OutputReply
267
 
Object = Term | Binary
268
 
Outfun = fun(OCommand) -> OReply
269
 
Output = FileName | Outfun
270
 
OutputReply = Term
271
 
Term = term()
272
 
Value = Term</pre>
273
221
  </description>
 
222
 
 
223
  <datatypes>
 
224
    <datatype>
 
225
      <name name="file_name"/><br/>
 
226
    </datatype>
 
227
    <datatype>
 
228
      <name name="file_names"/><br/>
 
229
    </datatype>
 
230
    <datatype>
 
231
      <name name="i_command"/><br/>
 
232
    </datatype>
 
233
    <datatype>
 
234
      <name name="i_reply"/><br/>
 
235
    </datatype>
 
236
    <datatype>
 
237
      <name name="infun"/><br/>
 
238
    </datatype>
 
239
    <datatype>
 
240
      <name name="input"/><br/>
 
241
    </datatype>
 
242
    <datatype>
 
243
      <name name="input_reply"/><br/>
 
244
    </datatype>
 
245
    <datatype>
 
246
      <name name="o_command"/><br/>
 
247
    </datatype>
 
248
    <datatype>
 
249
      <name name="o_reply"/><br/>
 
250
    </datatype>
 
251
    <datatype>
 
252
      <name name="object"/><br/>
 
253
    </datatype>
 
254
    <datatype>
 
255
      <name name="outfun"/><br/>
 
256
    </datatype>
 
257
    <datatype>
 
258
      <name name="output"/><br/>
 
259
    </datatype>
 
260
    <datatype>
 
261
      <name name="output_reply"/><br/>
 
262
    </datatype>
 
263
    <datatype>
 
264
      <name name="value"/><br/>
 
265
    </datatype>
 
266
    <datatype>
 
267
      <name name="options"/><br/>
 
268
    </datatype>
 
269
    <datatype>
 
270
      <name name="option"/><br/>
 
271
    </datatype>
 
272
    <datatype>
 
273
      <name name="format"/><br/>
 
274
    </datatype>
 
275
    <datatype>
 
276
      <name name="format_fun"/><br/>
 
277
    </datatype>
 
278
    <datatype>
 
279
      <name name="header_length"/><br/>
 
280
    </datatype>
 
281
    <datatype>
 
282
      <name name="key_pos"/><br/>
 
283
    </datatype>
 
284
    <datatype>
 
285
      <name name="no_files"/><br/>
 
286
    </datatype>
 
287
    <datatype>
 
288
      <name name="order"/><br/>
 
289
    </datatype>
 
290
    <datatype>
 
291
      <name name="order_fun"/><br/>
 
292
    </datatype>
 
293
    <datatype>
 
294
      <name name="size"/><br/>
 
295
    </datatype>
 
296
    <datatype>
 
297
      <name name="tmp_directory"/><br/>
 
298
    </datatype>
 
299
    <datatype>
 
300
      <name name="reason"/><br/>
 
301
    </datatype>
 
302
  </datatypes>
 
303
 
274
304
  <funcs>
275
305
    <func>
276
 
      <name>sort(FileName) -> Reply</name>
277
 
      <name>sort(Input, Output) -> Reply</name>
278
 
      <name>sort(Input, Output, Options) -> Reply</name>
279
 
      <fsummary>Sort terms on files.</fsummary>
280
 
      <type>
281
 
        <v>Reply = ok | {error, Reason} | InputReply | OutputReply</v>
282
 
      </type>
283
 
      <desc>
284
 
        <p>Sorts terms on files. 
285
 
          </p>
286
 
        <p><c>sort(FileName)</c> is equivalent to
287
 
          <c>sort([FileName], FileName)</c>.
288
 
          </p>
289
 
        <p><c>sort(Input, Output)</c> is equivalent to
290
 
          <c>sort(Input, Output, [])</c>.
291
 
          </p>
292
 
        <p></p>
293
 
      </desc>
294
 
    </func>
295
 
    <func>
296
 
      <name>keysort(KeyPos, FileName) -> Reply</name>
297
 
      <name>keysort(KeyPos, Input, Output) -> Reply</name>
298
 
      <name>keysort(KeyPos, Input, Output, Options) -> Reply</name>
299
 
      <fsummary>Sort terms on files by key.</fsummary>
300
 
      <type>
301
 
        <v>Reply = ok | {error, Reason} | InputReply | OutputReply</v>
302
 
      </type>
 
306
      <name name="sort" arity="1"/>
 
307
      <fsummary>Sort terms on files.</fsummary>
 
308
      <desc>
 
309
        <p>Sorts terms on files. <c>sort(FileName)</c> is equivalent
 
310
          to <c>sort([FileName], FileName)</c>.</p>
 
311
      </desc>
 
312
    </func>
 
313
    <func>
 
314
      <name name="sort" arity="2"/>
 
315
      <name name="sort" arity="3"/>
 
316
      <fsummary>Sort terms on files.</fsummary>
 
317
      <desc>
 
318
        <p>Sorts terms on files. <c>sort(Input, Output)</c> is
 
319
          equivalent to <c>sort(Input, Output, [])</c>.</p>
 
320
      </desc>
 
321
    </func>
 
322
    <func>
 
323
      <name name="keysort" arity="2"/>
 
324
      <fsummary>Sort terms on files by key.</fsummary>
 
325
      <desc>
 
326
        <p>Sorts tuples on files. <c>keysort(N, FileName)</c> is
 
327
          equivalent to <c>keysort(N, [FileName], FileName)</c>.</p>
 
328
      </desc>
 
329
    </func>
 
330
    <func>
 
331
      <name name="keysort" arity="3"/>
 
332
      <name name="keysort" arity="4"/>
 
333
      <fsummary>Sort terms on files by key.</fsummary>
303
334
      <desc>
304
335
        <p>Sorts tuples on files. The sort is performed on the
305
 
          element(s) mentioned in <c>KeyPos</c>. If two tuples
306
 
          compare equal (<c>==</c>) on one element, next element according to
307
 
          <c>KeyPos</c> is compared. The sort is stable.
308
 
          </p>
309
 
        <p><c>keysort(N, FileName)</c> is equivalent to
310
 
          <c>keysort(N, [FileName], FileName)</c>.
311
 
          </p>
 
336
          element(s) mentioned in <c><anno>KeyPos</anno></c>. If two
 
337
          tuples compare equal (<c>==</c>) on one element, next
 
338
          element according to <c><anno>KeyPos</anno></c>
 
339
          is compared. The sort is stable.</p>
312
340
        <p><c>keysort(N, Input, Output)</c> is equivalent to
313
 
          <c>keysort(N, Input, Output, [])</c>.
314
 
          </p>
315
 
        <p></p>
 
341
          <c>keysort(N, Input, Output, [])</c>.</p>
316
342
      </desc>
317
343
    </func>
318
344
    <func>
319
 
      <name>merge(FileNames, Output) -> Reply</name>
320
 
      <name>merge(FileNames, Output, Options) -> Reply</name>
 
345
      <name name="merge" arity="2"/>
 
346
      <name name="merge" arity="3"/>
321
347
      <fsummary>Merge terms on files.</fsummary>
322
 
      <type>
323
 
        <v>Reply = ok | {error, Reason} | OutputReply</v>
324
 
      </type>
325
348
      <desc>
326
349
        <p>Merges terms on files. Each input file is assumed to be
327
 
          sorted.
328
 
          </p>
 
350
          sorted.</p>
329
351
        <p><c>merge(FileNames, Output)</c> is equivalent to
330
 
          <c>merge(FileNames, Output, [])</c>.
331
 
          </p>
 
352
          <c>merge(FileNames, Output, [])</c>.</p>
332
353
      </desc>
333
354
    </func>
334
355
    <func>
335
 
      <name>keymerge(KeyPos, FileNames, Output) -> Reply</name>
336
 
      <name>keymerge(KeyPos, FileNames, Output, Options) -> Reply</name>
 
356
      <name name="keymerge" arity="3"/>
 
357
      <name name="keymerge" arity="4"/>
337
358
      <fsummary>Merge terms on files by key.</fsummary>
338
 
      <type>
339
 
        <v>Reply = ok | {error, Reason} | OutputReply</v>
340
 
      </type>
341
359
      <desc>
342
360
        <p>Merges tuples on files. Each input file is assumed to be
343
 
          sorted on key(s).
344
 
          </p>
 
361
          sorted on key(s).</p>
345
362
        <p><c>keymerge(KeyPos, FileNames, Output)</c> is equivalent
346
 
          to <c>keymerge(KeyPos, FileNames, Output, [])</c>.
347
 
          </p>
348
 
        <p></p>
 
363
          to <c>keymerge(KeyPos, FileNames, Output, [])</c>.</p>
349
364
      </desc>
350
365
    </func>
351
366
    <func>
352
 
      <name>check(FileName) -> Reply</name>
353
 
      <name>check(FileNames, Options) -> Reply</name>
 
367
      <name name="check" arity="1"/>
 
368
      <name name="check" arity="2"/>
354
369
      <fsummary>Check whether terms on files are sorted.</fsummary>
355
 
      <type>
356
 
        <v>Reply = {ok, [Result]} | {error, Reason}</v>
357
 
        <v>Result = {FileName, TermPosition, Term}</v>
358
 
        <v>TermPosition = int() > 1</v>
359
 
      </type>
360
370
      <desc>
361
371
        <p>Checks files for sortedness. If a file is not sorted, the
362
372
          first out-of-order element is returned. The first term on a
363
 
          file has position 1.
364
 
          </p>
 
373
          file has position 1.</p>
365
374
        <p><c>check(FileName)</c> is equivalent to
366
 
          <c>check([FileName], [])</c>.
367
 
          </p>
 
375
          <c>check([FileName], [])</c>.</p>
368
376
      </desc>
369
377
    </func>
370
378
    <func>
371
 
      <name>keycheck(KeyPos, FileName) -> CheckReply</name>
372
 
      <name>keycheck(KeyPos, FileNames, Options) -> Reply</name>
 
379
      <name name="keycheck" arity="2"/>
 
380
      <name name="keycheck" arity="3"/>
373
381
      <fsummary>Check whether terms on files are sorted by key.</fsummary>
374
 
      <type>
375
 
        <v>Reply = {ok, [Result]} | {error, Reason}</v>
376
 
        <v>Result = {FileName, TermPosition, Term}</v>
377
 
        <v>TermPosition = int() > 1</v>
378
 
      </type>
379
382
      <desc>
380
383
        <p>Checks files for sortedness. If a file is not sorted, the
381
384
          first out-of-order element is returned. The first term on a
382
 
          file has position 1.
383
 
          </p>
 
385
          file has position 1.</p>
384
386
        <p><c>keycheck(KeyPos, FileName)</c> is equivalent
385
 
          to <c>keycheck(KeyPos, [FileName], [])</c>.
386
 
          </p>
387
 
        <p></p>
 
387
          to <c>keycheck(KeyPos, [FileName], [])</c>.</p>
388
388
      </desc>
389
389
    </func>
390
390
  </funcs>