Skip to content

Commit dddf0da

Browse files
committed
Allow reserved words as record names w/out quotes
This motivation for this comes from the Nitrogen Web Frameworks's heavy use of records, and a clash between HTML <div> element and the Erlang div operator. In Nitrogen, HTML elements are represented by Erlang records. For example: the HTML `<span>` element is `#span{}` in Nitrogen. Logically, the heavily-used HTML `<div>` element would be represented by `#div{}` in Nitrogen, however, that specific syntax is illegal due to `div`'s reserved word status, and must instead be represented with `#'div'`. This syntax, however, is awkward, and has led to a workaround that *works*, but is itself awkward (using the term `#panel{}` instead of `#div{}` - but this in itself leads to a semantic clash, as some frontend HTML frameworks have their own 'panel' elements that might ideally be abstracted into a `#panel{}` element. But, As far as I understand, there is no potential syntax clash in allowing the syntax `#div` ito be acceptable, and have the parser recognize that the `div` (or any reserved word) in that `context` can only be an atom, and would never be an operator. So this change tweaks the grammar to recognize the circumstances of: `#reserved_word{}`. Further, this change does not change the way the records are defined (so the definition must still be defined with the atom properly wrapped in quotes (e.g. `-record('div', {a,b}).`). This PR also adds the appropriate tests in `erl_expand_records_SUITE`, which I wasn't sure if that was appropriate place, but it seemed the most relevant.
1 parent ed310cb commit dddf0da

File tree

2 files changed

+130
-3
lines changed

2 files changed

+130
-3
lines changed

lib/stdlib/src/erl_parse.yrl

Lines changed: 58 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ list_comprehension lc_expr lc_exprs
3434
map_comprehension
3535
binary_comprehension
3636
tuple
37-
record_expr record_tuple record_field record_fields
37+
record_expr record_tuple record_field record_fields res_rec
3838
map_expr map_tuple map_field map_field_assoc map_field_exact map_fields map_key
3939
if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr
4040
fun_expr fun_clause fun_clauses atom_or_var integer_or_var
@@ -192,6 +192,11 @@ type -> '{' top_types '}' : {type, ?anno('$1'), tuple, '$2'}.
192192
type -> '#' atom '{' '}' : {type, ?anno('$1'), record, ['$2']}.
193193
type -> '#' atom '{' field_types '}' : {type, ?anno('$1'),
194194
record, ['$2'|'$4']}.
195+
type -> '#' res_rec '{' '}' : {type, ?anno('$1'),
196+
record, [build_atom('$2')]}.
197+
type -> '#' res_rec '{' field_types '}' : {type, ?anno('$1'),
198+
record, [build_atom('$2')|'$4']}.
199+
195200
type -> binary_type : '$1'.
196201
type -> integer : '$1'.
197202
type -> char : '$1'.
@@ -315,6 +320,10 @@ record_pat_expr -> '#' atom '.' atom :
315320
{record_index,?anno('$1'),element(3, '$2'),'$4'}.
316321
record_pat_expr -> '#' atom record_tuple :
317322
{record,?anno('$1'),element(3, '$2'),'$3'}.
323+
record_pat_expr -> '#' res_rec'.' atom :
324+
{record_index,?anno('$1'),element(1, '$2'),'$4'}.
325+
record_pat_expr -> '#' res_rec record_tuple :
326+
{record,?anno('$1'),element(1, '$2'),'$3'}.
318327

319328
list -> '[' ']' : {nil,?anno('$1')}.
320329
list -> '[' expr tail : {cons,?anno('$1'),'$2','$3'}.
@@ -413,6 +422,19 @@ record_expr -> record_expr '#' atom '.' atom :
413422
record_expr -> record_expr '#' atom record_tuple :
414423
{record,?anno('$2'),'$1',element(3, '$3'),'$4'}.
415424

425+
record_expr -> '#' res_rec '.' atom :
426+
{record_index,?anno('$1'),element(1, '$2'),'$4'}.
427+
record_expr -> '#' res_rec record_tuple :
428+
{record, ?anno('$1'), element(1, '$2'), '$3'}.
429+
record_expr -> expr_max '#' res_rec '.' atom :
430+
{record_field,?anno('$2'),'$1',element(1, '$3'),'$5'}.
431+
record_expr -> expr_max '#' res_rec record_tuple :
432+
{record,?anno('$2'),'$1',element(1, '$3'),'$4'}.
433+
record_expr -> record_expr '#' res_rec '.' atom :
434+
{record_field,?anno('$2'),'$1',element(1, '$3'),'$5'}.
435+
record_expr -> record_expr '#' res_rec record_tuple :
436+
{record,?anno('$2'),'$1',element(1, '$3'),'$4'}.
437+
416438
record_tuple -> '{' '}' : [].
417439
record_tuple -> '{' record_fields '}' : '$2'.
418440

@@ -587,6 +609,34 @@ comp_op -> '>' : '$1'.
587609
comp_op -> '=:=' : '$1'.
588610
comp_op -> '=/=' : '$1'.
589611

612+
res_rec -> 'after' : '$1'.
613+
res_rec -> 'begin' : '$1'.
614+
res_rec -> 'case' : '$1'.
615+
res_rec -> 'try' : '$1'.
616+
res_rec -> 'catch' : '$1'.
617+
res_rec -> 'end' : '$1'.
618+
res_rec -> 'fun' : '$1'.
619+
res_rec -> 'if' : '$1'.
620+
res_rec -> 'of' : '$1'.
621+
res_rec -> 'receive' : '$1'.
622+
res_rec -> 'when' : '$1'.
623+
res_rec -> 'maybe' : '$1'.
624+
res_rec -> 'else' : '$1'.
625+
res_rec -> 'andalso' : '$1'.
626+
res_rec -> 'orelse' : '$1'.
627+
res_rec -> 'bnot' : '$1'.
628+
res_rec -> 'not' : '$1'.
629+
res_rec -> 'div' : '$1'.
630+
res_rec -> 'rem' : '$1'.
631+
res_rec -> 'band' : '$1'.
632+
res_rec -> 'and' : '$1'.
633+
res_rec -> 'bor' : '$1'.
634+
res_rec -> 'bxor' : '$1'.
635+
res_rec -> 'bsl' : '$1'.
636+
res_rec -> 'bsr' : '$1'.
637+
res_rec -> 'or' : '$1'.
638+
res_rec -> 'xor' : '$1'.
639+
590640
ssa_check_when_clauses -> ssa_check_when_clause : ['$1'].
591641
ssa_check_when_clauses -> ssa_check_when_clause ssa_check_when_clauses :
592642
['$1'|'$2'].
@@ -1364,6 +1414,13 @@ build_bin_type([], Int) ->
13641414
build_bin_type([{var, Aa, _}|_], _) ->
13651415
ret_err(Aa, "Bad binary type").
13661416

1417+
build_atom({Atom, Aa}) ->
1418+
{atom, Aa, Atom}.
1419+
1420+
%print(X) ->
1421+
% io:format("Details: ~p~n",[X]),
1422+
% X.
1423+
13671424
build_type({atom, A, Name}, Types) ->
13681425
Tag = type_tag(Name, length(Types)),
13691426
{Tag, A, Name, Types}.

lib/stdlib/test/erl_expand_records_SUITE.erl

Lines changed: 72 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@
3939
-export([attributes/1, expr/1, guard/1,
4040
init/1, pattern/1, strict/1, update/1,
4141
otp_5915/1, otp_7931/1, otp_5990/1,
42-
otp_7078/1, maps/1,
42+
otp_7078/1, pr_7873/1, maps/1,
4343
side_effects/1]).
4444

4545
init_per_testcase(_Case, Config) ->
@@ -59,7 +59,7 @@ all() ->
5959

6060
groups() ->
6161
[{tickets, [],
62-
[otp_5915, otp_7931, otp_5990, otp_7078]}].
62+
[otp_5915, otp_7931, otp_5990, otp_7078, pr_7873]}].
6363

