Skip to content

Commit

Permalink
Merge pull request #8811 from MarkoMin/erl_syntax_lib/annotate_maybe_…
Browse files Browse the repository at this point in the history
…match_correctly

erl_syntax_lib: annotate `maybe_match_expr` and `else_expr` correctly

OTP-19405
  • Loading branch information
bjorng authored Dec 18, 2024
2 parents 56ff90d + 95b849d commit 0129381
Show file tree
Hide file tree
Showing 2 changed files with 100 additions and 2 deletions.
44 changes: 44 additions & 0 deletions lib/syntax_tools/src/erl_syntax_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -470,8 +470,14 @@ vann(Tree, Env) ->
{ann_bindings(Tree, Env, Bound, Free), Bound, Free};
match_expr ->
vann_match_expr(Tree, Env);
maybe_expr ->
vann_maybe_expr(Tree, Env);
maybe_match_expr ->
vann_maybe_match_expr(Tree, Env);
case_expr ->
vann_case_expr(Tree, Env);
else_expr ->
vann_else_expr(Tree, Env);
if_expr ->
vann_if_expr(Tree, Env);
receive_expr ->
Expand Down Expand Up @@ -554,6 +560,27 @@ vann_match_expr(Tree, Env) ->
Tree1 = rewrite(Tree, erl_syntax:match_expr(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_maybe_expr(Tree, Env) ->
Body = erl_syntax:maybe_expr_body(Tree),
{B1, {_, Free1}} = vann_body(Body, Env),
Else = erl_syntax:maybe_expr_else(Tree),
{Else1, _, Free2} = vann_else_expr(Else, Env),
Free = ordsets:union(Free1, Free2),
Tree1 = rewrite(Tree, erl_syntax:maybe_expr(B1, Else1)),
Bound = [],
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_maybe_match_expr(Tree, Env) ->
E = erl_syntax:maybe_match_expr_body(Tree),
{E1, Bound1, Free1} = vann(E, Env),
Env1 = ordsets:union(Env, Bound1),
P = erl_syntax:maybe_match_expr_pattern(Tree),
{P1, Bound2, Free2} = vann_pattern(P, Env1),
Bound = ordsets:union(Bound1, Bound2),
Free = ordsets:union(Free1, Free2),
Tree1 = rewrite(Tree, erl_syntax:maybe_match_expr(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_case_expr(Tree, Env) ->
E = erl_syntax:case_expr_argument(Tree),
{E1, Bound1, Free1} = vann(E, Env),
Expand All @@ -565,6 +592,13 @@ vann_case_expr(Tree, Env) ->
Tree1 = rewrite(Tree, erl_syntax:case_expr(E1, Cs1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_else_expr(Tree, Env) ->
Cs = erl_syntax:else_expr_clauses(Tree),
{Cs1, {_, Free}} = vann_clauses(Cs, Env),
Bound = [],
Tree1 = rewrite(Tree, erl_syntax:else_expr(Cs1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_if_expr(Tree, Env) ->
Cs = erl_syntax:if_expr_clauses(Tree),
{Cs1, {Bound, Free}} = vann_clauses(Cs, Env),
Expand Down Expand Up @@ -765,6 +799,16 @@ vann_pattern(Tree, Env) ->
Free = ordsets:union(Free1, Free2),
Tree1 = rewrite(Tree, erl_syntax:match_expr(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free};
maybe_match_expr ->
%% Alias pattern
P = erl_syntax:maybe_match_expr_pattern(Tree),
{P1, Bound1, Free1} = vann_pattern(P, Env),
E = erl_syntax:maybe_match_expr_body(Tree),
{E1, Bound2, Free2} = vann_pattern(E, Env),
Bound = ordsets:union(Bound1, Bound2),
Free = ordsets:union(Free1, Free2),
Tree1 = rewrite(Tree, erl_syntax:maybe_match_expr(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free};
macro ->
%% The macro name must be ignored. The arguments are treated
%% as patterns.
Expand Down
58 changes: 56 additions & 2 deletions lib/syntax_tools/test/syntax_tools_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,8 @@
wrapped_subtrees/1,
t_abstract_type/1,t_erl_parse_type/1,t_type/1,
t_epp_dodger/1,t_epp_dodger_clever/1,
t_comment_scan/1,t_prettypr/1,test_named_fun_bind_ann/1]).
t_comment_scan/1,t_prettypr/1,test_named_fun_bind_ann/1,
test_maybe_expr_ann/1]).

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

Expand All @@ -38,7 +39,8 @@ all() ->
wrapped_subtrees,
t_abstract_type,t_erl_parse_type,t_type,
t_epp_dodger,t_epp_dodger_clever,
t_comment_scan,t_prettypr,test_named_fun_bind_ann].
t_comment_scan,t_prettypr,test_named_fun_bind_ann,
test_maybe_expr_ann].

groups() ->
[].
Expand Down Expand Up @@ -403,6 +405,58 @@ test_named_fun_bind_ann(Config) when is_list(Config) ->
{'bound',['Test']} = CBound,
{'free', []} = CFree.

%% Test annotation of maybe_expr, maybe_match_expr and else_expr (PR #8811)
test_maybe_expr_ann(Config) when is_list(Config) ->
%% maybe
%% ok ?= Test,
%% What ?= ok,
%% Var = What,
%% else
%% Error -> Error
%% end.
MaybeMatch1 = erl_syntax:maybe_match_expr(
erl_syntax:atom(ok),
erl_syntax:variable('Test')),
MaybeMatch2 = erl_syntax:maybe_match_expr(
erl_syntax:variable('What'),
erl_syntax:atom(ok)),
Match1 = erl_syntax:maybe_match_expr(
erl_syntax:variable('Var'),
erl_syntax:variable('What')),
Else = erl_syntax:else_expr(
[erl_syntax:clause(
[erl_syntax:variable('Err')],
'none',
[erl_syntax:variable('Err')])
]),
Maybe = erl_syntax:maybe_expr([MaybeMatch1, MaybeMatch2, Match1], Else),

MaybeAnn = erl_syntax_lib:annotate_bindings(Maybe, []),
[Env, Bound, Free] = erl_syntax:get_ann(MaybeAnn),
{'env',[]} = Env,
{'bound',[]} = Bound,
{'free',['Test']} = Free,

[MaybeMatchAnn1, MaybeMatchAnn2, MatchAnn1] = erl_syntax:maybe_expr_body(MaybeAnn),
[Env1, Bound1, Free1] = erl_syntax:get_ann(MaybeMatchAnn1),
{'env',[]} = Env1,
{'bound',[]} = Bound1,
{'free',['Test']} = Free1,
[Env2, Bound2, Free2] = erl_syntax:get_ann(MaybeMatchAnn2),
{'env',[]} = Env2,
{'bound',['What']} = Bound2,
{'free',[]} = Free2,
[Env3, Bound3, Free3] = erl_syntax:get_ann(MatchAnn1),
{'env',['What']} = Env3,
{'bound',['Var']} = Bound3,
{'free',['What']} = Free3,

ElseAnn = erl_syntax:maybe_expr_else(MaybeAnn),
[Env4, Bound4, Free4] = erl_syntax:get_ann(ElseAnn),
{'env',[]} = Env4,
{'bound',[]} = Bound4,
{'free',[]} = Free4.

test_files(Config) ->
DataDir = ?config(data_dir, Config),
[ filename:join(DataDir,Filename) || Filename <- test_files() ].
Expand Down

0 comments on commit 0129381

Please sign in to comment.