~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/parsetools/src/yeccparser.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
16
16
-file("/clearcase/otp/erts/lib/parsetools/include/yeccpre.hrl", 0).
17
17
%%
18
18
%% %CopyrightBegin%
19
 
%% 
20
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
21
 
%% 
 
19
%%
 
20
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
21
%%
22
22
%% The contents of this file are subject to the Erlang Public License,
23
23
%% Version 1.1, (the "License"); you may not use this file except in
24
24
%% compliance with the License. You should have received a copy of the
25
25
%% Erlang Public License along with this software. If not, it can be
26
26
%% retrieved online at http://www.erlang.org/.
27
 
%% 
 
27
%%
28
28
%% Software distributed under the License is distributed on an "AS IS"
29
29
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
30
30
%% the License for the specific language governing rights and limitations
31
31
%% under the License.
32
 
%% 
 
32
%%
33
33
%% %CopyrightEnd%
34
34
%%
35
35
 
36
36
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
37
37
% The parser generator will insert appropriate declarations before this line.%
38
38
 
39
 
-type(yecc_ret() :: {'error', _} | {'ok', _}).
 
39
-type yecc_ret() :: {'error', _} | {'ok', _}.
40
40
 
41
 
-spec(parse/1 :: (_) -> yecc_ret()).
 
41
-spec parse(Tokens :: list()) -> yecc_ret().
42
42
parse(Tokens) ->
43
 
    yeccpars0(Tokens, false).
 
43
    yeccpars0(Tokens, {no_func, no_line}, 0, [], []).
44
44
 
45
 
-spec(parse_and_scan/1 ::
46
 
      ({function() | {atom(), atom()}, [_]} | {atom(), atom(), [_]}) ->
47
 
            yecc_ret()).
 
45
-spec parse_and_scan({function() | {atom(), atom()}, [_]}
 
46
                     | {atom(), atom(), [_]}) -> yecc_ret().
48
47
parse_and_scan({F, A}) -> % Fun or {M, F}
49
 
    yeccpars0([], {F, A});
 
48
    yeccpars0([], {{F, A}, no_line}, 0, [], []);
50
49
parse_and_scan({M, F, A}) ->
51
 
    yeccpars0([], {{M, F}, A}).
 
50
    yeccpars0([], {{{M, F}, A}, no_line}, 0, [], []).
52
51
 
53
 
-spec(format_error/1 :: (any()) -> [char() | list()]).
 
52
-spec format_error(any()) -> [char() | list()].
54
53
format_error(Message) ->
55
54
    case io_lib:deep_char_list(Message) of
56
 
        true ->
57
 
            Message;
58
 
        _ ->
59
 
            io_lib:write(Message)
 
55
        true ->
 
56
            Message;
 
57
        _ ->
 
58
            io_lib:write(Message)
60
59
    end.
61
60
 
62
 
% To be used in grammar files to throw an error message to the parser
63
 
% toplevel. Doesn't have to be exported!
64
 
-compile({nowarn_unused_function,{return_error,2}}).
65
 
-spec(return_error/2 :: (integer(), any()) -> no_return()).
 
61
%% To be used in grammar files to throw an error message to the parser
 
62
%% toplevel. Doesn't have to be exported!
 
63
-compile({nowarn_unused_function, return_error/2}).
 
64
-spec return_error(integer(), any()) -> no_return().
66
65
return_error(Line, Message) ->
67
66
    throw({error, {Line, ?MODULE, Message}}).
68
67
 
69
 
-define(CODE_VERSION, "1.3").
 
68
-define(CODE_VERSION, "1.4").
70
69
 
71
 
yeccpars0(Tokens, MFA) ->
72
 
    try yeccpars1(Tokens, MFA, 0, [], [])
 
70
yeccpars0(Tokens, Tzr, State, States, Vstack) ->
 
71
    try yeccpars1(Tokens, Tzr, State, States, Vstack)
73
72
    catch 
74
73
        error: Error ->
75
74
            Stacktrace = erlang:get_stacktrace(),
76
75
            try yecc_error_type(Error, Stacktrace) of
77
 
                {syntax_error, Token} ->
78
 
                    yeccerror(Token);
79
 
                {missing_in_goto_table=Tag, Symbol, State} ->
80
 
                    Desc = {Symbol, State, Tag},
 
76
                Desc ->
