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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/io.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>io</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>io</module>
 
33
  <modulesummary>Standard IO Server Interface Functions</modulesummary>
 
34
  <description>
 
35
    <p>This module provides an interface to standard Erlang IO servers.
 
36
      The output functions all return <c>ok</c> if they are successful,
 
37
      or exit if they are not.</p>
 
38
    <p>In the following description, all functions have an optional
 
39
      parameter <c>IoDevice</c>. If included, it must be the pid of a
 
40
      process which handles the IO protocols. Normally, it is the
 
41
      <c>IoDevice</c> returned by
 
42
      <seealso marker="kernel:file#open/2">file:open/2</seealso>.</p>
 
43
    <p>For a description of the IO protocols refer to Armstrong,
 
44
      Virding and Williams, 'Concurrent Programming in Erlang', Chapter
 
45
      13, unfortunately now very outdated, but the general principles
 
46
      still apply.</p>
 
47
  </description>
 
48
 
 
49
  <section>
 
50
    <title>DATA TYPES</title>
 
51
    <code type="none">
 
52
io_device()
 
53
  as returned by file:open/2, a process handling IO protocols</code>
 
54
  </section>
 
55
  <funcs>
 
56
    <func>
 
57
      <name>columns([IoDevice]) -> {ok,int()} | {error, enotsup}</name>
 
58
      <fsummary>Get the number of columns of a device</fsummary>
 
59
      <type>
 
60
        <v>IoDevice = io_device()</v>
 
61
      </type>
 
62
      <desc>
 
63
          <p>Retrieves the number of columns of the 
 
64
          <c>IoDevice</c> (i.e. the width of a terminal). The function
 
65
          only succeeds for terminal devices, for all other devices
 
66
          the function returns <c>{error, enotsup}</c></p>
 
67
      </desc>
 
68
    </func>
 
69
    <func>
 
70
      <name>put_chars([IoDevice,] IoData) -> ok</name>
 
71
      <fsummary>Write a list of characters</fsummary>
 
72
      <type>
 
73
        <v>IoDevice = io_device()</v>
 
74
        <v>IoData = iodata() -- see erlang(3)</v>
 
75
      </type>
 
76
      <desc>
 
77
        <p>Writes the characters of <c>IoData</c> to the standard output
 
78
          (<c>IoDevice</c>).</p>
 
79
      </desc>
 
80
    </func>
 
81
    <func>
 
82
      <name>nl([IoDevice]) -> ok</name>
 
83
      <fsummary>Write a newline</fsummary>
 
84
      <type>
 
85
        <v>IoDevice = io_device()</v>
 
86
      </type>
 
87
      <desc>
 
88
        <p>Writes new line to the standard output (<c>IoDevice</c>).</p>
 
89
      </desc>
 
90
    </func>
 
91
    <func>
 
92
      <name>get_chars([IoDevice,] Prompt, Count) -> string() | eof</name>
 
93
      <fsummary>Read a specified number of characters</fsummary>
 
94
      <type>
 
95
        <v>IoDevice = io_device()</v>
 
96
        <v>Prompt = atom() | string()</v>
 
97
        <v>Count = int()</v>
 
98
      </type>
 
99
      <desc>
 
100
        <p>Reads <c>Count</c> characters from standard input
 
101
          (<c>IoDevice</c>), prompting it with <c>Prompt</c>. It
 
102
          returns:</p>
 
103
        <taglist>
 
104
          <tag><c>String</c></tag>
 
105
          <item>
 
106
            <p>The input characters.</p>
 
107
          </item>
 
108
          <tag><c>eof</c></tag>
 
109
          <item>
 
110
            <p>End of file was encountered.</p>
 
111
          </item>
 
112
        </taglist>
 
113
      </desc>
 
114
    </func>
 
115
    <func>
 
116
      <name>get_line([IoDevice,] Prompt) -> string() | eof | {error,Reason}</name>
 
117
      <fsummary>Read a line</fsummary>
 
118
      <type>
 
119
        <v>IoDevice = io_device()</v>
 
120
        <v>Prompt = atom() | string()</v>
 
121
      </type>
 
122
      <desc>
 
123
        <p>Reads a line from the standard input (<c>IoDevice</c>),
 
124
          prompting it with <c>Prompt</c>. It returns:</p>
 
125
        <taglist>
 
126
          <tag><c>String</c></tag>
 
127
          <item>
 
128
            <p>The characters in the line terminated by a LF (or end of
 
129
              file).</p>
 
130
          </item>
 
131
          <tag><c>eof</c></tag>
 
132
          <item>
 
133
            <p>End of file was encountered.</p>
 
134
          </item>
 
135
          <tag><c>{error,Reason}</c></tag>
 
136
          <item>
 
137
            <p>Other (rare) error condition, for instance <c>{error,estale}</c>
 
138
            if reading from an NFS file system.</p>
 
139
          </item>
 
140
        </taglist>
 
141
      </desc>
 
142
    </func>
 
143
    <func>
 
144
      <name>setopts([IoDevice,] Opts) -> ok | {error, Reason}</name>
 
145
      <fsummary>Set options</fsummary>
 
