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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/io_lib_fread.erl

  • 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:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(io_lib_fread).
19
20
 
26
27
%% fread(Continuation, CharList, FormatString)
27
28
%%  This is the main function into the re-entrant formatted reader. It
28
29
%%  repeatedly collects lines and calls fread/2 to format the input until
29
 
%%  all the format string has been used. 
 
30
%%  all the format string has been used. And it counts the characters.
30
31
 
31
32
fread([], Chars, Format) ->
32
 
    fread({[],Format,0,[]}, Chars, Format);
33
 
fread({Rest,RestFormat,N,Inputs}, MoreChars, _Format) ->
34
 
    %%io:format("FREAD: ~w `~s'~n", [{Rest,RestFormat,N,Inputs},MoreChars]),
35
 
    fread_collect(MoreChars, [], Rest, RestFormat, N, Inputs).
36
 
 
37
 
fread_collect([$\r|More], Stack, Rest, RestFormat, N, Inputs) ->
38
 
    fread(RestFormat, Rest ++ reverse(Stack), N, Inputs, More);
39
 
fread_collect([$\n|More], Stack, Rest, RestFormat, N, Inputs) ->
40
 
    fread(RestFormat, Rest ++ reverse(Stack), N, Inputs, More);
41
 
fread_collect([C|More], Stack, Rest, RestFormat, N, Inputs) ->
42
 
    fread_collect(More, [C|Stack], Rest, RestFormat, N, Inputs);
43
 
fread_collect([], Stack, Rest, RestFormat, N, Inputs) ->
44
 
    {more,{reverse(Stack, Rest),RestFormat,N,Inputs}};
45
 
fread_collect(eof, Stack, Rest, RestFormat, N, Inputs) ->
46
 
    fread(RestFormat, Rest ++ reverse(Stack), N, Inputs, eof).
47
 
 
48
 
fread(Format, Line, N0, Inputs0, More) ->
49
 
    %%io:format("FREAD1: `~s' `~s'~n", [Format,Line]),
50
 
    case fread(Format, Line, N0, Inputs0) of
51
 
        {ok,Input,Rest} ->
52
 
            {done,{ok,Input},case More of eof -> Rest; _ -> Rest ++ More end};
53
 
        {more,RestFormat,N,Inputs} ->
54
 
            case More of
55
 
                eof ->
56
 
                    fread(RestFormat,eof,N,Inputs,eof);
57
 
                _ ->
58
 
                    %% Don't forget to count the newline.
59
 
                    {more,{More,RestFormat,N+1,Inputs}}
60
 
            end;
 
33
    %%io:format("FREAD: ~w `~s'~n", [Format,Chars]),
 
34
    fread_collect(Format, [], 0, [], Chars);
 
35
fread({Format,Stack,N,Results}=_Continuation, Chars, _) ->
 
36
    %%io:format("FREAD: ~w `~s'~n", [_Continuation,Chars]),
 
37
    fread_collect(Format, Stack, N, Results, Chars).
 
38
 
 
39
fread_collect(Format, [$\r|Stack], N, Results, [$\n|Chars]) ->
 
40
    fread_line(Format, reverse(Stack), N, Results, Chars, [$\r,$\n]);
 
41
fread_collect(Format, Stack, N, Results, [$\n|Chars]) ->
 
42
    fread_line(Format, reverse(Stack), N, Results, Chars, [$\n]);
 
43
fread_collect(Format, Stack, N, Results, []) ->
 
44
    Continuation = {Format,Stack,N,Results},
 
45
    {more,Continuation};
 
46
fread_collect(Format, [$\r|Stack], N, Results, Chars) -> % Maybe eof
 
47
    fread_line(Format, reverse(Stack), N, Results, Chars, [$\r]);
 
48
fread_collect(Format, Stack, N, Results, [C|Chars]) ->
 
49
    fread_collect(Format, [C|Stack], N, Results, Chars);
 
50
fread_collect(Format, Stack, N, Results, Chars) -> % eof
 
51
    fread_line(Format, reverse(Stack), N, Results, Chars, []).
 
52
 
 
53
fread_line(Format0, Line, N0, Results0, More, Newline) ->
 
54
    %%io:format("FREAD1: `~s' `~s'~n", [Format0,Line]),
 
55
    Chars = if is_list(More) -> More; true -> [] end,
 
56
    case fread(Format0, Line, N0, Results0) of
 
57
        {ok,Results,[]} ->
 
