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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_parse.yrl

  • 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:
1
1
%% -*- erlang -*-
2
2
%%
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
%%
20
20
 
30
30
expr_max
31
31
list tail
32
32
list_comprehension lc_expr lc_exprs
33
 
binary_comprehension 
 
33
binary_comprehension
34
34
tuple
35
 
atom1
36
35
%struct
37
36
record_expr record_tuple record_field record_fields
38
37
if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr
39
38
fun_expr fun_clause fun_clauses
40
 
%% cond_expr cond_clause cond_clauses
41
39
try_expr try_catch try_clause try_clauses query_expr
42
40
function_call argument_list
43
41
exprs guard
49
47
top_type top_type_100 top_types type typed_expr typed_attr_val
50
48
type_sig type_sigs type_guard type_guards fun_type fun_type_100 binary_type
51
49
type_spec spec_fun typed_exprs typed_record_fields field_types field_type
52
 
bin_base_type bin_unit_type int_type.
 
50
bin_base_type bin_unit_type type_200 type_300 type_400 type_500.
53
51
 
54
52
Terminals
55
53
char integer float atom string var
56
54
 
57
55
'(' ')' ',' '->' ':-' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.'
58
56
'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when'
59
 
'andalso' 'orelse' 'query' 'spec'
60
 
%% 'cond'
 
57
'andalso' 'orelse' 'query'
61
58
'bnot' 'not'
62
59
'*' '/' 'div' 'rem' 'band' 'and'
63
60
'+' '-' 'bor' 'bxor' 'bsl' 'bsr' 'or' 'xor'
64
61
'++' '--'
65
62
'==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<='
66
63
'<<' '>>'
67
 
'!' '=' '::'
 
64
'!' '=' '::' '..' '...'
 
65
'spec' % helper
68
66
dot.
69
67
 
70
68
Expect 2.
79
77
attribute -> '-' atom typed_attr_val         : build_typed_attribute('$2','$3').
80
78
attribute -> '-' atom '(' typed_attr_val ')' : build_typed_attribute('$2','$4').
81
79
attribute -> '-' 'spec' type_spec            : build_type_spec('$2', '$3').
82
 
   
83
 
atom1 -> 'spec' : {atom, ?line('$1'), 'spec'}.
84
 
atom1 -> atom   : '$1'.
85
80
 
86
81
type_spec -> spec_fun type_sigs : {'$1', '$2'}.
87
82
type_spec -> '(' spec_fun type_sigs ')' : {'$2', '$3'}.
88
83
 
89
 
spec_fun ->                            atom1 : '$1'.
90
 
spec_fun ->                  atom1 ':' atom1 : {'$1', '$3'}.
 
84
spec_fun ->                           atom : '$1'.
 
85
spec_fun ->                  atom ':' atom : {'$1', '$3'}.
91
86
%% The following two are retained only for backwards compatibility;
92
87
%% they are not part of the EEP syntax and should be removed.
93
 
spec_fun ->           atom1 '/' integer '::' : {'$1', '$3'}.
94
 
spec_fun -> atom1 ':' atom1 '/' integer '::' : {'$1', '$3', '$5'}.
 
88
spec_fun ->          atom '/' integer '::' : {'$1', '$3'}.
 
89
spec_fun -> atom ':' atom '/' integer '::' : {'$1', '$3', '$5'}.
95
90
 
96
91
typed_attr_val -> expr ',' typed_record_fields : {typed_record, '$1', '$3'}.
97
92
typed_attr_val -> expr '::' top_type           : {type_def, '$1', '$3'}.
109
104
type_sigs -> type_sig ';' type_sigs       : ['$1'|'$3'].
110
105
 
111
106
type_sig -> fun_type                      : '$1'.
112
 