81
77
                    erlang:raise(error, {yecc_bug, ?CODE_VERSION, Desc},
82
 
                                Stacktrace)
 
78
                                 Stacktrace)
83
79
            catch _:_ -> erlang:raise(error, Error, Stacktrace)
84
80
            end;
85
 
        throw: {error, {_Line, ?MODULE, _M}} = Error -> 
86
 
            Error % probably from return_error/2
 
81
        %% Probably thrown from return_error/2:
 
82
        throw: {error, {_Line, ?MODULE, _M}} = Error ->
 
83
            Error
87
84
    end.
88
85
 
89
 
yecc_error_type(function_clause, [{?MODULE,F,[State,_,_,_,Token,_,_]} | _]) ->
 
86
yecc_error_type(function_clause, [{?MODULE,F,ArityOrArgs} | _]) ->
90
87
    case atom_to_list(F) of
91
 
        "yeccpars2" ++ _ ->
92
 
            {syntax_error, Token};
93
88
        "yeccgoto_" ++ SymbolL ->
94
89
            {ok,[{atom,_,Symbol}],_} = erl_scan:string(SymbolL),
95
 
            {missing_in_goto_table, Symbol, State}
 
90
            State = case ArityOrArgs of
 
91
                        [S,_,_,_,_,_,_] -> S;
 
92
                        _ -> state_is_unknown
 
93
                    end,
 
94
            {Symbol, State, missing_in_goto_table}
96
95
    end.
97
96
 
98
 
yeccpars1([Token | Tokens], Tokenizer, State, States, Vstack) ->
99
 
    yeccpars2(State, element(1, Token), States, Vstack, Token, Tokens, 
100
 
              Tokenizer);
101
 
yeccpars1([], {F, A}, State, States, Vstack) ->
 
97
yeccpars1([Token | Tokens], Tzr, State, States, Vstack) ->
 
98
    yeccpars2(State, element(1, Token), States, Vstack, Token, Tokens, Tzr);
 
99
yeccpars1([], {{F, A},_Line}, State, States, Vstack) ->
102
100
    case apply(F, A) of
103
 
        {ok, Tokens, _Endline} ->
104
 
            yeccpars1(Tokens, {F, A}, State, States, Vstack);
105
 
        {eof, _Endline} ->
106
 
            yeccpars1([], false, State, States, Vstack);
 
101
        {ok, Tokens, Endline} ->
 
102
            yeccpars1(Tokens, {{F, A}, Endline}, State, States, Vstack);
 
103
        {eof, Endline} ->
 
104
            yeccpars1([], {no_func, Endline}, State, States, Vstack);
107
105
        {error, Descriptor, _Endline} ->
108
106
            {error, Descriptor}
109
107
    end;
110
 
yeccpars1([], false, State, States, Vstack) ->
111
 
    yeccpars2(State, '$end', States, Vstack, {'$end', 999999}, [], false).
 
108
yeccpars1([], {no_func, no_line}, State, States, Vstack) ->
 
109
    Line = 999999,
 
110
    yeccpars2(State, '$end', States, Vstack, yecc_end(Line), [],
 
111
              {no_func, Line});
 
112
yeccpars1([], {no_func, Endline}, State, States, Vstack) ->
 
113
    yeccpars2(State, '$end', States, Vstack, yecc_end(Endline), [],
 
114
              {no_func, Endline}).
112
115
 
113
116
%% yeccpars1/7 is called from generated code.
114
117
%%
116
119
%% yeccpars1/7 can be found by parsing the file without following
117
120
%% include directives. yecc will otherwise assume that an old
118
121
%% yeccpre.hrl is included (one which defines yeccpars1/5).
119
 
yeccpars1(State1, State, States, Vstack, Stack1, [Token | Tokens], 
120
 
          Tokenizer) ->
 
122
yeccpars1(State1, State, States, Vstack, Token0, [Token | Tokens], Tzr) ->
121
123
    yeccpars2(State, element(1, Token), [State1 | States],
122
 
              [Stack1 | Vstack], Token, Tokens, Tokenizer);
123
 
yeccpars1(State1, State, States, Vstack, Stack1, [], {F, A}) ->
124
 
    case apply(F, A) of
125
 
        {ok, Tokens, _Endline} ->
126
 
            yeccpars1(State1, State, States, Vstack, Stack1, Tokens, {F, A});
127
 
        {eof, _Endline} ->
128
 
            yeccpars1(State1, State, States, Vstack, Stack1, [], false);
