Skip to content

Commit 5939061

Browse files
committed
Implement more record like record declaration, for all record names
1 parent 7204580 commit 5939061

File tree

1 file changed

+36
-4
lines changed

1 file changed

+36
-4
lines changed

lib/stdlib/src/erl_parse.yrl

Lines changed: 36 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ list_comprehension lc_expr lc_exprs
3535
map_comprehension
3636
binary_comprehension
3737
tuple
38-
record_expr record_tuple record_field record_fields record_name
38+
record_expr record_tuple record_field record_fields record_name record_spec
3939
map_expr map_tuple map_field map_field_assoc map_field_exact map_fields map_key
4040
if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr
4141
fun_expr fun_clause fun_clauses atom_or_var integer_or_var
@@ -48,7 +48,8 @@ binary bin_elements bin_element bit_expr sigil
4848
opt_bit_size_expr bit_size_expr opt_bit_type_list bit_type_list bit_type
4949
top_type top_types type typed_expr typed_attr_val
5050
type_sig type_sigs type_guard type_guards fun_type binary_type
51-
type_spec spec_fun typed_exprs typed_record_fields field_types field_type
51+
type_spec spec_fun typed_exprs
52+
typed_record_spec typed_record_fields field_types field_type
5253
map_pair_types map_pair_type
5354
bin_base_type bin_unit_type
5455
maybe_expr maybe_match_exprs maybe_match
@@ -92,7 +93,8 @@ char integer float atom sigil_prefix string sigil_suffix var
9293
'<<' '>>'
9394
'!' '=' '::' '..' '...'
9495
'?='
95-
'spec' 'callback' % helper
96+
%% helper: special handling in parse_form like reserved word
97+
'spec' 'callback' 'record'
9698
dot
9799
'%ssa%'.
98100

@@ -128,6 +130,9 @@ form -> function dot : '$1'.
128130
attribute -> '-' atom attr_val : build_attribute('$2', '$3').
129131
attribute -> '-' atom typed_attr_val : build_typed_attribute('$2','$3').
130132
attribute -> '-' atom '(' typed_attr_val ')' : build_typed_attribute('$2','$4').
133+
attribute -> '-' 'record' record_spec : build_attribute(build_atom('$2'), '$3').
134+
attribute -> '-' 'record' typed_record_spec : build_typed_attribute(build_atom('$2'), '$3').
135+
attribute -> '-' 'record' '(' typed_record_spec ')' : build_typed_attribute(build_atom('$2'), '$4').
131136
attribute -> '-' 'spec' type_spec : build_type_spec('$2', '$3').
132137
attribute -> '-' 'callback' type_spec : build_type_spec('$2', '$3').
133138

@@ -140,6 +145,19 @@ spec_fun -> atom ':' atom : {'$1', '$3'}.
140145
typed_attr_val -> expr ',' typed_record_fields : {typed_record, '$1', '$3'}.
141146
typed_attr_val -> expr '::' top_type : {type_def, '$1', '$3'}.
142147

148+
%% Pretty much like attr_val, but record name must be an atom,
149+
%% to not allow variable names as record names when there is no leading '#'
150+
record_spec -> atom : ['$1'].
151+
record_spec -> atom ',' exprs: ['$1' | '$3'].
152+
record_spec -> '(' atom ',' exprs ')': ['$2' | '$4'].
153+
%% More record like record declararion that allows record_name
154+
record_spec -> '#' record_name : ['$2'].
155+
record_spec -> '#' record_name exprs: ['$2' | '$3'].
156+
record_spec -> '(' '#' record_name exprs ')': ['$3' | '$4'].
157+
158+
typed_record_spec -> atom ',' typed_record_fields : {typed_record, '$1', '$3'}.
159+
typed_record_spec -> '#' record_name typed_record_fields : {typed_record, '$2', '$3'}.
160+
143161
typed_record_fields -> '{' typed_exprs '}' : {tuple, ?anno('$1'), '$2'}.
144162

145163
typed_exprs -> typed_expr : ['$1'].
@@ -1281,6 +1299,10 @@ parse_form([{'-',A1},{atom,A2,callback}|Tokens]) ->
12811299
NewTokens = [{'-',A1},{'callback',A2}|Tokens],
12821300
?ANNO_CHECK(NewTokens),
12831301
parse(NewTokens);
1302+
parse_form([{'-',A1},{atom,A2,record}|Tokens]) ->
1303+
NewTokens = [{'-',A1},{'record',A2}|Tokens],
1304+
?ANNO_CHECK(NewTokens),
1305+
parse(NewTokens);
12841306
parse_form(Tokens) ->
12851307
?ANNO_CHECK(Tokens),
12861308
parse(Tokens).
@@ -1323,6 +1345,12 @@ parse_term(Tokens) ->
13231345
build_typed_attribute({atom,Aa,record},
13241346
{typed_record, {atom,_An,RecordName}, RecTuple}) ->
13251347
{attribute,Aa,record,{RecordName,record_tuple(RecTuple)}};
1348+
build_typed_attribute({atom,Aa,record},
1349+
{typed_record, {var,_An,RecordName}, RecTuple}) ->
1350+
{attribute,Aa,record,{RecordName,record_tuple(RecTuple)}};
1351+
build_typed_attribute({atom,Aa,record},
1352+
{typed_record, {ReservedWord,_An}, RecTuple}) ->
1353+
{attribute,Aa,record,{ReservedWord,record_tuple(RecTuple)}};
13261354
build_typed_attribute({atom,Aa,Attr},
13271355
{type_def, {call,_,{atom,_,TypeName},Args}, Type})
13281356
when Attr =:= 'type' ; Attr =:= 'opaque' ->
@@ -1334,7 +1362,7 @@ build_typed_attribute({atom,Aa,Attr},
13341362
"bad type variable")
13351363
end, Args),
13361364
{attribute,Aa,Attr,{TypeName,Type,Args}};
1337-
build_typed_attribute({atom,Aa,Attr}=Abstr,_) ->
1365+
build_typed_attribute({atom,Aa,Attr}=Abstr,_What) ->
13381366
case Attr of
13391367
record -> error_bad_decl(Abstr, record);
13401368
type -> error_bad_decl(Abstr, type);
@@ -1464,6 +1492,10 @@ build_attribute({atom,Aa,record}, Val) ->
14641492
case Val of
14651493
[{atom,_An,Record},RecTuple] ->
14661494
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
1495+
[{var,_An,Record},RecTuple] ->
1496+
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
1497+
[{Record,_An},RecTuple] ->
1498+
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
14671499
[Other|_] -> error_bad_decl(Other, record)
14681500
end;
14691501
build_attribute({atom,Aa,file}, Val) ->

0 commit comments

Comments
 (0)