146
      <type>
 
147
        <v>IoDevice = io_device()</v>
 
148
        <v>Opts = [Opt]</v>
 
149
        <v>&nbsp;&nbsp;Opt = binary | list</v>
 
150
        <v>Reason = term()</v>
 
151
      </type>
 
152
      <desc>
 
153
        <p>Set options for standard input/output (<c>IoDevice</c>).
 
154
          Possible options are:</p>
 
155
        <taglist>
 
156
          <tag><c>binary</c></tag>
 
157
          <item>
 
158
            <p>Makes <c>get_chars/2,3</c> and <c>get_line/1,2</c> return
 
159
              binaries instead of lists of chars.</p>
 
160
          </item>
 
161
          <tag><c>list</c></tag>
 
162
          <item>
 
163
            <p>Makes <c>get_chars/2,3</c> and <c>get_line/1,2</c> return
 
164
              lists of chars, which is the default.</p>
 
165
          </item>
 
166
          <tag><c>expand_fun</c></tag>
 
167
          <item>
 
168
            <p>Provide a function for tab-completion (expansion)
 
169
              like the erlang shell. This function is called
 
170
              when the user presses the Tab key. The expansion is
 
171
              active when calling line-reading functions such as
 
172
              <c>get_line/1,2</c>.</p>
 
173
            <p>The function is called with the current line, upto
 
174
              the cursor, as a reversed string. It should return a
 
175
              three-tuple: <c>{yes|no, string(), [string(), ...]}</c>. The
 
176
              first element gives a beep if <c>no</c>, otherwise the
 
177
              expansion is silent, the second is a string that will be
 
178
              entered at the cursor position, and the third is a list of
 
179
              possible expansions. If this list is non-empty, the list
 
180
              will be printed and the current input line will be written
 
181
              once again.</p>
 
182
            <p>Trivial example (beep on anything except empty line, which
 
183
              is expanded to "quit"):</p>
 
184
            <code type="none">
 
185
 fun("") -> {yes, "quit", []};
 
186
    (_) -> {no, "", ["quit"]} end</code>
 
187
          </item>
 
188
        </taglist>
 
189
        <note>
 
190
          <p>The <c>binary</c> option does not work against IO servers
 
191
            on remote nodes running an older version of Erlang/OTP than
 
192
            R9C.</p>
 
193
        </note>
 
194
      </desc>
 
195
    </func>
 
196
    <func>
 
197
      <name>write([IoDevice,] Term) -> ok</name>
 
198
      <fsummary>Write a term</fsummary>
 
199
      <type>
 
200
        <v>IoDevice = io_device()</v>
 
201
        <v>Term = term()</v>
 
202
      </type>
 
203
      <desc>
 
204
        <p>Writes the term <c>Term</c> to the standard output
 
205
          (<c>IoDevice</c>).</p>
 
206
      </desc>
 
207
    </func>
 
208
    <func>
 
209
      <name>read([IoDevice,] Prompt) -> Result</name>
 
210
      <fsummary>Read a term</fsummary>
 
211
      <type>
 
212
        <v>IoDevice = io_device()</v>
 
213
        <v>Prompt = atom() | string()</v>
 
214
        <v>Result = {ok, Term} | eof | {error, ErrorInfo}</v>
 
215
        <v>&nbsp;Term = term()</v>
 
216
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
217
      </type>
 
218
      <desc>
 
219
        <p>Reads a term <c>Term</c> from the standard input
 
220
          (<c>IoDevice</c>), prompting it with <c>Prompt</c>. It
 
221
          returns:</p>
 
222
        <taglist>
 
223
          <tag><c>{ok, Term}</c></tag>
 
224
          <item>
 
225
            <p>The parsing was successful.</p>
 
226
          </item>
 
227
          <tag><c>eof</c></tag>
 
228
          <item>
 
229
            <p>End of file was encountered.</p>
 
230
          </item>
 
231
          <tag><c>{error, ErrorInfo}</c></tag>
 
232
          <item>
 
233
            <p>The parsing failed.</p>
 
234
          </item>
 
235
        </taglist>
 
236
      </desc>
 
237
    </func>
 
238
    <func>
 
239
      <name>read(IoDevice, Prompt, StartLine) -> Result</name>
 
240
      <fsummary>Read a term</fsummary>
 
241
      <type>
 
242
        <v>IoDevice = io_device()</v>
 
243
        <v>Prompt = atom() | string()</v>
 
244
        <v>StartLine = int()</v>
 
245
        <v>Result = {ok, Term, EndLine} | {eof, EndLine} |  {error, ErrorInfo, EndLine}</v>
 
246
        <v>&nbsp;Term = term()</v>
 
247
        <v>&nbsp;EndLine = int()</v>
 
248
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
249
      </type>
 
250
      <desc>
 
251
        <p>Reads a term <c>Term</c> from <c>IoDevice</c>, prompting it
 
252
          with <c>Prompt</c>. Reading starts at line number
 
253
          <c>StartLine</c>. It returns:</p>
 
254
        <taglist>
 
255
          <tag><c>{ok, Term, EndLine}</c></tag>
 
