~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/parsetools/include/leexinc.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% The source of this file is part of leex distribution, as such it
 
2
%% has the same Copyright as the other files in the leex
 
3
%% distribution. The Copyright is defined in the accompanying file
 
4
%% COPYRIGHT. However, the resultant scanner generated by leex is the
 
5
%% property of the creator of the scanner and is not covered by that
 
6
%% Copyright.
 
7
 
 
8
##module
 
9
 
 
10
-export([string/1,string/2,token/2,token/3,tokens/2,tokens/3]).
 
11
-export([format_error/1]).
 
12
 
 
13
%% User code. This is placed here to allow extra attributes.
 
14
##code
 
15
 
 
16
format_error({illegal,S}) -> ["illegal characters ",io_lib:write_string(S)];
 
17
format_error({user,S}) -> S.
 
18
 
 
19
string(String) -> string(String, 1).
 
20
 
 
21
string(String, Line) -> string(String, Line, String, []).
 
22
 
 
23
%% string(InChars, Line, TokenChars, Tokens) ->
 
24
%% {ok,Tokens,Line} | {error,ErrorInfo,Line}.
 
25
%% Note the line number going into yystate, L0, is line of token
 
26
%% start while line number returned is line of token end. We want line
 
27
%% of token start.
 
28
 
 
29
string([], L, [], Ts) ->                     % No partial tokens!
 
30
    {ok,yyrev(Ts),L};
 
31
string(Ics0, L0, Tcs, Ts) ->
 
32
    case yystate(yystate(), Ics0, L0, 0, reject, 0) of
 
33
        {A,Alen,Ics1,L1} ->                  % Accepting end state
 
34
            string_cont(Ics1, L1, yyaction(A, Alen, Tcs, L0), Ts);
 
35
        {A,Alen,Ics1,L1,_S1} ->              % Accepting transistion state
 
36
            string_cont(Ics1, L1, yyaction(A, Alen, Tcs, L0), Ts);
 
37
        {reject,_Alen,Tlen,_Ics1,L1,_S1} ->  % After a non-accepting state
 
38
            {error,{L0,?MODULE,{illegal,yypre(Tcs, Tlen+1)}},L1};
 
39
        {A,Alen,_Tlen,_Ics1,L1,_S1} ->
 
40
            string_cont(yysuf(Tcs, Alen), L1, yyaction(A, Alen, Tcs, L0), Ts)
 
41
    end.
 
42
 
 
43
%% string_cont(RestChars, Line, Token, Tokens)
 
44
%% Test for and remove the end token wrapper. Push back characters
 
45
%% are prepended to RestChars.
 
46
 
 
47
string_cont(Rest, Line, {token,T}, Ts) ->
 
48
    string(Rest, Line, Rest, [T|Ts]);
 
49
string_cont(Rest, Line, {token,T,Push}, Ts) ->
 
50
    NewRest = Push ++ Rest,
 
51
    string(NewRest, Line, NewRest, [T|Ts]);
 
52
string_cont(Rest, Line, {end_token,T}, Ts) ->
 
53
    string(Rest, Line, Rest, [T|Ts]);
 
54
string_cont(Rest, Line, {end_token,T,Push}, Ts) ->
 
55
    NewRest = Push ++ Rest,
 
56
    string(NewRest, Line, NewRest, [T|Ts]);
 
57
string_cont(Rest, Line, skip_token, Ts) ->
 
58
    string(Rest, Line, Rest, Ts);
 
59
string_cont(Rest, Line, {skip_token,Push}, Ts) ->
 
60
    NewRest = Push ++ Rest,
 
61
    string(NewRest, Line, NewRest, Ts);
 
62
string_cont(_Rest, Line, {error,S}, _Ts) ->
 
63
    {error,{Line,?MODULE,{user,S}},Line}.
 
64
 
 
65
%% token(Continuation, Chars) ->
 
66
%% token(Continuation, Chars, Line) ->
 
67
%% {more,Continuation} | {done,ReturnVal,RestChars}.
 
68
%% Must be careful when re-entering to append the latest characters to the
 
69
%% after characters in an accept. The continuation is:
 
70
%% {token,State,CurrLine,TokenChars,TokenLen,TokenLine,AccAction,AccLen}
 
71
 
 
72
token(Cont, Chars) -> token(Cont, Chars, 1).
 
73
 
 
74
token([], Chars, Line) ->
 
75
    token(yystate(), Chars, Line, Chars, 0, Line, reject, 0);
 
76
token({token,State,Line,Tcs,Tlen,Tline,Action,Alen}, Chars, _) ->
 
77
    token(State, Chars, Line, Tcs ++ Chars, Tlen, Tline, Action, Alen).
 