58
            {done,{ok,Results},Chars};
 
59
        {ok,Results,Rest} ->
 
60
            %% Don't loose the whitespace
 
61
            {done,{ok,Results},Rest++(Newline++Chars)};
 
62
        %% fread/4 should not return {more,...} on eof; guard just in case...
 
63
        %% Count newline characters here since fread/4 does not get them.
 
64
        {more,Format,N,Results} when is_list(Line), is_list(More) ->
 
65
            fread_collect(Format, [], N+length(Newline), Results, More);
 
66
        {more,Format,N,Results} when is_list(Line) -> % eof
 
67
            fread_line(Format, eof, N+length(Newline), Results, More, []);
61
68
        Other ->                                %An error has occurred
62
69
            {done,Other,More}
63
70
    end.
64
71
 
 
72
 
65
73
%% Conventions
66
74
%%   ~s         String White terminated
67
75
%%   ~d         Integer terminated by ~[0-9]
78
86
    fread(Format, Line, 0, []).
79
87
 
80
88
fread([$~|Format0], Line, N, Results) ->
81
 
    {Format,F,Sup} = fread_field(Format0),
82
 
    fread1(Format, F, Sup, Line, N, Results, Format0);
 
89
    {Format,F,Sup,Unicode} = fread_field(Format0),
 
90
    fread1(Format, F, Sup, Unicode, Line, N, Results, Format0);
83
91
fread([$\s|Format], Line, N, Results) ->
84
92
    fread_skip_white(Format, Line, N, Results);
85
93
fread([$\t|Format], Line, N, Results) ->
111
119
%%
112
120
%%      {RestFormat,FieldWidth,Suppress}
113
121
 
114
 
fread_field([$*|Format]) -> fread_field(Format, true);
115
 
fread_field(Format) -> fread_field(Format, false).
116
 
 
117
 
fread_field([C|Format], Sup) when C >= $0, C =< $9 ->
118
 
    fread_field(Format, C - $0, Sup);
119
 
fread_field(Format, Sup) -> {Format,none,Sup}.
120
 
 
121
 
fread_field([C|Format], F, Sup) when C >= $0, C =< $9 ->
122
 
    fread_field(Format, 10*F + C - $0, Sup);
123
 
fread_field(Format, F, Sup) ->
124
 
    {Format,F,Sup}.
 
122
fread_field([$*|Format]) -> fread_field(Format, true, false);
 
123
fread_field(Format) -> fread_field(Format, false, false).
 
124
 
 
125
fread_field([C|Format], Sup, Unic) when C >= $0, C =< $9 ->
 
126
    fread_field(Format, C - $0, Sup, Unic);
 
127
fread_field([$t|Format], Sup, _Unic) -> 
 
128
    {Format,none,Sup,true};
 
129
fread_field(Format, Sup, Unic) -> 
 
130
    {Format,none,Sup,Unic}.
 
131
 
 
132
fread_field([C|Format], F, Sup, Unic) when C >= $0, C =< $9 ->
 
133
    fread_field(Format, 10*F + C - $0, Sup, Unic);
 
134
fread_field([$t|Format], F, Sup, _Unic) ->
 
135
    {Format,F,Sup,true};
 
136
fread_field(Format, F, Sup, Unic) ->
 
137
    {Format,F,Sup,Unic}.
125
138
 
126
139
%% fread1(Format, FieldWidth, Suppress, Line, N, Results, AllFormat)
127
140
%% fread1(Format, FieldWidth, Suppress, Line, N, Results)
128
141
%%  The main dispatch function for the formatting commands. Done in two
129
142
%%  stages so format commands that need no input can always be processed.
130
143
 
131
 
fread1([$l|Format], _F, Sup, Line, N, Res, _AllFormat) ->
 
144
fread1([$l|Format], _F, Sup, _U, Line, N, Res, _AllFormat) ->
132
145
    fread(Format, Line, N, fread_result(Sup, N, Res));
133
 
fread1(_Format, _F, _Sup, [], N, Res, AllFormat) ->
 
146
fread1(_Format, _F, _Sup, _U, [], N, Res, AllFormat) ->
134
147
    %% Need more input here.
135
148
    {more,[$~|AllFormat],N,Res};
136
 
fread1(_Format, _F, _Sup, eof, _N, [], _AllFormat) ->
 
149
fread1(_Format, _F, _Sup, _U, eof, _N, [], _AllFormat) ->
137
150
    %% This is at start of format string so no error.
