Skip to content

Commit f30c236

Browse files
committed
Implement record style record declarations, for all record names
1 parent 2b0e1ca commit f30c236

File tree

2 files changed

+47
-6
lines changed

2 files changed

+47
-6
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'].
@@ -1342,6 +1360,10 @@ parse_form([{'-',A1},{atom,A2,callback}|Tokens]) ->
13421360
NewTokens = [{'-',A1},{'callback',A2}|Tokens],
13431361
?ANNO_CHECK(NewTokens),
13441362
parse(NewTokens);
1363+
parse_form([{'-',A1},{atom,A2,record}|Tokens]) ->
1364+
NewTokens = [{'-',A1},{'record',A2}|Tokens],
1365+
?ANNO_CHECK(NewTokens),
1366+
parse(NewTokens);
13451367
parse_form(Tokens) ->
13461368
?ANNO_CHECK(Tokens),
13471369
parse(Tokens).
@@ -1404,6 +1426,12 @@ parse_term(Tokens) ->
14041426
build_typed_attribute({atom,Aa,record},
14051427
{typed_record, {atom,_An,RecordName}, RecTuple}) ->
14061428
{attribute,Aa,record,{RecordName,record_tuple(RecTuple)}};
1429+
build_typed_attribute({atom,Aa,record},
1430+
{typed_record, {var,_An,RecordName}, RecTuple}) ->
1431+
{attribute,Aa,record,{RecordName,record_tuple(RecTuple)}};
1432+
build_typed_attribute({atom,Aa,record},
1433+
{typed_record, {ReservedWord,_An}, RecTuple}) ->
1434+
{attribute,Aa,record,{ReservedWord,record_tuple(RecTuple)}};
14071435
build_typed_attribute({atom,Aa,Attr},
14081436
{type_def, {call,_,{atom,_,TypeName},Args}, Type})
14091437
when Attr =:= 'type' ; Attr =:= 'opaque' ->
@@ -1415,7 +1443,7 @@ build_typed_attribute({atom,Aa,Attr},
14151443
"bad type variable")
14161444
end, Args),
14171445
{attribute,Aa,Attr,{TypeName,Type,Args}};
1418-
build_typed_attribute({atom,Aa,Attr}=Abstr,_) ->
1446+
build_typed_attribute({atom,Aa,Attr}=Abstr,_What) ->
14191447
case Attr of
14201448
record -> error_bad_decl(Abstr, record);
14211449
type -> error_bad_decl(Abstr, type);
@@ -1545,6 +1573,10 @@ build_attribute({atom,Aa,record}, Val) ->
15451573
case Val of
15461574
[{atom,_An,Record},RecTuple] ->
15471575
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
1576+
[{var,_An,Record},RecTuple] ->
1577+
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
1578+
[{Record,_An},RecTuple] ->
1579+
{attribute,Aa,record,{Record,record_tuple(RecTuple)}};
15481580
[Other|_] -> error_bad_decl(Other, record)
15491581
end;
15501582
build_attribute({atom,Aa,file}, Val) ->

lib/stdlib/test/erl_expand_records_SUITE.erl

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -758,7 +758,8 @@ otp_7078(Config) when is_list(Config) ->
758758
run(Config, Ts, [strict_record_tests]),
759759
ok.
760760

761-
%% PR-7873. Reserved words and variable names as record names
761+
%% PR-7873. Reserved words and variable names as record names,
762+
%% and record style record declarations
762763
pr_7873(Config) when is_list(Config) ->
763764
Words = [
764765
<<"Abc">>,
@@ -797,7 +798,15 @@ pr_7873(Config) when is_list(Config) ->
797798
[~"-record('WORD', {a = 1}).",
798799
~"-record('WORD', {a = 1 :: integer()}).",
799800
~"-record 'WORD', {a = 1}.",
800-
~"-record 'WORD', {a = 1 :: integer()}."],
801+
~"-record 'WORD', {a = 1 :: integer()}.",
802+
~"-record(#WORD{a = 1}).",
803+
~"-record(#WORD{a = 1 :: integer()}).",
804+
~"-record #WORD{a = 1}.",
805+
~"-record #WORD{a = 1 :: integer()}.",
806+
~"-record # WORD{a = 1}.",
807+
~"-record #WORD {a = 1}.",
808+
~"-record # WORD {a = 1}.",
809+
~"-record #'WORD'{a = 1}."],
801810

802811
Code =
803812
~"""

0 commit comments

Comments
 (0)