type_sig -> fun_type 'when' type_guards   : {type, ?line('$1'), bounded_fun, 
 
107
type_sig -> fun_type 'when' type_guards   : {type, ?line('$1'), bounded_fun,
113
108
                                             ['$1','$3']}.
114
109
 
115
110
type_guards -> type_guard                 : ['$1'].
116
111
type_guards -> type_guard ',' type_guards : ['$1'|'$3'].
117
112
 
118
 
type_guard -> atom1 '(' top_types ')'     : {type, ?line('$1'), constraint, 
 
113
type_guard -> atom '(' top_types ')'      : {type, ?line('$1'), constraint,
119
114
                                             ['$1', '$3']}.
 
115
type_guard -> var '::' top_type           : build_def('$1', '$3').
120
116
 
121
117
top_types -> top_type                     : ['$1'].
122
118
top_types -> top_type ',' top_types       : ['$1'|'$3'].
124
120
top_type -> var '::' top_type_100         : {ann_type, ?line('$1'), ['$1','$3']}.
125
121
top_type -> top_type_100                  : '$1'.
126
122
 
127
 
top_type_100 -> type                      : '$1'.
128
 
top_type_100 -> type '|' top_type_100     : lift_unions('$1','$3').
 
123
top_type_100 -> type_200                  : '$1'.
 
124
top_type_100 -> type_200 '|' top_type_100 : lift_unions('$1','$3').
 
125
 
 
126
type_200 -> type_300 '..' type_300        : {type, ?line('$1'), range,
 
127
                                             [skip_paren('$1'),
 
128
                                              skip_paren('$3')]}.
 
129
type_200 -> type_300                      : '$1'.
 
130
 
 
131
type_300 -> type_300 add_op type_400      : ?mkop2(skip_paren('$1'),
 
132
                                                   '$2', skip_paren('$3')).
 
133
type_300 -> type_400                      : '$1'.
 
134
 
 
135
type_400 -> type_400 mult_op type_500     : ?mkop2(skip_paren('$1'),
 
136
                                                   '$2', skip_paren('$3')).
 
137
type_400 -> type_500                      : '$1'.
 
138
 
 
139
type_500 -> prefix_op type                : ?mkop1('$1', skip_paren('$2')).
 
140
type_500 -> type                          : '$1'.
129
141
 
130
142
type -> '(' top_type ')'                  : {paren_type, ?line('$2'), ['$2']}.
131
143
type -> var                               : '$1'.
132
 
type -> atom1                             : '$1'.
133
 
type -> atom1 '(' ')'                     : build_gen_type('$1').
134
 
type -> atom1 '(' top_types ')'           : {type, ?line('$1'), 
 
144
type -> atom                              : '$1'.
 
145
type -> atom '(' ')'                      : build_gen_type('$1').
 
146
type -> atom '(' top_types ')'            : {type, ?line('$1'),
135
147
                                             normalise('$1'), '$3'}.
136
 
type -> atom1 ':' atom1 '(' ')'           : {remote_type, ?line('$1'), 
 
148
type -> atom ':' atom '(' ')'             : {remote_type, ?line('$1'),
137
149
                                             ['$1', '$3', []]}.
138
 
type -> atom1 ':' atom1 '(' top_types ')' : {remote_type, ?line('$1'), 
 
150
type -> atom ':' atom '(' top_types ')'   : {remote_type, ?line('$1'),
139
151
                                             ['$1', '$3', '$5']}.
140
152
type -> '[' ']'                           : {type, ?line('$1'), nil, []}.
141
153
type -> '[' top_type ']'                  : {type, ?line('$1'), list, ['$2']}.
142
 
type -> '[' top_type ',' '.' '.' '.' ']'  : {type, ?line('$1'), 
 
154
type -> '[' top_type ',' '...' ']'        : {type, ?line('$1'),
143
155
                                             nonempty_list, ['$2']}.
144
156
type -> '{' '}'                           : {type, ?line('$1'), tuple, []}.
145
157
type -> '{' top_types '}'                 : {type, ?line('$1'), tuple, '$2'}.
146
 
type -> '#' atom1 '{' '}'                 : {type, ?line('$1'), record, ['$2']}.
147
 
type -> '#' atom1 '{' field_types '}'     : {type, ?line('$1'), 
 
158
type -> '#' atom '{' '}'                  : {type, ?line('$1'), record, ['$2']}.
 
159
type -> '#' atom '{' field_types '}'      : {type, ?line('$1'),
148
160
                                             record, ['$2'|'$4']}.
149
161
type -> binary_type                       : '$1'.
150
 
type -> int_type                          : '$1'.
151
 
type -> int_type '.' '.' int_type         : {type, ?line('$1'), range, 
152
 
                                             ['$1', '$4']}.
 
162
type -> integer                           : '$1'.
153
163
type -> 'fun' '(' ')'                     : {type, ?line('$1'), 'fun', []}.
154
164
type -> 'fun' '(' fun_type_100 ')'        : '$3'.
155
165
 
156
 
int_type -> integer                       : '$1'.
157
 
int_type -> '-' integer                   : abstract(-normalise('$2'), 
158
 
                                                     ?line('$2')).
159
 
 
160
 
fun_type_100 -> '(' '.' '.' '.' ')' '->' top_type 
 
166
fun_type_100 -> '(' '...' ')' '->' top_type
161
167
                                          : {type, ?line('$1'), 'fun',
162
 
                                             [{type, ?line('$1'), any}, '$7']}.
 
168
                                             [{type, ?line('$1'), any}, '$5']}.
163
169
fun_type_100 -> fun_type                  : '$1'.
164
170
 
165
171
fun_type -> '(' ')' '->' top_type  : {type, ?line('$1'), 'fun',
166
172
                                      [{type, ?line('$1'), product, []}, '$4']}.
167
 
fun_type -> '(' top_types ')' '->' top_type 
 
173
fun_type -> '(' top_types ')' '->' top_type
168
174
                                   : {type, ?line('$1'), 'fun',
169
175
                                      [{type, ?line('$1'), product, '$2'},'$5']}.
170
176
 
171
177
field_types -> field_type                 : ['$1'].
172
178
field_types -> field_type ',' field_types : ['$1'|'$3'].
173
179
 
174
 
field_type -> atom1 '::' top_type          : {type, ?line('$1'), field_type, 
 
180
field_type -> atom '::' top_type          : {type, ?line('$1'), field_type,
175
181
                                             ['$1', '$3']}.
176
182
 
177
 
binary_type -> '<<' '>>'                  : {type, ?line('$1'),binary, 
178
 
                                             [abstract(0, ?line('$1')), 
 
183
binary_type -> '<<' '>>'                  : {type, ?line('$1'),binary,
 
184
                                             [abstract(0, ?line('$1')),
179
185
                                              abstract(0, ?line('$1'))]}.
180
186
binary_type -> '<<' bin_base_type '>>'    : {type, ?line('$1'),binary,
181
187
                                             ['$2', abstract(0, ?line('$1'))]}.
184
190
binary_type -> '<<' bin_base_type ',' bin_unit_type '>>'
185
191
                                    : {type, ?line('$1'), binary, ['$2', '$4']}.
186
192
 
187
 
bin_base_type -> var ':' integer          : build_bin_type(['$1'], '$3').
 
193
bin_base_type -> var ':' type          : build_bin_type(['$1'], '$3').
188
194
 
189
 
bin_unit_type -> var ':' var '*' integer  : build_bin_type(['$1', '$3'], '$5').
 
195
bin_unit_type -> var ':' var '*' type  : build_bin_type(['$1', '$3'], '$5').
190
196
 
191
197
attr_val -> expr                     : ['$1'].
192
198
attr_val -> expr ',' exprs           : ['$1' | '$3'].
197
203
function_clauses -> function_clause : ['$1'].
198
204
function_clauses -> function_clause ';' function_clauses : ['$1'|'$3'].
199
205
 
200
 
function_clause -> atom1 clause_args clause_guard clause_body :
 
206
function_clause -> atom clause_args clause_guard clause_body :
201
207
        {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}.
202
208
 
203
209
 
250
256
        {remote,?line('$2'),'$1','$3'}.
251
257
expr_800 -> expr_900 : '$1'.
252
258
 
253
 
expr_900 -> '.' atom1 :
 
259
expr_900 -> '.' atom :
254
260
        {record_field,?line('$1'),{atom,?line('$1'),''},'$2'}.
255
 
expr_900 -> expr_900 '.' atom1 :
 
261
expr_900 -> expr_900 '.' atom :
256
262
        {record_field,?line('$2'),'$1','$3'}.
257
263
expr_900 -> expr_max : '$1'.
258
264
 
270
276
expr_max -> case_expr : '$1'.
271
277
expr_max -> receive_expr : '$1'.
272
278
expr_max -> fun_expr : '$1'.
273
 
%%expr_max -> cond_expr : '$1'.
274
279
expr_max -> try_expr : '$1'.
275
280
expr_max -> query_expr : '$1'.
276
281
 
304
309
bit_type_list -> bit_type '-' bit_type_list : ['$1' | '$3'].
305
310
bit_type_list -> bit_type : ['$1'].
306
311
 
307
 
bit_type -> atom1             : element(3,'$1').
308
 
bit_type -> atom1 ':' integer : { element(3,'$1'), element(3,'$3') }.
 
312
bit_type -> atom             : element(3,'$1').
 
313
bit_type -> atom ':' integer : { element(3,'$1'), element(3,'$3') }.
309
314
 
310
315
bit_size_expr -> expr_max : '$1'.
311
316
 
325
330
tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}.
326
331
 
327
332
 
328
 
%%struct -> atom1 tuple :
 
333
%%struct -> atom tuple :
329
334
%%      {struct,?line('$1'),element(3, '$1'),element(3, '$2')}.
330
335
 
331
336
 
333
338
%% N.B. Field names are returned as the complete object, even if they are
334
339
%% always atoms for the moment, this might change in the future.
335
340
 
336
 
record_expr -> '#' atom1 '.' atom1 :
 
341
record_expr -> '#' atom '.' atom :
337
342
        {record_index,?line('$1'),element(3, '$2'),'$4'}.
338
 
record_expr -> '#' atom1 record_tuple :
 
343
record_expr -> '#' atom record_tuple :
339
344
        {record,?line('$1'),element(3, '$2'),'$3'}.
340
 
record_expr -> expr_max '#' atom1 '.' atom1 :
341
 
        {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}.
342
 
record_expr -> expr_max '#' atom1 record_tuple :
 
345
record_expr -> expr_max '#' atom '.' atom :
 
346
        {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}.
 
347
record_expr -> expr_max '#' atom record_tuple :
 
348
        {record,?line('$2'),'$1',element(3, '$3'),'$4'}.
 
349
record_expr -> record_expr '#' atom '.' atom :
 
350
        {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}.
 
351
record_expr -> record_expr '#' atom record_tuple :
343
352
        {record,?line('$2'),'$1',element(3, '$3'),'$4'}.
344
353
 
345
354
record_tuple -> '{' '}' : [].
349
358
record_fields -> record_field ',' record_fields : ['$1' | '$3'].
350
359
 
351
360
record_field -> var '=' expr : {record_field,?line('$1'),'$1','$3'}.
352
 
record_field -> atom1 '=' expr : {record_field,?line('$1'),'$1','$3'}.
 
361
record_field -> atom '=' expr : {record_field,?line('$1'),'$1','$3'}.
353
362
 
354
363
%% N.B. This is called from expr_700.
355
364
 
383
392
        {'receive',?line('$1'),'$2','$4','$5'}.
384
393
 
385
394
 
386
 
fun_expr -> 'fun' atom1 '/' integer :
 
395
fun_expr -> 'fun' atom '/' integer :
387
396
        {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}.
388
 
fun_expr -> 'fun' atom1 ':' atom1 '/' integer :
 
397
fun_expr -> 'fun' atom ':' atom '/' integer :
389
398
        {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4'),element(3,'$6')}}.
390
399
fun_expr -> 'fun' fun_clauses 'end' :
391
400
        build_fun(?line('$1'), '$2').
415
424
try_clause -> expr clause_guard clause_body :
416
425
        L = ?line('$1'),
417
426
        {clause,L,[{tuple,L,[{atom,L,throw},'$1',{var,L,'_'}]}],'$2','$3'}.
418
 
try_clause -> atom1 ':' expr clause_guard clause_body :
 
427
try_clause -> atom ':' expr clause_guard clause_body :
419
428
        L = ?line('$1'),
420
429
        {clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}.
421
430
try_clause -> var ':' expr clause_guard clause_body :
422
431
        L = ?line('$1'),
423
432
        {clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}.
424
433
 
425
 
%%cond_expr -> 'cond' cond_clauses 'end' : {'cond',?line('$1'),'$2'}.
426
 
 
427
 
%%cond_clauses -> cond_clause : ['$1'].
428
 
%%cond_clauses -> cond_clause ';' cond_clauses : ['$1' | '$3'].
429
 
 
430
 
%%cond_clause -> expr clause_body :
431
 
%%      {clause,?line('$1'),[],[['$1']],'$2'}.
432
 
 
433
434
query_expr -> 'query' list_comprehension 'end' :
434
435
        {'query',?line('$1'),'$2'}.
435
436
 
447
448
atomic -> char : '$1'.
448
449
atomic -> integer : '$1'.
449
450
atomic -> float : '$1'.
450
 
atomic -> atom1 : '$1'.
 
451
atomic -> atom : '$1'.
451
452
atomic -> strings : '$1'.
452
453
 
453
454
strings -> string : '$1'.
492
493
rule_clauses -> rule_clause : ['$1'].
493
494
rule_clauses -> rule_clause ';' rule_clauses : ['$1'|'$3'].
494
495
 
495
 
rule_clause -> atom1 clause_args clause_guard rule_body :
 
496
rule_clause -> atom clause_args clause_guard rule_body :
496
497
        {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}.
497
498
 
498
499
rule_body -> ':-' lc_exprs: '$2'.
514
515
%% mkop(Op, Arg) -> {op,Line,Op,Arg}.
515
516
%% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}.
516
517
 
517
 
-define(mkop2(L, OpPos, R), 
518
 
        begin 
 
518
-define(mkop2(L, OpPos, R),
 
519
        begin
519
520
            {Op,Pos} = OpPos,
520
521
            {op,Pos,Op,L,R}
521
522
        end).
533
534
%% These really suck and are only here until Calle gets multiple
534
535
%% entry points working.
535
536
 
 
537
parse_form([{'-',L1},{atom,L2,spec}|Tokens]) ->
 
538
    parse([{'-',L1},{'spec',L2}|Tokens]);
536
539
parse_form(Tokens) ->
537
540
    parse(Tokens).
538
541
 
559
562
-type attributes() :: 'export' | 'file' | 'import' | 'module'
560
563
                    | 'opaque' | 'record' | 'type'.
561
564
 
562
 
build_typed_attribute({atom,La,record}, 
 
565
build_typed_attribute({atom,La,record},
563
566
                      {typed_record, {atom,_Ln,RecordName}, RecTuple}) ->
564
567
    {attribute,La,record,{RecordName,record_tuple(RecTuple)}};
565
568
build_typed_attribute({atom,La,Attr},
582
585
build_type_spec({spec,La}, {SpecFun, TypeSpecs}) ->
583
586
    NewSpecFun =
584
587
        case SpecFun of
585
 
            {atom, _, Fun} -> 
 
588
            {atom, _, Fun} ->
586
589
                {Fun, find_arity_from_specs(TypeSpecs)};
587
590
            {{atom,_, Mod}, {atom,_, Fun}} ->
588
591
                {Mod,Fun,find_arity_from_specs(TypeSpecs)};
605
608
    {type, _, 'fun', [{type, _, product, Args},_]} = Fun,
606
609
    length(Args).
607
610
 
 
611
build_def(LHS, Types) ->
 
612
    IsSubType = {atom, ?line(LHS), is_subtype},
 
613
    {type, ?line(LHS), constraint, [IsSubType, [LHS, Types]]}.
 
614
 
608
615
lift_unions(T1, {type, _La, union, List}) ->
609
616
    {type, ?line(T1), union, [T1|List]};
610
617
lift_unions(T1, T2) ->
611
618
    {type, ?line(T1), union, [T1, T2]}.
612
619
 
 
620
skip_paren({paren_type,_L,[Type]}) ->
 
621
    skip_paren(Type);
 
622
skip_paren(Type) ->
 
623
    Type.
 
624
 
613
625
build_gen_type({atom, La, tuple}) ->
614
626
    {type, La, tuple, any};
615
627
build_gen_type({atom, La, Name}) ->
618
630
build_bin_type([{var, _, '_'}|Left], Int) ->
619
631
    build_bin_type(Left, Int);
620
632
build_bin_type([], Int) ->
621
 
    Int;
 
633
    skip_paren(Int);
622
634
build_bin_type([{var, La, _}|_], _) ->
623
635
    ret_err(La, "Bad binary type").
624
636
 
716
728
 
717
729
attribute_farity_list(Args) ->
718
730
    [attribute_farity(A) || A <- Args].
719
 
    
 
731
 
720
732
-spec error_bad_decl(integer(), attributes()) -> no_return().
721
733
 
722
734
error_bad_decl(L, S) ->
739
751
    [{record_field,La,{atom,La,A},Expr}|record_fields(Fields)];
740
752
record_fields([{typed,Expr,TypeInfo}|Fields]) ->
741
753
    [Field] = record_fields([Expr]),
742
 
    TypeInfo1 = 
 
754
    TypeInfo1 =
743
755
        case Expr of
744
756
            {match, _, _, _} -> TypeInfo; %% If we have an initializer.
745
 
            {atom, La, _} -> 
746
 
                lift_unions(abstract(undefined, La), TypeInfo)
747
 
        end, 
 
757
            {atom, La, _} ->
 
758
                case has_undefined(TypeInfo) of
 
759
                    false ->
 
760
                        lift_unions(abstract(undefined, La), TypeInfo);
 
761
                    true ->
 
762
                        TypeInfo
 
763
                end
 
764
        end,
748
765
    [{typed_record_field,Field,TypeInfo1}|record_fields(Fields)];
749
766
record_fields([Other|_Fields]) ->
750
767
    ret_err(?line(Other), "bad record field");
751
768
record_fields([]) -> [].
752
769
 
 
770
has_undefined({atom,_,undefined}) ->
 
771
    true;
 
772
has_undefined({ann_type,_,[_,T]}) ->
 
773
    has_undefined(T);
 
774
has_undefined({paren_type,_,[T]}) ->
 
775
    has_undefined(T);
 
776
has_undefined({type,_,union,Ts}) ->
 
777
    lists:any(fun has_undefined/1, Ts);
 
778
has_undefined(_) ->
 
779
    false.
 
780
 
753
781
term(Expr) ->
754
782
    try normalise(Expr)
755
783
    catch _:_R -> ret_err(?line(Expr), "bad attribute")
989
1017
inop_prec(':') -> {900,800,900};
990
1018
inop_prec('.') -> {900,900,1000}.
991
1019
 
992
 
-type pre_op() :: 'catch' | '+' | '-' | 'bnot' | '#'.
 
1020
-type pre_op() :: 'catch' | '+' | '-' | 'bnot' | 'not' | '#'.
993
1021
 
994
1022
-spec preop_prec(pre_op()) -> {0 | 600 | 700, 100 | 700 | 800}.
995
1023