138
151
    eof;
139
 
fread1(_Format, _F, _Sup, eof, _N, _Res, _AllFormat) ->
 
152
fread1(_Format, _F, _Sup, _U, eof, _N, _Res, _AllFormat) ->
140
153
    %% This is an error as there is no more input.
141
154
    fread_error(input);
142
 
fread1(Format, F, Sup, Line, N, Res, _AllFormat) ->
143
 
    fread1(Format, F, Sup, Line, N, Res).
 
155
fread1(Format, F, Sup, U, Line, N, Res, _AllFormat) ->
 
156
    fread1(Format, F, Sup, U, Line, N, Res).
144
157
 
145
 
fread1([$f|Format], none, Sup, Line0, N0, Res) ->
 
158
fread1([$f|Format], none, Sup, false, Line0, N0, Res) ->
146
159
    {Line,N,Cs} = fread_float_cs(Line0, N0),
147
160
    fread_float(Cs, Sup, Format, Line, N, Res);
148
 
fread1([$f|Format], F, Sup, Line0, N, Res) ->
149
 
    {Line,Cs} = fread_chars(Line0, F),
 
161
fread1([$f|Format], F, Sup, false, Line0, N, Res) ->
 
162
    {Line,Cs} = fread_chars(Line0, F, false),
150
163
    fread_float(Cs, Sup, Format, Line, N+F, Res);
151
 
fread1([$d|Format], none, Sup, Line0, N0, Res) ->
 
164
fread1([$d|Format], none, Sup, false, Line0, N0, Res) ->
152
165
    {Line,N,Cs} = fread_int_cs(Line0, N0),
153
166
    fread_integer(Cs, 10, Sup, Format, Line, N, Res);
154
 
fread1([$d|Format], F, Sup, Line0, N, Res) ->
155
 
    {Line,Cs} = fread_chars(Line0, F),
 
167
fread1([$d|Format], F, Sup, false, Line0, N, Res) ->
 
168
    {Line,Cs} = fread_chars(Line0, F, false),
156
169
    fread_integer(Cs, 10, Sup, Format, Line, N+F, Res);
157
 
fread1([$u|Format], none, Sup, Line0, N0, Res) ->
 
170
fread1([$u|Format], none, Sup, false, Line0, N0, Res) ->
158
171
    {Line,N,Cs} = fread_digits(Line0, N0, 10, []),
159
172
    fread_unsigned(Cs, 10, Sup, Format, Line, N, Res);
160
 
fread1([$u|Format], F, Sup, Line0, N0, Res) when F >= 2, F =< 1+$Z-$A+10 ->
 
173
fread1([$u|Format], F, Sup, false, Line0, N0, Res) when F >= 2, F =< 1+$Z-$A+10 ->
161
174
    {Line,N,Cs} = fread_digits(Line0, N0, F, []),
162
175
    fread_unsigned(Cs, F, Sup, Format, Line, N, Res);
163
 
fread1([$-|Format], _F, Sup, Line, N, Res) ->
 
176
fread1([$-|Format], _F, Sup, false, Line, N, Res) ->
164
177
    fread_sign_char(Sup, Format, Line, N, Res);
165
 