129
 
        {error, Descriptor, _Endline} ->
130
 
            {error, Descriptor}
131
 
    end;
132
 
yeccpars1(State1, State, States, Vstack, Stack1, [], false) ->
133
 
    yeccpars2(State, '$end', [State1 | States], [Stack1 | Vstack],
134
 
              {'$end', 999999}, [], false).
135
 
 
136
 
% For internal use only.
 
124
              [Token0 | Vstack], Token, Tokens, Tzr);
 
125
yeccpars1(State1, State, States, Vstack, Token0, [], {{_F,_A}, _Line}=Tzr) ->
 
126
    yeccpars1([], Tzr, State, [State1 | States], [Token0 | Vstack]);
 
127
yeccpars1(State1, State, States, Vstack, Token0, [], {no_func, no_line}) ->
 
128
    Line = yecctoken_end_location(Token0),
 
129
    yeccpars2(State, '$end', [State1 | States], [Token0 | Vstack],
 
130
              yecc_end(Line), [], {no_func, Line});
 
131
yeccpars1(State1, State, States, Vstack, Token0, [], {no_func, Line}) ->
 
132
    yeccpars2(State, '$end', [State1 | States], [Token0 | Vstack],
 
133
              yecc_end(Line), [], {no_func, Line}).
 
134
 
 
135
%% For internal use only.
 
136
yecc_end({Line,_Column}) ->
 
137
    {'$end', Line};
 
138
yecc_end(Line) ->
 
139
    {'$end', Line}.
 
140
 
 
141
yecctoken_end_location(Token) ->
 
142
    try
 
143
        {text, Str} = erl_scan:token_info(Token, text),
 
144
        {line, Line} = erl_scan:token_info(Token, line),
 
145
        Parts = re:split(Str, "\n"),
 
146
        Dline = length(Parts) - 1,
 
147
        Yline = Line + Dline,
 
148
        case erl_scan:token_info(Token, column) of
 
149
            {column, Column} ->
 
150
                Col = byte_size(lists:last(Parts)),
 
151
                {Yline, Col + if Dline =:= 0 -> Column; true -> 1 end};
 
152
            undefined ->
 
153
                Yline
 
154
        end
 
155
    catch _:_ ->
 
156
        yecctoken_location(Token)
 
157
    end.
 
158
 
137
159
yeccerror(Token) ->
138
 
    Text = case catch erl_scan:token_info(Token, text) of
139
 
               {text, Txt} -> Txt;
140
 
               _ -> yecctoken2string(Token)
141
 
           end,
142
 
    Location = case catch erl_scan:token_info(Token, location) of
143
 
                   {location, Loc} -> Loc;
144
 
                   _ -> element(2, Token)
145
 
               end,
 
160
    Text = yecctoken_to_string(Token),
 
161
    Location = yecctoken_location(Token),
146
162
    {error, {Location, ?MODULE, ["syntax error before: ", Text]}}.
147
163
 
 
164
yecctoken_to_string(Token) ->
 
165
    case catch erl_scan:token_info(Token, text) of
 
166
        {text, Txt} -> Txt;
 
167
        _ -> yecctoken2string(Token)
 
168
    end.
 
169
 
 
170
yecctoken_location(Token) ->
 
171
    case catch erl_scan:token_info(Token, location) of
 
172
        {location, Loc} -> Loc;
 
173
        _ -> element(2, Token)
 
174
    end.
 
175
 
148
176
yecctoken2string({atom, _, A}) -> io_lib:write(A);
149
177
yecctoken2string({integer,_,N}) -> io_lib:write(N);
150
178
yecctoken2string({float,_,F}) -> io_lib:write(F);
151
179
yecctoken2string({char,_,C}) -> io_lib:write_char(C);
152
180
yecctoken2string({var,_,V}) -> io_lib:format("~s", [V]);
153
181
yecctoken2string({string,_,S}) -> io_lib:write_unicode_string(S);
154
 
yecctoken2string({reserved_symbol, _, A}) -> io_lib:format("~w", [A]);
155
 
yecctoken2string({_Cat, _, Val}) -> io_lib:format("~w", [Val]);
 
182
yecctoken2string({reserved_symbol, _, A}) -> io_lib:write(A);
 
183
yecctoken2string({_Cat, _, Val}) -> io_lib:write(Val);
156
184
yecctoken2string({dot, _}) -> "'.'";
157
185
yecctoken2string({'$end', _}) ->
158
186
    [];