256
          <item>
 
257
            <p>The parsing was successful.</p>
 
258
          </item>
 
259
          <tag><c>{eof, EndLine}</c></tag>
 
260
          <item>
 
261
            <p>End of file was encountered.</p>
 
262
          </item>
 
263
          <tag><c>{error, ErrorInfo, EndLine}</c></tag>
 
264
          <item>
 
265
            <p>The parsing failed.</p>
 
266
          </item>
 
267
        </taglist>
 
268
      </desc>
 
269
    </func>
 
270
    <func>
 
271
      <name>fwrite(Format) -></name>
 
272
      <name>fwrite([IoDevice,] Format, Data) -> ok</name>
 
273
      <name>format(Format) -></name>
 
274
      <name>format([IoDevice,] Format, Data) -> ok</name>
 
275
      <fsummary>Write formatted output</fsummary>
 
276
      <type>
 
277
        <v>IoDevice = io_device()</v>
 
278
        <v>Format = atom() | string() | binary()</v>
 
279
        <v>Data = [term()]</v>
 
280
      </type>
 
281
      <desc>
 
282
        <p>Writes the items in <c>Data</c> (<c>[]</c>) on the standard
 
283
          output (<c>IoDevice</c>) in accordance with <c>Format</c>.
 
284
          <c>Format</c> contains plain characters which are copied to
 
285
          the output device, and control sequences for formatting, see
 
286
          below. If <c>Format</c> is an atom or a binary, it is first 
 
287
          converted to a list with the aid of <c>atom_to_list/1</c>
 
288
          or <c>binary_to_list/1</c>.</p>
 
289
        <pre>
 
290
1> <input>io:fwrite("Hello world!~n", []).</input>
 
291
Hello world!
 
292
ok</pre>
 
293
        <p>The general format of a control sequence is <c>~F.P.PadC</c>.
 
294
          The character <c>C</c> determines the type of control sequence
 
295
          to be used, <c>F</c> and <c>P</c> are optional numeric
 
296
          arguments. If <c>F</c>, <c>P</c>, or <c>Pad</c> is <c>*</c>,
 
297
          the next argument in <c>Data</c> is used as the numeric value
 
298
          of <c>F</c> or <c>P</c>.</p>
 
299
        <p><c>F</c> is the <c>field width</c> of the printed argument. A
 
300
          negative value means that the argument will be left justified
 
301
          within the field, otherwise it will be right justified. If no
 
302
          field width is specified, the required print width will be
 
303
          used. If the field width specified is too small, then the
 
304
          whole field will be filled with <c>*</c> characters.</p>
 
305
        <p><c>P</c> is the <c>precision</c> of the printed argument. A
 
306
          default value is used if no precision is specified. The
 
307
          interpretation of precision depends on the control sequences.
 
308
          Unless otherwise specified, the argument <c>within</c> is used
 
309
          to determine print width.</p>
 
310
        <p><c>Pad</c> is the padding character. This is the character
 
311
          used to pad the printed representation of the argument so that
 
312
          it conforms to the specified field width and precision. Only
 
313
          one padding character can be specified and, whenever
 
314
          applicable, it is used for both the field width and precision.
 
315
          The default padding character is <c>' '</c> (space).</p>
 
316
        <p>The following control sequences are available:</p>
 
317
        <taglist>
 
318
          <tag><c>~</c></tag>
 
319
          <item>
 
320
            <p>The character <c>~</c> is written.</p>
 
321
          </item>
 
322
          <tag><c>c</c></tag>
 
323
          <item>
 
324
            <p>The argument is a number that will be interpreted as an
 
325
              ASCII code. The precision is the number of times the
 
326
              character is printed and it defaults to the field width,
 
327
              which in turn defaults to 1. The following example
 
328
              illustrates:</p>
 
329
            <pre>
 
330
2> <input>io:fwrite("|~10.5c|~-10.5c|~5c|~n", [$a, $b, $c]).</input>
 
331
|     aaaaa|bbbbb     |ccccc|
 
332
ok</pre>
 
333
          </item>
 
334
          <tag><c>f</c></tag>
 
335
          <item>
 
336
            <p>The argument is a float which is written as
 
337
              <c>[-]ddd.ddd</c>, where the precision is the number of
 
338
              digits after the decimal point. The default precision is 6
 
339
              and it cannot be less than 1.</p>
 
340
          </item>
 
341
          <tag><c>e</c></tag>
 
342
          <item>
 
343
            <p>The argument is a float which is written as
 
344
              <c>[-]d.ddde+-ddd</c>, where the precision is the number
 
345
              of digits written. The default precision is 6 and it
 
346
              cannot be less than 2.</p>
 
347
          </item>
 
348
          <tag><c>g</c></tag>
 
349
          <item>
 
350
            <p>The argument is a float which is written as <c>f</c>, if
 
351
              it is &gt;= 0.1 and &lt; 10000.0. Otherwise, it is written
 
352
              in the <c>e</c> format. The precision is the number of
 
353
              significant digits. It defaults to 6 and should not be
 
354
              less than 2. If the absolute value of the float does not
 
