Skip to content

Commit 4ed5f0c

Browse files
committed
stdlib: fix review comments
Add sequence number for init record functions
1 parent e4b004f commit 4ed5f0c

File tree

1 file changed

+21
-13
lines changed

1 file changed

+21
-13
lines changed

Diff for: lib/stdlib/src/erl_expand_records.erl

+21-13
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ Section [The Abstract Format](`e:erts:absform.md`) in ERTS User's Guide.
4040
strict_ra=[], % Strict record accesses
4141
checked_ra=[], % Successfully accessed records
4242
dialyzer=false, % Compiler option 'dialyzer'
43+
rec_init_count=0, % Number of generated record init functions
4344
new_forms=#{}, % New forms
4445
strict_rec_tests=true :: boolean()
4546
}).
@@ -96,7 +97,12 @@ forms([{function,Anno,N,A,Cs0} | Fs0], St0) ->
9697
forms([F | Fs0], St0) ->
9798
{Fs,St} = forms(Fs0, St0),
9899
{[F | Fs], St};
99-
forms([], #exprec{new_forms=FsN}=St) -> {maps:values(FsN),St};
100+
forms([], #exprec{new_forms=FsN}=St) ->
101+
{[{'function', Anno,
102+
maps:get(Def,FsN),
103+
0,
104+
[{'clause', Anno, [], [], [Def]}]}
105+
|| {_,Anno,_}=Def <- maps:keys(FsN)], St};
100106
forms([], St) -> {[],St}.
101107

102108
clauses([{clause,Anno,H0,G0,B0} | Cs0], St0) ->
@@ -373,28 +379,30 @@ expr({record_index,Anno,Name,F}, St) ->
373379
expr(I, St);
374380
expr({record,Anno0,Name,Is}, St) ->
375381
Anno = mark_record(Anno0, St),
376-
377-
IsUndefined = [{RF, AnnoRF, Field, {atom, AnnoRF, 'undefined'}} || {record_field=RF, AnnoRF, Field, _} <- Is],
378-
Fields = lists:flatten(lists:sort([atom_to_list(FieldAtom) || {record_field, _, {atom, _, FieldAtom}, _} <- Is])),
379-
R_default_init = [{atom,Anno,Name} |
380-
record_inits(record_fields(Name, Anno0, St),IsUndefined)],
381382
R_init = [{atom,Anno,Name} |
382383
record_inits(record_fields(Name, Anno0, St), Is)],
383384
Vars = lists:flatten(traverse_af(Is, fun save_vars/2)),
384385
%% If R_init contains free variables that was not bound via Is
385386
case free_variables(R_init, Vars) of
386387
true ->
387-
FName = list_to_atom("erl_expand_records_init_"++atom_to_list(Name)++"_"++Fields),
388+
IsUndefined = [{RF, AnnoRF, Field, {atom, AnnoRF, 'undefined'}} || {record_field=RF, AnnoRF, Field, _} <- Is],
389+
R_default_init = [{atom,Anno,Name} |
390+
record_inits(record_fields(Name, Anno0, St),IsUndefined)],
388391
%% add a function to the module that returns the
389392
%% initialized record, we generate different init functions
390393
%% depending on which fields that will override the default value
391-
{Tup, St1} = expr({tuple,Anno,R_default_init},St),
392-
F = {'function', Anno, FName, 0,
393-
[{'clause', Anno, [], [], [Tup]}]},
394-
%% replace the record expression with a call expression
394+
{Def, St1} = expr({tuple,Anno,R_default_init},St),
395+
Map=St1#exprec.new_forms,
396+
{FName,St2} = case maps:get(Def, Map, undefined) of
397+
undefined->
398+
C=St1#exprec.rec_init_count,
399+
NewName=list_to_atom("rec_init$^" ++ integer_to_list(C)),
400+
{NewName, St1#exprec{rec_init_count=C+1, new_forms=Map#{Def=>NewName}}};
401+
OldName -> {OldName,St1}
402+
end,
403+
%% replace the init record expression with a call expression
395404
%% to the newly added function and a record update
396-
C = {call,Anno,{atom,Anno,FName},[]},
397-
expr({record, Anno0, C, Name, Is},St1#exprec{new_forms=(St#exprec.new_forms)#{FName=>F}});
405+
expr({record, Anno0, {call,Anno,{atom,Anno,FName},[]}, Name, Is},St2);
398406
false ->
399407
%% No free variables means that we can just
400408
%% output the record as a tuple.

0 commit comments

Comments
 (0)