~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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
 
19
20
%% Erlang token scanning functions of io library.
21
22
%% For handling ISO 8859-1 (Latin-1) we use the following type
22
23
%% information:
23
24
%%
24
 
%% 000 - 037    NUL - US        control
25
 
%% 040 - 057    SPC - /         punctuation
26
 
%% 060 - 071    0 - 9           digit
27
 
%% 072 - 100    : - @           punctuation
28
 
%% 101 - 132    A - Z           uppercase
29
 
%% 133 - 140    [ - `           punctuation
30
 
%% 141 - 172    a - z           lowercase
31
 
%% 173 - 176    { - ~           punctuation
32
 
%% 177          DEL             control
33
 
%% 200 - 237                    control
34
 
%% 240 - 277    NBSP - �        punctuation
35
 
%% 300 - 326    � - �           uppercase
36
 
%% 327          �               punctuation
37
 
%% 330 - 336    � - �           uppercase
38
 
%% 337 - 366    � - �           lowercase
39
 
%% 367          �               punctuation
40
 
%% 370 - 377    � - �           lowercase
41
 
%%
42
 
%% Many punctuation characters region have special meaning.  Must
43
 
%% watch using � \327, bvery close to x \170
 
25
%% 000 - 037    NUL - US        control
 
26
%% 040 - 057    SPC - /         punctuation
 
27
%% 060 - 071    0 - 9           digit
 
28
%% 072 - 100    : - @           punctuation
 
29
%% 101 - 132    A - Z           uppercase
 
30
%% 133 - 140    [ - `           punctuation
 
31
%% 141 - 172    a - z           lowercase
 
32
%% 173 - 176    { - ~           punctuation
 
33
%% 177          DEL             control
 
34
%% 200 - 237                    control
 
35
%% 240 - 277    NBSP - �        punctuation
 
36
%% 300 - 326    � - �           uppercase
 
37
%% 327          �               punctuation
 
38
%% 330 - 336    � - �           uppercase
 
39
%% 337 - 366    � - �           lowercase
 
40
%% 367          �               punctuation
 
41
%% 370 - 377    � - �           lowercase
 
42
%%
 
43
%% Many punctuation characters have special meaning:
 
44
%%  $\s, $_, $", $$, $%, $', $.
 
45
%% DEL is a punctuation.
 
46
%%
 
47
%% Must watch using � \327, very close to x \170.
44
48
 
45
49
-module(erl_scan).
46
50
 
47
 
-export([string/1,string/2,tokens/3,format_error/1,reserved_word/1]).
48
 
 
49
 
-import(lists, [reverse/1]).
50
 
 
51
 
%% format_error(Error)
52
 
%%  Return a string describing the error.
53
 
 
 
51
%%% External exports 
 
52
 
 
53
-export([string/1,string/2,string/3,tokens/3,tokens/4,
 
54
         format_error/1,reserved_word/1,
 
55
         token_info/1,token_info/2,
 
56
         attributes_info/1,attributes_info/2,set_attribute/3]).
 
57
 
 
58
%%% Local record.
 
59
-record(erl_scan,
 
60
        {resword_fun=fun reserved_word/1,
 
61
         ws=false,
 
62
         comment=false,
 
63
         text=false}).
 
64
 
 
65
%%%
 
66
%%% Exported functions
 
67
%%%
 
68
 
 
69
-define(COLUMN(C), is_integer(C), C >= 1).
 
70
%% Line numbers less than zero have always been allowed:
 
71
-define(ALINE(L), is_integer(L)).
 
72
-define(STRING(S), is_list(S)).
 
73
-define(RESWORDFUN(F), is_function(F, 1)).
 
74
-define(SETATTRFUN(F), is_function(F, 1)).
 
75
 
 
76
-type category() :: atom().
 
77
-type column() :: pos_integer().
 
78
-type line() :: integer().
 
79
-type location() :: line() | {line(),column()}.
 
80
-type resword_fun() :: fun((atom()) -> bool()).
 
81
-type option() :: 'return' | 'return_white_spaces' | 'return_comments'
 
82
                | 'text' | {'reserved_word_fun', resword_fun()}.
 
83
-type options() :: option() | [option()].
 
84
-type symbol() :: atom() | float() | integer() | string().
 
85
-opaque attributes_data() :: list() | tuple().
 
86
%% The fact that {line(),column()} is a possible attributes() type
 
87
%% is hidden.
 
88
-type attributes() :: line() | attributes_data().
 
89
-type token() :: {category(), attributes(), symbol()}
 
90
               | {category(), attributes()}.
 
91
-type tokens() :: [token()].
 
92
-type error_description() :: term().
 
93
-type error_info() :: {location(), module(), error_description()}.
 
94
 
 
95
-spec format_error(Error :: term()) -> string().
54
96
format_error({string,Quote,Head}) ->
55
 
    ["unterminated " ++ string_thing(Quote) ++
56
 
     " starting with " ++ io_lib:write_string(Head,Quote)];
57
 
format_error({illegal,Type}) -> io_lib:fwrite("illegal ~w", [Type]);
 
97
    lists:flatten(["unterminated " ++ string_thing(Quote) ++
 
98
                   " starting with " ++ 
 
99
                   io_lib:write_unicode_string(Head, Quote)]);
 
100
format_error({illegal,Type}) -> 
 
101
    lists:flatten(io_lib:fwrite("illegal ~w", [Type]));
58
102
format_error(char) -> "unterminated character";
59
 
format_error(scan) -> "premature end";
60
 
format_error({base,Base}) -> io_lib:fwrite("illegal base '~w'", [Base]);
61
 
format_error(float) -> "bad float";
62
 
%%
63
 
format_error(Other) -> io_lib:write(Other).
 
103
format_error({base,Base}) -> 
 
104
    lists:flatten(io_lib:fwrite("illegal base '~w'", [Base]));
 
105
format_error(Other) -> 
 
106
    lists:flatten(io_lib:write(Other)).
 
107
 
 
108
-type string_return() :: {'ok', tokens(), location()} 
 
109
                       | {'error', error_info(), location()}.
 
110
 
 
111
-spec string(String :: string()) -> string_return().
 
112
string(String) ->
 
113
    string(String, 1, []).
 
114
 
 
115
-spec string(String :: string(), StartLocation :: location()) -> 
 
116
                   string_return().
 
117
string(String, StartLocation) ->
 
118
    string(String, StartLocation, []).
 
119
 
 
120
-spec string(String :: string(), StartLocation :: location(), 
 
121
             Options :: options()) -> string_return().
 
122
string(String, Line, Options) when ?STRING(String), ?ALINE(Line) ->
 
123
    string1(String, options(Options), Line, no_col, []);
 
124
string(String, {Line,Column}, Options) when ?STRING(String),
 
125
                                            ?ALINE(Line), 
 
126
                                            ?COLUMN(Column) ->
 
127
    string1(String, options(Options), Line, Column, []).
 
128
 
 
129
-type char_spec() :: string() | 'eof'.
 
130
-opaque return_cont() :: tuple().
 
131
-type cont() :: return_cont() | [].
 
132
-type tokens_result() :: {'ok', tokens(), location()}
 
133
                       | {'eof', location()}
 
134
                       | {'error', error_info(), location()}.
 
135
-type tokens_return() :: {'done', tokens_result(), char_spec()}
 
136
                       | {'more', return_cont()}.
 
137
 
 
138
-spec tokens(Cont :: cont(), CharSpec :: char_spec(), 
 
139
             StartLocation :: location()) -> tokens_return().
 
140
tokens(Cont, CharSpec, StartLocation) ->
 
141
    tokens(Cont, CharSpec, StartLocation, []).
 
142
 
 
143
-spec tokens(Cont :: cont(), CharSpec :: char_spec(), 
 
144
             StartLocation :: location(), Options :: options()) -> 
 
145
          tokens_return().
 
146
tokens([], CharSpec, Line, Options) when ?ALINE(Line) ->
 
147
    tokens1(CharSpec, options(Options), Line, no_col, [], fun scan/6, []);
 
148
tokens([], CharSpec, {Line,Column}, Options) when ?ALINE(Line),
 
149
                                                  ?COLUMN(Column) ->
 
150
    tokens1(CharSpec, options(Options), Line, Column, [], fun scan/6, []);
 
151
tokens({Cs,Col,Toks,Line,St,Any,Fun}, CharSpec, _Loc, _Opts) ->
 
152
    tokens1(Cs++CharSpec, St, Line, Col, Toks, Fun, Any).
 
153
 
 
154
-type attribute_item() :: 'column' | 'length' | 'line' 
 
155
                        | 'location' | 'text'.
 
156
-type info_line() :: integer() | term().
 
157
-type info_location() :: location() | term().
 
158
-type attribute_info() :: {'column', column()}| {'length', pos_integer()} 
 
159
                        | {'line', info_line()} 
 
160
                        | {'location', info_location()}
 
161
                        | {'text', string()}.
 
162
-type token_item() :: 'category' | 'symbol' | attribute_item().
 
163
-type token_info() :: {'category', category()} | {'symbol', symbol()} 
 
164
                    | attribute_info().
 
165
 
 
166
-spec token_info(token()) -> [token_info()].
 
167
token_info(Token) ->
 
168
    Items = [category,column,length,line,symbol,text], % undefined order
 
169
    token_info(Token, Items).
 
170
 
 
171
-spec token_info(token(), token_item()) -> token_info() | 'undefined';
 
172
                (token(), [token_item()]) -> [token_info()].
 
173
token_info(_Token, []) ->
 
174
    [];
 
175
token_info(Token, [Item|Items]) when is_atom(Item) ->
 
176
    case token_info(Token, Item) of
 
177
        undefined ->
 
178
            token_info(Token, Items);
 
179
        TokenInfo when is_tuple(TokenInfo) ->
 
180
            [TokenInfo|token_info(Token, Items)]
 
181
    end;
 
182
token_info({Category,_Attrs}, category=Item) ->
 
183
    {Item,Category};
 
184
token_info({Category,_Attrs,_Symbol}, category=Item) ->
 
185
    {Item,Category};
 
186
token_info({Category,_Attrs}, symbol=Item) ->
 
187
    {Item,Category};
 
188
token_info({_Category,_Attrs,Symbol}, symbol=Item) ->
 
189
    {Item,Symbol};
 
190
token_info({_Category,Attrs}, Item) ->
 
191
    attributes_info(Attrs, Item);
 
192
token_info({_Category,Attrs,_Symbol}, Item) ->
 
193
    attributes_info(Attrs, Item).
 
194
 
 
195
-spec attributes_info(attributes()) -> [attribute_info()].
 
196
attributes_info(Attributes) ->
 
197
    Items = [column,length,line,text], % undefined order
 
198
    attributes_info(Attributes, Items).
 
199
 
 
200
-spec attributes_info(attributes(), attribute_item()) ->
 
201
                        attribute_info() | 'undefined';
 
202
                     (attributes(), [attribute_item()]) -> [attribute_info()].
 
203
attributes_info(_Attrs, []) ->
 
204
    [];
 
205
attributes_info(Attrs, [A|As]) when is_atom(A) ->
 
206
    case attributes_info(Attrs, A) of
 
207
        undefined ->
 
208
            attributes_info(Attrs, As);
 
209
        AttributeInfo when is_tuple(AttributeInfo) ->
 
210
            [AttributeInfo|attributes_info(Attrs, As)]
 
211
    end;
 
212
attributes_info({Line,Column}, column=Item) when ?ALINE(Line), 
 
213
                                                 ?COLUMN(Column) ->
 
214
    {Item,Column};
 
215
attributes_info(Line, column) when ?ALINE(Line) ->
 
216
    undefined;
 
217
attributes_info(Attrs, column=Item) ->
 
218
    attr_info(Attrs, Item);
 
219
attributes_info(Attrs, length=Item) ->
 
220
    case attributes_info(Attrs, text) of
 
221
        undefined ->
 
222
            undefined;
 
223
        {text,Text} ->
 
224
            {Item,length(Text)}
 
225
    end;
 
226
attributes_info(Line, line=Item) when ?ALINE(Line) ->
 
227
    {Item,Line};
 
228
attributes_info({Line,Column}, line=Item) when ?ALINE(Line), 
 
229
                                               ?COLUMN(Column) ->
 
230
    {Item,Line};
 
231
attributes_info(Attrs, line=Item) ->
 
232
    attr_info(Attrs, Item);
 
233
attributes_info({Line,Column}=Location, location=Item) when ?ALINE(Line), 
 
234
                                                            ?COLUMN(Column) ->
 
235
    {Item,Location};
 
236
attributes_info(Line, location=Item) when ?ALINE(Line) ->
 
237
    {Item,Line};
 
238
attributes_info(Attrs, location=Item) ->
 
239
    {line,Line} = attributes_info(Attrs, line), % assume line is present
 
240
    case attributes_info(Attrs, column) of
 
241
        undefined ->
 
242
            %% If set_attribute() has assigned a term such as {17,42}
 
243
            %% to 'line', then Line will look like {Line,Column}. One
 
244
            %% should not use 'location' but 'line' and 'column' in
 
245
            %% such special cases.
 
246
            {Item,Line};
 
247
        {column,Column} ->
 
248
            {Item,{Line,Column}}
 
249
    end;
 
250
attributes_info({Line,Column}, text) when ?ALINE(Line), ?COLUMN(Column) ->
 
251
    undefined;
 
252
attributes_info(Line, text) when ?ALINE(Line) ->
 
253
    undefined;
 
254
attributes_info(Attrs, text=Item) ->
 
255
    attr_info(Attrs, Item);
 
256
attributes_info(T1, T2) ->
 
257
    erlang:error(badarg, [T1,T2]).
 
258
 
 
259
-type setlineattr_fun() :: fun((info_line()) -> info_line()).
 
260
 
 
261
-spec set_attribute('line', attributes(), setlineattr_fun()) -> attributes().
 
262
set_attribute(Tag, Attributes, Fun) when ?SETATTRFUN(Fun) ->
 
263
    set_attr(Tag, Attributes, Fun).
 
264
 
 
265
%%%
 
266
%%% Local functions
 
267
%%%
64
268
 
65
269
string_thing($') -> "atom";   %' Stupid Emacs
66
270
string_thing(_) -> "string".
67
271
 
68
 
 
69
 
%% string(CharList, StartPos)
70
 
%%  Takes a list of characters and tries to tokenise them.
71
 
%%
72
 
%%  Returns:
73
 
%%      {ok,[Tok]}
74
 
%%      {error,{ErrorPos,?MODULE,What},EndPos}
75
 
 
76
 
string(Cs) ->
77
 
    string(Cs, 1).
78
 
 
79
 
string(Cs, Pos) when is_list(Cs), is_integer(Pos) ->
80
 
%     %% Debug replacement line for chopping string into 1-char segments
81
 
%     scan([], [], [], Pos, Cs, []).
82
 
    scan(Cs, [], [], Pos, [], []).
83
 
 
84
 
%% tokens(Continuation, CharList, StartPos) ->
85
 
%%      {done, {ok, [Tok], EndPos}, Rest} |
86
 
%%      {done, {error,{ErrorPos,?MODULE,What}, EndPos}, Rest} |
87
 
%%      {more, Continuation'}
88
 
%%  This is the main function into the re-entrant scanner. 
89
 
%%
90
 
%%  The continuation has the form:
91
 
%%      {RestChars,ScanStateStack,ScannedTokens,
92
 
%%       CurrentPos,ContState,ErrorStack,ContFunArity5}
93
 
 
94
 
tokens([], Chars, Pos) ->
95
 
    tokens({[],[],[],Pos,io,[],fun scan/6}, Chars, Pos);
96
 
tokens({Cs,_Stack,_Toks,Pos,eof,_Fun}, eof, _) ->
97
 
    {done,{eof,Pos},Cs};
98
 
tokens({Cs,Stack,Toks,Pos,_State,Errors,Fun}, eof, _) ->
99
 
    Fun(Cs++eof, Stack, Toks, Pos, eof, Errors);
100
 
tokens({Cs,Stack,Toks,Pos,State,Errors,Fun}, Chars, _) ->
101
 
    Fun(Cs++Chars, Stack, Toks, Pos, State, Errors).
102
 
 
103
 
 
104
 
%% Scan loop.
105
 
%%
106
 
%% The scan_*/6 and sub_scan_*/6 functions does tail recursive calls 
107
 
%% between themselves to change state. State data is kept on the Stack. 
108
 
%% Results are passed on the Stack and on the stream (Cs). The variable 
109
 
%% State in this loop is not the scan loop state, but the state for 
110
 
%% instream handling by more/7 and done/5. The variable Stack is not
111
 
%% always a stack, it is just stacked state data for the scan loop, and
112
 
%% the variable Errors is a reversed list of scan error {Error,Pos} tuples.
113
 
%%
114
 
%% All the scan_*/6 functions have the same arguments (in the same order), 
115
 
%% to keep the tail recursive calls (jumps) fast.
116
 
%%
117
 
%% When more data is needed from the stream, the tail recursion loop is
118
 
%% broken by calling more/7 that either returns to the I/O-server to 
119
 
%% get more data or fetches it from a string, or by calling done/5 when
120
 
%% scanning is done.
121
 
%%
122
 
%% The last argument to more/7 is a fun to jump back to with more data 
123
 
%% to continue scanning where it was interrupted.
124
 
%%
125
 
%% more/7 and done/5 handles scanning from I/O-server (Stream) or from String.
126
 
%%
127
 
 
128
 
%% String
129
 
more(Cs, Stack, Toks, Pos, eos, Errors, Fun) ->
130
 
    erlang:error(badstate, [Cs,Stack,Toks,Pos,eos,Errors,Fun]);
131
 
% %% Debug clause for chopping string into 1-char segments
132
 
% more(Cs, Stack, Toks, Pos, [H|T], Errors, Fun) ->
133
 
%     Fun(Cs++[H], Stack, Toks, Pos, T, Errors);
134
 
more(Cs, Stack, Toks, Pos, [], Errors, Fun) ->
135
 
    Fun(Cs++eof, Stack, Toks, Pos, eos, Errors);
136
 
%% Stream
137
 
more(Cs, Stack, Toks, Pos, eof, Errors, Fun) ->
138
 
    erlang:error(badstate, [Cs,Stack,Toks,Pos,eof,Errors,Fun]);
139
 
more(Cs, Stack, Toks, Pos, io, Errors,Fun) ->
140
 
    {more,{Cs,Stack,Toks,Pos,io,Errors,Fun}}.
141
 
 
142
 
%% String
143
 
done(eof, [], Toks, Pos, eos) ->
144
 
    {ok,reverse(Toks),Pos};
145
 
done(eof, Errors, _Toks, Pos, eos) ->
146
 
    {Error,ErrorPos} = lists:last(Errors),
147
 
    {error,{ErrorPos,?MODULE,Error},Pos};
148
 
done(Cs, Errors, Toks, Pos, eos) ->
149
 
    scan(Cs, [], Toks, Pos, eos, Errors);
150
 
% %% Debug clause for chopping string into 1-char segments
151
 
% done(Cs, Errors, Toks, Pos, [H|T]) ->
152
 
%    scan(Cs++[H], [], Toks, Pos, T, Errors);
153
 
done(Cs, Errors, Toks, Pos, []) ->
154
 
    scan(Cs++eof, [], Toks, Pos, eos, Errors);
155
 
%% Stream
156
 
done(Cs, [], [{dot,_}|_]=Toks, Pos, io) ->
157
 
    {done,{ok,reverse(Toks),Pos},Cs};
158
 
done(Cs, [], [_|_], Pos, io) ->
159
 
    {done,{error,{Pos,?MODULE,scan},Pos},Cs};
160
 
done(Cs, [], [], Pos, eof) ->
161
 
    {done,{eof,Pos},Cs};
162
 
done(Cs, [], [{dot,_}|_]=Toks, Pos, eof) ->
163
 
    {done,{ok,reverse(Toks),Pos},Cs};
164
 
done(Cs, [], _Toks, Pos, eof) ->
165
 
    {done,{error,{Pos,?MODULE,scan},Pos},Cs};
166
 
done(Cs, Errors, _Toks, Pos, io) ->
167
 
    {Error,ErrorPos} = lists:last(Errors),
168
 
    {done,{error,{ErrorPos,?MODULE,Error},Pos},Cs};
169
 
done(Cs, Errors, _Toks, Pos, eof) ->
170
 
    {Error,ErrorPos} = lists:last(Errors),
171
 
    {done,{error,{ErrorPos,?MODULE,Error},Pos},Cs}.
172
 
 
173
 
 
174
 
%% The actual scan loop
175
 
%% Stack is assumed to be [].
176
 
 
177
 
scan([$\n|Cs], Stack, Toks, Pos, State, Errors) ->      % Newline - skip
178
 
    scan(Cs, Stack, Toks, Pos+1, State, Errors);
179
 
scan([C|Cs], Stack, Toks, Pos, State, Errors) 
180
 
  when C >= $\000, C =< $\s ->                          % Control chars - skip
181
 
    scan(Cs, Stack, Toks, Pos, State, Errors);
182
 
scan([C|Cs], Stack, Toks, Pos, State, Errors) 
183
 
  when C >= $\200, C =< $\240 ->                        % Control chars -skip
184
 
    scan(Cs, Stack, Toks, Pos, State, Errors);
185
 
scan([C|Cs], _Stack, Toks, Pos, State, Errors) 
186
 
  when C >= $a, C =< $z ->                              % Atoms
187
 
    sub_scan_name(Cs, [C,fun scan_atom/6], Toks, Pos, State, Errors);
188
 
scan([C|Cs], _Stack, Toks, Pos, State, Errors) 
189
 
  when C >= $�, C =< $�, C =/= $� ->                     % Atoms
190
 
    sub_scan_name(Cs, [C,fun scan_atom/6], Toks, Pos, State, Errors);
191
 
scan([C|Cs], _Stack, Toks, Pos, State, Errors) 
192
 
  when C >= $A, C =< $Z ->                              % Variables
193
 
    sub_scan_name(Cs, [C,fun scan_variable/6], Toks, Pos, State, Errors);
194
 
scan([C|Cs], _Stack, Toks, Pos, State, Errors) 
195
 
  when C >= $�, C =< $�, C =/= $� ->                     % Variables
196
 
    sub_scan_name(Cs, [C,fun scan_variable/6], Toks, Pos, State, Errors);
197
 
scan([$_|Cs], _Stack, Toks, Pos, State, Errors) ->      % _Variables
198
 
    sub_scan_name(Cs, [$_,fun scan_variable/6], Toks, Pos, State, Errors);
199
 
scan([C|Cs], _Stack, Toks, Pos, State, Errors)
200
 
    when C >= $0, C =< $9 ->                            % Numbers
201
 
    scan_number(Cs, [C], Toks, Pos, State, Errors);
202
 
scan([$$|Cs], Stack, Toks, Pos, State, Errors) ->       % Character constant
203
 
    scan_char(Cs, Stack, Toks, Pos, State, Errors);
204
 
scan([$'|Cs], _Stack, Toks, Pos, State, Errors) ->      % Quoted atom
205
 
    scan_qatom(Cs, [$',Pos], Toks, Pos, State, Errors);
206
 
scan([$"|Cs], _Stack, Toks, Pos, State, Errors) ->      % String
207
 
    scan_string(Cs, [$",Pos], Toks, Pos, State, Errors);
208
 
scan([$%|Cs], Stack, Toks, Pos, State, Errors) ->       % Comment
209
 
    scan_comment(Cs, Stack, Toks, Pos, State, Errors);
 
272
-define(WHITE_SPACE(C),
 
273
        is_integer(C) andalso
 
274
         (C >= $\000 andalso C =< $\s orelse C >= $\200 andalso C =< $\240)).
 
275
-define(DIGIT(C), C >= $0, C =< $9).
 
276
-define(CHAR(C), is_integer(C), C >= 0).
 
277
 
 
278
-define(STR(Col, S), if Col =:= no_col -> []; true -> S end).
 
279
 
 
280
%% A workaround: Unicode strings are not returned as strings, but as
 
281
%% lists of integers. For instance, "b\x{aaa}c" => [98,2730,99]. This
 
282
%% is to protect the system from character codes greater than 255. To
 
283
%% be removed. Search for UNI to find workaround code.
 
284
-define(NO_UNICODE, 0).
 
285
-define(UNI255(C), (C) =< 16#ff).
 
286
 
 
287
options(Opts0) when is_list(Opts0) ->
 
288
    Opts = lists:foldr(fun expand_opt/2, [], Opts0),
 
289
    [RW_fun] = 
 
290
        case opts(Opts, [reserved_word_fun], []) of
 
291
            badarg ->
 
292
                erlang:error(badarg, [Opts0]);
 
293
            R -> 
 
294
                R
 
295
        end,
 
296
    Comment = proplists:get_bool(return_comments, Opts),
 
297
    WS = proplists:get_bool(return_white_spaces, Opts),
 
298
    Txt = proplists:get_bool(text, Opts),
 
299
    #erl_scan{resword_fun = RW_fun,
 
300
              comment     = Comment,
 
301
              ws          = WS,
 
302
              text        = Txt};
 
303
options(Opt) ->
 
304
    options([Opt]).
 
305
 
 
306
opts(Options, [Key|Keys], L) ->
 
307
    V = case lists:keysearch(Key, 1, Options) of
 
308
            {value,{reserved_word_fun,F}} when ?RESWORDFUN(F) ->
 
309
                {ok,F};
 
310
            {value,{Key,_}} ->
 
311
                badarg;
 
312
            false ->
 
313
                {ok,default_option(Key)}
 
314
        end,
 
315
    case V of
 
316
        badarg ->
 
317
            badarg;
 
318
        {ok,Value} ->
 
319
            opts(Options, Keys, [Value|L])
 
320
    end;
 
321
opts(_Options, [], L) ->
 
322
    lists:reverse(L).
 
323
 
 
324
default_option(reserved_word_fun) ->
 
325
    fun reserved_word/1.
 
326
 
 
327
expand_opt(return, Os) ->
 
328
    [return_comments,return_white_spaces|Os];
 
329
expand_opt(O, Os) ->
 
330
    [O|Os].
 
331
 
 
332
attr_info(Attrs, Item) ->
 
333
    case catch lists:keysearch(Item, 1, Attrs) of
 
334
        {value,{Item,Value}} ->
 
335
            {Item,Value};
 
336
        false -> 
 
337
            undefined;
 
338
        _ ->
 
339
            erlang:error(badarg, [Attrs, Item])
 
340
    end.
 
341
 
 
342
set_attr(line, Line, Fun) when ?ALINE(Line) ->
 
343
    Ln = Fun(Line),
 
344
    if
 
345
        ?ALINE(Ln) ->
 
346
            Ln;
 
347
        true ->
 
348
            [{line,Ln}]
 
349
    end;
 
350
set_attr(line, {Line,Column}, Fun) when ?ALINE(Line), ?COLUMN(Column) ->
 
351
    Ln = Fun(Line),
 
352
    if
 
353
        ?ALINE(Ln) ->
 
354
            {Ln,Column};
 
355
        true ->
 
356
            [{line,Ln},{column,Column}]
 
357
    end;
 
358
set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) ->
 
359
    {line,Line} = lists:keyfind(Tag, 1, Attrs),
 
360
    lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)});
 
361
set_attr(T1, T2, T3) ->
 
362
    erlang:error(badarg, [T1,T2,T3]).
 
363
 
 
364
tokens1(Cs, St, Line, Col, Toks, Fun, Any) when ?STRING(Cs); Cs =:= eof ->
 
365
    case Fun(Cs, St, Line, Col, Toks, Any) of
 
366
        {more,{Cs0,Ncol,Ntoks,Nline,Nany,Nfun}} ->
 
367
            {more,{Cs0,Ncol,Ntoks,Nline,St,Nany,Nfun}};
 
368
        {ok,Toks0,eof,Nline,Ncol} ->
 
369
            Res = case Toks0 of
 
370
                      [] ->
 
371
                          {eof,location(Nline, Ncol)};
 
372
                      _ ->
 
373
                          {ok,lists:reverse(Toks0),location(Nline,Ncol)}
 
374
                  end,
 
375
            {done,Res,eof};
 
376
        {ok,Toks0,Rest,Nline,Ncol} ->
 
377
            {done,{ok,lists:reverse(Toks0),location(Nline, Ncol)},Rest};
 
378
        {error,_,_}=Error ->
 
379
            {done,Error,[]}
 
380
    end.
 
381
 
 
382
string1(Cs, St, Line, Col, Toks) ->
 
383
    case scan1(Cs, St, Line, Col, Toks) of
 
384
        {more,{Cs0,Ncol,Ntoks,Nline,Any,Fun}} ->
 
385
            case Fun(Cs0++eof, St, Nline, Ncol, Ntoks, Any) of
 
386
                {ok,Toks1,_Rest,Line2,Col2} ->
 
387
                    {ok,lists:reverse(Toks1),location(Line2, Col2)};
 
388
                {error,_,_}=Error ->
 
389
                    Error
 
390
            end;
 
391
        {ok,Ntoks,[_|_]=Rest,Nline,Ncol} ->
 
392
            string1(Rest, St, Nline, Ncol, Ntoks);
 
393
        {ok,Ntoks,_,Nline,Ncol} ->
 
394
            {ok,lists:reverse(Ntoks),location(Nline, Ncol)};
 
395
        {error,_,_}=Error ->
 
396
            Error
 
397
    end.
 
398
 
 
399
scan(Cs, St, Line, Col, Toks, _) ->
 
400
    scan1(Cs, St, Line, Col, Toks).
 
401
 
 
402
scan1([$\s|Cs], St, Line, Col, Toks) when St#erl_scan.ws ->
 
403
    scan_spcs(Cs, St, Line, Col, Toks, 1);
 
404
scan1([$\s|Cs], St, Line, Col, Toks) ->
 
405
    skip_white_space(Cs, St, Line, Col, Toks, 1);
 
406
scan1([$\n|Cs], St, Line, Col, Toks) when St#erl_scan.ws ->
 
407
    scan_newline(Cs, St, Line, Col, Toks);
 
408
scan1([$\n|Cs], St, Line, Col, Toks) ->
 
409
    skip_white_space(Cs, St, Line+1, new_column(Col, 1), Toks, 0);
 
410
scan1([C|Cs], St, Line, Col, Toks) when C >= $A, C =< $Z ->
 
411
    scan_variable(Cs, St, Line, Col, Toks, [C]);
 
412
scan1([C|Cs], St, Line, Col, Toks) when C >= $a, C =< $z ->
 
413
    scan_atom(Cs, St, Line, Col, Toks, [C]);
 
414
%% Optimization: some very common punctuation characters:
 
415
scan1([$,|Cs], St, Line, Col, Toks) ->
 
416
    tok2(Cs, St, Line, Col, Toks, ",", ',', 1);
 
417
scan1([$(|Cs], St, Line, Col, Toks) ->
 
418
    tok2(Cs, St, Line, Col, Toks, "(", '(', 1);
 
419
scan1([$)|Cs], St, Line, Col, Toks) ->
 
420
    tok2(Cs, St, Line, Col, Toks, ")", ')', 1);
 
421
scan1([${|Cs], St, Line, Col, Toks) ->
 
422
    tok2(Cs, St, Line, Col, Toks, "{", '{', 1);
 
423
scan1([$}|Cs], St, Line, Col, Toks) ->
 
424
    tok2(Cs, St, Line, Col, Toks, "}", '}', 1);
 
425
scan1([$[|Cs], St, Line, Col, Toks) ->
 
426
    tok2(Cs, St, Line, Col, Toks, "[", '[', 1);
 
427
scan1([$]|Cs], St, Line, Col, Toks) ->
 
428
    tok2(Cs, St, Line, Col, Toks, "]", ']', 1);
 
429
scan1([$;|Cs], St, Line, Col, Toks) ->
 
430
    tok2(Cs, St, Line, Col, Toks, ";", ';', 1);
 
431
scan1([$_=C|Cs], St, Line, Col, Toks) ->
 
432
    scan_variable(Cs, St, Line, Col, Toks, [C]);
 
433
%% More punctuation characters below.
 
434
scan1([$\%|Cs], St, Line, Col, Toks) when not St#erl_scan.comment ->
 
435
    skip_comment(Cs, St, Line, Col, Toks, 1);
 
436
scan1([$\%=C|Cs], St, Line, Col, Toks) ->
 
437
    scan_comment(Cs, St, Line, Col, Toks, [C]);
 
438
scan1([C|Cs], St, Line, Col, Toks) when ?DIGIT(C) ->
 
439
    scan_number(Cs, St, Line, Col, Toks, [C]);
 
440
scan1([$.=C|Cs], St, Line, Col, Toks) ->
 
441
    scan_dot(Cs, St, Line, Col, Toks, [C]);
 
442
scan1([$"|Cs], St, Line, Col, Toks) -> %" Emacs
 
443
    State0 = {[],[],Line,Col,?NO_UNICODE},
 
444
    scan_string(Cs, St, Line, incr_column(Col, 1), Toks, State0);
 
445
scan1([$'|Cs], St, Line, Col, Toks) -> %' Emacs
 
446
    State0 = {[],[],Line,Col,?NO_UNICODE},
 
447
    scan_qatom(Cs, St, Line, incr_column(Col, 1), Toks, State0);
 
448
scan1([$$|Cs], St, Line, Col, Toks) ->
 
449
    scan_char(Cs, St, Line, Col, Toks);
 
450
scan1([$\r|Cs], St, Line, Col, Toks) when St#erl_scan.ws ->
 
451
    white_space_end(Cs, St, Line, Col, Toks, 1, "\r");
 
452
scan1([C|Cs], St, Line, Col, Toks) when C >= $�, C =< $�, C =/= $� ->
 
453
    scan_atom(Cs, St, Line, Col, Toks, [C]);
 
454
scan1([C|Cs], St, Line, Col, Toks) when C >= $�, C =< $�, C /= $� ->
 
455
    scan_variable(Cs, St, Line, Col, Toks, [C]);
 
456
scan1([$\t|Cs], St, Line, Col, Toks) when St#erl_scan.ws ->
 
457
    scan_tabs(Cs, St, Line, Col, Toks, 1);
 
458
scan1([$\t|Cs], St, Line, Col, Toks) ->
 
459
    skip_white_space(Cs, St, Line, Col, Toks, 1);
 
460
scan1([C|Cs], St, Line, Col, Toks) when ?WHITE_SPACE(C) ->
 
461
    case St#erl_scan.ws of
 
462
        true ->
 
463
            scan_white_space(Cs, St, Line, Col, Toks, [C]);
 
464
        false ->
 
465
            skip_white_space(Cs, St, Line, Col, Toks, 1)
 
466
    end;
210
467
%% Punctuation characters and operators, first recognise multiples.
211
 
%% Clauses are rouped by first character (a short with the same head has
212
 
%% to come after a longer).
213
 
%%
214
468
%% << <- <=
215
 
scan("<<"++Cs, Stack, Toks, Pos, State, Errors) ->
216
 
    scan(Cs, Stack, [{'<<',Pos}|Toks], Pos, State, Errors);
217
 
scan("<-"++Cs, Stack, Toks, Pos, State, Errors) ->
218
 
    scan(Cs, Stack, [{'<-',Pos}|Toks], Pos, State, Errors);
219
 
scan("<="++Cs, Stack, Toks, Pos, State, Errors) ->
220
 
    scan(Cs, Stack, [{'<=',Pos}|Toks], Pos, State, Errors);
221
 
scan("<"=Cs, Stack, Toks, Pos, State, Errors) ->
222
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
469
scan1("<<"++Cs, St, Line, Col, Toks) ->
 
470
    tok2(Cs, St, Line, Col, Toks, "<<", '<<', 2);
 
471
scan1("<-"++Cs, St, Line, Col, Toks) ->
 
472
    tok2(Cs, St, Line, Col, Toks, "<-", '<-', 2);
 
473
scan1("<="++Cs, St, Line, Col, Toks) ->
 
474
    tok2(Cs, St, Line, Col, Toks, "<=", '<=', 2);
 
475
scan1("<"=Cs, _St, Line, Col, Toks) ->
 
476
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
223
477
%% >> >=
224
 
scan(">>"++Cs, Stack, Toks, Pos, State, Errors) ->
225
 
    scan(Cs, Stack, [{'>>',Pos}|Toks], Pos, State, Errors);
226
 
scan(">="++Cs, Stack, Toks, Pos, State, Errors) ->
227
 
    scan(Cs, Stack, [{'>=',Pos}|Toks], Pos, State, Errors);
228
 
scan(">"=Cs, Stack, Toks, Pos, State, Errors) ->
229
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
478
scan1(">>"++Cs, St, Line, Col, Toks) ->
 
479
    tok2(Cs, St, Line, Col, Toks, ">>", '>>', 2);
 
480
scan1(">="++Cs, St, Line, Col, Toks) ->
 
481
    tok2(Cs, St, Line, Col, Toks, ">=", '>=', 2);
 
482
scan1(">"=Cs, _St, Line, Col, Toks) ->
 
483
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
230
484
%% -> --
231
 
scan("->"++Cs, Stack, Toks, Pos, State, Errors) ->
232
 
    scan(Cs, Stack, [{'->',Pos}|Toks], Pos, State, Errors);
233
 
scan("--"++Cs, Stack, Toks, Pos, State, Errors) ->
234
 
    scan(Cs, Stack, [{'--',Pos}|Toks], Pos, State, Errors);
235
 
scan("-"=Cs, Stack, Toks, Pos, State, Errors) ->
236
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
485
scan1("->"++Cs, St, Line, Col, Toks) ->
 
486
    tok2(Cs, St, Line, Col, Toks, "->", '->', 2);
 
487
scan1("--"++Cs, St, Line, Col, Toks) ->
 
488
    tok2(Cs, St, Line, Col, Toks, "--", '--', 2);
 
489
scan1("-"=Cs, _St, Line, Col, Toks) ->
 
490
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
237
491
%% ++
238
 
scan("++"++Cs, Stack, Toks, Pos, State, Errors) ->
239
 
    scan(Cs, Stack, [{'++',Pos}|Toks], Pos, State, Errors);
240
 
scan("+"=Cs, Stack, Toks, Pos, State, Errors) ->
241
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
492
scan1("++"++Cs, St, Line, Col, Toks) ->
 
493
    tok2(Cs, St, Line, Col, Toks, "++", '++', 2);
 
494
scan1("+"=Cs, _St, Line, Col, Toks) ->
 
495
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
242
496
%% =:= =/= =< ==
243
 
scan("=:="++Cs, Stack, Toks, Pos, State, Errors) ->
244
 
    scan(Cs, Stack, [{'=:=',Pos}|Toks], Pos, State, Errors);
245
 
scan("=:"=Cs, Stack, Toks, Pos, State, Errors) ->
246
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
247
 
scan("=/="++Cs, Stack, Toks, Pos, State, Errors) ->
248
 
    scan(Cs, Stack, [{'=/=',Pos}|Toks], Pos, State, Errors);
249
 
scan("=/"=Cs, Stack, Toks, Pos, State, Errors) ->
250
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
251
 
scan("=<"++Cs, Stack, Toks, Pos, State, Errors) ->
252
 
    scan(Cs, Stack, [{'=<',Pos}|Toks], Pos, State, Errors);
253
 
scan("=="++Cs, Stack, Toks, Pos, State, Errors) ->
254
 
    scan(Cs, Stack, [{'==',Pos}|Toks], Pos, State, Errors);
255
 
scan("="=Cs, Stack, Toks, Pos, State, Errors) ->
256
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
497
scan1("=:="++Cs, St, Line, Col, Toks) ->
 
498
    tok2(Cs, St, Line, Col, Toks, "=:=", '=:=', 3);
 
499
scan1("=:"=Cs, _St, Line, Col, Toks) ->
 
500
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
 
501
scan1("=/="++Cs, St, Line, Col, Toks) ->
 
502
    tok2(Cs, St, Line, Col, Toks, "=/=", '=/=', 3);
 
503
scan1("=/"=Cs, _St, Line, Col, Toks) ->
 
504
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
 
505
scan1("=<"++Cs, St, Line, Col, Toks) ->
 
506
    tok2(Cs, St, Line, Col, Toks, "=<", '=<', 2);
 
507
scan1("=="++Cs, St, Line, Col, Toks) ->
 
508
    tok2(Cs, St, Line, Col, Toks, "==", '==', 2);
 
509
scan1("="=Cs, _St, Line, Col, Toks) ->
 
510
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
257
511
%% /=
258
 
scan("/="++Cs, Stack, Toks, Pos, State, Errors) ->
259
 
    scan(Cs, Stack, [{'/=',Pos}|Toks], Pos, State, Errors);
260
 
scan("/"=Cs, Stack, Toks, Pos, State, Errors) ->
261
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
512
scan1("/="++Cs, St, Line, Col, Toks) ->
 
513
    tok2(Cs, St, Line, Col, Toks, "/=", '/=', 2);
 
514
scan1("/"=Cs, _St, Line, Col, Toks) ->
 
515
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
262
516
%% ||
263
 
scan("||"++Cs, Stack, Toks, Pos, State, Errors) ->
264
 
    scan(Cs, Stack, [{'||',Pos}|Toks], Pos, State, Errors);
265
 
scan("|"=Cs, Stack, Toks, Pos, State, Errors) ->
266
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
 
517
scan1("||"++Cs, St, Line, Col, Toks) ->
 
518
    tok2(Cs, St, Line, Col, Toks, "||", '||', 2);
 
519
scan1("|"=Cs, _St, Line, Col, Toks) ->
 
520
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
267
521
%% :-
268
 
scan(":-"++Cs, Stack, Toks, Pos, State, Errors) ->
269
 
    scan(Cs, Stack, [{':-',Pos}|Toks], Pos, State, Errors);
 
522
scan1(":-"++Cs, St, Line, Col, Toks) ->
 
523
    tok2(Cs, St, Line, Col, Toks, ":-", ':-', 2);
270
524
%% :: for typed records
271
 
scan("::"++Cs, Stack, Toks, Pos, State, Errors) ->
272
 
    scan(Cs, Stack, [{'::',Pos}|Toks], Pos, State, Errors);
273
 
%%
274
 
scan(":"=Cs, Stack, Toks, Pos, State, Errors) ->
275
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan/6);
276
 
%% Full stop and plain '.'
277
 
scan("."++Cs, Stack, Toks, Pos, State, Errors) ->
278
 
    scan_dot(Cs, Stack, Toks, Pos, State, Errors);
279
 
%% All single-char punctuation characters and operators (except '.')
280
 
scan([C|Cs], Stack, Toks, Pos, State, Errors) ->
281
 
    scan(Cs, Stack, [{list_to_atom([C]),Pos}|Toks], Pos, State, Errors);
282
 
%%
283
 
scan([], Stack, Toks, Pos, State, Errors) ->
284
 
    more([], Stack, Toks, Pos, State, Errors, fun scan/6);
285
 
scan(Eof, _Stack, Toks, Pos, State, Errors) ->
286
 
    done(Eof, Errors, Toks, Pos, State).
287
 
 
288
 
 
289
 
scan_atom(Cs, Name, Toks, Pos, State, Errors) ->
290
 
    case catch list_to_atom(Name) of
291
 
        Atom when is_atom(Atom) ->
292
 
            case reserved_word(Atom) of
293
 
                true ->
294
 
                    scan(Cs, [], [{Atom,Pos}|Toks], Pos, State, Errors);
295
 
                false ->
296
 
                    scan(Cs, [], [{atom,Pos,Atom}|Toks], Pos, State, Errors)
297
 
            end;
298
 
        _ ->
299
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,atom},Pos}|Errors])
300
 
    end.
301
 
 
302
 
scan_variable(Cs, Name, Toks, Pos, State, Errors) ->
303
 
    case catch list_to_atom(Name) of
304
 
        A when is_atom(A) ->
305
 
            scan(Cs, [], [{var,Pos,A}|Toks], Pos, State, Errors);
306
 
        _ ->
307
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,var},Pos}|Errors])
308
 
    end.
309
 
 
310
 
 
311
 
%% Scan for a name - unqouted atom or variable, after the first character.
312
 
%%
313
 
%% Stack argument: return fun.
314
 
%% Returns the scanned name on the stack, unreversed.
315
 
%%
316
 
sub_scan_name([C|Cs]=Css, Stack, Toks, Pos, State, Errors) ->
317
 
    case name_char(C) of
318
 
        true ->
319
 
            sub_scan_name(Cs, [C|Stack], Toks, Pos, State, Errors);
320
 
        false ->
321
 
            [Fun|Name] = reverse(Stack),
322
 
            Fun(Css, Name, Toks, Pos, State, Errors)
323
 
    end;
324
 
sub_scan_name([], Stack, Toks, Pos, State, Errors) ->
325
 
    more([], Stack, Toks, Pos, State, Errors, fun sub_scan_name/6);
326
 
sub_scan_name(Eof, Stack, Toks, Pos, State, Errors) ->
327
 
    [Fun|Name] = reverse(Stack),
328
 
    Fun(Eof, Name, Toks, Pos, State, Errors).
329
 
 
330
 
name_char(C) when C >= $a, C =< $z -> true;
331
 
name_char(C) when C >= $�, C =< $�, C =/= $� -> true;
332
 
name_char(C) when C >= $A, C =< $Z -> true;
333
 
name_char(C) when C >= $�, C =< $�, C =/= $� -> true;
334
 
name_char(C) when C >= $0, C =< $9 -> true;
335
 
name_char($_) -> true;
336
 
name_char($@) -> true;
337
 
name_char(_) -> false.
338
 
 
339
 
 
340
 
scan_char([$\\|Cs], Stack, Toks, Pos, State, Errors) ->
341
 
    sub_scan_escape(Cs,[fun scan_char_escape/6|Stack], 
342
 
                    Toks, Pos, State, Errors);
343
 
scan_char([$\n|Cs], Stack, Toks, Pos, State, Errors) ->
344
 
    scan(Cs, Stack, [{char,Pos,$\n}|Toks], Pos+1, State, Errors);
345
 
scan_char([], Stack, Toks, Pos, State, Errors) ->
346
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_char/6);
347
 
scan_char(Cs, Stack, Toks, Pos, State, Errors) ->
348
 
    scan_char_escape(Cs, Stack, Toks, Pos, State, Errors).
349
 
 
350
 
scan_char_escape([nl|Cs], Stack, Toks, Pos, State, Errors) ->
351
 
    scan(Cs, Stack, [{char,Pos,$\n}|Toks], Pos+1, State, Errors);
352
 
scan_char_escape([C|Cs], Stack, Toks, Pos, State, Errors) ->
353
 
    scan(Cs, Stack, [{char,Pos,C}|Toks], Pos, State, Errors);
354
 
scan_char_escape(Eof, _Stack, _Toks, Pos, State, Errors) ->
355
 
    done(Eof, [{char,Pos}|Errors], [], Pos, State).
356
 
 
357
 
 
358
 
 
359
 
scan_string([$"|Cs], Stack, Toks, Pos, State, Errors) ->
360
 
    [StartPos,$"|S] = reverse(Stack),
361
 
    scan(Cs, [], [{string,StartPos,S}|Toks], Pos, State, Errors);
362
 
scan_string([$\n|Cs], Stack, Toks, Pos, State, Errors) ->
363
 
    scan_string(Cs, [$\n|Stack], Toks, Pos+1, State, Errors);
364
 
scan_string([$\\|Cs], Stack, Toks, Pos, State, Errors) ->
365
 
    sub_scan_escape(Cs, [fun scan_string_escape/6|Stack], 
366
 
                    Toks, Pos, State, Errors);
367
 
scan_string([C|Cs], Stack, Toks, Pos, State, Errors) ->
368
 
    scan_string(Cs, [C|Stack], Toks, Pos, State, Errors);
369
 
scan_string([], Stack, Toks, Pos, State, Errors) ->
370
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_string/6);
371
 
scan_string(Eof, Stack, _Toks, Pos, State, Errors) ->
372
 
    [StartPos,$"|S] = reverse(Stack),
373
 
    SS = string:substr(S, 1, 16),
374
 
    done(Eof, [{{string,$",SS},StartPos}|Errors], [], Pos, State).
375
 
 
376
 
scan_string_escape([nl|Cs], Stack, Toks, Pos, State, Errors) ->
377
 
    scan_string(Cs, [$\n|Stack], Toks, Pos+1, State, Errors);
378
 
scan_string_escape([C|Cs], Stack, Toks, Pos, State, Errors) ->
379
 
    scan_string(Cs, [C|Stack], Toks, Pos, State, Errors);
380
 
scan_string_escape(Eof, Stack, _Toks, Pos, State, Errors) ->
381
 
    [StartPos,$"|S] = reverse(Stack),
382
 
    SS = string:substr(S, 1, 16),
383
 
    done(Eof, [{{string,$",SS},StartPos}|Errors], [], Pos, State).
384
 
 
385
 
 
386
 
 
387
 
scan_qatom([$'|Cs], Stack, Toks, Pos, State, Errors) ->
388
 
    [StartPos,$'|S] = reverse(Stack),
389
 
    case catch list_to_atom(S) of
390
 
        A when is_atom(A) ->
391
 
            scan(Cs, [], [{atom,StartPos,A}|Toks], Pos, State, Errors);
392
 
        _ ->
393
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,atom},StartPos}|Errors])
394
 
    end;
395
 
scan_qatom([$\n|Cs], Stack, Toks, Pos, State, Errors) ->
396
 
    scan_qatom(Cs, [$\n|Stack], Toks, Pos+1, State, Errors);
397
 
scan_qatom([$\\|Cs], Stack, Toks, Pos, State, Errors) ->
398
 
    sub_scan_escape(Cs, [fun scan_qatom_escape/6|Stack], 
399
 
                    Toks, Pos, State, Errors);
400
 
scan_qatom([C|Cs], Stack, Toks, Pos, State, Errors) ->
401
 
    scan_qatom(Cs, [C|Stack], Toks, Pos, State, Errors);
402
 
scan_qatom([], Stack, Toks, Pos, State, Errors) ->
403
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_qatom/6);
404
 
scan_qatom(Eof, Stack, _Toks, Pos, State, Errors) ->
405
 
    [StartPos,$'|S] = reverse(Stack),
406
 
    SS = string:substr(S, 1, 16),
407
 
    done(Eof, [{{string,$',SS},StartPos}|Errors], [], Pos, State).
408
 
 
409
 
scan_qatom_escape([nl|Cs], Stack, Toks, Pos, State, Errors) ->
410
 
    scan_qatom(Cs, [$\n|Stack], Toks, Pos+1, State, Errors);
411
 
scan_qatom_escape([C|Cs], Stack, Toks, Pos, State, Errors) ->
412
 
    scan_qatom(Cs, [C|Stack], Toks, Pos, State, Errors);
413
 
scan_qatom_escape(Eof, Stack, _Toks, Pos, State, Errors) ->
414
 
    [StartPos,$'|S] = reverse(Stack),
415
 
    SS = string:substr(S, 1, 16),
416
 
    done(Eof, [{{string,$',SS},StartPos}|Errors], [], Pos, State).
417
 
 
418
 
 
419
 
%% Scan for a character escape sequence, in character literal or string. 
420
 
%% A string is a syntactical sugar list (e.g "abc") 
421
 
%% or a quoted atom (e.g 'EXIT').
422
 
%%
423
 
%% Stack argument: return fun.
424
 
%% Returns the resulting escape character on the stream.
425
 
%% The return atom 'nl' means that the escape sequence Backslash Newline
426
 
%% was found, i.e an actual Newline in the input.
427
 
%%
 
525
scan1("::"++Cs, St, Line, Col, Toks) ->
 
526
    tok2(Cs, St, Line, Col, Toks, "::", '::', 2);
 
527
scan1(":"=Cs, _St, Line, Col, Toks) ->
 
528
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
 
529
%% Optimization: punctuation characters less than 127:
 
530
scan1([$=|Cs], St, Line, Col, Toks) ->
 
531
    tok2(Cs, St, Line, Col, Toks, "=", '=', 1);
 
532
scan1([$:|Cs], St, Line, Col, Toks) ->
 
533
    tok2(Cs, St, Line, Col, Toks, ":", ':', 1);
 
534
scan1([$||Cs], St, Line, Col, Toks) ->
 
535
    tok2(Cs, St, Line, Col, Toks, "|", '|', 1);
 
536
scan1([$#|Cs], St, Line, Col, Toks) ->
 
537
    tok2(Cs, St, Line, Col, Toks, "#", '#', 1);
 
538
scan1([$/|Cs], St, Line, Col, Toks) ->
 
539
    tok2(Cs, St, Line, Col, Toks, "/", '/', 1);
 
540
scan1([$?|Cs], St, Line, Col, Toks) ->
 
541
    tok2(Cs, St, Line, Col, Toks, "?", '?', 1);
 
542
scan1([$-|Cs], St, Line, Col, Toks) ->
 
543
    tok2(Cs, St, Line, Col, Toks, "-", '-', 1);
 
544
scan1([$+|Cs], St, Line, Col, Toks) ->
 
545
    tok2(Cs, St, Line, Col, Toks, "+", '+', 1);
 
546
scan1([$*|Cs], St, Line, Col, Toks) ->
 
547
    tok2(Cs, St, Line, Col, Toks, "*", '*', 1);
 
548
scan1([$<|Cs], St, Line, Col, Toks) ->
 
549
    tok2(Cs, St, Line, Col, Toks, "<", '<', 1);
 
550
scan1([$>|Cs], St, Line, Col, Toks) ->
 
551
    tok2(Cs, St, Line, Col, Toks, ">", '>', 1);
 
552
scan1([$!|Cs], St, Line, Col, Toks) ->
 
553
    tok2(Cs, St, Line, Col, Toks, "!", '!', 1);
 
554
scan1([$@|Cs], St, Line, Col, Toks) ->
 
555
    tok2(Cs, St, Line, Col, Toks, "@", '@', 1);
 
556
scan1([$\\|Cs], St, Line, Col, Toks) ->
 
557
    tok2(Cs, St, Line, Col, Toks, "\\", '\\', 1);
 
558
scan1([$^|Cs], St, Line, Col, Toks) ->
 
559
    tok2(Cs, St, Line, Col, Toks, "^", '^', 1);
 
560
scan1([$`|Cs], St, Line, Col, Toks) ->
 
561
    tok2(Cs, St, Line, Col, Toks, "`", '`', 1);
 
562
scan1([$~|Cs], St, Line, Col, Toks) ->
 
563
    tok2(Cs, St, Line, Col, Toks, "~", '~', 1);
 
564
scan1([$&|Cs], St, Line, Col, Toks) ->
 
565
    tok2(Cs, St, Line, Col, Toks, "&", '&', 1);
 
566
%% End of optimization.
 
567
scan1([C|Cs], St, Line, Col, Toks) when ?CHAR(C) ->
 
568
    Str = [C],
 
569
    case catch list_to_atom(Str) of
 
570
        Sym when is_atom(Sym) ->
 
571
            tok2(Cs, St, Line, Col, Toks, Str, Sym, 1);
 
572
        _ ->
 
573
            Ncol = incr_column(Col, 1),
 
574
            scan_error({illegal,character}, Line, Col, Line, Ncol)
 
575
    end;
 
576
scan1([]=Cs, _St, Line, Col, Toks) ->
 
577
    {more,{Cs,Col,Toks,Line,[],fun scan/6}};
 
578
scan1(eof=Cs, _St, Line, Col, Toks) ->
 
579
    {ok,Toks,Cs,Line,Col}.
 
580
 
 
581
scan_atom(Cs0, St, Line, Col, Toks, Ncs0) ->
 
582
    case scan_name(Cs0, Ncs0) of
 
583
        {more,Ncs} ->
 
584
            {more,{[],Col,Toks,Line,Ncs,fun scan_atom/6}};
 
585
        {Wcs,Cs} ->
 
586
            case catch list_to_atom(Wcs) of
 
587
                Name when is_atom(Name) ->
 
588
                    case (St#erl_scan.resword_fun)(Name) of
 
589
                        true -> 
 
590
                            tok2(Cs, St, Line, Col, Toks, Wcs, Name);
 
591
                        false -> 
 
592
                            tok3(Cs, St, Line, Col, Toks, atom, Wcs, Name)
 
593
                    end;
 
594
                _Error -> 
 
595
                    Ncol = incr_column(Col, length(Wcs)),
 
596
                    scan_error({illegal,atom}, Line, Col, Line, Ncol)
 
597
            end
 
598
    end.
 
599
 
 
600
scan_variable(Cs0, St, Line, Col, Toks, Ncs0) ->
 
601
    case scan_name(Cs0, Ncs0) of
 
602
        {more,Ncs} ->
 
603
            {more,{[],Col,Toks,Line,Ncs,fun scan_variable/6}};
 
604
        {Wcs,Cs} ->
 
605
            case catch list_to_atom(Wcs) of
 
606
                Name when is_atom(Name) ->
 
607
                    tok3(Cs, St, Line, Col, Toks, var, Wcs, Name);
 
608
                _Error -> 
 
609
                    Ncol = incr_column(Col, length(Wcs)),
 
610
                    scan_error({illegal,var}, Line, Col, Line, Ncol)
 
611
            end
 
612
    end.
 
613
 
 
614
scan_name([C|Cs], Ncs) when C >= $a, C =< $z ->
 
615
    scan_name(Cs, [C|Ncs]);
 
616
scan_name([C|Cs], Ncs) when C >= $A, C =< $Z ->
 
617
    scan_name(Cs, [C|Ncs]);
 
618
scan_name([$_=C|Cs], Ncs) ->
 
619
    scan_name(Cs, [C|Ncs]);
 
620
scan_name([C|Cs], Ncs) when ?DIGIT(C) ->
 
621
    scan_name(Cs, [C|Ncs]);
 
622
scan_name([$@=C|Cs], Ncs) ->
 
623
    scan_name(Cs, [C|Ncs]);
 
624
scan_name([C|Cs], Ncs) when C >= $�, C =< $�, C =/= $� ->
 
625
    scan_name(Cs, [C|Ncs]);
 
626
scan_name([C|Cs], Ncs) when C >= $�, C =< $�, C =/= $� ->
 
627
    scan_name(Cs, [C|Ncs]);
 
628
scan_name([], Ncs) ->
 
629
    {more,Ncs};
 
630
scan_name(Cs, Ncs) ->
 
631
    {lists:reverse(Ncs),Cs}.
 
632
 
 
633
scan_dot([$%|_]=Cs, St, Line, Col, Toks, Ncs) ->
 
634
    Attrs = attributes(Line, Col, St, Ncs),
 
635
    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 1)};
 
636
scan_dot([$\n=C|Cs], St, Line, Col, Toks, Ncs) ->
 
637
    Attrs = attributes(Line, Col, St, ?STR(Col, Ncs++[C])),
 
638
    {ok,[{dot,Attrs}|Toks],Cs,Line+1,new_column(Col, 1)};
 
639
scan_dot([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->
 
640
    Attrs = attributes(Line, Col, St, ?STR(Col, Ncs++[C])),
 
641
    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 2)};
 
642
scan_dot([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
643
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_dot/6}};
 
644
scan_dot(eof=Cs, St, Line, Col, Toks, Ncs) ->
 
645
    Attrs = attributes(Line, Col, St, Ncs),
 
646
    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 1)};
 
647
scan_dot(Cs, St, Line, Col, Toks, Ncs) ->
 
648
    tok2(Cs, St, Line, Col, Toks, Ncs, '.', 1).
 
649
 
 
650
%%% White space characters are very common, so it is worthwhile to
 
651
%%% scan them fast and store them compactly. (The words "whitespace"
 
652
%%% and "white space" usually mean the same thing. The Erlang
 
653
%%% specification denotes the characters with ASCII code in the
 
654
%%% interval 0 to 32 as "white space".)
 
655
%%%
 
656
%%% Convention: if there is a white newline ($\n) it will always be
 
657
%%% the first character in the text string. As a consequence, there
 
658
%%% cannot be more than one newline in a white_space token string.
 
659
%%%
 
660
%%% Some common combinations are recognized, some are not. Examples
 
661
%%% of the latter are tab(s) followed by space(s), like "\t  ".
 
662
%%% (They will be represented by two (or more) tokens.)
 
663
%%%
 
664
%%% Note: the character sequence "\r\n" is *not* recognized since it
 
665
%%% would violate the property that $\n will always be the first
 
666
%%% character. (But since "\r\n\r\n" is common, it pays off to
 
667
%%% recognize "\n\r".)
 
668
 
 
669
scan_newline([$\s|Cs], St, Line, Col, Toks) ->
 
670
    scan_nl_spcs(Cs, St, Line, Col, Toks, 2);
 
671
scan_newline([$\t|Cs], St, Line, Col, Toks) ->
 
672
    scan_nl_tabs(Cs, St, Line, Col, Toks, 2);
 
673
scan_newline([$\r|Cs], St, Line, Col, Toks) ->
 
674
    newline_end(Cs, St, Line, Col, Toks, 2, "\n\r");
 
675
scan_newline([$\f|Cs], St, Line, Col, Toks) ->
 
676
    newline_end(Cs, St, Line, Col, Toks, 2, "\n\f");
 
677
scan_newline([], _St, Line, Col, Toks) ->
 
678
    {more,{[$\n],Col,Toks,Line,[],fun scan/6}};
 
679
scan_newline(Cs, St, Line, Col, Toks) ->
 
680
    scan_nl_white_space(Cs, St, Line, Col, Toks, "\n").
 
681
 
 
682
scan_nl_spcs([$\s|Cs], St, Line, Col, Toks, N) when N < 17 ->
 
683
    scan_nl_spcs(Cs, St, Line, Col, Toks, N+1);
 
684
scan_nl_spcs([]=Cs, _St, Line, Col, Toks, N) ->
 
685
    {more,{Cs,Col,Toks,Line,N,fun scan_nl_spcs/6}};
 
686
scan_nl_spcs(Cs, St, Line, Col, Toks, N) ->
 
687
    newline_end(Cs, St, Line, Col, Toks, N, nl_spcs(N)).
 
688
    
 
689
scan_nl_tabs([$\t|Cs], St, Line, Col, Toks, N) when N < 11 ->
 
690
    scan_nl_tabs(Cs, St, Line, Col, Toks, N+1);
 
691
scan_nl_tabs([]=Cs, _St, Line, Col, Toks, N) ->
 
692
    {more,{Cs,Col,Toks,Line,N,fun scan_nl_tabs/6}};
 
693
scan_nl_tabs(Cs, St, Line, Col, Toks, N) ->
 
694
    newline_end(Cs, St, Line, Col, Toks, N, nl_tabs(N)).
 
695
 
 
696
%% Note: returning {more,Cont} is meaningless here; one could just as
 
697
%% well return several tokens. But since tokens() scans up to a full
 
698
%% stop anyway, nothing is gained by not collecting all white spaces.
 
699
scan_nl_white_space([$\n|Cs], #erl_scan{text = false}=St, Line, no_col=Col, 
 
700
                    Toks0, Ncs) ->
 
701
    Toks = [{white_space,Line,lists:reverse(Ncs)}|Toks0],
 
702
    scan_newline(Cs, St, Line+1, Col, Toks);
 
703
scan_nl_white_space([$\n|Cs], St, Line, Col, Toks, Ncs0) ->
 
704
    Ncs = lists:reverse(Ncs0),
 
705
    Attrs = attributes(Line, Col, St, Ncs),
 
706
    Token = {white_space,Attrs,Ncs},
 
707
    scan_newline(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]);
 
708
scan_nl_white_space([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->
 
709
    scan_nl_white_space(Cs, St, Line, Col, Toks, [C|Ncs]);
 
710
scan_nl_white_space([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
711
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_nl_white_space/6}};
 
712
scan_nl_white_space(Cs, #erl_scan{text = false}=St, Line, no_col=Col, 
 
713
                    Toks, Ncs) ->
 
714
    scan1(Cs, St, Line+1, Col, [{white_space,Line,lists:reverse(Ncs)}|Toks]);
 
715
scan_nl_white_space(Cs, St, Line, Col, Toks, Ncs0) ->
 
716
    Ncs = lists:reverse(Ncs0),
 
717
    Attrs = attributes(Line, Col, St, Ncs),
 
718
    Token = {white_space,Attrs,Ncs},
 
719
    scan1(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]).
 
720
 
 
721
newline_end(Cs, #erl_scan{text = false}=St, Line, no_col=Col, 
 
722
            Toks, _N, Ncs) ->
 
723
    scan1(Cs, St, Line+1, Col, [{white_space,Line,Ncs}|Toks]);
 
724
newline_end(Cs, St, Line, Col, Toks, N, Ncs) ->
 
725
    Attrs = attributes(Line, Col, St, Ncs),
 
726
    scan1(Cs, St, Line+1, new_column(Col, N), [{white_space,Attrs,Ncs}|Toks]).
 
727
 
 
728
scan_spcs([$\s|Cs], St, Line, Col, Toks, N) when N < 16 ->
 
729
    scan_spcs(Cs, St, Line, Col, Toks, N+1);
 
730
scan_spcs([]=Cs, _St, Line, Col, Toks, N) ->
 
731
    {more,{Cs,Col,Toks,Line,N,fun scan_spcs/6}};
 
732
scan_spcs(Cs, St, Line, Col, Toks, N) ->
 
733
    white_space_end(Cs, St, Line, Col, Toks, N, spcs(N)).
 
734
 
 
735
scan_tabs([$\t|Cs], St, Line, Col, Toks, N) when N < 10 ->
 
736
    scan_tabs(Cs, St, Line, Col, Toks, N+1);
 
737
scan_tabs([]=Cs, _St, Line, Col, Toks, N) ->
 
738
    {more,{Cs,Col,Toks,Line,N,fun scan_tabs/6}};
 
739
scan_tabs(Cs, St, Line, Col, Toks, N) ->
 
740
    white_space_end(Cs, St, Line, Col, Toks, N, tabs(N)).
 
741
 
 
742
skip_white_space([$\n|Cs], St, Line, Col, Toks, _N) ->
 
743
    skip_white_space(Cs, St, Line+1, new_column(Col, 1), Toks, 0);
 
744
skip_white_space([C|Cs], St, Line, Col, Toks, N) when ?WHITE_SPACE(C) ->
 
745
    skip_white_space(Cs, St, Line, Col, Toks, N+1);
 
746
skip_white_space([]=Cs, _St, Line, Col, Toks, N) ->
 
747
    {more,{Cs,Col,Toks,Line,N,fun skip_white_space/6}};
 
748
skip_white_space(Cs, St, Line, Col, Toks, N) ->
 
749
    scan1(Cs, St, Line, incr_column(Col, N), Toks).
 
750
 
 
751
%% Maybe \t and \s should break the loop.
 
752
scan_white_space([$\n|_]=Cs, St, Line, Col, Toks, Ncs) ->
 
753
    white_space_end(Cs, St, Line, Col, Toks, length(Ncs), lists:reverse(Ncs));
 
754
scan_white_space([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->
 
755
    scan_white_space(Cs, St, Line, Col, Toks, [C|Ncs]);
 
756
scan_white_space([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
757
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_white_space/6}};
 
758
scan_white_space(Cs, St, Line, Col, Toks, Ncs) ->
 
759
    white_space_end(Cs, St, Line, Col, Toks, length(Ncs), lists:reverse(Ncs)).
 
760
 
 
761
-compile({inline,[white_space_end/7]}).
 
762
 
 
763
white_space_end(Cs, St, Line, Col, Toks, N, Ncs) ->
 
764
    tok3(Cs, St, Line, Col, Toks, white_space, Ncs, Ncs, N).
 
765
 
 
766
scan_char([$\\|Cs]=Cs0, St, Line, Col, Toks) ->
 
767
    case scan_escape(Cs, incr_column(Col, 2)) of
 
768
        more ->
 
769
            {more,{[$$|Cs0],Col,Toks,Line,[],fun scan/6}};
 
770
        {error,Error,Ncol} ->
 
771
            scan_error(Error, Line, Col, Line, Ncol);
 
772
        {eof,Ncol} ->
 
773
            scan_error(char, Line, Col, Line, Ncol);
 
774
        {nl,Val,Str,Ncs,Ncol} ->
 
775
            Attrs = attributes(Line, Col, St, ?STR(Ncol, "$\\"++Str)),
 
776
            Ntoks = [{char,Attrs,Val}|Toks],
 
777
            scan1(Ncs, St, Line+1, Ncol, Ntoks);
 
778
        {unicode,Val,Str,Ncs,Ncol} ->
 
779
            Attrs = attributes(Line, Col, St, ?STR(Ncol, "$\\"++Str)),
 
780
            Ntoks = [{integer,Attrs,Val}|Toks], % UNI
 
781
            scan1(Ncs, St, Line, Ncol, Ntoks);
 
782
        {Val,Str,Ncs,Ncol} ->
 
783
            Attrs = attributes(Line, Col, St, ?STR(Ncol, "$\\"++Str)),
 
784
            Ntoks = [{char,Attrs,Val}|Toks],
 
785
            scan1(Ncs, St, Line, Ncol, Ntoks)
 
786
    end;
 
787
scan_char([$\n=C|Cs], St, Line, Col, Toks) ->    
 
788
    Attrs = attributes(Line, Col, St, ?STR(Col, [$$,C])),
 
789
    scan1(Cs, St, Line+1, new_column(Col, 1), [{char,Attrs,C}|Toks]);
 
790
scan_char([C|Cs], St, Line, Col, Toks) when ?CHAR(C) ->
 
791
    Tag = if ?UNI255(C) -> char; true -> integer end, % UNI
 
792
    Attrs = attributes(Line, Col, St, ?STR(Col, [$$,C])),
 
793
    scan1(Cs, St, Line, incr_column(Col, 2), [{Tag,Attrs,C}|Toks]);
 
794
scan_char([], _St, Line, Col, Toks) ->
 
795
    {more,{[$$],Col,Toks,Line,[],fun scan/6}};
 
796
scan_char(eof, _St, Line, Col, _Toks) ->
 
797
    scan_error(char, Line, Col, Line, incr_column(Col, 1)).
 
798
 
 
799
scan_string(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0,Uni0}) ->
 
800
    case scan_string0(Cs, Line, Col, $\", Str, Wcs, Uni0) of
 
801
        {more,Ncs,Nline,Ncol,Nstr,Nwcs,Uni} ->
 
802
            State = {Nwcs,Nstr,Line0,Col0,Uni},
 
803
            {more,{Ncs,Ncol,Toks,Nline,State,fun scan_string/6}};
 
804
        {char_error,Error,Nline,Ncol,EndCol} ->
 
805
            scan_error(Error, Nline, Ncol, Nline, EndCol);
 
806
        {error,Nline,Ncol,Nwcs} ->
 
807
            Estr = string:substr(Nwcs, 1, 16), % Expanded escape chars.
 
808
            scan_error({string,$\",Estr}, Line0, Col0, Nline, Ncol);
 
809
        {Ncs,Nline,Ncol,Nstr,Nwcs,?NO_UNICODE} ->
 
810
            Attrs = attributes(Line0, Col0, St, Nstr),
 
811
            scan1(Ncs, St, Nline, Ncol, [{string,Attrs,Nwcs}|Toks]);
 
812
        {Ncs,Nline,Ncol,Nstr,_Nwcs,_Uni} ->
 
813
            Ntoks = unicode_string_to_list(Line0, Col0, St, Nstr, Toks),
 
814
            scan1(Ncs, St, Nline, Ncol, Ntoks)
 
815
    end.
 
816
 
 
817
%% UNI
 
818
unicode_string_to_list(Line, Col, St, [$"=C|Nstr], Toks) -> %" Emacs
 
819
    Paren = {'[',attributes(Line, Col, St, ?STR(Col, [C]))},
 
820
    u2l(Nstr, Line, incr_column(Col, 1), St, [Paren|Toks]).
 
821
 
 
822
u2l([$"]=Cs, Line, Col, St, Toks) -> %" Emacs
 
823
    [{']',attributes(Line, Col, St, ?STR(Col, Cs))}|Toks];
 
824
u2l([$\n=C|Cs], Line, Col, St, Toks) ->
 
825
    Ntoks = unicode_nl_tokens(Line, Col, ?STR(Col, [C]), C, St, Toks, Cs),
 
826
    u2l(Cs, Line+1, new_column(Col, 1), St, Ntoks);
 
827
u2l([$\\|Cs], Line, Col, St, Toks) ->
 
828
    case scan_escape(Cs, Col) of
 
829
        {nl,Val,ValStr,Ncs,Ncol} ->
 
830
            Nstr = ?STR(Ncol, [$\\|ValStr]),
 
831
            Ntoks = unicode_nl_tokens(Line, Col, Nstr, Val, St, Toks, Ncs),
 
832
            u2l(Ncs, Line+1, Ncol, St, Ntoks);
 
833
        {unicode,Val,ValStr,Ncs,Ncol} ->
 
834
            Nstr = ?STR(Ncol, [$\\|ValStr]),
 
835
            Ntoks = unicode_tokens(Line, Col, Nstr, Val, St, Toks, Ncs),
 
836
            u2l(Ncs, Line, incr_column(Ncol, 1), St, Ntoks);
 
837
        {Val,ValStr,Ncs,Ncol} ->
 
838
            Nstr = ?STR(Ncol, [$\\|ValStr]),
 
839
            Ntoks = unicode_tokens(Line, Col, Nstr, Val, St, Toks, Ncs),
 
840
            u2l(Ncs, Line, incr_column(Ncol, 1), St, Ntoks)
 
841
    end;
 
842
u2l([C|Cs], Line, Col, St, Toks) ->
 
843
    Ntoks = unicode_tokens(Line, Col, ?STR(Col, [C]), C, St, Toks, Cs),
 
844
    u2l(Cs, Line, incr_column(Col, 1), St, Ntoks).
 
845
 
 
846
unicode_nl_tokens(Line, Col, Str, Val, St, Toks, Cs) ->
 
847
    Ccol = new_column(Col, 1),
 
848
    unicode_tokens(Line, Col, Str, Val, St, Toks, Cs, Line+1, Ccol).
 
849
 
 
850
unicode_tokens(Line, Col, Str, Val, St, Toks, Cs) ->
 
851
    Ccol = incr_column(Col, length(Str)),
 
852
    unicode_tokens(Line, Col, Str, Val, St, Toks, Cs, Line, Ccol).
 
853
 
 
854
unicode_tokens(Line, Col, Str, Val, St, Toks, Cs, Cline, Ccol) ->
 
855
    Attrs = attributes(Line, Col, St, Str),
 
856
    Tag = if ?UNI255(Val) -> char; true -> integer end,
 
857
    Token = {Tag,Attrs,Val},
 
858
    [{',',attributes(Cline, Ccol, St, "")} || Cs =/= "\""] ++ [Token|Toks].
 
859
 
 
860
scan_qatom(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0,Uni0}) ->
 
861
    case scan_string0(Cs, Line, Col, $\', Str, Wcs, Uni0) of
 
862
        {more,Ncs,Nline,Ncol,Nstr,Nwcs,Uni} ->
 
863
            State = {Nwcs,Nstr,Line0,Col0,Uni},
 
864
            {more,{Ncs,Ncol,Toks,Nline,State,fun scan_qatom/6}};
 
865
        {char_error,Error,Nline,Ncol,EndCol} ->
 
866
            scan_error(Error, Nline, Ncol, Nline, EndCol);
 
867
        {error,Nline,Ncol,Nwcs} ->
 
868
            Estr = string:substr(Nwcs, 1, 16), % Expanded escape chars.
 
869
            scan_error({string,$\',Estr}, Line0, Col0, Nline, Ncol);
 
870
        {Ncs,Nline,Ncol,Nstr,Nwcs,?NO_UNICODE} ->
 
871
            case catch list_to_atom(Nwcs) of
 
872
                A when is_atom(A) ->
 
873
                    Attrs = attributes(Line0, Col0, St, Nstr),
 
874
                    scan1(Ncs, St, Nline, Ncol, [{atom,Attrs,A}|Toks]);
 
875
                _ ->
 
876
                    scan_error({illegal,atom}, Line0, Col0, Nline, Ncol)
 
877
            end
 
878
    end.
 
879
 
 
880
scan_string0(Cs, Line, no_col=Col, Q, [], Wcs, Uni) ->
 
881
    scan_string_no_col(Cs, Line, Col, Q, Wcs, Uni);
 
882
scan_string0(Cs, Line, Col, Q, [], Wcs, Uni) ->
 
883
    scan_string_col(Cs, Line, Col, Q, Wcs, Uni);
 
884
scan_string0(Cs, Line, Col, Q, Str, Wcs, Uni) ->
 
885
    scan_string1(Cs, Line, Col, Q, Str, Wcs, Uni).
 
886
 
 
887
%% Optimization. Col =:= no_col.
 
888
scan_string_no_col([Q|Cs], Line, Col, Q, Wcs, Uni) ->
 
889
    {Cs,Line,Col,_DontCare=[],lists:reverse(Wcs),Uni};
 
890
scan_string_no_col([$\n=C|Cs], Line, Col, Q, Wcs, Uni) ->
 
891
    scan_string_no_col(Cs, Line+1, Col, Q, [C|Wcs], Uni);
 
892
scan_string_no_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, 
 
893
                                                        ?CHAR(C), ?UNI255(C) ->
 
894
    scan_string_no_col(Cs, Line, Col, Q, [C|Wcs], Uni);
 
895
scan_string_no_col(Cs, Line, Col, Q, Wcs, Uni) ->
 
896
    scan_string1(Cs, Line, Col, Q, Wcs, Wcs, Uni).
 
897
 
 
898
%% Optimization. Col =/= no_col.
 
899
scan_string_col([Q|Cs], Line, Col, Q, Wcs0, Uni) ->
 
900
    Wcs = lists:reverse(Wcs0),
 
901
    Str = [Q|Wcs++[Q]],
 
902
    {Cs,Line,Col+1,Str,Wcs,Uni};
 
903
scan_string_col([$\n=C|Cs], Line, _xCol, Q, Wcs, Uni) ->
 
904
    scan_string_col(Cs, Line+1, 1, Q, [C|Wcs], Uni);
 
905
scan_string_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, 
 
906
                                                     ?CHAR(C), ?UNI255(C) ->
 
907
    scan_string_col(Cs, Line, Col+1, Q, [C|Wcs], Uni);
 
908
scan_string_col(Cs, Line, Col, Q, Wcs, Uni) ->
 
909
    scan_string1(Cs, Line, Col, Q, Wcs, Wcs, Uni).
 
910
 
 
911
%% UNI_STR is to be replaced by STR when the Unicode-string-to-list
 
912
%% workaround is eventually removed.
 
913
-define(UNI_STR(Col, S), S).
 
914
 
 
915
scan_string1([Q|Cs], Line, Col, Q, Str0, Wcs0, Uni) ->
 
916
    Wcs = lists:reverse(Wcs0),
 
917
    Str = ?UNI_STR(Col, [Q|lists:reverse(Str0, [Q])]),
 
918
    {Cs,Line,incr_column(Col, 1),Str,Wcs,Uni};
 
919
scan_string1([$\n=C|Cs], Line, Col, Q, Str, Wcs, Uni) ->
 
920
    Ncol = new_column(Col, 1),
 
921
    scan_string1(Cs, Line+1, Ncol, Q, ?UNI_STR(Col, [C|Str]), [C|Wcs], Uni);
 
922
scan_string1([$\\|Cs]=Cs0, Line, Col, Q, Str, Wcs, Uni) ->
 
923
    case scan_escape(Cs, Col) of
 
924
        more ->
 
925
            {more,Cs0,Line,Col,Str,Wcs,Uni};
 
926
        {error,Error,Ncol} ->
 
927
            {char_error,Error,Line,Col,incr_column(Ncol, 1)};
 
928
        {eof,Ncol} ->
 
929
            {error,Line,incr_column(Ncol, 1),lists:reverse(Wcs)};
 
930
        {nl,Val,ValStr,Ncs,Ncol} ->
 
931
            Nstr = ?UNI_STR(Ncol, lists:reverse(ValStr, [$\\|Str])),
 
932
            Nwcs = [Val|Wcs],
 
933
            scan_string1(Ncs, Line+1, Ncol, Q, Nstr, Nwcs, Uni);
 
934
        {unicode,_Val,_ValStr,_Ncs,Ncol} when Q =:= $' -> %' Emacs
 
935
            {char_error,{illegal,character},Line,Col,incr_column(Ncol, 1)};
 
936
        {unicode,Val,ValStr,Ncs,Ncol} -> % UNI. Uni is set to Val.
 
937
            Nstr = ?UNI_STR(Ncol, lists:reverse(ValStr, [$\\|Str])),
 
938
            Nwcs = [Val|Wcs], % not used
 
939
            scan_string1(Ncs, Line, incr_column(Ncol, 1), Q, Nstr, Nwcs, Val);
 
940
        {Val,ValStr,Ncs,Ncol} ->
 
941
            Nstr = ?UNI_STR(Ncol, lists:reverse(ValStr, [$\\|Str])),
 
942
            Nwcs = [Val|Wcs],
 
943
            scan_string1(Ncs, Line, incr_column(Ncol, 1), Q, Nstr, Nwcs, Uni)
 
944
    end;
 
945
scan_string1([C|Cs], Line, no_col=Col, Q, Str, Wcs, Uni) when ?CHAR(C),
 
946
                                                              ?UNI255(C) ->
 
947
    %% scan_string1(Cs, Line, Col, Q, Str, [C|Wcs], Uni);
 
948
    scan_string1(Cs, Line, Col, Q, [C|Str], [C|Wcs], Uni); % UNI
 
949
scan_string1([C|Cs], Line, Col, Q, Str, Wcs, Uni) when ?CHAR(C), ?UNI255(C) ->
 
950
    scan_string1(Cs, Line, Col+1, Q, [C|Str], [C|Wcs], Uni);
 
951
scan_string1([C|_Cs], Line, Col, $', _Str, _Wcs, _Uni) when ?CHAR(C) -> %' UNI
 
952
    {char_error,{illegal,character},Line,Col,incr_column(Col, 1)};
 
953
scan_string1([C|Cs], Line, Col, Q, Str, Wcs, _Uni) when ?CHAR(C) -> % UNI
 
954
    scan_string1(Cs, Line, incr_column(Col, 1), Q, [C|Str], [C|Wcs], C);
 
955
scan_string1([]=Cs, Line, Col, _Q, Str, Wcs, Uni) ->
 
956
    {more,Cs,Line,Col,Str,Wcs,Uni};
 
957
scan_string1(eof, Line, Col, _Q, _Str, Wcs, _Uni) ->
 
958
    {error,Line,Col,lists:reverse(Wcs)}.
 
959
 
 
960
-define(OCT(C), C >= $0, C =< $7).
 
961
-define(HEX(C), C >= $0 andalso C =< $9 orelse 
 
962
                C >= $A andalso C =< $F orelse 
 
963
                C >= $a andalso C =< $f).
 
964
 
428
965
%% \<1-3> octal digits
429
 
sub_scan_escape([O1,O2,O3|Cs], [Fun|Stack], Toks, Pos, State, Errors) 
430
 
  when O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 ->
 
966
scan_escape([O1,O2,O3|Cs], Col) when ?OCT(O1), ?OCT(O2), ?OCT(O3) ->
431
967
    Val = (O1*8 + O2)*8 + O3 - 73*$0,
432
 
    Fun([Val|Cs], Stack, Toks, Pos, State, Errors);
433
 
sub_scan_escape([O1,O2]=Cs, Stack, Toks, Pos, State, Errors) 
434
 
  when O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7 ->
435
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun sub_scan_escape/6);
436
 
sub_scan_escape([O1,O2|Cs], [Fun|Stack], Toks, Pos, State, Errors) 
437
 
  when O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7 ->
 
968
    {Val,?UNI_STR(Col, [O1,O2,O3]),Cs,incr_column(Col, 3)};
 
969
scan_escape([O1,O2], _Col) when ?OCT(O1), ?OCT(O2) ->
 
970
    more;
 
971
scan_escape([O1,O2|Cs], Col) when ?OCT(O1), ?OCT(O2) ->
438
972
    Val = (O1*8 + O2) - 9*$0,
439
 
    Fun([Val|Cs], Stack, Toks, Pos, State, Errors);
440
 
sub_scan_escape([O1]=Cs, Stack, Toks, Pos, State, Errors) 
441
 
  when O1 >= $0, O1 =< $7 ->
442
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun sub_scan_escape/6);
443
 
sub_scan_escape([O1|Cs], [Fun|Stack], Toks, Pos, State, Errors) 
444
 
  when O1 >= $0, O1 =< $7 ->
445
 
    Val = O1 - $0,
446
 
    Fun([Val|Cs], Stack, Toks, Pos, State, Errors);
 
973
    {Val,?UNI_STR(Col, [O1,O2]),Cs,incr_column(Col, 2)};
 
974
scan_escape([O1], _Col) when ?OCT(O1) ->
 
975
    more;
 
976
scan_escape([O1|Cs], Col) when ?OCT(O1) ->
 
977
    {O1 - $0,?UNI_STR(Col, [O1]),Cs,incr_column(Col, 1)};
 
978
%% \x{<hex digits>}
 
979
scan_escape([$x,${|Cs], Col) ->
 
980
    scan_hex(Cs, incr_column(Col, 2), []);
 
981
scan_escape([$x], _Col) ->
 
982
    more;
 
983
scan_escape([$x|eof], Col) ->
 
984
    {eof,incr_column(Col, 1)};
 
985
%% \x<2> hexadecimal digits
 
986
scan_escape([$x,H1,H2|Cs], Col) when ?HEX(H1), ?HEX(H2) ->
 
987
    Val = erlang:list_to_integer([H1,H2], 16),
 
988
    {Val,?UNI_STR(Col, [$x,H1,H2]),Cs,incr_column(Col, 3)};
 
989
scan_escape([$x,H1], _Col) when ?HEX(H1) ->
 
990
    more;
 
991
scan_escape([$x|_], Col) ->
 
992
    {error,{illegal,character},incr_column(Col, 1)};
447
993
%% \^X -> CTL-X
448
 
sub_scan_escape([$^,C|Cs], [Fun|Stack], Toks, Pos, State, Errors) ->
 
994
scan_escape([$^=C0,$\n=C|Cs], Col) ->
 
995
    {nl,C,?UNI_STR(Col, [C0,C]),Cs,new_column(Col, 1)};
 
996
scan_escape([$^=C0,C|Cs], Col) when ?CHAR(C) ->
449
997
    Val = C band 31,
450
 
    Fun([Val|Cs], Stack, Toks, Pos, State, Errors);
451
 
sub_scan_escape([$^]=Cs, Stack, Toks, Pos, State, Errors) ->
452
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun sub_scan_escape/6);
453
 
sub_scan_escape([$^|Eof], [Fun|Stack], Toks, Pos, State, Errors) ->
454
 
    Fun(Eof, Stack, Toks, Pos, State, Errors);
455
 
%% \NL (backslash newline)
456
 
sub_scan_escape([$\n|Cs],[Fun|Stack], Toks, Pos, State, Errors) ->
457
 
    Fun([nl|Cs], Stack, Toks, Pos, State, Errors);
458
 
%% \X - familiar escape sequences
459
 
sub_scan_escape([C|Cs], [Fun|Stack], Toks, Pos, State, Errors) ->
460
 
    Val = escape_char(C),
461
 
    Fun([Val|Cs], Stack, Toks, Pos, State, Errors);
462
 
%%
463
 
sub_scan_escape([], Stack, Toks, Pos, State, Errors) ->
464
 
    more([], Stack, Toks, Pos, State, Errors, fun sub_scan_escape/6);
465
 
sub_scan_escape(Eof, [Fun|Stack], Toks, Pos, State, Errors) ->
466
 
    Fun(Eof, Stack, Toks, Pos, State, Errors).
467
 
 
468
 
escape_char($n) -> $\n;                         %\n = LF
469
 
escape_char($r) -> $\r;                         %\r = CR
470
 
escape_char($t) -> $\t;                         %\t = TAB
471
 
escape_char($v) -> $\v;                         %\v = VT
472
 
escape_char($b) -> $\b;                         %\b = BS
473
 
escape_char($f) -> $\f;                         %\f = FF
474
 
escape_char($e) -> $\e;                         %\e = ESC
475
 
escape_char($s) -> $\s;                         %\s = SPC
476
 
escape_char($d) -> $\d;                         %\d = DEL
 
998
    {Val,?UNI_STR(Col, [C0,C]),Cs,incr_column(Col, 2)};
 
999
scan_escape([$^], _Col) ->
 
1000
    more;
 
1001
scan_escape([$^|eof], Col) ->
 
1002
    {eof,incr_column(Col, 1)};
 
1003
scan_escape([$\n=C|Cs], Col) ->
 
1004
    {nl,C,?UNI_STR(Col, [C]),Cs,new_column(Col, 1)};
 
1005
scan_escape([C0|Cs], Col) when ?CHAR(C0), ?UNI255(C0) ->
 
1006
    C = escape_char(C0),
 
1007
    {C,?UNI_STR(Col, [C0]),Cs,incr_column(Col, 1)};
 
1008
scan_escape([C|Cs], Col) when ?CHAR(C) -> % UNI
 
1009
    {unicode,C,?UNI_STR(Col, [C]),Cs,incr_column(Col, 1)};
 
1010
scan_escape([], _Col) ->
 
1011
    more;
 
1012
scan_escape(eof, Col) ->
 
1013
    {eof,Col}.
 
1014
 
 
1015
scan_hex([C|Cs], no_col=Col, Wcs) when ?HEX(C) ->
 
1016
    scan_hex(Cs, Col, [C|Wcs]);
 
1017
scan_hex([C|Cs], Col, Wcs) when ?HEX(C) ->
 
1018
    scan_hex(Cs, Col+1, [C|Wcs]);
 
1019
scan_hex(Cs, Col, Wcs) ->
 
1020
    scan_esc_end(Cs, Col, Wcs, 16, "x{").
 
1021
 
 
1022
scan_esc_end([$}|Cs], Col, Wcs0, B, Str0) ->
 
1023
    Wcs = lists:reverse(Wcs0),
 
1024
    case catch erlang:list_to_integer(Wcs, B) of
 
1025
        Val when Val =< 16#FF ->
 
1026
            {Val,?UNI_STR(Col, Str0++Wcs++[$}]),Cs,incr_column(Col, 1)};
 
1027
        Val when Val =< 16#10FFFF ->
 
1028
            {unicode,Val,?UNI_STR(Col, Str0++Wcs++[$}]),Cs,incr_column(Col,1)};
 
1029
        _ ->
 
1030
            {error,{illegal,character},incr_column(Col, 1)}
 
1031
    end;
 
1032
scan_esc_end([], _Col, _Wcs, _B, _Str0) ->
 
1033
    more;
 
1034
scan_esc_end(eof, Col, _Wcs, _B, _Str0) ->
 
1035
    {eof,Col};
 
1036
scan_esc_end(_Cs, Col, _Wcs, _B, _Str0) ->
 
1037
    {error,{illegal,character},Col}.
 
1038
 
 
1039
escape_char($n) -> $\n;                         % \n = LF
 
1040
escape_char($r) -> $\r;                         % \r = CR
 
1041
escape_char($t) -> $\t;                         % \t = TAB
 
1042
escape_char($v) -> $\v;                         % \v = VT
 
1043
escape_char($b) -> $\b;                         % \b = BS
 
1044
escape_char($f) -> $\f;                         % \f = FF
 
1045
escape_char($e) -> $\e;                         % \e = ESC
 
1046
escape_char($s) -> $\s;                         % \s = SPC
 
1047
escape_char($d) -> $\d;                         % \d = DEL
477
1048
escape_char(C) -> C.
478
1049
 
479
 
 
480
 
scan_number([$.,C|Cs], Stack, Toks, Pos, State, Errors) when C >= $0, C =< $9 ->
481
 
    scan_fraction(Cs, [C,$.|Stack], Toks, Pos, State, Errors);
482
 
scan_number([$.]=Cs, Stack, Toks, Pos, State, Errors) ->
483
 
    more(Cs, Stack, Toks, Pos, State, Errors, fun scan_number/6);
484
 
scan_number([C|Cs], Stack, Toks, Pos, State, Errors) when C >= $0, C =< $9 ->
485
 
    scan_number(Cs, [C|Stack], Toks, Pos, State, Errors);
486
 
scan_number([$#|Cs], Stack, Toks, Pos, State, Errors) ->
487
 
    case catch list_to_integer(reverse(Stack)) of
488
 
        B when is_integer(B), B >= 2, B =< 1+$Z-$A+10 ->
489
 
            scan_based_int(Cs, [B], Toks, Pos, State, Errors);
490
 
        B ->
491
 
            scan(Cs, [], Toks, Pos, State, [{{base,B},Pos}|Errors])
 
1050
scan_number([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
 
1051
    scan_number(Cs, St, Line, Col, Toks, [C|Ncs]);
 
1052
scan_number([$.,C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
 
1053
    scan_fraction(Cs, St, Line, Col, Toks, [C,$.|Ncs]);
 
1054
scan_number([$.]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1055
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_number/6}};
 
1056
scan_number([$#|Cs], St, Line, Col, Toks, Ncs0) ->
 
1057
    Ncs = lists:reverse(Ncs0),
 
1058
    case catch list_to_integer(Ncs) of
 
1059
        B when B >= 2, B =< 1+$Z-$A+10 ->
 
1060
            Bcs = ?STR(Col, Ncs++[$#]),
 
1061
            scan_based_int(Cs, St, Line, Col, Toks, {B,[],Bcs});
 
1062
        B ->
 
1063
            Len = length(Ncs),
 
1064
            scan_error({base,B}, Line, Col, Line, incr_column(Col, Len))
492
1065
    end;
493
 
scan_number([], Stack, Toks, Pos, State, Errors) ->
494
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_number/6);
495
 
scan_number(Cs, Stack, Toks, Pos, State, Errors) ->
496
 
    case catch list_to_integer(reverse(Stack)) of
497
 
        N when is_integer(N) ->
498
 
            scan(Cs, [], [{integer,Pos,N}|Toks], Pos, State, Errors);
499
 
        _ ->
500
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,integer},Pos}|Errors])
501
 
    end.
502
 
 
503
 
scan_based_int([C|Cs], [B|Stack], Toks, Pos, State, Errors) 
504
 
  when C >= $0, C =< $9, C < $0+B ->
505
 
    scan_based_int(Cs, [B,C|Stack], Toks, Pos, State, Errors);
506
 
scan_based_int([C|Cs], [B|Stack], Toks, Pos, State, Errors) 
507
 
  when C >= $A, B > 10, C < $A+B-10 ->
508
 
    scan_based_int(Cs, [B,C|Stack], Toks, Pos, State, Errors);
509
 
scan_based_int([C|Cs], [B|Stack], Toks, Pos, State, Errors) 
510
 
  when C >= $a, B > 10, C < $a+B-10 ->
511
 
    scan_based_int(Cs, [B,C|Stack], Toks, Pos, State, Errors);
512
 
scan_based_int([], Stack, Toks, Pos, State, Errors) ->
513
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_based_int/6);
514
 
scan_based_int(Cs, [B|Stack], Toks, Pos, State, Errors) ->
515
 
    case catch erlang:list_to_integer(reverse(Stack), B) of
516
 
        N when is_integer(N) ->
517
 
            scan(Cs, [], [{integer,Pos,N}|Toks], Pos, State, Errors);
518
 
        _ ->
519
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,integer},Pos}|Errors])
520
 
    end.
521
 
 
522
 
scan_fraction([C|Cs], Stack, Toks, Pos, State, Errors) when C >= $0, C =< $9 ->
523
 
    scan_fraction(Cs, [C|Stack], Toks, Pos, State, Errors);
524
 
scan_fraction([$e|Cs], Stack, Toks, Pos, State, Errors) ->
525
 
    scan_exponent_sign(Cs, [$E|Stack], Toks, Pos, State, Errors);
526
 
scan_fraction([$E|Cs], Stack, Toks, Pos, State, Errors) ->
527
 
    scan_exponent_sign(Cs, [$E|Stack], Toks, Pos, State, Errors);
528
 
scan_fraction([], Stack, Toks, Pos, State, Errors) ->
529
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_fraction/6);
530
 
scan_fraction(Cs, Stack, Toks, Pos, State, Errors) ->
531
 
    case catch list_to_float(reverse(Stack)) of
532
 
        F when is_float(F) ->
533
 
            scan(Cs, [], [{float,Pos,F}|Toks], Pos, State, Errors);
534
 
        _ ->
535
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,float},Pos}|Errors])
536
 
    end.
537
 
 
538
 
scan_exponent_sign([$+|Cs], Stack, Toks, Pos, State, Errors) ->
539
 
    scan_exponent(Cs, [$+|Stack], Toks, Pos, State, Errors);
540
 
scan_exponent_sign([$-|Cs], Stack, Toks, Pos, State, Errors) ->
541
 
    scan_exponent(Cs, [$-|Stack], Toks, Pos, State, Errors);
542
 
scan_exponent_sign([], Stack, Toks, Pos, State, Errors) ->
543
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_exponent_sign/6);
544
 
scan_exponent_sign(Cs, Stack, Toks, Pos, State, Errors) ->
545
 
    scan_exponent(Cs, Stack, Toks, Pos, State, Errors).
546
 
        
547
 
scan_exponent([C|Cs], Stack, Toks, Pos, State, Errors) when C >= $0, C =< $9 ->
548
 
    scan_exponent(Cs, [C|Stack], Toks, Pos, State, Errors);
549
 
scan_exponent([], Stack, Toks, Pos, State, Errors) ->
550
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_exponent/6);
551
 
scan_exponent(Cs, Stack, Toks, Pos, State, Errors) ->
552
 
    case catch list_to_float(reverse(Stack)) of
553
 
        F when is_float(F) ->
554
 
            scan(Cs, [], [{float,Pos,F}|Toks], Pos, State, Errors);
555
 
        _ ->
556
 
            scan(Cs, [], Toks, Pos, State, [{{illegal,float},Pos}|Errors])
557
 
    end.
558
 
 
559
 
 
560
 
scan_comment([$\n|Cs], Stack, Toks, Pos, State, Errors) ->
561
 
    scan(Cs, Stack, Toks, Pos+1, State, Errors);
562
 
scan_comment([_|Cs], Stack, Toks, Pos, State, Errors) ->
563
 
    scan_comment(Cs, Stack, Toks, Pos, State, Errors);
564
 
scan_comment([], Stack, Toks, Pos, State, Errors) ->
565
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_comment/6);
566
 
scan_comment(Eof, _Stack, Toks, Pos, State, Errors) ->
567
 
    done(Eof, Errors, Toks, Pos, State).
568
 
 
569
 
 
570
 
 
571
 
scan_dot([$%|_]=Cs, _Stack, Toks, Pos, State, Errors) ->
572
 
    done(Cs, Errors, [{dot,Pos}|Toks], Pos, State);
573
 
scan_dot([$\n|Cs], _Stack, Toks, Pos, State, Errors) ->
574
 
    done(Cs, Errors, [{dot,Pos}|Toks], Pos+1, State);
575
 
scan_dot([C|Cs], _Stack, Toks, Pos, State, Errors) when C>=$\000, C=<$\s ->
576
 
    done(Cs, Errors, [{dot,Pos}|Toks], Pos, State);
577
 
scan_dot([C|Cs], _Stack, Toks, Pos, State, Errors) when C>=$\200, C=<$\240 ->
578
 
    done(Cs, Errors, [{dot,Pos}|Toks], Pos, State);
579
 
scan_dot([], Stack, Toks, Pos, State, Errors) ->
580
 
    more([], Stack, Toks, Pos, State, Errors, fun scan_dot/6);
581
 
scan_dot(eof, _Stack, Toks, Pos, State, Errors) ->
582
 
    done(eof, Errors, [{dot,Pos}|Toks], Pos, State);
583
 
scan_dot(Cs, Stack, Toks, Pos, State, Errors) ->
584
 
    scan(Cs, Stack, [{'.',Pos}|Toks], Pos, State, Errors).
585
 
 
586
 
 
587
 
%% reserved_word(Atom) -> Bool
588
 
%%   return 'true' if Atom is an Erlang reserved word, else 'false'.
589
 
 
 
1066
scan_number([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1067
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_number/6}};
 
1068
scan_number(Cs, St, Line, Col, Toks, Ncs0) ->
 
1069
    Ncs = lists:reverse(Ncs0),
 
1070
    case catch list_to_integer(Ncs) of
 
1071
        N when is_integer(N) ->
 
1072
            tok3(Cs, St, Line, Col, Toks, integer, Ncs, N);
 
1073
        _ ->
 
1074
            Ncol = incr_column(Col, length(Ncs)),
 
1075
            scan_error({illegal,integer}, Line, Col, Line, Ncol)
 
1076
    end.
 
1077
    
 
1078
scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
 
1079
    when ?DIGIT(C), C < $0+B ->
 
1080
    scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
 
1081
scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
 
1082
    when C >= $A, B > 10, C < $A+B-10 ->
 
1083
    scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
 
1084
scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
 
1085
    when C >= $a, B > 10, C < $a+B-10 ->
 
1086
    scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
 
1087
scan_based_int([]=Cs, _St, Line, Col, Toks, State) ->
 
1088
    {more,{Cs,Col,Toks,Line,State,fun scan_based_int/6}};
 
1089
scan_based_int(Cs, St, Line, Col, Toks, {B,Ncs0,Bcs}) ->
 
1090
    Ncs = lists:reverse(Ncs0),
 
1091
    case catch erlang:list_to_integer(Ncs, B) of
 
1092
        N when is_integer(N) ->
 
1093
            tok3(Cs, St, Line, Col, Toks, integer, ?STR(Col, Bcs++Ncs), N);
 
1094
        _ ->
 
1095
            Len = length(Bcs)+length(Ncs),
 
1096
            Ncol = incr_column(Col, Len),
 
1097
            scan_error({illegal,integer}, Line, Col, Line, Ncol)
 
1098
    end.
 
1099
 
 
1100
scan_fraction([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
 
1101
    scan_fraction(Cs, St, Line, Col, Toks, [C|Ncs]);
 
1102
scan_fraction([E|Cs], St, Line, Col, Toks, Ncs) when E =:= $e; E =:= $E ->
 
1103
    scan_exponent_sign(Cs, St, Line, Col, Toks, [E|Ncs]);
 
1104
scan_fraction([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1105
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_fraction/6}};
 
1106
scan_fraction(Cs, St, Line, Col, Toks, Ncs) ->
 
1107
    float_end(Cs, St, Line, Col, Toks, Ncs).
 
1108
 
 
1109
scan_exponent_sign([C|Cs], St, Line, Col, Toks, Ncs) when C =:= $+; C =:= $- ->
 
1110
    scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs]);
 
1111
scan_exponent_sign([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1112
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_exponent_sign/6}};
 
1113
scan_exponent_sign(Cs, St, Line, Col, Toks, Ncs) ->
 
1114
    scan_exponent(Cs, St, Line, Col, Toks, Ncs).
 
1115
 
 
1116
scan_exponent([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
 
1117
    scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs]);
 
1118
scan_exponent([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1119
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_exponent/6}};
 
1120
scan_exponent(Cs, St, Line, Col, Toks, Ncs) ->
 
1121
    float_end(Cs, St, Line, Col, Toks, Ncs).
 
1122
 
 
1123
float_end(Cs, St, Line, Col, Toks, Ncs0) ->
 
1124
    Ncs = lists:reverse(Ncs0),
 
1125
    case catch list_to_float(Ncs) of
 
1126
        F when is_float(F) ->
 
1127
            tok3(Cs, St, Line, Col, Toks, float, Ncs, F);
 
1128
        _ ->
 
1129
            Ncol = incr_column(Col, length(Ncs)),
 
1130
            scan_error({illegal,float}, Line, Col, Line, Ncol)
 
1131
    end.
 
1132
 
 
1133
skip_comment([C|Cs], St, Line, Col, Toks, N) when C =/= $\n, ?CHAR(C) ->
 
1134
    skip_comment(Cs, St, Line, Col, Toks, N+1);
 
1135
skip_comment([]=Cs, _St, Line, Col, Toks, N) ->
 
1136
    {more,{Cs,Col,Toks,Line,N,fun skip_comment/6}};
 
1137
skip_comment(Cs, St, Line, Col, Toks, N) ->
 
1138
    scan1(Cs, St, Line, incr_column(Col, N), Toks).
 
1139
 
 
1140
scan_comment([C|Cs], St, Line, Col, Toks, Ncs) when C =/= $\n, ?CHAR(C) ->
 
1141
    scan_comment(Cs, St, Line, Col, Toks, [C|Ncs]);
 
1142
scan_comment([]=Cs, _St, Line, Col, Toks, Ncs) ->
 
1143
    {more,{Cs,Col,Toks,Line,Ncs,fun scan_comment/6}};
 
1144
scan_comment(Cs, St, Line, Col, Toks, Ncs0) ->
 
1145
    Ncs = lists:reverse(Ncs0),
 
1146
    tok3(Cs, St, Line, Col, Toks, comment, Ncs, Ncs).
 
1147
 
 
1148
tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P) ->
 
1149
    scan1(Cs, St, Line, Col, [{P,Line}|Toks]);
 
1150
tok2(Cs, St, Line, Col, Toks, Wcs, P) ->
 
1151
    Attrs = attributes(Line, Col, St, Wcs),
 
1152
    scan1(Cs, St, Line, incr_column(Col, length(Wcs)), [{P,Attrs}|Toks]).
 
1153
 
 
1154
tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P, _N) ->
 
1155
    scan1(Cs, St, Line, Col, [{P,Line}|Toks]);
 
1156
tok2(Cs, St, Line, Col, Toks, Wcs, P, N) ->
 
1157
    Attrs = attributes(Line, Col, St, Wcs),
 
1158
    scan1(Cs, St, Line, incr_column(Col, N), [{P,Attrs}|Toks]).
 
1159
 
 
1160
tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item, _S, Sym) ->
 
1161
    scan1(Cs, St, Line, Col, [{Item,Line,Sym}|Toks]);
 
1162
tok3(Cs, St, Line, Col, Toks, Item, String, Sym) ->
 
1163
    Token = {Item,attributes(Line, Col, St, String),Sym},
 
1164
    scan1(Cs, St, Line, incr_column(Col, length(String)), [Token|Toks]).
 
1165
 
 
1166
tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item,
 
1167
     _String, Sym, _Length) ->
 
1168
    scan1(Cs, St, Line, Col, [{Item,Line,Sym}|Toks]);
 
1169
tok3(Cs, St, Line, Col, Toks, Item, String, Sym, Length) ->
 
1170
    Token = {Item,attributes(Line, Col, St, String),Sym},
 
1171
    scan1(Cs, St, Line, incr_column(Col, Length), [Token|Toks]).
 
1172
 
 
1173
scan_error(Error, Line, Col, EndLine, EndCol) ->
 
1174
    Loc = location(Line, Col),
 
1175
    EndLoc = location(EndLine, EndCol),
 
1176
    scan_error(Error, Loc, EndLoc).
 
1177
 
 
1178
scan_error(Error, ErrorLoc, EndLoc) ->
 
1179
    {error,{ErrorLoc,?MODULE,Error},EndLoc}.
 
1180
 
 
1181
-compile({inline,[attributes/4]}).
 
1182
 
 
1183
attributes(Line, no_col, #erl_scan{text = false}, _String) ->
 
1184
    Line;
 
1185
attributes(Line, no_col, #erl_scan{text = true}, String) ->
 
1186
    [{line,Line},{text,String}];
 
1187
attributes(Line, Col, #erl_scan{text = false}, _String) ->
 
1188
    {Line,Col};
 
1189
attributes(Line, Col, #erl_scan{text = true}, String) ->
 
1190
    [{line,Line},{column,Col},{text,String}].
 
1191
 
 
1192
location(Line, no_col) ->
 
1193
    Line;
 
1194
location(Line, Col) when is_integer(Col) ->
 
1195
    {Line,Col}.
 
1196
 
 
1197
-compile({inline,[incr_column/2,new_column/2]}).
 
1198
 
 
1199
incr_column(no_col=Col, _N) ->
 
1200
    Col;
 
1201
incr_column(Col, N) when is_integer(Col) ->
 
1202
    Col + N.
 
1203
 
 
1204
new_column(no_col=Col, _Ncol) ->
 
1205
    Col;
 
1206
new_column(Col, Ncol) when is_integer(Col) ->
 
1207
    Ncol.
 
1208
 
 
1209
nl_spcs(2)  -> "\n ";
 
1210
nl_spcs(3)  -> "\n  ";
 
1211
nl_spcs(4)  -> "\n   ";
 
1212
nl_spcs(5)  -> "\n    ";
 
1213
nl_spcs(6)  -> "\n     ";
 
1214
nl_spcs(7)  -> "\n      ";
 
1215
nl_spcs(8)  -> "\n       ";
 
1216
nl_spcs(9)  -> "\n        ";
 
1217
nl_spcs(10) -> "\n         ";
 
1218
nl_spcs(11) -> "\n          ";
 
1219
nl_spcs(12) -> "\n           ";
 
1220
nl_spcs(13) -> "\n            ";
 
1221
nl_spcs(14) -> "\n             ";
 
1222
nl_spcs(15) -> "\n              ";
 
1223
nl_spcs(16) -> "\n               ";
 
1224
nl_spcs(17) -> "\n                ".
 
1225
 
 
1226
spcs(1)  -> " ";
 
1227
spcs(2)  -> "  ";
 
1228
spcs(3)  -> "   ";
 
1229
spcs(4)  -> "    ";
 
1230
spcs(5)  -> "     ";
 
1231
spcs(6)  -> "      ";
 
1232
spcs(7)  -> "       ";
 
1233
spcs(8)  -> "        ";
 
1234
spcs(9)  -> "         ";
 
1235
spcs(10) -> "          ";
 
1236
spcs(11) -> "           ";
 
1237
spcs(12) -> "            ";
 
1238
spcs(13) -> "             ";
 
1239
spcs(14) -> "              ";
 
1240
spcs(15) -> "               ";
 
1241
spcs(16) -> "                ".
 
1242
 
 
1243
nl_tabs(2)  -> "\n\t";
 
1244
nl_tabs(3)  -> "\n\t\t";
 
1245
nl_tabs(4)  -> "\n\t\t\t";
 
1246
nl_tabs(5)  -> "\n\t\t\t\t";
 
1247
nl_tabs(6)  -> "\n\t\t\t\t\t";
 
1248
nl_tabs(7)  -> "\n\t\t\t\t\t\t";
 
1249
nl_tabs(8)  -> "\n\t\t\t\t\t\t\t";
 
1250
nl_tabs(9)  -> "\n\t\t\t\t\t\t\t\t";
 
1251
nl_tabs(10) -> "\n\t\t\t\t\t\t\t\t\t";
 
1252
nl_tabs(11) -> "\n\t\t\t\t\t\t\t\t\t\t".
 
1253
    
 
1254
tabs(1)  ->  "\t";
 
1255
tabs(2)  ->  "\t\t";
 
1256
tabs(3)  ->  "\t\t\t";
 
1257
tabs(4)  ->  "\t\t\t\t";
 
1258
tabs(5)  ->  "\t\t\t\t\t";
 
1259
tabs(6)  ->  "\t\t\t\t\t\t";
 
1260
tabs(7)  ->  "\t\t\t\t\t\t\t";
 
1261
tabs(8)  ->  "\t\t\t\t\t\t\t\t";
 
1262
tabs(9)  ->  "\t\t\t\t\t\t\t\t\t";
 
1263
tabs(10) ->  "\t\t\t\t\t\t\t\t\t\t".
 
1264
 
 
1265
-spec reserved_word(atom()) -> bool().
590
1266
reserved_word('after') -> true;
591
1267
reserved_word('begin') -> true;
592
1268
reserved_word('case') -> true;