355
              allow it to be written in the <c>f</c> format with the
 
356
              desired number of significant digits, it is also written
 
357
              in the <c>e</c> format.</p>
 
358
          </item>
 
359
          <tag><c>s</c></tag>
 
360
          <item>
 
361
            <p>Prints the argument with the <c>string</c> syntax. The
 
362
              argument is an <seealso marker="kernel:erlang#iolist_definition">I/O list</seealso>, a binary, or an atom. The characters
 
363
              are printed without quotes. In this format, the printed
 
364
              argument is truncated to the given precision and field
 
365
              width.</p>
 
366
            <p>This format can be used for printing any object and
 
367
              truncating the output so it fits a specified field:</p>
 
368
            <pre>
 
369
3> <input>io:fwrite("|~10w|~n", [{hey, hey, hey}]).</input>
 
370
|**********|
 
371
ok
 
372
4> <input>io:fwrite("|~10s|~n", [io_lib:write({hey, hey, hey})]).</input>
 
373
|{hey,hey,h|
 
374
ok</pre>
 
375
          </item>
 
376
          <tag><c>w</c></tag>
 
377
          <item>
 
378
            <p>Writes data with the standard syntax. This is used to
 
379
              output Erlang terms. Atoms are printed within quotes if
 
380
              they contain embedded non-printable characters, and
 
381
              floats are printed accurately as the shortest, correctly
 
382
              rounded string.</p>
 
383
          </item>
 
384
          <tag><c>p</c></tag>
 
385
          <item>
 
386
            <p>Writes the data with standard syntax in the same way as
 
387
              <c>~w</c>, but breaks terms whose printed representation
 
388
              is longer than one line into many lines and indents each
 
389
              line sensibly. It also tries to detect lists of printable
 
390
              characters and to output these as strings. For example:</p>
 
391
            <pre>
 
392
5> <input>T = [{attributes,[[{id,age,1.50000},{mode,explicit},</input>
 
393
<input>{typename,"INTEGER"}], [{id,cho},{mode,explicit},{typename,'Cho'}]]},</input>
 
394
<input>{typename,'Person'},{tag,{'PRIVATE',3}},{mode,implicit}].</input>
 
395
...
 
396
6> <input>io:fwrite("~w~n", [T]).</input>
 
397
[{attributes,[[{id,age,1.5},{mode,explicit},{typename,
 
398
[73,78,84,69,71,69,82]}],[{id,cho},{mode,explicit},{typena
 
399
me,'Cho'}]]},{typename,'Person'},{tag,{'PRIVATE',3}},{mode
 
400
,implicit}]
 
401
ok
 
402
7> <input>io:fwrite("~62p~n", [T]).</input>
 
403
[{attributes,[[{id,age,1.5},
 
404
               {mode,explicit},
 
405
               {typename,"INTEGER"}],
 
406
              [{id,cho},{mode,explicit},{typename,'Cho'}]]},
 
407
 {typename,'Person'},
 
408
 {tag,{'PRIVATE',3}},
 
409
 {mode,implicit}]
 
410
ok</pre>
 
411
            <p>The field width specifies the maximum line length. It
 
412
              defaults to 80. The precision specifies the initial
 
413
              indentation of the term. It defaults to the number of
 
414
              characters printed on this line in the <c>same</c> call to
 
415
              <c>io:fwrite</c> or <c>io:format</c>. For example, using
 
416
              <c>T</c> above:</p>
 
417
            <pre>
 
418
8> <input>io:fwrite("Here T = ~62p~n", [T]).</input>
 
419
Here T = [{attributes,[[{id,age,1.5},
 
420
                        {mode,explicit},
 
421
                        {typename,"INTEGER"}],
 
422
                       [{id,cho},
 
423
                        {mode,explicit},
 
424
                        {typename,'Cho'}]]},
 
425
          {typename,'Person'},
 
426
          {tag,{'PRIVATE',3}},
 
427
          {mode,implicit}]
 
428
ok</pre>
 
429
          </item>
 
430
          <tag><c>W</c></tag>
 
431
          <item>
 
432
            <p>Writes data in the same way as <c>~w</c>, but takes an
 
433
              extra argument which is the maximum depth to which terms
 
434
              are printed. Anything below this depth is replaced with
 
435
              <c>...</c>. For example, using <c>T</c> above:</p>
 
436
            <pre>
 
437
9> <input>io:fwrite("~W~n", [T,9]).</input>
 
438
[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],
 
439
[{id,cho},{mode,...},{...}]]},{typename,'Person'},
 
440
{tag,{'PRIVATE',3}},{mode,implicit}]
 
441
ok</pre>
 
442
            <p>If the maximum depth has been reached, then it is
 
443
              impossible to read in the resultant output. Also, the
 
444
              <c>,...</c> form in a tuple denotes that there are more
 
445
              elements in the tuple but these are below the print depth.</p>
 
446
          </item>
 
447
          <tag><c>P</c></tag>
 
448
          <item>
 
449
            <p>Writes data in the same way as <c>~p</c>, but takes an
 
450
              extra argument which is the maximum depth to which terms
 
