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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/io_lib.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>
38
38
      flattening deep lists.</p>
39
39
  </description>
40
40
 
41
 
  <section>
42
 
    <title>DATA TYPES</title>
43
 
    <code type="none">
44
 
chars() = [char() | chars()]</code>
45
 
  </section>
 
41
  <datatypes>
 
42
    <datatype>
 
43
      <name name="chars"/>
 
44
    </datatype>
 
45
    <datatype>
 
46
      <name name="continuation"/>
 
47
      <desc><p>A continuation as returned by <seealso marker="#fread/3"><c>fread/3</c></seealso>.</p>
 
48
      </desc>
 
49
    </datatype>
 
50
    <datatype>
 
51
      <name name="depth"/>
 
52
    </datatype>
 
53
  </datatypes>
46
54
  <funcs>
47
55
    <func>
48
 
      <name>nl() -> chars()</name>
 
56
      <name name="nl" arity="0"/>
49
57
      <fsummary>Write a newline</fsummary>
50
58
      <desc>
51
59
        <p>Returns a character list which represents a new line
53
61
      </desc>
54
62
    </func>
55
63
    <func>
56
 
      <name>write(Term) -></name>
57
 
      <name>write(Term, Depth) -> chars()</name>
 
64
      <name name="write" arity="1"/>
 
65
      <name name="write" arity="2"/>
58
66
      <fsummary>Write a term</fsummary>
59
 
      <type>
60
 
        <v>Term = term()</v>
61
 
        <v>Depth = int()</v>
62
 
      </type>
63
67
      <desc>
64
 
        <p>Returns a character list which represents <c>Term</c>. The
65
 
          <c>Depth</c> (-1) argument controls the depth of the
 
68
        <p>Returns a character list which represents <c><anno>Term</anno></c>. The
 
69
          <c><anno>Depth</anno></c> (-1) argument controls the depth of the
66
70
          structures written. When the specified depth is reached,
67
71
          everything below this level is replaced by "...". For
68
72
          example:</p>
74
78
      </desc>
75
79
    </func>
76
80
    <func>
77
 
      <name>print(Term) -></name>
78
 
      <name>print(Term, Column, LineLength, Depth) -> chars()</name>
 
81
      <name name="print" arity="1"/>
 
82
      <name name="print" arity="4"/>
79
83
      <fsummary>Pretty print a term</fsummary>
80
 
      <type>
81
 
        <v>Term = term()</v>
82
 
        <v>Column = LineLenght = Depth = int()</v>
83
 
      </type>
84
84
      <desc>
85
85
        <p>Also returns a list of characters which represents
86
 
          <c>Term</c>, but breaks representations which are longer than
 
86
          <c><anno>Term</anno></c>, but breaks representations which are longer than
87
87
          one line into many lines and indents each line sensibly. It
88
88
          also tries to detect and output lists of printable characters 
89
 
          as strings. <c>Column</c> is the starting column (1),
90
 
          <c>LineLength</c> the maximum line length (80), and
91
 
          <c>Depth</c> (-1) the maximum print depth.</p>
 
89
          as strings. <c><anno>Column</anno></c> is the starting column (1),
 
90
          <c><anno>LineLength</anno></c> the maximum line length (80), and
 
91
          <c><anno>Depth</anno></c> (-1) the maximum print depth.</p>
92
92
      </desc>
93
93
    </func>
94
94
    <func>
95
 
      <name>fwrite(Format, Data) -></name>
96
 
      <name>format(Format, Data) -> chars() | UnicodeList</name>
 
95
      <name name="fwrite" arity="2"/>
 
96
      <name name="format" arity="2"/>
97
97
      <fsummary>Write formatted output</fsummary>
98
 
      <type>
99
 
        <v>Format = atom() | string() | binary()</v>
100
 
        <v>Data = [term()]</v>
101
 
        <v>UnicodeList = [Unicode]</v>
102
 
        <v>Unicode = int() representing valid unicode codepoint</v>
103
 
      </type>
104
98
      <desc>
105
 
        <p>Returns a character list which represents <c>Data</c>
106
 
          formatted in accordance with <c>Format</c>. See
 
99
        <p>Returns a character list which represents <c><anno>Data</anno></c>
 
100
          formatted in accordance with <c><anno>Format</anno></c>. See
107
101
          <seealso marker="io#fwrite/1">io:fwrite/1,2,3</seealso> for a detailed
108
102
          description of the available formatting options. A fault is
109
103
          generated if there is an error in the format string or
119
113
      </desc>
120
114
    </func>
121
115
    <func>
122
 
      <name>fread(Format, String) -> Result</name>
 
116
      <name name="fread" arity="2"/>
123
117
      <fsummary>Read formatted input</fsummary>
124
 
      <type>
125
 
        <v>Format = String = string()</v>
126
 
        <v>Result = {ok, InputList, LeftOverChars} | {more, RestFormat, Nchars, InputStack} | {error, What}</v>
127
 
        <v>&nbsp;InputList = chars()</v>
128
 
        <v>&nbsp;LeftOverChars = string()</v>
129
 
        <v>&nbsp;RestFormat = string()</v>