6464
init_per_suite(Config) ->
6565
Config.
@@ -719,6 +719,76 @@ otp_7078(Config) when is_list(Config) ->
719719
run(Config, Ts, [strict_record_tests]),
720720
ok.
721721

722+
%% PR-7873. Reserved words as record names.
723+
pr_7873(Config) when is_list(Config) ->
724+
Words = [
725+
<<"after">>,
726+
<<"begin">>,
727+
<<"case">>,
728+
<<"try">>,
729+
<<"catch">>,
730+
<<"end">>,
731+
<<"fun">>,
732+
<<"if">>,
733+
<<"of">>,
734+
<<"receive">>,
735+
<<"when">>,
736+
<<"maybe">>,
737+
<<"else">>,
738+
<<"andalso">>,
739+
<<"orelse">>,
740+
<<"bnot">>,
741+
<<"not">>,
742+
<<"div">>,
743+
<<"rem">>,
744+
<<"band">>,
745+
<<"and">>,
746+
<<"bor">>,
747+
<<"bxor">>,
748+
<<"bsl">>,
749+
<<"bsr">>,
750+
<<"or">>,
751+
<<"xor">>
752+
],
753+
754+
Code = <<"
755+
-record('WORD', {a = 1}).
756+
757+
-type x() :: #WORD{}.
758+
759+
t() ->
760+
'WORD' = element(1, #WORD{}),
761+
2 = #WORD.a,
762+
A = #WORD{},
763+
_ = #WORD{a=5},
764+
1 = A#WORD.a,
765+
_ = A#WORD{},
766+
C = A#WORD{a = 2},
767+
2 = C#WORD.a,
768+
#WORD{a = X} = C,
769+
2 = X,
770+
D = #WORD{a = 2}#WORD{a = 3},
771+
4 = D#WORD{a = 4}#WORD.a,
772+
3 = match1(D),
773+
ok = match2(D, 3),
774+
ok = match3(#WORD{a=#WORD{}}),
775+
ok.
776+
777+
-spec match1(x()) -> any().
778+
match1(#WORD{a = X}) -> X.
779+
780+
-spec match2(#WORD{}, any()) -> ok.
781+
match2(Rec, V) when Rec#WORD.a == V -> ok.
782+
783+
match3(#WORD{a=#WORD{}}) -> ok.
784+
">>,
785+
F = fun(Word) ->
786+
binary:replace(Code, <<"WORD">>, Word, [global])
787+
end,
788+
Ts = lists:map(F, Words),
789+
run(Config, Ts, [strict_record_tests]),
790+
ok.
791+
722792
id(I) -> I.
723793

724794
-record(side_effects, {a,b,c}).

0 commit comments

Comments
 (0)