diff options
author | Hans Bolinder <[email protected]> | 2010-04-19 11:40:22 +0000 |
---|---|---|
committer | Erlang/OTP <[email protected]> | 2010-04-19 11:40:22 +0000 |
commit | a7ec8726e2f3c5259c2233cc2ab3fc56147febf9 (patch) | |
tree | 2c5bf13e512fc26dce2ca3e82bf3e70277820e2f /lib/stdlib/src/erl_parse.yrl | |
parent | b66483f46bf9f998a1320606d27ab73cf2ce739b (diff) | |
download | otp-a7ec8726e2f3c5259c2233cc2ab3fc56147febf9.tar.gz otp-a7ec8726e2f3c5259c2233cc2ab3fc56147febf9.tar.bz2 otp-a7ec8726e2f3c5259c2233cc2ab3fc56147febf9.zip |
OTP-8567 The word 'spec' is no longer reserved.
The function erl_scan:reserved_word/1 no longer returns true when given the
word spec. This bug was introduced in STDLIB-1.15.3 (R12B-3).
Diffstat (limited to 'lib/stdlib/src/erl_parse.yrl')
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 101 |
1 files changed, 50 insertions, 51 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 786319d79c..7145cf13fd 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -30,9 +30,8 @@ expr_600 expr_700 expr_800 expr_900 expr_max list tail list_comprehension lc_expr lc_exprs -binary_comprehension +binary_comprehension tuple -atom1 %struct record_expr record_tuple record_field record_fields if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr @@ -55,7 +54,7 @@ char integer float atom string var '(' ')' ',' '->' ':-' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.' 'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when' -'andalso' 'orelse' 'query' 'spec' +'andalso' 'orelse' 'query' 'bnot' 'not' '*' '/' 'div' 'rem' 'band' 'and' '+' '-' 'bor' 'bxor' 'bsl' 'bsr' 'or' 'xor' @@ -63,6 +62,7 @@ char integer float atom string var '==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<=' '<<' '>>' '!' '=' '::' +'spec' % helper dot. Expect 2. @@ -77,19 +77,16 @@ attribute -> '-' atom attr_val : build_attribute('$2', '$3'). attribute -> '-' atom typed_attr_val : build_typed_attribute('$2','$3'). attribute -> '-' atom '(' typed_attr_val ')' : build_typed_attribute('$2','$4'). attribute -> '-' 'spec' type_spec : build_type_spec('$2', '$3'). - -atom1 -> 'spec' : {atom, ?line('$1'), 'spec'}. -atom1 -> atom : '$1'. type_spec -> spec_fun type_sigs : {'$1', '$2'}. type_spec -> '(' spec_fun type_sigs ')' : {'$2', '$3'}. -spec_fun -> atom1 : '$1'. -spec_fun -> atom1 ':' atom1 : {'$1', '$3'}. +spec_fun -> atom : '$1'. +spec_fun -> atom ':' atom : {'$1', '$3'}. %% The following two are retained only for backwards compatibility; %% they are not part of the EEP syntax and should be removed. -spec_fun -> atom1 '/' integer '::' : {'$1', '$3'}. -spec_fun -> atom1 ':' atom1 '/' integer '::' : {'$1', '$3', '$5'}. +spec_fun -> atom '/' integer '::' : {'$1', '$3'}. +spec_fun -> atom ':' atom '/' integer '::' : {'$1', '$3', '$5'}. typed_attr_val -> expr ',' typed_record_fields : {typed_record, '$1', '$3'}. typed_attr_val -> expr '::' top_type : {type_def, '$1', '$3'}. @@ -107,13 +104,13 @@ type_sigs -> type_sig : ['$1']. type_sigs -> type_sig ';' type_sigs : ['$1'|'$3']. type_sig -> fun_type : '$1'. -type_sig -> fun_type 'when' type_guards : {type, ?line('$1'), bounded_fun, +type_sig -> fun_type 'when' type_guards : {type, ?line('$1'), bounded_fun, ['$1','$3']}. type_guards -> type_guard : ['$1']. type_guards -> type_guard ',' type_guards : ['$1'|'$3']. -type_guard -> atom1 '(' top_types ')' : {type, ?line('$1'), constraint, +type_guard -> atom '(' top_types ')' : {type, ?line('$1'), constraint, ['$1', '$3']}. top_types -> top_type : ['$1']. @@ -127,53 +124,53 @@ top_type_100 -> type '|' top_type_100 : lift_unions('$1','$3'). type -> '(' top_type ')' : {paren_type, ?line('$2'), ['$2']}. type -> var : '$1'. -type -> atom1 : '$1'. -type -> atom1 '(' ')' : build_gen_type('$1'). -type -> atom1 '(' top_types ')' : {type, ?line('$1'), +type -> atom : '$1'. +type -> atom '(' ')' : build_gen_type('$1'). +type -> atom '(' top_types ')' : {type, ?line('$1'), normalise('$1'), '$3'}. -type -> atom1 ':' atom1 '(' ')' : {remote_type, ?line('$1'), +type -> atom ':' atom '(' ')' : {remote_type, ?line('$1'), ['$1', '$3', []]}. -type -> atom1 ':' atom1 '(' top_types ')' : {remote_type, ?line('$1'), +type -> atom ':' atom '(' top_types ')' : {remote_type, ?line('$1'), ['$1', '$3', '$5']}. type -> '[' ']' : {type, ?line('$1'), nil, []}. type -> '[' top_type ']' : {type, ?line('$1'), list, ['$2']}. -type -> '[' top_type ',' '.' '.' '.' ']' : {type, ?line('$1'), +type -> '[' top_type ',' '.' '.' '.' ']' : {type, ?line('$1'), nonempty_list, ['$2']}. type -> '{' '}' : {type, ?line('$1'), tuple, []}. type -> '{' top_types '}' : {type, ?line('$1'), tuple, '$2'}. -type -> '#' atom1 '{' '}' : {type, ?line('$1'), record, ['$2']}. -type -> '#' atom1 '{' field_types '}' : {type, ?line('$1'), +type -> '#' atom '{' '}' : {type, ?line('$1'), record, ['$2']}. +type -> '#' atom '{' field_types '}' : {type, ?line('$1'), record, ['$2'|'$4']}. type -> binary_type : '$1'. type -> int_type : '$1'. -type -> int_type '.' '.' int_type : {type, ?line('$1'), range, +type -> int_type '.' '.' int_type : {type, ?line('$1'), range, ['$1', '$4']}. type -> 'fun' '(' ')' : {type, ?line('$1'), 'fun', []}. type -> 'fun' '(' fun_type_100 ')' : '$3'. int_type -> integer : '$1'. -int_type -> '-' integer : abstract(-normalise('$2'), +int_type -> '-' integer : abstract(-normalise('$2'), ?line('$2')). -fun_type_100 -> '(' '.' '.' '.' ')' '->' top_type +fun_type_100 -> '(' '.' '.' '.' ')' '->' top_type : {type, ?line('$1'), 'fun', [{type, ?line('$1'), any}, '$7']}. fun_type_100 -> fun_type : '$1'. fun_type -> '(' ')' '->' top_type : {type, ?line('$1'), 'fun', [{type, ?line('$1'), product, []}, '$4']}. -fun_type -> '(' top_types ')' '->' top_type +fun_type -> '(' top_types ')' '->' top_type : {type, ?line('$1'), 'fun', [{type, ?line('$1'), product, '$2'},'$5']}. field_types -> field_type : ['$1']. field_types -> field_type ',' field_types : ['$1'|'$3']. -field_type -> atom1 '::' top_type : {type, ?line('$1'), field_type, +field_type -> atom '::' top_type : {type, ?line('$1'), field_type, ['$1', '$3']}. -binary_type -> '<<' '>>' : {type, ?line('$1'),binary, - [abstract(0, ?line('$1')), +binary_type -> '<<' '>>' : {type, ?line('$1'),binary, + [abstract(0, ?line('$1')), abstract(0, ?line('$1'))]}. binary_type -> '<<' bin_base_type '>>' : {type, ?line('$1'),binary, ['$2', abstract(0, ?line('$1'))]}. @@ -195,7 +192,7 @@ function -> function_clauses : build_function('$1'). function_clauses -> function_clause : ['$1']. function_clauses -> function_clause ';' function_clauses : ['$1'|'$3']. -function_clause -> atom1 clause_args clause_guard clause_body : +function_clause -> atom clause_args clause_guard clause_body : {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. @@ -248,9 +245,9 @@ expr_800 -> expr_900 ':' expr_max : {remote,?line('$2'),'$1','$3'}. expr_800 -> expr_900 : '$1'. -expr_900 -> '.' atom1 : +expr_900 -> '.' atom : {record_field,?line('$1'),{atom,?line('$1'),''},'$2'}. -expr_900 -> expr_900 '.' atom1 : +expr_900 -> expr_900 '.' atom : {record_field,?line('$2'),'$1','$3'}. expr_900 -> expr_max : '$1'. @@ -301,8 +298,8 @@ opt_bit_type_list -> '$empty' : default. bit_type_list -> bit_type '-' bit_type_list : ['$1' | '$3']. bit_type_list -> bit_type : ['$1']. -bit_type -> atom1 : element(3,'$1'). -bit_type -> atom1 ':' integer : { element(3,'$1'), element(3,'$3') }. +bit_type -> atom : element(3,'$1'). +bit_type -> atom ':' integer : { element(3,'$1'), element(3,'$3') }. bit_size_expr -> expr_max : '$1'. @@ -322,7 +319,7 @@ tuple -> '{' '}' : {tuple,?line('$1'),[]}. tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}. -%%struct -> atom1 tuple : +%%struct -> atom tuple : %% {struct,?line('$1'),element(3, '$1'),element(3, '$2')}. @@ -330,13 +327,13 @@ tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}. %% N.B. Field names are returned as the complete object, even if they are %% always atoms for the moment, this might change in the future. -record_expr -> '#' atom1 '.' atom1 : +record_expr -> '#' atom '.' atom : {record_index,?line('$1'),element(3, '$2'),'$4'}. -record_expr -> '#' atom1 record_tuple : +record_expr -> '#' atom record_tuple : {record,?line('$1'),element(3, '$2'),'$3'}. -record_expr -> expr_max '#' atom1 '.' atom1 : +record_expr -> expr_max '#' atom '.' atom : {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}. -record_expr -> expr_max '#' atom1 record_tuple : +record_expr -> expr_max '#' atom record_tuple : {record,?line('$2'),'$1',element(3, '$3'),'$4'}. record_tuple -> '{' '}' : []. @@ -346,7 +343,7 @@ record_fields -> record_field : ['$1']. record_fields -> record_field ',' record_fields : ['$1' | '$3']. record_field -> var '=' expr : {record_field,?line('$1'),'$1','$3'}. -record_field -> atom1 '=' expr : {record_field,?line('$1'),'$1','$3'}. +record_field -> atom '=' expr : {record_field,?line('$1'),'$1','$3'}. %% N.B. This is called from expr_700. @@ -380,9 +377,9 @@ receive_expr -> 'receive' cr_clauses 'after' expr clause_body 'end' : {'receive',?line('$1'),'$2','$4','$5'}. -fun_expr -> 'fun' atom1 '/' integer : +fun_expr -> 'fun' atom '/' integer : {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}. -fun_expr -> 'fun' atom1 ':' atom1 '/' integer : +fun_expr -> 'fun' atom ':' atom '/' integer : {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4'),element(3,'$6')}}. fun_expr -> 'fun' fun_clauses 'end' : build_fun(?line('$1'), '$2'). @@ -412,7 +409,7 @@ try_clauses -> try_clause ';' try_clauses : ['$1' | '$3']. try_clause -> expr clause_guard clause_body : L = ?line('$1'), {clause,L,[{tuple,L,[{atom,L,throw},'$1',{var,L,'_'}]}],'$2','$3'}. -try_clause -> atom1 ':' expr clause_guard clause_body : +try_clause -> atom ':' expr clause_guard clause_body : L = ?line('$1'), {clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}. try_clause -> var ':' expr clause_guard clause_body : @@ -436,7 +433,7 @@ guard -> exprs ';' guard : ['$1'|'$3']. atomic -> char : '$1'. atomic -> integer : '$1'. atomic -> float : '$1'. -atomic -> atom1 : '$1'. +atomic -> atom : '$1'. atomic -> strings : '$1'. strings -> string : '$1'. @@ -481,7 +478,7 @@ rule -> rule_clauses : build_rule('$1'). rule_clauses -> rule_clause : ['$1']. rule_clauses -> rule_clause ';' rule_clauses : ['$1'|'$3']. -rule_clause -> atom1 clause_args clause_guard rule_body : +rule_clause -> atom clause_args clause_guard rule_body : {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. rule_body -> ':-' lc_exprs: '$2'. @@ -503,8 +500,8 @@ Erlang code. %% mkop(Op, Arg) -> {op,Line,Op,Arg}. %% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}. --define(mkop2(L, OpPos, R), - begin +-define(mkop2(L, OpPos, R), + begin {Op,Pos} = OpPos, {op,Pos,Op,L,R} end). @@ -522,6 +519,8 @@ Erlang code. %% These really suck and are only here until Calle gets multiple %% entry points working. +parse_form([{'-',L1},{atom,L2,spec}|Tokens]) -> + parse([{'-',L1},{'spec',L2}|Tokens]); parse_form(Tokens) -> parse(Tokens). @@ -548,7 +547,7 @@ parse_term(Tokens) -> -type attributes() :: 'export' | 'file' | 'import' | 'module' | 'opaque' | 'record' | 'type'. -build_typed_attribute({atom,La,record}, +build_typed_attribute({atom,La,record}, {typed_record, {atom,_Ln,RecordName}, RecTuple}) -> {attribute,La,record,{RecordName,record_tuple(RecTuple)}}; build_typed_attribute({atom,La,Attr}, @@ -571,7 +570,7 @@ build_typed_attribute({atom,La,Attr},_) -> build_type_spec({spec,La}, {SpecFun, TypeSpecs}) -> NewSpecFun = case SpecFun of - {atom, _, Fun} -> + {atom, _, Fun} -> {Fun, find_arity_from_specs(TypeSpecs)}; {{atom,_, Mod}, {atom,_, Fun}} -> {Mod,Fun,find_arity_from_specs(TypeSpecs)}; @@ -705,7 +704,7 @@ attribute_farity(Other) -> Other. attribute_farity_list(Args) -> [attribute_farity(A) || A <- Args]. - + -spec error_bad_decl(integer(), attributes()) -> no_return(). error_bad_decl(L, S) -> @@ -728,17 +727,17 @@ record_fields([{match,_Lm,{atom,La,A},Expr}|Fields]) -> [{record_field,La,{atom,La,A},Expr}|record_fields(Fields)]; record_fields([{typed,Expr,TypeInfo}|Fields]) -> [Field] = record_fields([Expr]), - TypeInfo1 = + TypeInfo1 = case Expr of {match, _, _, _} -> TypeInfo; %% If we have an initializer. - {atom, La, _} -> + {atom, La, _} -> case has_undefined(TypeInfo) of false -> lift_unions(abstract(undefined, La), TypeInfo); true -> TypeInfo end - end, + end, [{typed_record_field,Field,TypeInfo1}|record_fields(Fields)]; record_fields([Other|_Fields]) -> ret_err(?line(Other), "bad record field"); |