~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/edoc/src/edoc_parser.yrl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
22
22
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
23
23
%% USA
24
24
%%
25
 
%% Author contact: richardc@it.uu.se
26
 
%%
27
 
%% $Id$
28
 
%%
 
25
%% Author contact: carlsson.richard@gmail.com
29
26
%% =====================================================================
30
27
 
31
28
Nonterminals
32
29
start spec func_type utype_list utype_tuple utypes utype ptypes ptype
33
 
nutype function_name where_defs defs def typedef etype throws qname ref
34
 
aref mref lref pref var_list vars fields field.
 
30
nutype function_name where_defs defs defs2 def typedef etype
 
31
throws qname ref aref mref lref pref var_list vars fields field
 
32
futype_list bin_base_type bin_unit_type.
35
33
 
36
34
Terminals
37
 
atom float integer var string start_spec start_typedef start_throws
 
35
atom float integer var an_var string start_spec start_typedef start_throws
38
36
start_ref
39
37
 
40
38
'(' ')' ',' '.' '->' '{' '}' '[' ']' '|' '+' ':' '::' '=' '/' '//' '*'
41
 
'#' 'where'.
 
39
'#' 'where' '<<' '>>' '..' '...'.
42
40
 
43
41
Rootsymbol start.
44
42
 
52
50
qname -> qname '.' atom: [tok_val('$3') | '$1'].
53
51
 
54
52
spec -> func_type where_defs:
55
 
    #t_spec{type = '$1', defs = lists:reverse('$2')}.
 
53
    #t_spec{type = '$1', defs = '$2'}.
56
54
spec -> function_name func_type where_defs:
57
 
    #t_spec{name = '$1', type = '$2', defs = lists:reverse('$3')}.
 
55
    #t_spec{name = '$1', type = '$2', defs = '$3'}.
58
56
 
59
57
where_defs -> 'where' defs: '$2'.
60
58
where_defs -> defs: '$1'.
66
64
 
67
65
 
68
66
%% Paired with line number, for later error reporting
69
 
utype_list -> '(' ')' : {[], tok_line('$1')}.
70
67
utype_list -> '(' utypes ')' : {lists:reverse('$2'), tok_line('$1')}.
71
68
 
72
 
utype_tuple -> '{' '}' : [].
 
69
futype_list -> utype_list : '$1'.
 
70
futype_list -> '(' '...' ')' : {[#t_var{name = '...'}], tok_line('$1')}.
 
71
 
73
72
utype_tuple -> '{' utypes '}' : lists:reverse('$2').
74
73
 
75
74
%% Produced in reverse order.
 
75
utypes -> '$empty' : [].
76
76
utypes -> utype : ['$1'].
77
77
utypes -> utypes ',' utype : ['$3' | '$1'].
78
78
 
90
90
ptype -> var : #t_var{name = tok_val('$1')}.
91
91
ptype -> atom : #t_atom{val = tok_val('$1')}.
92
92
ptype -> integer: #t_integer{val = tok_val('$1')}.
 
93
ptype -> integer '..' integer: #t_integer_range{from = tok_val('$1'),
 
94
                                                   to = tok_val('$3')}.
93
95
ptype -> float: #t_float{val = tok_val('$1')}.
94
96
ptype -> utype_tuple : #t_tuple{types = '$1'}.
95
97
ptype -> '[' ']' : #t_nil{}.
96
98
ptype -> '[' utype ']' : #t_list{type = '$2'}.
 
99
ptype -> '[' utype ',' '...' ']' : #t_nonempty_list{type = '$2'}.
97
100
ptype -> utype_list:
98
 
        if length(element(1, '$1')) == 1 -> 
 
101
        if length(element(1, '$1')) == 1 ->
99
102
                %% there must be exactly one utype in the list
100
103
                hd(element(1, '$1'));
 
104
                %% Replace last line when releasing next major release:
 
105
                %% #t_paren{type = hd(element(1, '$1'))};
101
106
           length(element(1, '$1')) == 0 ->
102
107
                return_error(element(2, '$1'), "syntax error before: ')'");
103
108
           true ->
104
109
                return_error(element(2, '$1'), "syntax error before: ','")
105
110
        end.
106
 
ptype -> utype_list '->' ptype:
 
111
ptype -> futype_list '->' ptype:
107
112
        #t_fun{args = element(1, '$1'), range = '$3'}.
108
113
ptype -> '#' atom '{' '}' :
109
114
        #t_record{name = #t_atom{val = tok_val('$2')}}.
111
116
        #t_record{name = #t_atom{val = tok_val('$2')},
112
117
                  fields = lists:reverse('$4')}.