130
 
        <v>&nbsp;Nchars = int()</v>
131
 
        <v>&nbsp;InputStack = chars()</v>
132
 
        <v>&nbsp;What = term()</v>
133
 
      </type>
134
118
      <desc>
135
 
        <p>Tries to read <c>String</c> in accordance with the control
136
 
          sequences in <c>Format</c>. See
 
119
        <p>Tries to read <c><anno>String</anno></c> in accordance with the control
 
120
          sequences in <c><anno>Format</anno></c>. See
137
121
          <seealso marker="io#fread/3">io:fread/3</seealso> for a detailed
138
122
          description of the available formatting options. It is
139
 
          assumed that <c>String</c> contains whole lines. It returns:</p>
 
123
          assumed that <c><anno>String</anno></c> contains whole lines. It returns:</p>
140
124
        <taglist>
141
 
          <tag><c>{ok, InputList, LeftOverChars}</c></tag>
 
125
          <tag><c>{ok, <anno>InputList</anno>, <anno>LeftOverChars</anno>}</c></tag>
142
126
          <item>
143
 
            <p>The string was read. <c>InputList</c> is the list of
 
127
            <p>The string was read. <c><anno>InputList</anno></c> is the list of
144
128
              successfully matched and read items, and
145
 
              <c>LeftOverChars</c> are the input characters not used.</p>
 
129
              <c><anno>LeftOverChars</anno></c> are the input characters not used.</p>
146
130
          </item>
147
 
          <tag><c>{more, RestFormat, Nchars, InputStack}</c></tag>
 
131
          <tag><c>{more, <anno>RestFormat</anno>, <anno>Nchars</anno>, <anno>InputStack</anno>}</c></tag>
148
132
          <item>
149
133
            <p>The string was read, but more input is needed in order
150
 
              to complete the original format string. <c>RestFormat</c>
151
 
              is the remaining format string, <c>NChars</c> the number
152
 
              of characters scanned, and <c>InputStack</c> is the
 
134
              to complete the original format string. <c><anno>RestFormat</anno></c>
 
135
              is the remaining format string, <c><anno>Nchars</anno></c> the number
 
136
              of characters scanned, and <c><anno>InputStack</anno></c> is the
153
137
              reversed list of inputs matched up to that point.</p>
154
138
          </item>
155
 
          <tag><c>{error, What}</c></tag>
 
139
          <tag><c>{error, <anno>What</anno>}</c></tag>
156
140
          <item>
157
 
            <p>The read operation failed and the parameter <c>What</c>
 
141
            <p>The read operation failed and the parameter <c><anno>What</anno></c>
158
142
              gives a hint about the error.</p>
159
143
          </item>
160
144
        </taglist>
165
149
      </desc>
166
150
    </func>
167
151
    <func>
168
 
      <name>fread(Continuation, String, Format) -> Return</name>
 
152
      <name name="fread" arity="3"/>
169
153
      <fsummary>Re-entrant formatted reader</fsummary>
170
 
      <type>
171
 
        <v>Continuation = see below</v>
172
 
        <v>String = Format = string()</v>
173
 
        <v>Return = {done, Result, LeftOverChars} | {more, Continuation}</v>
174
 
        <v>&nbsp;Result = {ok, InputList} | eof | {error, What}</v>
175
 
        <v>&nbsp;&nbsp;InputList = chars()</v>
176
 
        <v>&nbsp;&nbsp;What = term()()</v>
177
 
        <v>&nbsp;LeftOverChars = string()</v>
178
 
      </type>
179
154
      <desc>
180
155
        <p>This is the re-entrant formatted reader. The continuation of
181
156
          the first call to the functions must be <c>[]</c>. Refer to
184
159
          re-entrant input scheme works.</p>
185
160
        <p>The function returns:</p>
186
161
        <taglist>
187
 
          <tag><c>{done, Result, LeftOverChars}</c></tag>
 
162
          <tag><c>{done, <anno>Result</anno>, <anno>LeftOverChars</anno>}</c></tag>
188
163
          <item>
189
164
            <p>The input is complete. The result is one of the
190
165
              following:</p>
191
166
            <taglist>
192
 
              <tag><c>{ok, InputList}</c></tag>
 
167
              <tag><c>{ok, <anno>InputList</anno>}</c></tag>
193
168
              <item>
194
 
                <p>The string was read. <c>InputList</c> is the list of
 
169
                <p>The string was read. <c><anno>InputList</anno></c> is the list of
195
170
                  successfully matched and read items, and
196
 
                  <c>LeftOverChars</c> are the remaining characters.</p>
 
171
                  <c><anno>LeftOverChars</anno></c> are the remaining characters.</p>
197
172
              </item>
198
173
              <tag><c>eof</c></tag>
199
174
              <item>
200
175
                <p>End of file has been encountered.
201
 
                  <c>LeftOverChars</c> are the input characters not
 
176
                  <c><anno>LeftOverChars</anno></c> are the input characters not
202
177
                  used.</p>
203
178
              </item>
204
 
              <tag><c>{error, What}</c></tag>
 
179
              <tag><c>{error, <anno>What</anno>}</c></tag>