159
187
yecctoken2string({Other, _}) when is_atom(Other) ->
160
 
    io_lib:format("~w", [Other]);
 
188
    io_lib:write(Other);
161
189
yecctoken2string(Other) ->
162
190
    io_lib:write(Other).
163
191
 
165
193
 
166
194
 
167
195
 
168
 
-file("yeccparser.erl", 168).
 
196
-file("yeccparser.erl", 196).
169
197
 
170
198
yeccpars2(0=S, Cat, Ss, Stack, T, Ts, Tzr) ->
171
199
 yeccpars2_0(S, Cat, Ss, Stack, T, Ts, Tzr);
249
277
yeccpars2_0(S, reserved_word, Ss, Stack, T, Ts, Tzr) ->
250
278
 yeccpars1(S, 8, Ss, Stack, T, Ts, Tzr);
251
279
yeccpars2_0(S, var, Ss, Stack, T, Ts, Tzr) ->
252
 
 yeccpars1(S, 9, Ss, Stack, T, Ts, Tzr).
 
280
 yeccpars1(S, 9, Ss, Stack, T, Ts, Tzr);
 
281
yeccpars2_0(_, _, _, _, T, _, _) ->
 
282
 yeccerror(T).
253
283
 
254
284
yeccpars2_1(S, atom, Ss, Stack, T, Ts, Tzr) ->
255
285
 yeccpars1(S, 6, Ss, Stack, T, Ts, Tzr);
268
298
 yeccgoto_grammar(hd(Ss), Cat, Ss, Stack, T, Ts, Tzr).
269
299
 
270
300
yeccpars2_3(S, '->', Ss, Stack, T, Ts, Tzr) ->
271
 
 yeccpars1(S, 10, Ss, Stack, T, Ts, Tzr).
 
301
 yeccpars1(S, 10, Ss, Stack, T, Ts, Tzr);
 
302
yeccpars2_3(_, _, _, _, T, _, _) ->
 
303
 yeccerror(T).
272
304
 
273
 
yeccpars2_4(_S, '$end', _Ss, Stack,  _T, _Ts, _Tzr) ->
274
 
 {ok, hd(Stack)}.
 
305
yeccpars2_4(_S, '$end', _Ss, Stack, _T, _Ts, _Tzr) ->
 
306
 {ok, hd(Stack)};
 
307
yeccpars2_4(_, _, _, _, T, _, _) ->
 
308
 yeccerror(T).
275
309
 
276
310
yeccpars2_5(_S, Cat, Ss, Stack, T, Ts, Tzr) ->
277
311
 yeccgoto_grammar(hd(Ss), Cat, Ss, Stack, T, Ts, Tzr).
318
352
 yeccgoto_symbols(hd(Nss), Cat, Nss, NewStack, T, Ts, Tzr).
319
353
 
320
354
yeccpars2_14(S, dot, Ss, Stack, T, Ts, Tzr) ->
321
 
 yeccpars1(S, 29, Ss, Stack, T, Ts, Tzr).
 
355
 yeccpars1(S, 29, Ss, Stack, T, Ts, Tzr);
 
356
yeccpars2_14(_, _, _, _, T, _, _) ->
 
357
 yeccerror(T).
322
358
 
323
359
yeccpars2_15(S, '->', Ss, Stack, T, Ts, Tzr) ->
324
360
 yeccpars1(S, 18, Ss, Stack, T, Ts, Tzr);
339
375
yeccpars2_15(S, string, Ss, Stack, T, Ts, Tzr) ->
340
376
 yeccpars1(S, 26, Ss, Stack, T, Ts, Tzr);
341
377
yeccpars2_15(S, var, Ss, Stack, T, Ts, Tzr) ->
342
 
 yeccpars1(S, 27, Ss, Stack, T, Ts, Tzr).
 
378
 yeccpars1(S, 27, Ss, Stack, T, Ts, Tzr);
 
379
yeccpars2_15(_, _, _, _, T, _, _) ->
 
380
 yeccerror(T).
343
381
 
344
382
yeccpars2_16(_S, Cat, Ss, Stack, T, Ts, Tzr) ->
345
383
 [_|Nss] = Ss,
415
453
 yeccgoto_rule(hd(Nss), Cat, Nss, NewStack, T, Ts, Tzr).
416
454
 