451
              are printed. Anything below this depth is replaced with
 
452
              <c>...</c>. For example:</p>
 
453
            <pre>
 
454
10> <input>io:fwrite("~62P~n", [T,9]).</input>
 
455
[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],
 
456
              [{id,cho},{mode,...},{...}]]},
 
457
 {typename,'Person'},
 
458
 {tag,{'PRIVATE',3}},
 
459
 {mode,implicit}]
 
460
ok</pre>
 
461
          </item>
 
462
          <tag><c>B</c></tag>
 
463
          <item>
 
464
            <p>Writes an integer in base 2..36, the default base is
 
465
              10. A leading dash is printed for negative integers.</p>
 
466
            <p>The precision field selects base. For example:</p>
 
467
            <pre>
 
468
11> <input>io:fwrite("~.16B~n", [31]).</input>
 
469
1F
 
470
ok
 
471
12> <input>io:fwrite("~.2B~n", [-19]).</input>
 
472
-10011
 
473
ok
 
474
13> <input>io:fwrite("~.36B~n", [5*36+35]).</input>
 
475
5Z
 
476
ok</pre>
 
477
          </item>
 
478
          <tag><c>X</c></tag>
 
479
          <item>
 
480
            <p>Like <c>B</c>, but takes an extra argument that is a
 
481
              prefix to insert before the number, but after the leading
 
482
              dash, if any.</p>
 
483
            <p>The prefix can be a possibly deep list of characters or
 
484
              an atom.</p>
 
485
            <pre>
 
486
14> <input>io:fwrite("~X~n", [31,"10#"]).</input>
 
487
10#31
 
488
ok
 
489
15> <input>io:fwrite("~.16X~n", [-31,"0x"]).</input>
 
490
-0x1F
 
491
ok</pre>
 
492
          </item>
 
493
          <tag><c>#</c></tag>
 
494
          <item>
 
495
            <p>Like <c>B</c>, but prints the number with an Erlang style
 
496
              '#'-separated base prefix.</p>
 
497
            <pre>
 
498
16> <input>io:fwrite("~.10#~n", [31]).</input>
 
499
10#31
 
500
ok
 
501
17> <input>io:fwrite("~.16#~n", [-31]).</input>
 
502
-16#1F
 
503
ok</pre>
 
504
          </item>
 
505
          <tag><c>b</c></tag>
 
506
          <item>
 
507
            <p>Like <c>B</c>, but prints lowercase letters.</p>
 
508
          </item>
 
509
          <tag><c>x</c></tag>
 
510
          <item>
 
511
            <p>Like <c>X</c>, but prints lowercase letters.</p>
 
512
          </item>
 
513
          <tag><c>+</c></tag>
 
514
          <item>
 
515
            <p>Like <c>#</c>, but prints lowercase letters.</p>
 
516
          </item>
 
517
          <tag><c>n</c></tag>
 
518
          <item>
 
519
            <p>Writes a new line.</p>
 
520
          </item>
 
521
          <tag><c>i</c></tag>
 
522
          <item>
 
523
            <p>Ignores the next term.</p>
 
524
          </item>
 
525
        </taglist>
 
526
        <p>Returns:</p>
 
527
        <taglist>
 
528
          <tag><c>ok</c></tag>
 
529
          <item>
 
530
            <p>The formatting succeeded.</p>
 
531
          </item>
 
532
        </taglist>
 
533
        <p>If an error occurs, there is no output. For example:</p>
 
534
        <pre>
 
535
18> <input>io:fwrite("~s ~w ~i ~w ~c ~n",['abc def', 'abc def', {foo, 1},{foo, 1}, 65]).</input>
 
536
abc def 'abc def'  {foo,1} A
 
537
ok
 
538
19> <input>io:fwrite("~s", [65]).</input>
 
539
** exception exit: {badarg,[{io,format,[&lt;0.22.0>,"~s","A"]},
 
540
                            {erl_eval,do_apply,5},
 
541
                            {shell,exprs,6},
 
542
                            {shell,eval_exprs,6},
 
543
                            {shell,eval_loop,3}]}
 
544
     in function  io:o_request/2</pre>
 
545
        <p>In this example, an attempt was made to output the single
 
546
          character '65' with the aid of the string formatting directive
 
547
          "~s".</p>
 
548
      </desc>
 
549
    </func>
 
550
    <func>
 
551
      <name>fread([IoDevice,] Prompt, Format) -> Result</name>
 
552
      <fsummary>Read formatted input</fsummary>
 
553
      <type>
 
554
        <v>IoDevice = io_device()</v>
 
555
        <v>Prompt = atom() | string()</v>
 
556
        <v>Format = string()</v>
 
557
        <v>Result = {ok, Terms} | eof | {error, What}</v>
 
558
        <v>&nbsp;Terms = [term()]</v>
 
559
        <v>&nbsp;What = term()</v>
 
560
      </type>
 
561
      <desc>
 
562
        <p>Reads characters from the standard input (<c>IoDevice</c>),
 
563
          prompting it with <c>Prompt</c>. Interprets the characters in
 