205
180
              <item>
206
 
                <p>An error occurred and the parameter <c>What</c> gives
 
181
                <p>An error occurred and the parameter <c><anno>What</anno></c> gives
207
182
                  a hint about the error.</p>
208
183
              </item>
209
184
            </taglist>
210
185
          </item>
211
 
          <tag><c>{more, Continuation}</c></tag>
 
186
          <tag><c>{more, <anno>Continuation</anno>}</c></tag>
212
187
          <item>
213
188
            <p>More data is required to build a term.
214
 
              <c>Continuation</c> must be passed to <c>fread/3</c>,
 
189
              <c><anno>Continuation</anno></c> must be passed to <c>fread/3</c>,
215
190
              when more data becomes available.</p>
216
191
          </item>
217
192
        </taglist>
218
193
      </desc>
219
194
    </func>
220
195
    <func>
221
 
      <name>write_atom(Atom) -> chars()</name>
 
196
      <name name="write_atom" arity="1"/>
222
197
      <fsummary>Write an atom</fsummary>
223
 
      <type>
224
 
        <v>Atom = atom()</v>
225
 
      </type>
226
198
      <desc>
227
199
        <p>Returns the list of characters needed to print the atom
228
 
          <c>Atom</c>.</p>
 
200
          <c><anno>Atom</anno></c>.</p>
229
201
      </desc>
230
202
    </func>
231
203
    <func>
232
 
      <name>write_string(String) -> chars()</name>
 
204
      <name name="write_string" arity="1"/>
233
205
      <fsummary>Write a string</fsummary>
234
 
      <type>
235
 
        <v>String = string()</v>
236
 
      </type>
237
206
      <desc>
238
 
        <p>Returns the list of characters needed to print <c>String</c>
 
207
        <p>Returns the list of characters needed to print <c><anno>String</anno></c>
239
208
          as a string.</p>
240
209
      </desc>
241
210
    </func>
242
211
    <func>
243
 
      <name>write_char(Integer) -> chars()</name>
 
212
      <name name="write_char" arity="1"/>
244
213
      <fsummary>Write a character</fsummary>
245
 
      <type>
246
 
        <v>Integer = int()</v>
247
 
      </type>
248
214
      <desc>
249
215
        <p>Returns the list of characters needed to print a character
250
216
          constant in the ISO-latin-1 character set.</p>
251
217
      </desc>
252
218
    </func>
253
219
    <func>
254
 
      <name>indentation(String, StartIndent) -> int()</name>
 
220
      <name name="indentation" arity="2"/>
255
221
      <fsummary>Indentation after printing string</fsummary>
256
 
      <type>
257
 
        <v>String = string()</v>
258
 
        <v>StartIndent = int()</v>
259
 
      </type>
260
222
      <desc>
261
 
        <p>Returns the indentation if <c>String</c> has been printed,
262
 
          starting at <c>StartIndent</c>.</p>
 
223
        <p>Returns the indentation if <c><anno>String</anno></c> has been printed,
 
224
          starting at <c><anno>StartIndent</anno></c>.</p>
263
225
      </desc>
264
226
    </func>
265
227
    <func>
266
 
      <name>char_list(Term) -> bool()</name>
 
228
      <name name="char_list" arity="1"/>
267
229
      <fsummary>Test for a list of characters</fsummary>
268
 
      <type>
269
 
        <v>Term = term()</v>
270
 
      </type>
271
230
      <desc>
272
 
        <p>Returns <c>true</c> if <c>Term</c> is a flat list of
 
231
        <p>Returns <c>true</c> if <c><anno>Term</anno></c> is a flat list of
273
232
          characters in the ISO-latin-1 range, otherwise it returns <c>false</c>.</p>
274
233
      </desc>
275
234
    </func>
276
235
    <func>
277
 
      <name>deep_char_list(Term) -> bool()</name>
 
236
      <name name="deep_char_list" arity="1"/>
278
237
      <fsummary>Test for a deep list of characters</fsummary>
279
 
      <type>
280
 
        <v>Term = term()</v>
281
 
      </type>
282
238
      <desc>
283
 
        <p>Returns <c>true</c> if <c>Term</c> is a, possibly deep, list
 
239
        <p>Returns <c>true</c> if <c><anno>Term</anno></c> is a, possibly deep, list
284
240
          of characters in the ISO-latin-1 range, otherwise it returns <c>false</c>.</p>
285
241
      </desc>
286
242
    </func>
287
243
    <func>
288
 
      <name>printable_list(Term) -> bool()</name>
 
244
      <name name="printable_list" arity="1"/>
289
245
      <fsummary>Test for a list of printable ISO-latin-1 characters</fsummary>
290
 
      <type>
291
 
        <v>Term = term()</v>
292
 
      </type>
293
246
      <desc>
294
 
        <p>Returns <c>true</c> if <c>Term</c> is a flat list of
 
247
        <p>Returns <c>true</c> if <c><anno>Term</anno></c> is a flat list of
295
248
          printable ISO-latin-1 characters, otherwise it returns <c>false</c>.</p>
296
249
      </desc>
297
250
    </func>