fread1([$#|Format], none, Sup, Line0, N0, Res) ->
 
178
fread1([$#|Format], none, Sup, false, Line0, N0, Res) ->
166
179
    case catch
167
180
        begin
168
181
            {Line1,N1,B1} = fread_base(Line0, N0),
176
189
        Other ->
177
190
            Other
178
191
    end;
179
 
fread1([$#|Format], F, Sup, Line0, N, Res) ->
 
192
fread1([$#|Format], F, Sup, false, Line0, N, Res) ->
180
193
    case catch
181
194
        begin
182
 
            {Line1,Cs1} = fread_chars(Line0, F),
 
195
            {Line1,Cs1} = fread_chars(Line0, F, false),
183
196
            {Line2,_,B2} = fread_base(reverse(Cs1), N),
184
197
            true = ((B2 >= 2) and (B2 =< 1+$Z-$A+10)),
185
198
            fread_based(Line2, B2, Sup, Format, Line1, N+F, Res)
189
202
        Other ->
190
203
            Other
191
204
    end;
192
 
fread1([$s|Format], none, Sup, Line0, N0, Res) ->
193
 
    {Line,N,Cs} = fread_string_cs(Line0, N0),
194
 
    fread_string(Cs, Sup, Format, Line, N, Res);
195
 
fread1([$s|Format], F, Sup, Line0, N, Res) ->
196
 
    {Line,Cs} = fread_chars(Line0, F),
197
 
    fread_string(Cs, Sup, Format, Line, N+F, Res);
198
 
fread1([$a|Format], none, Sup, Line0, N0, Res) ->
199
 
    {Line,N,Cs} = fread_string_cs(Line0, N0),
 
205
fread1([$s|Format], none, Sup, U, Line0, N0, Res) ->
 
206
    {Line,N,Cs} = fread_string_cs(Line0, N0, U),
 
207
    fread_string(Cs, Sup, U, Format, Line, N, Res);
 
208
fread1([$s|Format], F, Sup, U, Line0, N, Res) ->
 
209
    {Line,Cs} = fread_chars(Line0, F, U),
 
210
    fread_string(Cs, Sup, U, Format, Line, N+F, Res);
 
211
%% XXX:PaN Atoms still only latin1...
 
212
fread1([$a|Format], none, Sup, false, Line0, N0, Res) ->
 
213
    {Line,N,Cs} = fread_string_cs(Line0, N0, false),
200
214
    fread_atom(Cs, Sup, Format, Line, N, Res);
201
 
fread1([$a|Format], F, Sup, Line0, N, Res) ->
202
 
    {Line,Cs} = fread_chars(Line0, F),
 
215
fread1([$a|Format], F, Sup, false, Line0, N, Res) ->
 
216
    {Line,Cs} = fread_chars(Line0, F, false),
203
217
    fread_atom(Cs, Sup, Format, Line, N+F, Res);
204
 
fread1([$c|Format], none, Sup, Line0, N, Res) ->
205
 
    {Line,Cs} = fread_chars(Line0, 1),
206
 
    fread_chars(Cs, Sup, Format, Line, N+1, Res);
207
 
fread1([$c|Format], F, Sup, Line0, N, Res) ->
208
 
    {Line,Cs} = fread_chars(Line0, F),
209
 
    fread_chars(Cs, Sup, Format, Line, N+F, Res);
210
 
fread1([$~|Format], _F, _Sup, [$~|Line], N, Res) ->
 
218
fread1([$c|Format], none, Sup, U, Line0, N, Res) ->
 
219
    {Line,Cs} = fread_chars(Line0, 1, U),
 
220
    fread_chars(Cs, Sup, U, Format, Line, N+1, Res);
 
221
fread1([$c|Format], F, Sup, U, Line0, N, Res) ->
 
222
    {Line,Cs} = fread_chars(Line0, F, U),
 
223
    fread_chars(Cs, Sup, U, Format, Line, N+F, Res);
 
224
fread1([$~|Format], _F, _Sup, _U, [$~|Line], N, Res) ->
211
225
    fread(Format, Line, N+1, Res);
212
 
fread1(_Format, _F, _Sup, _Line, _N, _Res) ->
 
226
fread1(_Format, _F, _Sup, _U, _Line, _N, _Res) ->
213
227
    fread_error(format).
214
228
 
215
229
%% fread_float(FloatChars, Suppress, Format, Line, N, Results)
266
280
 
267
281
%% fread_string(StringChars, Suppress, Format, Line, N, Results)
268
282
 
269
 
fread_string(error, _Sup, _Format, _Line, _N, _Res) ->
 
283
fread_string(error, _Sup, _U, _Format, _Line, _N, _Res) ->
270
284
    fread_error(string);
271
 
fread_string(Cs0, Sup, Format, Line, N, Res) ->
 
285
fread_string(Cs0, Sup, U, Format, Line, N, Res) ->
272
286
    Cs = fread_skip_white(reverse(fread_skip_white(Cs0))),
273
 
    fread(Format, Line, N, fread_result(Sup, Cs, Res)).
 
287
    fread(Format, Line, N, fread_convert(fread_result(Sup, Cs, Res),U)).
274
288
 
275
289
%% fread_atom(AtomChars, Suppress, Format, Line, N, Results)
276
290
 
282
296
 
283
297
%% fread_chars(Characters, Suppress, Format, Line, N, Results)
284
298
 
285
 
fread_chars(error, _Sup, _Format, _Line, _N, _Res) ->
 
299
fread_chars(error, _Sup, _U, _Format, _Line, _N, _Res) ->
286
300
    fread_error(character);
287
 
fread_chars(Cs, Sup, Format, Line, N, Res) ->
288
 
    fread(Format, Line, N, fread_result(Sup, reverse(Cs), Res)).
 
301
fread_chars(Cs, Sup, U, Format, Line, N, Res) ->
 
302
    fread(Format, Line, N, fread_convert(fread_result(Sup, reverse(Cs), Res),U)).
289
303
 
290
304
%% fread_chars(Line, Count)
291
305
 
292
 
fread_chars(Line, C) ->
293
 
    fread_chars(C, Line, []).
 
306
fread_chars(Line, C, U) ->
 
307
    fread_chars(C, Line, U, []).
294
308
 
295
 
fread_chars(0, Line, Cs) -> {Line,Cs};
296
 
fread_chars(_N, [$\n|Line], _Cs) -> {[$\n|Line],error};
297
 
fread_chars(N, [C|Line], Cs) ->
298
 
    fread_chars(N-1, Line, [C|Cs]);
299
 
fread_chars(_N, [], _Cs) -> {[],error}.
 
309
fread_chars(0, Line, _U, Cs) -> {Line,Cs};
 
310
fread_chars(_N, [$\n|Line], _U, _Cs) -> {[$\n|Line],error};
 
311
fread_chars(N, [C|Line], true, Cs) ->
 
312
    fread_chars(N-1, Line, true, [C|Cs]);
 
313
fread_chars(N, [C|Line], false, Cs) when C >= 0, C =< 255 ->
 
314
    fread_chars(N-1, Line, false, [C|Cs]);
 
315
fread_chars(_N, L, _U, _Cs) ->
 
316
    {L,error}.
 
317
%%fread_chars(_N, [], _U,_Cs) -> 
 
318
%%    {[],error}.
300
319
 
301
320
%% fread_int_cs(Line, N)
302
321
 
329
348
fread_float_cs_2(Line, N, Cs) ->
330
349
    {Line,N,Cs}.
331
350
 
332
 
%% fread_string_cs(Line, N)
 
351
%% fread_string_cs(Line, N, Unicode)
333
352
 
334
 
fread_string_cs(Line0, N0) ->
 
353
fread_string_cs(Line0, N0, false) ->
 
354
    {Line,N} = fread_skip_white(Line0, N0),
 
355
    fread_skip_latin1_nonwhite(Line, N, []);
 
356
fread_string_cs(Line0, N0, true) ->
335
357
    {Line,N} = fread_skip_white(Line0, N0),
336
358
    fread_skip_nonwhite(Line, N, []).
337
359
 
353
375
    fread_skip_white(Line, N+1);
354
376
fread_skip_white([$\t|Line], N) ->
355
377
    fread_skip_white(Line, N+1);
 
378
fread_skip_white([$\r|Line], N) ->
 
379
    fread_skip_white(Line, N+1);
356
380
fread_skip_white([$\n|Line], N) ->
357
381
    fread_skip_white(Line, N+1);
358
382
fread_skip_white(Line, N) -> {Line,N}.
359
383
 
 
384
fread_skip_latin1_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs};
 
385
fread_skip_latin1_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs};
 
386
fread_skip_latin1_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs};
 
387
fread_skip_latin1_nonwhite([$\n|Line], N, Cs) -> {[$\n|Line],N,Cs};
 
388
fread_skip_latin1_nonwhite([C|Line], N, []) when C > 255 ->
 
389
    {[C|Line],N,error};
 
390
fread_skip_latin1_nonwhite([C|Line], N, Cs) when C > 255 ->
 
391
    {[C|Line],N,Cs};
 
392
fread_skip_latin1_nonwhite([C|Line], N, Cs) ->
 
393
    fread_skip_latin1_nonwhite(Line, N+1, [C|Cs]);
 
394
fread_skip_latin1_nonwhite([], N, Cs) -> {[],N,Cs}.
 
395
 
360
396
fread_skip_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs};
361
397
fread_skip_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs};
362
398
fread_skip_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs};
393
429
fread_result(true, _V, Res) -> Res;
394
430
fread_result(false, V, Res) -> [V|Res].
395
431
 
 
432
-ifdef(UNICODE_AS_BINARIES).
 
433
fread_convert([L|R],true) when is_list(L) ->
 
434
    [unicode:characters_to_binary(L) | R];
 
435
fread_convert(Any,_) ->
 
436
    Any.
 
437
-else.
 
438
fread_convert(Any,_) ->
 
439
    Any.
 
440
-endif.
396
441
fread_error(In) ->
397
442
    {error,{fread,In}}.