564
          accordance with <c>Format</c>. <c>Format</c> contains control
 
565
          sequences which directs the interpretation of the input.</p>
 
566
        <p><c>Format</c> may contain:</p>
 
567
        <list type="bulleted">
 
568
          <item>
 
569
            <p>White space characters (SPACE, TAB and NEWLINE) which
 
570
              cause input to be read to the next non-white space
 
571
              character.</p>
 
572
          </item>
 
573
          <item>
 
574
            <p>Ordinary characters which must match the next input
 
575
              character.</p>
 
576
          </item>
 
577
          <item>
 
578
            <p>Control sequences, which have the general format
 
579
              <c>~*FC</c>. The character <c>*</c> is an optional return
 
580
              suppression character. It provides a method to specify a
 
581
              field which is to be omitted. <c>F</c> is the <c>field width</c> of the input field and <c>C</c> determines the
 
582
              type of control sequence.</p>
 
583
            <p>Unless otherwise specified, leading white-space is
 
584
              ignored for all control sequences. An input field cannot
 
585
              be more than one line wide. The following control
 
586
              sequences are available:</p>
 
587
            <taglist>
 
588
              <tag><c>~</c></tag>
 
589
              <item>
 
590
                <p>A single <c>~</c> is expected in the input.</p>
 
591
              </item>
 
592
              <tag><c>d</c></tag>
 
593
              <item>
 
594
                <p>A decimal integer is expected.</p>
 
595
              </item>
 
596
              <tag><c>u</c></tag>
 
597
              <item>
 
598
                <p>An unsigned integer in base 2..36 is expected. The
 
599
                  field width parameter is used to specify base. Leading
 
600
                  white-space characters are not skipped.</p>
 
601
              </item>
 
602
              <tag><c>-</c></tag>
 
603
              <item>
 
604
                <p>An optional sign character is expected. A sign
 
605
                  character '-' gives the return value <c>-1</c>. Sign
 
606
                  character '+' or none gives <c>1</c>. The field width
 
607
                  parameter is ignored. Leading white-space characters
 
608
                  are not skipped.</p>
 
609
              </item>
 
610
              <tag><c>#</c></tag>
 
611
              <item>
 
612
                <p>An integer in base 2..36 with Erlang-style base
 
613
                  prefix (for example <c>"16#ffff"</c>) is expected.</p>
 
614
              </item>
 
615
              <tag><c>f</c></tag>
 
616
              <item>
 
617
                <p>A floating point number is expected. It must follow
 
618
                  the Erlang floating point number syntax.</p>
 
619
              </item>
 
620
              <tag><c>s</c></tag>
 
621
              <item>
 
622
                <p>A string of non-white-space characters is read. If a
 
623
                  field width has been specified, this number of
 
624
                  characters are read and all trailing white-space
 
625
                  characters are stripped. An Erlang string (list of
 
626
                  characters) is returned.</p>
 
627
              </item>
 
628
              <tag><c>a</c></tag>
 
629
              <item>
 
630
                <p>Similar to <c>s</c>, but the resulting string is
 
631
                  converted into an atom.</p>
 
632
              </item>
 
633
              <tag><c>c</c></tag>
 
634
              <item>
 
635
                <p>The number of characters equal to the field width are
 
636
                  read (default is 1) and returned as an Erlang string.
 
637
                  However, leading and trailing white-space characters
 
638
                  are not omitted as they are with <c>s</c>. All
 
639
                  characters are returned.</p>
 
640
              </item>
 
641
              <tag><c>l</c></tag>
 
642
              <item>
 
643
                <p>Returns the number of characters which have been
 
644
                  scanned up to that point, including white-space
 
645
                  characters.</p>
 
646
              </item>
 
647
            </taglist>
 
648
            <p>It returns:</p>
 
649
            <taglist>
 
650
              <tag><c>{ok, Terms}</c></tag>
 
651
              <item>
 
652
                <p>The read was successful and <c>Terms</c> is the list
 
653
                  of successfully matched and read items.</p>
 
654
              </item>
 
655
              <tag><c>eof</c></tag>
 
656
              <item>
 
657
                <p>End of file was encountered.</p>
 
658
              </item>
 
659
              <tag><c>{error, What}</c></tag>
 
660
              <item>
 
661
                <p>The read operation failed and the parameter
 
662
                  <c>What</c> gives a hint about the error.</p>
 
663
              </item>
 
664
            </taglist>
 
665
          </item>
 
666
        </list>
 
667
        <p>Examples:</p>
 
668
        <pre>
 
669
20> <input>io:fread('enter>', "~f~f~f").</input>
 
670
enter><input>1.9 35.5e3 15.0</input>
 
671
{ok,[1.9,3.55e4,15.0]}
 
672
21> <input>io:fread('enter>', "~10f~d").</input>
 
673
enter>     <input>5.67899</input>
 
674
{ok,[5.678,99]}
 
675
22> <input>io:fread('enter>', ":~10s:~10c:").</input>
 
676
enter><input>:</input>   <input>alan</input>   <input>:</input>   <input>joe</input>    <input>:</input>
 
677
{ok, ["alan", "   joe    "]}</pre>
 
