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

« back to all changes in this revision

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

  • 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
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
49
50
return_error(Line, Message) ->
50
51
    throw({error, {Line, ?MODULE, Message}}).
51
52
 
52
 
-define(CODE_VERSION, "1.2").
 
53
-define(CODE_VERSION, "1.3").
53
54
 
54
55
yeccpars0(Tokens, MFA) ->
55
56
    try yeccpars1(Tokens, MFA, 0, [], [])
59
60
            try yecc_error_type(Error, Stacktrace) of
60
61
                {syntax_error, Token} ->
61
62
                    yeccerror(Token);
62
 
                {missing_in_goto_table=Tag, State} ->
63
 
                    Desc = {State, Tag},
64
 
                    erlang:raise(error, {yecc_bug, ?CODE_VERSION, Desc},
65
 
                                Stacktrace);
66
63
                {missing_in_goto_table=Tag, Symbol, State} ->
67
64
                    Desc = {Symbol, State, Tag},
68
65
                    erlang:raise(error, {yecc_bug, ?CODE_VERSION, Desc},
73
70
            Error % probably from return_error/2
74
71
    end.
75
72
 
76
 
yecc_error_type(function_clause, [{?MODULE,F,[_,_,_,_,Token,_,_]} | _]) ->
77
 
    "yeccpars2" ++ _ = atom_to_list(F),
78
 
    {syntax_error, Token};
79
 
yecc_error_type({case_clause,{State}}, [{?MODULE,yeccpars2,_}|_]) ->
80
 
    %% Inlined goto-function
81
 
    {missing_in_goto_table, State};
82
 
yecc_error_type(function_clause, [{?MODULE,F,[State]}|_]) ->
83
 
    "yeccgoto_" ++ SymbolL = atom_to_list(F),
84
 
    {ok,[{atom,_,Symbol}]} = erl_scan:string(SymbolL),
85
 
    {missing_in_goto_table, Symbol, State}.
 
73
yecc_error_type(function_clause, [{?MODULE,F,[State,_,_,_,Token,_,_]} | _]) ->
 
74
    case atom_to_list(F) of
 
75
        "yeccpars2" ++ _ ->
 
76
            {syntax_error, Token};
 
77
        "yeccgoto_" ++ SymbolL ->
 
78
            {ok,[{atom,_,Symbol}],_} = erl_scan:string(SymbolL),
 
79
            {missing_in_goto_table, Symbol, State}
 
80
    end.
86
81
 
87
82
yeccpars1([Token | Tokens], Tokenizer, State, States, Vstack) ->
88
83
    yeccpars2(State, element(1, Token), States, Vstack, Token, Tokens, 
124
119
 
125
120
% For internal use only.
126
121
yeccerror(Token) ->
127
 
    {error,
128
 
     {element(2, Token), ?MODULE,
129
 
      ["syntax error before: ", yecctoken2string(Token)]}}.
 
122
    Text = case catch erl_scan:token_info(Token, text) of
 
123
               {text, Txt} -> Txt;
 
124
               _ -> yecctoken2string(Token)
 
125
           end,
 
126
    Location = case catch erl_scan:token_info(Token, location) of
 
127
                   {location, Loc} -> Loc;
 
128
                   _ -> element(2, Token)
 
129
               end,
 
130
    {error, {Location, ?MODULE, ["syntax error before: ", Text]}}.
130
131
 
131
132
yecctoken2string({atom, _, A}) -> io_lib:write(A);
132
133
yecctoken2string({integer,_,N}) -> io_lib:write(N);
133
134
yecctoken2string({float,_,F}) -> io_lib:write(F);
134
135
yecctoken2string({char,_,C}) -> io_lib:write_char(C);
135
136
yecctoken2string({var,_,V}) -> io_lib:format("~s", [V]);
136
 
yecctoken2string({string,_,S}) -> io_lib:write_string(S);
 
137
yecctoken2string({string,_,S}) -> io_lib:write_unicode_string(S);
137
138
yecctoken2string({reserved_symbol, _, A}) -> io_lib:format("~w", [A]);
138
139
yecctoken2string({_Cat, _, Val}) -> io_lib:format("~w", [Val]);
139
140
yecctoken2string({dot, _}) -> "'.'";