78
 
 
79
%% token(State, InChars, Line, TokenChars, TokenLen, TokenLine,
 
80
%% AcceptAction, AcceptLen) ->
 
81
%% {more,Continuation} | {done,ReturnVal,RestChars}.
 
82
%% The argument order is chosen to be more efficient.
 
83
 
 
84
token(S0, Ics0, L0, Tcs, Tlen0, Tline, A0, Alen0) ->
 
85
    case yystate(S0, Ics0, L0, Tlen0, A0, Alen0) of
 
86
        %% Accepting end state, we have a token.
 
87
        {A1,Alen1,Ics1,L1} ->
 
88
            token_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline));
 
89
        %% Accepting transition state, can take more chars.
 
90
        {A1,Alen1,[],L1,S1} ->                  % Need more chars to check
 
91
            {more,{token,S1,L1,Tcs,Alen1,Tline,A1,Alen1}};
 
92
        {A1,Alen1,Ics1,L1,_S1} ->               % Take what we got
 
93
            token_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline));
 
94
        %% After a non-accepting state, maybe reach accept state later.
 
95
        {A1,Alen1,Tlen1,[],L1,S1} ->            % Need more chars to check
 
96
            {more,{token,S1,L1,Tcs,Tlen1,Tline,A1,Alen1}};
 
97
        {reject,_Alen1,Tlen1,eof,L1,_S1} ->     % No token match
 
98
            %% Check for partial token which is error.
 
99
            Ret = if Tlen1 > 0 -> {error,{Tline,?MODULE,
 
100
                                          %% Skip eof tail in Tcs.
 
101
                                          {illegal,yypre(Tcs, Tlen1)}},L1};
 
102
                     true -> {eof,L1}
 
103
                  end,
 
104
            {done,Ret,eof};
 
105
        {reject,_Alen1,Tlen1,Ics1,L1,_S1} ->    % No token match
 
106
            Error = {Tline,?MODULE,{illegal,yypre(Tcs, Tlen1+1)}},
 
107
            {done,{error,Error,L1},Ics1};
 
108
        {A1,Alen1,_Tlen1,_Ics1,L1,_S1} ->       % Use last accept match
 
109
            token_cont(yysuf(Tcs, Alen1), L1, yyaction(A1, Alen1, Tcs, Tline))
 
110
    end.
 
111
 
 
112
%% token_cont(RestChars, Line, Token)
 
113
%% If we have a token or error then return done, else if we have a
 
114
%% skip_token then continue.
 
115
 
 
116
token_cont(Rest, Line, {token,T}) ->
 
117
    {done,{ok,T,Line},Rest};
 
118
token_cont(Rest, Line, {token,T,Push}) ->
 
119
    NewRest = Push ++ Rest,
 
120
    {done,{ok,T,Line},NewRest};
 
121
token_cont(Rest, Line, {end_token,T}) ->
 
122
    {done,{ok,T,Line},Rest};
 
123
token_cont(Rest, Line, {end_token,T,Push}) ->
 
124
    NewRest = Push ++ Rest,
 
125
    {done,{ok,T,Line},NewRest};
 
126
token_cont(Rest, Line, skip_token) ->
 
127
    token(yystate(), Rest, Line, Rest, 0, Line, reject, 0);
 
128
token_cont(Rest, Line, {skip_token,Push}) ->
 
129
    NewRest = Push ++ Rest,
 
130
    token(yystate(), NewRest, Line, NewRest, 0, Line, reject, 0);
 
131
token_cont(Rest, Line, {error,S}) ->
 
132
    {done,{error,{Line,?MODULE,{user,S}},Line},Rest}.
 
133
 
 
134
%% tokens(Continuation, Chars, Line) ->
 
135
%% {more,Continuation} | {done,ReturnVal,RestChars}.
 
136
%% Must be careful when re-entering to append the latest characters to the
 
137
%% after characters in an accept. The continuation is:
 
138
%% {tokens,State,CurrLine,TokenChars,TokenLen,TokenLine,Tokens,AccAction,AccLen}
 
139
%% {skip_tokens,State,CurrLine,TokenChars,TokenLen,TokenLine,Error,AccAction,AccLen}
 
140
 
 
141
tokens(Cont, Chars) -> tokens(Cont, Chars, 1).
 
142
 
 
143
tokens([], Chars, Line) ->
 
144
    tokens(yystate(), Chars, Line, Chars, 0, Line, [], reject, 0);
 
145
tokens({tokens,State,Line,Tcs,Tlen,Tline,Ts,Action,Alen}, Chars, _) ->
 
146
    tokens(State, Chars, Line, Tcs ++ Chars, Tlen, Tline, Ts, Action, Alen);
 
147
tokens({skip_tokens,State,Line,Tcs,Tlen,Tline,Error,Action,Alen}, Chars, _) ->
 