678
      </desc>
 
679
    </func>
 
680
    <func>
 
681
      <name>rows([IoDevice]) -> {ok,int()} | {error, enotsup}</name>
 
682
      <fsummary>Get the number of rows of a device</fsummary>
 
683
      <type>
 
684
        <v>IoDevice = io_device()</v>
 
685
      </type>
 
686
      <desc>
 
687
          <p>Retrieves the number of rows of the 
 
688
          <c>IoDevice</c> (i.e. the height of a terminal). The function
 
689
          only succeeds for terminal devices, for all other devices
 
690
          the function returns <c>{error, enotsup}</c></p>
 
691
      </desc>
 
692
    </func>
 
693
    <func>
 
694
      <name>scan_erl_exprs(Prompt) -></name>
 
695
      <name>scan_erl_exprs([IoDevice,] Prompt, StartLine) -> Result</name>
 
696
      <fsummary>Read and tokenize Erlang expressions</fsummary>
 
697
      <type>
 
698
        <v>IoDevice = io_device()</v>
 
699
        <v>Prompt = atom() | string()</v>
 
700
        <v>StartLine = int()</v>
 
701
        <v>Result = {ok, Tokens, EndLine} | {eof, EndLine} | {error, ErrorInfo, EndLine}</v>
 
702
        <v>&nbsp;Tokens -- see erl_scan(3)</v>
 
703
        <v>&nbsp;EndLine = int()</v>
 
704
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
705
      </type>
 
706
      <desc>
 
707
        <p>Reads data from the standard input (<c>IoDevice</c>),
 
708
          prompting it with <c>Prompt</c>. Reading starts at line number
 
709
          <c>StartLine</c> (1). The data is tokenized as if it were a
 
710
          sequence of Erlang expressions until a final <c>'.'</c> is
 
711
          reached. This token is also returned. It returns:</p>
 
712
        <taglist>
 
713
          <tag><c>{ok, Tokens, EndLine}</c></tag>
 
714
          <item>
 
715
            <p>The tokenization succeeded.</p>
 
716
          </item>
 
717
          <tag><c>{eof, EndLine}</c></tag>
 
718
          <item>
 
719
            <p>End of file was encountered.</p>
 
720
          </item>
 
721
          <tag><c>{error, ErrorInfo, EndLine}</c></tag>
 
722
          <item>
 
723
            <p>An error occurred.</p>
 
724
          </item>
 
725
        </taglist>
 
726
        <p>Example:</p>
 
727
        <pre>
 
728
23> <input>io:scan_erl_exprs('enter>').</input>
 
729
enter><input>abc(), "hey".</input>
 
730
{ok,[{atom,1,abc},{'(',1},{')',1},{',',1},{string,1,"hey"},{dot,1}],2}
 
731
24> <input>io:scan_erl_exprs('enter>').</input>
 
732
enter><input>1.0er.</input>
 
733
{error,{1,erl_scan,{illegal,float}},2}</pre>
 
734
      </desc>
 
735
    </func>
 
736
    <func>
 
737
      <name>scan_erl_form(Prompt) -></name>
 
738
      <name>scan_erl_form([IoDevice,] Prompt, StartLine) -> Result</name>
 
739
      <fsummary>Read and tokenize an Erlang form</fsummary>
 
740
      <type>
 
741
        <v>IoDevice = io_device()</v>
 
742
        <v>Prompt = atom() | string()</v>
 
743
        <v>StartLine = int()</v>
 
744
        <v>Result = {ok, Tokens, EndLine} | {eof, EndLine} | {error, ErrorInfo, EndLine}</v>
 
745
        <v>&nbsp;Tokens -- see erl_scan(3)</v>
 
746
        <v>&nbsp;EndLine = int()</v>
 
747
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
748
      </type>
 
749
      <desc>
 
750
        <p>Reads data from the standard input (<c>IoDevice</c>),
 
751
          prompting it with <c>Prompt</c>. Starts reading at line number
 
752
          <c>StartLine</c> (1). The data is tokenized as if it were an
 
753
          Erlang form - one of the valid Erlang expressions in an
 
754
          Erlang source file - until a final <c>'.'</c> is reached.
 
755
          This last token is also returned. The return values are the
 
756
          same as for <c>scan_erl_exprs/1,2,3</c> above.</p>
 
757
      </desc>
 
758
    </func>
 
759
    <func>
 
760
      <name>parse_erl_exprs(Prompt) -></name>
 
761
      <name>parse_erl_exprs([IoDevice,] Prompt, StartLine) -> Result</name>
 
762
      <fsummary>Read, tokenize and parse Erlang expressions</fsummary>
 
763
      <type>
 
764
        <v>IoDevice = io_device()</v>
 
765
        <v>Prompt = atom() | string()</v>
 
766
        <v>StartLine = int()</v>
 
767
        <v>Result = {ok, Expr_list, EndLine} | {eof, EndLine} | {error, ErrorInfo, EndLine}</v>
 
768
        <v>&nbsp;Expr_list -- see erl_parse(3)</v>
 
769
        <v>&nbsp;EndLine = int()</v>
 