113
118
ptype -> atom utype_list:
114
 
        #t_type{name = #t_name{name = tok_val('$1')},
115
 
                args = element(1, '$2')}.
116
 
ptype -> qname ':' atom utype_list : 
 
119
             case {tok_val('$1'), element(1, '$2')} of
 
120
                 {nil, []} ->
 
121
                     %% Prefer '[]' before 'nil(). Due to
 
122
                     %% compatibility with Erlang types, which do not
 
123
                     %% separate '[]' from 'nil()'.
 
124
                     #t_nil{};
 
125
                 {list, [T]} ->
 
126
                     %% Prefer '[T]' before 'list(T). Due to
 
127
                     %% compatibility with Erlang types, which do not
 
128
                     %% separate '[T]' from 'list(T)'.
 
129
                     #t_list{type = T};
 
130
                 {'fun', [#t_fun{}=Fun]} ->
 
131
                     %% An incompatible change as compared to EDOc 0.7.6.6.
 
132
                     %% Due to compatibility with Erlang types.
 
133
                     Fun;
 
134
                 {'fun', []} ->
 
135
                     #t_type{name = #t_name{name = function}};
 
136
                 {Name, Args} ->
 
137
                     #t_type{name = #t_name{name = Name},
 
138
                             args = Args}
 
139
             end.
 
140
ptype -> qname ':' atom utype_list :
117
141
        #t_type{name = #t_name{module = qname('$1'),
118
142
                               name = tok_val('$3')},
119
143
                args = element(1, '$4')}.
120
 
ptype -> '//' atom '/' qname ':' atom utype_list : 
 
144
ptype -> '//' atom '/' qname ':' atom utype_list :
121
145
        #t_type{name = #t_name{app = tok_val('$2'),
122
146
                               module = qname('$4'),
123
147
                               name = tok_val('$6')},
124
148
                args = element(1, '$7')}.
 
149
ptype -> '<<' '>>' : #t_binary{}.
 
150
ptype -> '<<' bin_base_type '>>' : #t_binary{base_size = '$2'}.
 
151
ptype -> '<<' bin_unit_type '>>' : #t_binary{unit_size = '$2'}.
 
152
ptype -> '<<' bin_base_type ',' bin_unit_type '>>' :
 
153
        #t_binary{base_size = '$2', unit_size = '$4'}.
 
154
 
 
155
bin_base_type -> an_var ':' integer: tok_val('$3').
 
156
 
 
157
bin_unit_type -> an_var ':' an_var '*' integer : tok_val('$5').
125
158
 
126
159
%% Produced in reverse order.
127
160
fields -> field : ['$1'].
130
163
field -> atom '=' utype :
131
164
        #t_field{name = #t_atom{val = tok_val('$1')}, type = '$3'}.
132
165
 
133
 
%% Produced in reverse order.
134
166
defs -> '$empty' : [].
135
 
defs -> defs def : ['$2' | '$1'].
136
 
defs -> defs ',' def : ['$3' | '$1'].
 
167
defs -> def defs2 : ['$1' | lists:reverse('$2')].
 
168
 
 
169
%% Produced in reverse order.
 
170
defs2 -> '$empty' : [].
 
171
defs2 -> defs2 def : ['$2' | '$1'].
 
172
defs2 -> defs2 ',' def : ['$3' | '$1'].
137
173
 
138
174
def -> var '=' utype:
139
175
       #t_def{name =  #t_var{name = tok_val('$1')},
140
176
              type = '$3'}.
141
 
def -> atom var_list '=' utype:
142
 
       #t_def{name = #t_type{name = #t_name{name = tok_val('$1')},
143
 
                             args = '$2'},