148
    skip_tokens(State, Chars, Line, Tcs ++ Chars, Tlen, Tline, Error, Action, Alen).
 
149
 
 
150
%% tokens(State, InChars, Line, TokenChars, TokenLen, TokenLine, Tokens,
 
151
%% AcceptAction, AcceptLen) ->
 
152
%% {more,Continuation} | {done,ReturnVal,RestChars}.
 
153
 
 
154
tokens(S0, Ics0, L0, Tcs, Tlen0, Tline, Ts, A0, Alen0) ->
 
155
    case yystate(S0, Ics0, L0, Tlen0, A0, Alen0) of
 
156
        %% Accepting end state, we have a token.
 
157
        {A1,Alen1,Ics1,L1} ->
 
158
            tokens_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline), Ts);
 
159
        %% Accepting transition state, can take more chars.
 
160
        {A1,Alen1,[],L1,S1} ->                  % Need more chars to check
 
161
            {more,{tokens,S1,L1,Tcs,Alen1,Tline,Ts,A1,Alen1}};
 
162
        {A1,Alen1,Ics1,L1,_S1} ->               % Take what we got
 
163
            tokens_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline), Ts);
 
164
        %% After a non-accepting state, maybe reach accept state later.
 
165
        {A1,Alen1,Tlen1,[],L1,S1} ->            % Need more chars to check
 
166
            {more,{tokens,S1,L1,Tcs,Tlen1,Tline,Ts,A1,Alen1}};
 
167
        {reject,_Alen1,Tlen1,eof,L1,_S1} ->     % No token match
 
168
            %% Check for partial token which is error, no need to skip here.
 
169
            Ret = if Tlen1 > 0 -> {error,{Tline,?MODULE,
 
170
                                          %% Skip eof tail in Tcs.
 
171
                                          {illegal,yypre(Tcs, Tlen1)}},L1};
 
172
                     Ts == [] -> {eof,L1};
 
173
                     true -> {ok,yyrev(Ts),L1}
 
174
                  end,
 
175
            {done,Ret,eof};
 
176
        {reject,_Alen1,Tlen1,_Ics1,L1,_S1} ->
 
177
            %% Skip rest of tokens.
 
178
            Error = {L1,?MODULE,{illegal,yypre(Tcs, Tlen1+1)}},
 
179
            skip_tokens(yysuf(Tcs, Tlen1+1), L1, Error);
 
180
        {A1,Alen1,_Tlen1,_Ics1,L1,_S1} ->
 
181
            Token = yyaction(A1, Alen1, Tcs, Tline),
 
182
            tokens_cont(yysuf(Tcs, Alen1), L1, Token, Ts)
 
183
    end.
 
184
 
 
185
%% tokens_cont(RestChars, Line, Token, Tokens)
 
186
%% If we have an end_token or error then return done, else if we have
 
187
%% a token then save it and continue, else if we have a skip_token
 
188
%% just continue.
 
189
 
 
190
tokens_cont(Rest, Line, {token,T}, Ts) ->
 
191
    tokens(yystate(), Rest, Line, Rest, 0, Line, [T|Ts], reject, 0);
 
192
tokens_cont(Rest, Line, {token,T,Push}, Ts) ->
 
193
    NewRest = Push ++ Rest,
 
194
    tokens(yystate(), NewRest, Line, NewRest, 0, Line, [T|Ts], reject, 0);
 
195
tokens_cont(Rest, Line, {end_token,T}, Ts) ->
 
196
    {done,{ok,yyrev(Ts, [T]),Line},Rest};
 
197
tokens_cont(Rest, Line, {end_token,T,Push}, Ts) ->
 
198
    NewRest = Push ++ Rest,
 
199
    {done,{ok,yyrev(Ts, [T]),Line},NewRest};
 
200
tokens_cont(Rest, Line, skip_token, Ts) ->
 
201
    tokens(yystate(), Rest, Line, Rest, 0, Line, Ts, reject, 0);
 
202
tokens_cont(Rest, Line, {skip_token,Push}, Ts) ->
 
203
    NewRest = Push ++ Rest,
 
204
    tokens(yystate(), NewRest, Line, NewRest, 0, Line, Ts, reject, 0);
 
205
tokens_cont(Rest, Line, {error,S}, _Ts) ->
 
206
    skip_tokens(Rest, Line, {Line,?MODULE,{user,S}}).
 
207
 
 
208
%%skip_tokens(InChars, Line, Error) -> {done,{error,Error,Line},Ics}.
 
209
%% Skip tokens until an end token, junk everything and return the error.
 
210
 
 
211
skip_tokens(Ics, Line, Error) ->
 