770
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
771
      </type>
 
772
      <desc>
 
773
        <p>Reads data from the standard input (<c>IoDevice</c>),
 
774
          prompting it with <c>Prompt</c>. Starts reading at line number
 
775
          <c>StartLine</c> (1). The data is tokenized and parsed as if
 
776
          it were a sequence of Erlang expressions until a final '.' is
 
777
          reached. It returns:</p>
 
778
        <taglist>
 
779
          <tag><c>{ok, Expr_list, EndLine}</c></tag>
 
780
          <item>
 
781
            <p>The parsing was successful.</p>
 
782
          </item>
 
783
          <tag><c>{eof, EndLine}</c></tag>
 
784
          <item>
 
785
            <p>End of file was encountered.</p>
 
786
          </item>
 
787
          <tag><c>{error, ErrorInfo, EndLine}</c></tag>
 
788
          <item>
 
789
            <p>An error occurred.</p>
 
790
          </item>
 
791
        </taglist>
 
792
        <p>Example:</p>
 
793
        <pre>
 
794
25> <input>io:parse_erl_exprs('enter>').</input>
 
795
enter><input>abc(), "hey".</input>
 
796
{ok, [{call,1,{atom,1,abc},[]},{string,1,"hey"}],2}
 
797
26> <input>io:parse_erl_exprs ('enter>').</input>
 
798
enter><input>abc("hey".</input>
 
799
{error,{1,erl_parse,["syntax error before: ",["'.'"]]},2}</pre>
 
800
      </desc>
 
801
    </func>
 
802
    <func>
 
803
      <name>parse_erl_form(Prompt) -></name>
 
804
      <name>parse_erl_form([IoDevice,] Prompt, StartLine) -> Result</name>
 
805
      <fsummary>Read, tokenize and parse an Erlang form</fsummary>
 
806
      <type>
 
807
        <v>IoDevice = io_device()</v>
 
808
        <v>Prompt = atom() | string()</v>
 
809
        <v>StartLine = int()</v>
 
810
        <v>Result = {ok, AbsForm, EndLine} | {eof, EndLine} | {error, ErrorInfo, EndLine}</v>
 
811
        <v>&nbsp;AbsForm -- see erl_parse(3)</v>
 
812
        <v>&nbsp;EndLine = int()</v>
 
813
        <v>&nbsp;ErrorInfo -- see section Error Information below</v>
 
814
      </type>
 
815
      <desc>
 
816
        <p>Reads data from the standard input (<c>IoDevice</c>),
 
817
          prompting it with <c>Prompt</c>. Starts reading at line number
 
818
          <c>StartLine</c> (1). The data is tokenized and parsed as if
 
819
          it were an Erlang form - one of the valid Erlang expressions
 
820
          in an Erlang source file - until a final '.' is reached. It
 
821
          returns:</p>
 
822
        <taglist>
 
823
          <tag><c>{ok, AbsForm, EndLine}</c></tag>
 
824
          <item>
 
825
            <p>The parsing was successful.</p>
 
826
          </item>
 
827
          <tag><c>{eof, EndLine}</c></tag>
 
828
          <item>
 
829
            <p>End of file was encountered.</p>
 
830
          </item>
 
831
          <tag><c>{error, ErrorInfo, EndLine}</c></tag>
 
832
          <item>
 
833
            <p>An error occurred.</p>
 
834
          </item>
 
835
        </taglist>
 
836
      </desc>
 
837
    </func>
 
838
  </funcs>
 
839
 
 
840
  <section>
 
841
    <title>Standard Input/Output</title>
 
842
    <p>All Erlang processes have a default standard IO device. This
 
843
      device is used when no <c>IoDevice</c> argument is specified in
 
844
      the above function calls. However, it is sometimes desirable to
 
845
      use an explicit <c>IoDevice</c> argument which refers to the
 
846
      default IO device. This is the case with functions that can
 
847
      access either a file or the default IO device. The atom
 
848
      <c>standard_io</c> has this special meaning. The following example
 
849
      illustrates this:</p>
 
850
    <pre>
 
851
27> <input>io:read('enter>').</input>
 
852
enter><input>foo.</input>
 
853
{ok,foo}
 
854
28> <input>io:read(standard_io, 'enter>').</input>
 
855
enter><input>bar.</input>
 
856
{ok,bar}</pre>
 
857
    <p>There is always a process registered under the name of
 
858
      <c>user</c>. This can be used for sending output to the user.</p>
 
859
  </section>
 
860
 
 
861
  <section>
 
862
    <title>Error Information</title>
 
863
    <p>The <c>ErrorInfo</c> mentioned above is the standard
 
864
      <c>ErrorInfo</c> structure which is returned from all IO modules.
 
865
      It has the format:</p>
 
866
    <code type="none">
 
867
{ErrorLine, Module, ErrorDescriptor}</code>
 
868
    <p>A string which describes the error is obtained with the following
 
869
      call:</p>
 
870
    <code type="none">
 
871
apply(Module, format_error, ErrorDescriptor)</code>
 
872
  </section>
 
873
</erlref>
 
874