144
 
              type = '$4'}.
 
177
def -> atom '(' utypes ')' '=' utype:
 
178
       build_def(tok_val('$1'), '$2', '$3', '$6').
145
179
 
146
180
var_list -> '(' ')' : [].
147
181
var_list -> '(' vars ')' : lists:reverse('$2').
153
187
typedef -> atom var_list where_defs:
154
188
       #t_typedef{name = #t_name{name = tok_val('$1')},
155
189
                  args = '$2',
156
 
                  defs = lists:reverse('$3')}.
 
190
                  defs = '$3'}.
157
191
typedef -> atom var_list '=' utype where_defs:
158
192
       #t_typedef{name = #t_name{name = tok_val('$1')},
159
193
                  args = '$2',
160
194
                  type = '$4',
161
 
                  defs = lists:reverse('$5')}.
 
195
                  defs = '$5'}.
162
196
 
163
197
%% References
164
198
 
195
229
 
196
230
throws -> etype where_defs:
197
231
        #t_throws{type = '$1',
198
 
                  defs = lists:reverse('$2')}.
 
232
                  defs = '$2'}.
199
233
 
200
234
%% (commented out for now)
201
235
%% Header
221
255
%% "%% USA"
222
256
%% "%%"
223
257
%% "%% @private"
224
 
%% "%% @author Richard Carlsson <richardc@it.uu.se>"
 
258
%% "%% @author Richard Carlsson <carlsson.richard@gmail.com>"
225
259
%% "%% ===================================================================="
226
260
%% .
227
261
 
297
331
    end.
298
332
 
299
333
annotate(T, A) -> ?add_t_ann(T, A).
300
 
    
 
334
 
 
335
build_def(S, P, As, T) ->
 
336
    case all_vars(As) of
 
337
        true ->
 
338
            #t_def{name = #t_type{name = #t_name{name = S},
 
339
                                  args = lists:reverse(As)},
 
340
                   type = T};
 
341
        false ->
 
342
            return_error(element(2, P), "variable expected after '('")
 
343
    end.
 
344
 
 
345
all_vars([#t_var{} | As]) ->
 
346
    all_vars(As);
 
347
all_vars(As) ->
 
348
    As =:= [].
 
349
 
301
350
%% ---------------------------------------------------------------------
302
351
 
303
352
%% @doc EDoc type specification parsing. Parses the content of
310
359
                {ok, Spec} ->
311
360
                    Spec;
312
361
                {error, E} ->
313
 
                    throw_error(E, L)
 
362
                    throw_error({parse_spec, E}, L)
314
363
            end;
315
364
        {error, E, _} ->
316
 
            throw_error(E, L)
 
365
            throw_error({parse_spec, E}, L)
317
366
    end.
318
367
 
319
368
%% ---------------------------------------------------------------------
379
428
    {S1, S2} = edoc_lib:split_at_space(edoc_lib:strip_space(S)),
380
429
    case edoc_lib:strip_space(S1) of
381
430
        "" -> throw_error(parse_param, L);
382
 
        Name -> 
 
431
        Name ->
383
432
            Text = edoc_lib:strip_space(S2),
384
433
            {list_to_atom(Name), edoc_wiki:parse_xml(Text, L)}
385
434
    end.
406
455
 
407
456
-spec throw_error(term(), erl_scan:line()) -> no_return().
408
457
 
409
 
throw_error({L, M, D}, _L0) ->
410
 
    throw({error,L,{format_error,M,D}});
411
458
throw_error({parse_spec, E}, L) ->
412
459
    throw_error({"specification", E}, L);
413
460
throw_error({parse_typedef, E}, L) ->
419
466
throw_error(parse_param, L) ->
420
467
    throw({error, L, "missing parameter name"});
421
468
throw_error({Where, E}, L) when is_list(Where) ->
422
 
    throw({error,L,{"unknown error parsing ~s: ~P.",[Where,E,15]}});
423
 
throw_error(E, L) ->
424
 
    %% Just in case.
425
 
    throw({error,L,{"unknown parse error: ~P.",[E,15]}}).
 
469
    throw({error,L,{"unknown error parsing ~s: ~P.",[Where,E,15]}}).