~statik/ubuntu/maverick/erlang/erlang-merge-testing

« 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-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

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>
8
 
      <year>2007</year>
9
 
      <holder>Ericsson AB, All Rights Reserved</holder>
 
7
      <year>1996</year><year>2009</year>
 
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
10
9
    </copyright>
11
10
    <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.
 
11
      The contents of this file are subject to the Erlang Public License,
 
12
      Version 1.1, (the "License"); you may not use this file except in
 
13
      compliance with the License. You should have received a copy of the
 
14
      Erlang Public License along with this software. If not, it can be
 
15
      retrieved online at http://www.erlang.org/.
 
16
    
 
17
      Software distributed under the License is distributed on an "AS IS"
 
18
      basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
19
      the License for the specific language governing rights and limitations
 
20
      under the License.
 
21
    
24
22
    </legalnotice>
25
23
 
26
24
    <title>io</title>
40
38
      process which handles the IO protocols. Normally, it is the
41
39
      <c>IoDevice</c> returned by
42
40
      <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>
 
41
    <p>For a description of the IO protocols refer to the STDLIB Users Guide.</p>
 
42
    <warning>
 
43
 
 
44
    <p>As of R13A, data supplied to the <seealso
 
45
    marker="#put_chars/2">put_chars</seealso> function should be in the
 
46
    <c>chardata()</c> format described below. This means that programs
 
47
    supplying binaries to this function need to convert them to UTF-8
 
48
    before trying to output the data on an
 
49
    <c>io_device()</c>.</p>
 
50
 
 
51
    <p>If an io_device() is set in binary mode, the functions <seealso
 
52
    marker="#get_chars/3">get_chars</seealso> and <seealso
 
53
    marker="#get_line/2">get_line</seealso> may return binaries
 
54
    instead of lists. The binaries will, as of R13A, be encoded in
 
55
    UTF-8.</p>
 
56
 
 
57
    <p>To work with binaries in ISO-latin-1 encoding, use the <seealso
 
58
    marker="kernel:file">file</seealso> module instead.</p>
 
59
 
 
60
    <p>For conversion functions between character encodings, see the <seealso
 
61
    marker="stdlib:unicode">unicode</seealso> module.</p>
 
62
 
 
63
    </warning>
 
64
 
47
65
  </description>
48
66
 
49
67
  <section>
51
69
    <code type="none">
52
70
io_device()
53
71
  as returned by file:open/2, a process handling IO protocols</code>
 
72
 
 
73
    <code type="none">
 
74
unicode_binary() = binary() with characters encoded in UTF-8 coding standard
 
75
unicode_char() = integer() representing valid unicode codepoint
 
76
 
 
77
chardata() = charlist() | unicode_binary()
 
78
 
 
79
charlist() = [unicode_char() | unicode_binary() | charlist()]
 
80
  a unicode_binary is allowed as the tail of the list</code>
54
81
  </section>
55
82
  <funcs>
56
83
    <func>
71
98
      <fsummary>Write a list of characters</fsummary>
72
99
      <type>
73
100
        <v>IoDevice = io_device()</v>
74
 
        <v>IoData = iodata() -- see erlang(3)</v>
 
101
        <v>IoData = chardata()</v>
75
102
      </type>
76
103
      <desc>
77
 
        <p>Writes the characters of <c>IoData</c> to the standard output
 
104
        <p>Writes the characters of <c>IoData</c> to the io_server()
78
105
          (<c>IoDevice</c>).</p>
79
106
      </desc>
80
107
    </func>
89
116
      </desc>
90
117
    </func>
91
118
    <func>
92
 
      <name>get_chars([IoDevice,] Prompt, Count) -> string() | eof</name>
 
119
      <name>get_chars([IoDevice,] Prompt, Count) -> Data | eof</name>
93
120
      <fsummary>Read a specified number of characters</fsummary>
94
121
      <type>
95
122
        <v>IoDevice = io_device()</v>
96
123
        <v>Prompt = atom() | string()</v>
97
124
        <v>Count = int()</v>
 
125
        <v>Data = [ unicode_char() ] | unicode_binary()</v>
