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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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(_) -> yecc_ret().
42
42
parse(Tokens) ->
43
43
    yeccpars0(Tokens, false).
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()}, [_]} | {atom(), atom(), [_]}) ->
 
46
            yecc_ret().
48
47
parse_and_scan({F, A}) -> % Fun or {M, F}
49
48
    yeccpars0([], {F, A});
50
49
parse_and_scan({M, F, A}) ->
51
50
    yeccpars0([], {{M, F}, A}).
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!
 
61
%% To be used in grammar files to throw an error message to the parser
 
62
%% toplevel. Doesn't have to be exported!
64
63
-compile({nowarn_unused_function,{return_error,2}}).
65
 
-spec(return_error/2 :: (integer(), any()) -> no_return()).
 
64
-spec return_error(integer(), any()) -> no_return().
66
65
return_error(Line, Message) ->
67
66
    throw({error, {Line, ?MODULE, Message}}).
68
67
 
101
100
yeccpars1([], {F, A}, State, States, Vstack) ->
102
101
    case apply(F, A) of
103
102
        {ok, Tokens, _Endline} ->
104
 
            yeccpars1(Tokens, {F, A}, State, States, Vstack);
 
103
            yeccpars1(Tokens, {F, A}, State, States, Vstack);
105
104
        {eof, _Endline} ->
106
105
            yeccpars1([], false, State, States, Vstack);
107
106
        {error, Descriptor, _Endline} ->
123
122
yeccpars1(State1, State, States, Vstack, Stack1, [], {F, A}) ->
124
123
    case apply(F, A) of
125
124
        {ok, Tokens, _Endline} ->
126
 
            yeccpars1(State1, State, States, Vstack, Stack1, Tokens, {F, A});
 
125
            yeccpars1(State1, State, States, Vstack, Stack1, Tokens, {F, A});
127
126
        {eof, _Endline} ->
128
127
            yeccpars1(State1, State, States, Vstack, Stack1, [], false);
129
128
        {error, Descriptor, _Endline} ->