417
455
yeccpars2_30(S, dot, Ss, Stack, T, Ts, Tzr) ->
418
 
 yeccpars1(S, 35, Ss, Stack, T, Ts, Tzr).
 
456
 yeccpars1(S, 35, Ss, Stack, T, Ts, Tzr);
 
457
yeccpars2_30(_, _, _, _, T, _, _) ->
 
458
 yeccerror(T).
419
459
 
420
460
yeccpars2_31(S, dot, Ss, Stack, T, Ts, Tzr) ->
421
 
 yeccpars1(S, 34, Ss, Stack, T, Ts, Tzr).
 
461
 yeccpars1(S, 34, Ss, Stack, T, Ts, Tzr);
 
462
yeccpars2_31(_, _, _, _, T, _, _) ->
 
463
 yeccerror(T).
422
464
 
423
465
yeccpars2_32(S, string, Ss, Stack, T, Ts, Tzr) ->
424
466
 yeccpars1(S, 32, Ss, Stack, T, Ts, Tzr);
487
529
yeccgoto_tokens(17=_S, Cat, Ss, Stack, T, Ts, Tzr) ->
488
530
 yeccpars2_28(_S, Cat, Ss, Stack, T, Ts, Tzr).
489
531
 
490
 
-compile({inline,{yeccpars2_6_,1}}).
 
532
-compile({inline,yeccpars2_6_/1}).
491
533
-file("yeccgramm.yrl", 44).
492
534
yeccpars2_6_(__Stack0) ->
493
535
 [__1 | __Stack] = __Stack0,
495
537
   symbol ( __1 )
496
538
  end | __Stack].
497
539
 
498
 
-compile({inline,{yeccpars2_7_,1}}).
 
540
-compile({inline,yeccpars2_7_/1}).
499
541
-file("yeccgramm.yrl", 45).
500
542
yeccpars2_7_(__Stack0) ->
501
543
 [__1 | __Stack] = __Stack0,
503
545
   symbol ( __1 )
504
546
  end | __Stack].
505
547
 
506
 
-compile({inline,{yeccpars2_8_,1}}).
 
548
-compile({inline,yeccpars2_8_/1}).
507
549
-file("yeccgramm.yrl", 46).
508
550
yeccpars2_8_(__Stack0) ->
509
551
 [__1 | __Stack] = __Stack0,
511
553
   symbol ( __1 )
512
554
  end | __Stack].
513
555
 
514
 
-compile({inline,{yeccpars2_9_,1}}).
 
556
-compile({inline,yeccpars2_9_/1}).
515
557
-file("yeccgramm.yrl", 43).
516
558
yeccpars2_9_(__Stack0) ->
517
559
 [__1 | __Stack] = __Stack0,
519
561
   symbol ( __1 )
520
562
  end | __Stack].
521
563
 
522
 
-compile({inline,{yeccpars2_11_,1}}).
 
564
-compile({inline,yeccpars2_11_/1}).
523
565
-file("yeccgramm.yrl", 40).
524
566
yeccpars2_11_(__Stack0) ->
525
567
 [begin
526
568
   { erlang_code , [ { atom , 0 , '$undefined' } ] }
527
569
  end | __Stack0].
528
570
 
529
 
-compile({inline,{yeccpars2_12_,1}}).
 
571
-compile({inline,yeccpars2_12_/1}).
530
572
-file("yeccgramm.yrl", 35).
531
573
yeccpars2_12_(__Stack0) ->
532
574
 [__1 | __Stack] = __Stack0,
534
576
   [ __1 ]
535
577
  end | __Stack].
536
578
 
537
 
-compile({inline,{yeccpars2_13_,1}}).
 
579
-compile({inline,yeccpars2_13_/1}).
538
580
-file("yeccgramm.yrl", 36).
539
581
yeccpars2_13_(__Stack0) ->
540
582
 [__2,__1 | __Stack] = __Stack0,
542
584
   [ __1 | __2 ]
543
585
  end | __Stack].
544
586
 
545
 
-compile({inline,{yeccpars2_16_,1}}).
 
587
-compile({inline,yeccpars2_16_/1}).
546
588
-file("yeccgramm.yrl", 39).
547
589
yeccpars2_16_(__Stack0) ->
548
590
 [__2,__1 | __Stack] = __Stack0,
550
592
   { erlang_code , __2 }
551
593
  end | __Stack].
552
594
 