98
126
      </type>
99
127
      <desc>
100
128
        <p>Reads <c>Count</c> characters from standard input
101
129
          (<c>IoDevice</c>), prompting it with <c>Prompt</c>. It
102
130
          returns:</p>
103
131
        <taglist>
104
 
          <tag><c>String</c></tag>
 
132
          <tag><c>Data</c></tag>
105
133
          <item>
106
 
            <p>The input characters.</p>
 
134
            <p>The input characters. If the device supports Unicode,
 
135
            the data may represent codepoints larger than 255 (the
 
136
            latin1 range). If the io_server() is set to deliver
 
137
            binaries, they will be encoded in UTF-8 (regardless of if
 
138
            the device actually supports Unicode or not).</p>
107
139
          </item>
108
140
          <tag><c>eof</c></tag>
109
141
          <item>
110
142
            <p>End of file was encountered.</p>
111
143
          </item>
 
144
          <tag><c>{error,Reason}</c></tag>
 
145
          <item>
 
146
            <p>Other (rare) error condition, for instance <c>{error,estale}</c>
 
147
            if reading from an NFS file system.</p>
 
148
          </item>
112
149
        </taglist>
113
150
      </desc>
114
151
    </func>
115
152
    <func>
116
 
      <name>get_line([IoDevice,] Prompt) -> string() | eof | {error,Reason}</name>
 
153
      <name>get_line([IoDevice,] Prompt) -> Data | eof | {error,Reason}</name>
117
154
      <fsummary>Read a line</fsummary>
118
155
      <type>
119
156
        <v>IoDevice = io_device()</v>
120
157
        <v>Prompt = atom() | string()</v>
 
158
        <v>Data = [ unicode_char() ] | unicode_binary()</v>
121
159
      </type>
122
160
      <desc>
123
161
        <p>Reads a line from the standard input (<c>IoDevice</c>),
124
162
          prompting it with <c>Prompt</c>. It returns:</p>
125
163
        <taglist>
126
 
          <tag><c>String</c></tag>
 
164
          <tag><c>Data</c></tag>
127
165
          <item>
128
166
            <p>The characters in the line terminated by a LF (or end of
129
 
              file).</p>
 
167
              file). If the device supports Unicode,
 
168
            the data  may represent codepoints larger than 255 (the
 
169
            latin1 range). If the io_server() is set to deliver
 
170
            binaries, they will be encoded in UTF-8 (regardless of if
 
171
            the device actually supports Unicode or not).</p>
130
172
          </item>
131
173
          <tag><c>eof</c></tag>
132
174
          <item>
141
183
      </desc>
142
184
    </func>
143
185
    <func>
 
186
      <name>getopts([IoDevice]) -> Opts</name>
 
187
      <fsummary>Get the supported options and values from an I/O-server</fsummary>
 
188
      <type>
 
189
        <v>IoDevice = io_device()</v>
 
190
        <v>Opts = [Opt]</v>
 
191
        <v>&nbsp;&nbsp;Opt = {atom(),Value}</v>
 
192
        <v>&nbsp;&nbsp;Value = term()</v>
 
193
      </type>
 
194
      <desc>
 
195
      <p>This function requests all available options and their current values for a specific io_device(). Example:</p>
 
196
<pre>
 
197
1> <input>{ok,F} = file:open("/dev/null",[read]).</input>
 
198
{ok,&lt;0.42.0&gt;}
 
199
2> <input>io:getopts(F).</input>
 
200
[{binary,false},{encoding,latin1}]</pre>
 
201
      <p>Here the file I/O-server returns all available options for a file,
 
202
      which are the expected ones, <c>encoding</c> and <c>binary</c>. The standard shell however has some more options:</p>
 
203
<pre>
 
204
3> io:getopts().
 
