Skip to content

Commit 90f71a1

Browse files
committed
syntax_tools: Annotate map comprehensions and generators
Fix #10119. This fix works for 26 and 27.
1 parent 940ec0f commit 90f71a1

File tree

2 files changed

+52
-38
lines changed

2 files changed

+52
-38
lines changed

lib/syntax_tools/src/erl_syntax_lib.erl

Lines changed: 36 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -496,10 +496,14 @@ vann(Tree, Env) ->
496496
vann_list_comp(Tree, Env);
497497
binary_comp ->
498498
vann_binary_comp(Tree, Env);
499+
map_comp ->
500+
vann_map_comp(Tree, Env);
499501
generator ->
500502
vann_generator(Tree, Env);
501503
binary_generator ->
502504
vann_binary_generator(Tree, Env);
505+
map_generator ->
506+
vann_map_generator(Tree, Env);
503507
block_expr ->
504508
vann_block_expr(Tree, Env);
505509
macro ->
@@ -653,7 +657,7 @@ vann_receive_expr(Tree, Env) ->
653657

654658
vann_list_comp(Tree, Env) ->
655659
Es = erl_syntax:list_comp_body(Tree),
656-
{Es1, {Bound1, Free1}} = vann_list_comp_body(Es, Env),
660+
{Es1, {Bound1, Free1}} = vann_comp_body(Es, Env),
657661
Env1 = ordsets:union(Env, Bound1),
658662
T = erl_syntax:list_comp_template(Tree),
659663
{T1, _, Free2} = vann(T, Env1),
@@ -662,34 +666,9 @@ vann_list_comp(Tree, Env) ->
662666
Tree1 = rewrite(Tree, erl_syntax:list_comp(T1, Es1)),
663667
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.
664668

665-
vann_list_comp_body_join() ->
666-
fun (T, {Env, Bound, Free}) ->
667-
{T1, Bound1, Free1} = case erl_syntax:type(T) of
668-
binary_generator ->
669-
vann_binary_generator(T,Env);
670-
generator ->
671-
vann_generator(T, Env);
672-
_ ->
673-
%% Bindings in filters are not
674-
%% exported to the rest of the
675-
%% body.
676-
{T2, _, Free2} = vann(T, Env),
677-
{T2, [], Free2}
678-
end,
679-
Env1 = ordsets:union(Env, Bound1),
680-
{T1, {Env1, ordsets:union(Bound, Bound1),
681-
ordsets:union(Free,
682-
ordsets:subtract(Free1, Bound))}}
683-
end.
684-
685-
vann_list_comp_body(Ts, Env) ->
686-
F = vann_list_comp_body_join(),
687-
{Ts1, {_, Bound, Free}} = lists:mapfoldl(F, {Env, [], []}, Ts),
688-
{Ts1, {Bound, Free}}.
689-
690669
vann_binary_comp(Tree, Env) ->
691670
Es = erl_syntax:binary_comp_body(Tree),
692-
{Es1, {Bound1, Free1}} = vann_binary_comp_body(Es, Env),
671+
{Es1, {Bound1, Free1}} = vann_comp_body(Es, Env),
693672
Env1 = ordsets:union(Env, Bound1),
694673
T = erl_syntax:binary_comp_template(Tree),
695674
{T1, _, Free2} = vann(T, Env1),
@@ -698,13 +677,31 @@ vann_binary_comp(Tree, Env) ->
698677
Tree1 = rewrite(Tree, erl_syntax:binary_comp(T1, Es1)),
699678
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.
700679

701-
vann_binary_comp_body_join() ->
680+
vann_map_comp(Tree, Env) ->
681+
Es = erl_syntax:map_comp_body(Tree),
682+
{Es1, {Bound1, Free1}} = vann_comp_body(Es, Env),
683+
Env1 = ordsets:union(Env, Bound1),
684+
T = erl_syntax:map_comp_template(Tree),
685+
{T1, _, Free2} = vann(T, Env1),
686+
Free = ordsets:union(Free1, ordsets:subtract(Free2, Bound1)),
687+
Bound = [],
688+
Tree1 = rewrite(Tree, erl_syntax:map_comp(T1, Es1)),
689+
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.
690+
691+
vann_comp_body(Ts, Env) ->
692+
F = vann_comp_body_join(),
693+
{Ts1, {_, Bound, Free}} = lists:mapfoldl(F, {Env, [], []}, Ts),
694+
{Ts1, {Bound, Free}}.
695+
696+
vann_comp_body_join() ->
702697
fun (T, {Env, Bound, Free}) ->
703698
{T1, Bound1, Free1} = case erl_syntax:type(T) of
704-
binary_generator ->
705-
vann_binary_generator(T, Env);
706-
generator ->
699+
binary_generator ->
700+
vann_binary_generator(T,Env);
701+
generator ->
707702
vann_generator(T, Env);
703+
map_generator ->
704+
vann_map_generator(T,Env);
708705
_ ->
709706
%% Bindings in filters are not
710707
%% exported to the rest of the
@@ -718,11 +715,6 @@ vann_binary_comp_body_join() ->
718715
ordsets:subtract(Free1, Bound))}}
719716
end.
720717