553
 
-compile({inline,{yeccpars2_17_,1}}).
 
595
-compile({inline,yeccpars2_17_/1}).
554
596
-file("yeccgramm.yrl", 41).
555
597
yeccpars2_17_(__Stack0) ->
556
598
 [__1 | __Stack] = __Stack0,
558
600
   [ __1 ]
559
601
  end | __Stack].
560
602
 
561
 
-compile({inline,{yeccpars2_18_,1}}).
 
603
-compile({inline,yeccpars2_18_/1}).
562
604
-file("yeccgramm.yrl", 55).
563
605
yeccpars2_18_(__Stack0) ->
564
606
 [__1 | __Stack] = __Stack0,
566
608
   { '->' , line_of ( __1 ) }
567
609
  end | __Stack].
568
610
 
569
 
-compile({inline,{yeccpars2_19_,1}}).
 
611
-compile({inline,yeccpars2_19_/1}).
570
612
-file("yeccgramm.yrl", 56).
571
613
yeccpars2_19_(__Stack0) ->
572
614
 [__1 | __Stack] = __Stack0,
574
616
   { ':' , line_of ( __1 ) }
575
617
  end | __Stack].
576
618
 
577
 
-compile({inline,{yeccpars2_24_,1}}).
 
619
-compile({inline,yeccpars2_24_/1}).
578
620
-file("yeccgramm.yrl", 53).
579
621
yeccpars2_24_(__Stack0) ->
580
622
 [__1 | __Stack] = __Stack0,
582
624
   { value_of ( __1 ) , line_of ( __1 ) }
583
625
  end | __Stack].
584
626
 
585
 
-compile({inline,{yeccpars2_25_,1}}).
 
627
-compile({inline,yeccpars2_25_/1}).
586
628
-file("yeccgramm.yrl", 54).
587
629
yeccpars2_25_(__Stack0) ->
588
630
 [__1 | __Stack] = __Stack0,
590
632
   { value_of ( __1 ) , line_of ( __1 ) }
591
633
  end | __Stack].
592
634
 
593
 
-compile({inline,{yeccpars2_28_,1}}).
 
635
-compile({inline,yeccpars2_28_/1}).
594
636
-file("yeccgramm.yrl", 42).
595
637
yeccpars2_28_(__Stack0) ->
596
638
 [__2,__1 | __Stack] = __Stack0,
598
640
   [ __1 | __2 ]
599
641
  end | __Stack].
600
642
 
601
 
-compile({inline,{yeccpars2_29_,1}}).
 
643
-compile({inline,yeccpars2_29_/1}).
602
644
-file("yeccgramm.yrl", 33).
603
645
yeccpars2_29_(__Stack0) ->
604
646
 [__5,__4,__3,__2,__1 | __Stack] = __Stack0,
606
648
   { rule , [ __1 | __3 ] , __4 }
607
649
  end | __Stack].
608
650
 
609
 
-compile({inline,{yeccpars2_32_,1}}).
 
651
-compile({inline,yeccpars2_32_/1}).
610
652
-file("yeccgramm.yrl", 37).
611
653
yeccpars2_32_(__Stack0) ->
612
654
 [__1 | __Stack] = __Stack0,
614
656
   [ __1 ]
615
657
  end | __Stack].
616
658
 
617
 
-compile({inline,{yeccpars2_33_,1}}).
 
659
-compile({inline,yeccpars2_33_/1}).
618
660
-file("yeccgramm.yrl", 38).
619
661
yeccpars2_33_(__Stack0) ->
620
662
 [__2,__1 | __Stack] = __Stack0,
622
664
   [ __1 | __2 ]
623
665
  end | __Stack].
624
666
 
625
 
-compile({inline,{yeccpars2_34_,1}}).
 
667
-compile({inline,yeccpars2_34_/1}).
626
668
-file("yeccgramm.yrl", 32).
627
669
yeccpars2_34_(__Stack0) ->
628
670
 [__3,__2,__1 | __Stack] = __Stack0,
630
672
   { __1 , __2 }
631
673
  end | __Stack].
632
674
 
633
 
-compile({inline,{yeccpars2_35_,1}}).
 
675
-compile({inline,yeccpars2_35_/1}).
634
676
-file("yeccgramm.yrl", 31).
635
677
yeccpars2_35_(__Stack0) ->
636
678
 [__3,__2,__1 | __Stack] = __Stack0,