205
[{expand_fun,#Fun&lt;group.0.120017273&gt;},
 
206
 {echo,true},
 
207
 {binary,false},
 
208
 {encoding,unicode}]</pre>
 
209
      <p>This example is, as can be seen, run in an environment where the terminal supports Unicode input and output.</p>
 
210
      </desc>
 
211
    </func>
 
212
    <func>
144
213
      <name>setopts([IoDevice,] Opts) -> ok | {error, Reason}</name>
145
214
      <fsummary>Set options</fsummary>
146
215
      <type>
147
216
        <v>IoDevice = io_device()</v>
148
217
        <v>Opts = [Opt]</v>
149
 
        <v>&nbsp;&nbsp;Opt = binary | list</v>
 
218
        <v>&nbsp;&nbsp;Opt = atom() | {atom(),Value}</v>
 
219
        <v>&nbsp;&nbsp;Value = term()</v>
150
220
        <v>Reason = term()</v>
151
221
      </type>
152
222
      <desc>
153
 
        <p>Set options for standard input/output (<c>IoDevice</c>).
154
 
          Possible options are:</p>
 
223
        <p>Set options for the io_device() (<c>IoDevice</c>).</p>
 
224
 
 
225
        <p>Possible options and values vary depending on the actual
 
226
        io_device(). For a list of supported options and their current values
 
227
        on a specific device, use the <seealso
 
228
        marker="#getopts/1">getopts/1</seealso> function.</p>
 
229
 
 
230
        <p>The options and values supported by the current OTP io_devices are:</p>
155
231
        <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>
 
232
          <tag><c>binary, list or {binary, bool()}</c></tag>
 
233
          <item>
 
234
            <p>If set in binary mode (binary or {binary,true}), the io_server() sends binary data (encoded in UTF-8) as answers to the get_line, get_chars and, if possible, get_until requests (see the I/O protocol description in STDLIB User's Guide for details). The immediate effect is that <c>get_chars/2,3</c> and <c>get_line/1,2</c> return UTF-8 binaries instead of lists of chars for the affected device.</p>
 
235
            <p>By default, all io_devices in OTP are set in list mode, but the io functions can handle any of these modes and so should other, user written, modules behaving as clients to I/O-servers.</p>
 
236
            <p>This option is supported by the standard shell (group.erl), the 'oldshell' (user.erl) and the file I/O servers.</p>
 
237
          </item>
 
238
          <tag><c>{echo, bool()}</c></tag>
 
239
          <item>
 
240
          <p>Denotes if the terminal shpould echo input. Only supported for the standard shell I/O-server (group.erl)</p>
 
241
          </item>
 
242
          <tag><c>{expand_fun, fun()}</c></tag>
167
243
          <item>
168
244
            <p>Provide a function for tab-completion (expansion)
169
245
              like the erlang shell. This function is called
184
260
            <code type="none">
185
261
 fun("") -> {yes, "quit", []};
186
262
    (_) -> {no, "", ["quit"]} end</code>
 
263
            <p>This option is supported by the standard shell only (group.erl).</p>
187
264
          </item>
 
265
          <tag><c>{encoding, latin1 | unicode}</c></tag>
 
266
          <item>
 
267
          <p>Specifies how characters are input or output from or to the actual device, implying that i.e. a terminal is set to handle Unicode input and output or a file is set to handle UTF-8 data encoding.</p>
 
268
          <p>The option <em>does not</em> affect how data is returned from the io-functions or how it is sent in the I/O-protocol, it only affects how the io_device() is to handle Unicode characters towards the &quot;physical&quot; device.</p>
 
269
          <p>The standard shell will be set for either unicode or latin1 encoding when the system is started. The actual encoding is set with the help of the "LANG" or "LC_CTYPE" environment variables on Unix-like system or by other means on other systems. The bottom line is that the user can input Unicode characters and the device will be in {encoding, unicode} mode if the device supports it. The mode can be changed, if the assumption of the runtime system is wrong, by setting this option.</p>
 
270
          <p>The io_device() used when Erlang is started with the "-oldshell" or "-noshell" flags is by default set to latin1 encoding, meaning that any characters beyond codepoint 255 will be escaped and that input is expected to be plain 8-bit ISO-latin-1. If the encoding is changed to Unicode, input and output from the standard file descriptors will be in UTF-8 (regardless of operating system).</p>
 
271
          <p>Files can also be set in {encoding, unicode}, meaning that data is written and read as UTF-8. More encodings are possible for files, see below.</p>
 
272
          <p>{encoding, unicode | latin1} is supported by both the standard shell (group.erl including werl on windows), the 'oldshell' (user.erl) and the file I/O servers.</p>
 
273
          </item>
 
274
          <tag><c>{encoding, utf8 | utf16 | utf32 | {utf16,big} | {utf16,little} | {utf32,big} | {utf32,little}}</c></tag>
 
275
          <item>
 
276
          <p>For disk files, the encoding can be set to various UTF variants. This will have the effect that data is expected to be read as the specified encoding from the file and the data will be wriiten in the specified encoding to the disk file.</p>
 
277
          <p>{encoding, utf8} will have the same effect as {encoding,unicode} on files.</p>
 
278
          <p>The extended encodings are only supported on disk files (opened by the <seealso marker="kernel:file#open/2">file:open/2</seealso> function)</p>
 
279
          </item>
188
280
        </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
281
      </desc>
195
282
    </func>
196
283
    <func>
290
377
1> <input>io:fwrite("Hello world!~n", []).</input>
291
378
Hello world!
292
379
ok</pre>
293
 
        <p>The general format of a control sequence is <c>~F.P.PadC</c>.
 
380
        <p>The general format of a control sequence is <c>~F.P.PadModC</c>.
294
381
          The character <c>C</c> determines the type of control sequence
295
382
          to be used, <c>F</c> and <c>P</c> are optional numeric
296
383
          arguments. If <c>F</c>, <c>P</c>, or <c>Pad</c> is <c>*</c>,
313
400
          one padding character can be specified and, whenever
314
401
          applicable, it is used for both the field width and precision.
315
402
          The default padding character is <c>' '</c> (space).</p>
316
 
        <p>The following control sequences are available:</p>
 
403
        <p><c>Mod</c> is the control sequence modifier. It is either a
 
404
        single character (currently only 't', for unicode translation,
 
405
        is supported) that changes the interpretation of Data.</p>
 
406
 
 
407
         <p>The following control sequences are available:</p>
317
408
        <taglist>
318
409
          <tag><c>~</c></tag>
319
410
          <item>
330
421
2> <input>io:fwrite("|~10.5c|~-10.5c|~5c|~n", [$a, $b, $c]).</input>
331
422
|     aaaaa|bbbbb     |ccccc|
332
423
ok</pre>
 
424
            <p>If the Unicode translation modifier ('t') is in effect,
 
425
            the integer argument can be any number representing a
 
426
            valid unicode codepoint, otherwise it should be an integer
 
427
            less than or equal to 255, otherwise it is masked with 16#FF:</p>
 
428
<pre>
 
429
1> <input>io:fwrite("~tc~n",[1024]).</input>
 
430
\x{400}
 
431
ok
 
432
2> <input>io:fwrite("~c~n",[1024]).</input>
 
433
^@
 
434
ok</pre>
 
435
 
333
436
          </item>
334
437
          <tag><c>f</c></tag>
335
438
          <item>
359
462
          <tag><c>s</c></tag>
360
463
          <item>
361
464
            <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
 
465
              argument is, if no Unicode translation modifier is present, an 
 
466
              <seealso marker="erts:erlang#iolist_definition">I/O list</seealso>, a binary, or an atom. If the Unicode translation modifier ('t') is in effect, the argument is chardata(), meaning that binaries are in UTF-8. The characters
363
467
              are printed without quotes. In this format, the printed
364
468
              argument is truncated to the given precision and field
365
469
              width.</p>
372
476
4> <input>io:fwrite("|~10s|~n", [io_lib:write({hey, hey, hey})]).</input>
373
477
|{hey,hey,h|
374
478
ok</pre>
 
479
          <p>A list with integers larger than 255 is considered an error if the Unicode translation modifier is not given:</p>
 
480
<pre>
 
481
1> <input>io:fwrite("~ts~n",[[1024]]).</input>
 
482
\x{400}
 
483
ok
 
484
2> io:fwrite("~s~n",[[1024]]).
 
485
** exception exit: {badarg,[{io,format,[&lt;0.26.0&gt;,"~s~n",[[1024]]]},
 
486
   ...</pre>
375
487
          </item>
376
488
          <tag><c>w</c></tag>
377
489
          <item>
575
687
              character.</p>
576
688
          </item>
577
689
          <item>
 
690
 
578
691
            <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>
 
692
              <c>~*FMC</c>. The character <c>*</c> is an optional
 
693
              return suppression character. It provides a method to
 
694
              specify a field which is to be omitted. <c>F</c> is the
 
695
              <c>field width</c> of the input field, <c>M</c> is an optional
 
696
              translation modifier (of which 't' is the only currently
 
697
              supported, meaning Unicode translation) and <c>C</c>
 
698
              determines the type of control sequence.</p>
 
699
 
583
700
            <p>Unless otherwise specified, leading white-space is
584
701
              ignored for all control sequences. An input field cannot
585
702
              be more than one line wide. The following control
624
741
                  characters are read and all trailing white-space
625
742
                  characters are stripped. An Erlang string (list of
626
743
                  characters) is returned.</p>
 
744
 
 
745
                  <p>If Unicode translation is in effect (~ts),
 
746
                  characters larger than 255 are accepted, otherwise
 
747
                  not. With the translation modifier, the list
 
748
                  returned may as a consequence also contain
 
749
                  integers larger than 255:</p>
 
750
 
 
751
<pre>
 
752
1> <input>io:fread("Prompt> ","~s").</input>
 
753
Prompt> <input>&lt;Characters beyond latin1 range not printable in this medium&gt;</input>
 
754
{error,{fread,string}}
 
755
2> <input>io:fread("Prompt> ","~ts").</input>
 
756
Prompt> <input>&lt;Characters beyond latin1 range not printable in this medium&gt;</input>
 
757
{ok,[[1091,1085,1080,1094,1086,1076,1077]]}</pre>
 
758
 
627
759
              </item>
628
760
              <tag><c>a</c></tag>
629
761
              <item>
630
762
                <p>Similar to <c>s</c>, but the resulting string is
631
763
                  converted into an atom.</p>
 
764
                  <p>The Unicode translation modifier is not allowed (atoms can not contain characters beyond the latin1 range).</p>
632
765
              </item>
633
766
              <tag><c>c</c></tag>
634
767
              <item>
637
770
                  However, leading and trailing white-space characters
638
771
                  are not omitted as they are with <c>s</c>. All
639
772
                  characters are returned.</p>
 
773
                  <p>The Unicode translation modifier works as with <c>s</c>:</p>
 
774
<pre>
 
775
1> <input>io:fread("Prompt> ","~c").</input>
 
776
Prompt> <input>&lt;Character beyond latin1 range not printable in this medium&gt;</input>
 
777
{error,{fread,string}}
 
778
2> <input>io:fread("Prompt> ","~tc").</input>
 
779
Prompt> <input>&lt;Character beyond latin1 range not printable in this medium&gt;</input>
 
780
{ok,[[1091]]}</pre>
 
781
 
640
782
              </item>
641
783
              <tag><c>l</c></tag>
642
784
              <item>
857
999
    <p>There is always a process registered under the name of
858
1000
      <c>user</c>. This can be used for sending output to the user.</p>
859
1001
  </section>
 
1002
 <section>
 
1003
    <title>Standard Error</title>
 
1004
    <p>In certain situations, especially when the standard output is redirected, access to an io_server() specific for error messages might be conveninet. The io_device 'standard_error' can be used to direct output to whatever the current operating system considers a suitable device for error output. Example on a Unix-like operating system:</p>
 
1005
<pre>
 
1006
$ <input>erl -noshell -noinput -eval 'io:format(standard_error,"Error: ~s~n",["error 11"]),init:stop().' > /dev/null</input>
 
1007
Error: error 11</pre>
 
1008
 
 
1009
 
 
1010
 
 
1011
  </section>
860
1012
 
861
1013
  <section>
862
1014
    <title>Error Information</title>