721-
vann_binary_comp_body(Ts, Env) ->
722-
F = vann_binary_comp_body_join(),
723-
{Ts1, {_, Bound, Free}} = lists:mapfoldl(F, {Env, [], []}, Ts),
724-
{Ts1, {Bound, Free}}.
725-
726718
%% In list comprehension generators, the pattern variables are always
727719
%% viewed as new occurrences, shadowing whatever is in the input
728720
%% environment (thus, the pattern contains no variable uses, only
@@ -744,6 +736,14 @@ vann_binary_generator(Tree, Env) ->
744736
Tree1 = rewrite(Tree, erl_syntax:binary_generator(P1, E1)),
745737
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.
746738

739+
vann_map_generator(Tree, Env) ->
740+
P = erl_syntax:map_generator_pattern(Tree),
741+
{P1, Bound, _} = vann_pattern(P, []),
742+
E = erl_syntax:map_generator_body(Tree),
743+
{E1, _, Free} = vann(E, Env),
744+
Tree1 = rewrite(Tree, erl_syntax:map_generator(P1, E1)),
745+
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.
746+
747747
vann_block_expr(Tree, Env) ->
748748
Es = erl_syntax:block_expr_body(Tree),
749749
{Es1, {Bound, Free}} = vann_body(Es, Env),

lib/syntax_tools/test/syntax_tools_SUITE.erl

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@
2929
t_abstract_type/1,t_erl_parse_type/1,t_type/1,
3030
t_epp_dodger/1,t_epp_dodger_clever/1,
3131
t_comment_scan/1,t_prettypr/1,test_named_fun_bind_ann/1,
32-
test_maybe_expr_ann/1]).
32+
test_maybe_expr_ann/1,test_mc_ann/1]).
3333

3434
suite() -> [{ct_hooks,[ts_install_cth]}].
3535

@@ -40,7 +40,7 @@ all() ->
4040
t_abstract_type,t_erl_parse_type,t_type,
4141
t_epp_dodger,t_epp_dodger_clever,
4242
t_comment_scan,t_prettypr,test_named_fun_bind_ann,
43-
test_maybe_expr_ann].
43+
test_maybe_expr_ann,test_mc_ann].
4444

4545
groups() ->
4646
[].
@@ -337,6 +337,8 @@ t_erl_parse_type(Config) when is_list(Config) ->
337337
{"[catch V||V <- Vs]", list_comp,false},
338338
{"<< <<B>> || <<B>> <= Bs>>", binary_comp,false},
339339
{"<< (catch <<B>>) || <<B>> <= Bs>>", binary_comp,false},
340+
{"#{K => V || {K,V} <- KVs}", map_comp,false},
341+
{"#{K => (catch V) || {K,V} <- KVs}", map_comp,false},
340342
{"#state{ a = A, b = B}", record_expr,false},
341343
{"#state{}", record_expr,false},
342344
{"#s{ a = #def{ a=A }, b = B}", record_expr,false},
@@ -464,7 +466,19 @@ test_maybe_expr_ann(Config) when is_list(Config) ->
464466
[MaybeMatchAnn1, MaybeMatchAnn2, MatchAnn1] = erl_syntax:maybe_expr_body(MaybeNoElseAnn),
465467
NoElseAnn = erl_syntax:maybe_expr_else(MaybeNoElseAnn),
466468
[] = erl_syntax:get_ann(NoElseAnn),
469+
ok.
467470

471+
test_mc_ann(Config) when is_list(Config) ->
472+
Expr = {mc,1,
473+
{map_field_assoc,1,{var,1,'X'},{var,1,'Y'}},
474+
[{generate,1,
475+
{tuple,1,[{var,1,'X'},{var,1,'Y'}]},
476+
{var,1,'Pairs'}}]},
477+
ZipAnn = erl_syntax_lib:annotate_bindings(Expr, []),
478+
[Env, Bound, Free] = erl_syntax:get_ann(ZipAnn),
479+
{'env',[]} = Env,
480+
{'bound',[]} = Bound,
481+
{'free',['Pairs']} = Free,
468482
ok.
469483

470484
test_files(Config) ->

0 commit comments

Comments
 (0)