212
    skip_tokens(yystate(), Ics, Line, Ics, 0, Line, Error, reject, 0).
 
213
 
 
214
%% skip_tokens(State, InChars, Line, TokenChars, TokenLen, TokenLine, Tokens,
 
215
%% AcceptAction, AcceptLen) ->
 
216
%% {more,Continuation} | {done,ReturnVal,RestChars}.
 
217
 
 
218
skip_tokens(S0, Ics0, L0, Tcs, Tlen0, Tline, Error, A0, Alen0) ->
 
219
    case yystate(S0, Ics0, L0, Tlen0, A0, Alen0) of
 
220
        {A1,Alen1,Ics1,L1} ->                  % Accepting end state
 
221
            skip_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline), Error);
 
222
        {A1,Alen1,[],L1,S1} ->                 % After an accepting state
 
223
            {more,{skip_tokens,S1,L1,Tcs,Alen1,Tline,Error,A1,Alen1}};
 
224
        {A1,Alen1,Ics1,L1,_S1} ->
 
225
            skip_cont(Ics1, L1, yyaction(A1, Alen1, Tcs, Tline), Error);
 
226
        {A1,Alen1,Tlen1,[],L1,S1} ->           % After a non-accepting state
 
227
            {more,{skip_tokens,S1,L1,Tcs,Tlen1,Tline,Error,A1,Alen1}};
 
228
        {reject,_Alen1,_Tlen1,eof,L1,_S1} ->
 
229
            {done,{error,Error,L1},eof};
 
230
        {reject,_Alen1,Tlen1,_Ics1,L1,_S1} ->
 
231
            skip_tokens(yysuf(Tcs, Tlen1+1), L1, Error);
 
232
        {A1,Alen1,_Tlen1,_Ics1,L1,_S1} ->
 
233
            Token = yyaction(A1, Alen1, Tcs, Tline),
 
234
            skip_cont(yysuf(Tcs, Alen1), L1, Token, Error)
 
235
    end.
 
236
 
 
237
%% skip_cont(RestChars, Line, Token, Error)
 
238
%% Skip tokens until we have an end_token or error then return done
 
239
%% with the original rror.
 
240
 
 
241
skip_cont(Rest, Line, {token,_T}, Error) ->
 
242
    skip_tokens(yystate(), Rest, Line, Rest, 0, Line, Error, reject, 0);
 
243
skip_cont(Rest, Line, {token,_T,Push}, Error) ->
 
244
    NewRest = Push ++ Rest,
 
245
    skip_tokens(yystate(), NewRest, Line, NewRest, 0, Line, Error, reject, 0);
 
246
skip_cont(Rest, Line, {end_token,_T}, Error) ->
 
247
    {done,{error,Error,Line},Rest};
 
248
skip_cont(Rest, Line, {end_token,_T,Push}, Error) ->
 
249
    NewRest = Push ++ Rest,
 
250
    {done,{error,Error,Line},NewRest};
 
251
skip_cont(Rest, Line, skip_token, Error) ->
 
252
    skip_tokens(yystate(), Rest, Line, Rest, 0, Line, Error, reject, 0);
 
253
skip_cont(Rest, Line, {skip_token,Push}, Error) ->
 
254
    NewRest = Push ++ Rest,
 
255
    skip_tokens(yystate(), NewRest, Line, NewRest, 0, Line, Error, reject, 0);
 
256
skip_cont(Rest, Line, {error,_S}, Error) ->
 
257
    skip_tokens(yystate(), Rest, Line, Rest, 0, Line, Error, reject, 0).
 
258
 
 
259
yyrev(List) -> lists:reverse(List).
 
260
yyrev(List, Tail) -> lists:reverse(List, Tail).
 
261
yypre(List, N) -> lists:sublist(List, N).
 
262
yysuf(List, N) -> lists:nthtail(N, List).
 
263
 
 
264
%% yystate() -> InitialState.
 
265
%% yystate(State, InChars, Line, CurrTokLen, AcceptAction, AcceptLen) ->
 
266
%% {Action, AcceptLen, RestChars, Line} |
 
267
%% {Action, AcceptLen, RestChars, Line, State} |
 
268
%% {reject, AcceptLen, CurrTokLen, RestChars, Line, State} |
 
269
%% {Action, AcceptLen, CurrTokLen, RestChars, Line, State}.
 
270
%% Generated state transition functions. The non-accepting end state
 
271
%% return signal either an unrecognised character or end of current
 
272
%% input.
 
273
 
 
274
##dfa
 
275
 
 
276
%% yyaction(Action, TokenLength, TokenChars, TokenLine) ->
 
277
%% {token,Token} | {end_token, Token} | skip_token | {error,String}.
 
278
%% Generated action function.
 
279
 
 
280
##actions
 
281