Skip to content

Commit

Permalink
Fix minor imparity issues between various generator types
Browse files Browse the repository at this point in the history
  • Loading branch information
dszoboszlay committed Oct 12, 2024
1 parent 6d4731b commit 0f0e375
Show file tree
Hide file tree
Showing 6 changed files with 33 additions and 12 deletions.
2 changes: 1 addition & 1 deletion lib/stdlib/src/erl_parse.yrl
Original file line number Diff line number Diff line change
Expand Up @@ -933,7 +933,7 @@ processed (see section [Error Information](#module-error-information)).

-type af_qualifier() :: af_generator() | af_filter().

-doc "Abstract representation of a generator or a bitstring generator.".
-doc "Abstract representation of a list, bitstring or map generator.".
-type af_generator() :: {'generate', anno(), af_pattern(), abstract_expr()}
| {'m_generate', anno(), af_assoc_exact(af_pattern()), abstract_expr()}
| {'b_generate', anno(), af_pattern(), abstract_expr()}.
Expand Down
5 changes: 4 additions & 1 deletion lib/stdlib/src/qlc_pt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -292,10 +292,13 @@ record_attributes(Forms) ->
%% transformation.
%%
compile_messages(Forms, FormsNoShadows, Options, State) ->
%% The qlc module cannot handle binary generators.
%% The qlc module can only handle list generators.
BGenF = fun(_QId,{b_generate,Anno,_P,_LE}=BGen, GA, A) ->
M = {loc(Anno),?APIMOD,binary_generator},
{BGen,[{get(?QLC_FILE),[M]}|GA],A};
(_QId,{m_generate,Anno,_P,_LE}=BGen, GA, A) ->
M = {loc(Anno),?APIMOD,map_generator},
{BGen,[{get(?QLC_FILE),[M]}|GA],A};
(_QId, Q, GA, A) ->
{Q,GA,A}
end,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -644,6 +644,8 @@ expand_quals([{generate,A,P,E}|Qs], C) ->
[{generate,A,P,expand_expr(E, C)}|expand_quals(Qs, C)];
expand_quals([{b_generate,A,P,E}|Qs], C) ->
[{b_generate,A,P,expand_expr(E, C)}|expand_quals(Qs, C)];
expand_quals([{m_generate,A,P,E}|Qs], C) ->
[{m_generate,A,P,expand_expr(E, C)}|expand_quals(Qs, C)];
expand_quals([E|Qs], C) ->
[expand_expr(E, C)|expand_quals(Qs, C)];
expand_quals([], _C) -> [].
Expand Down
8 changes: 4 additions & 4 deletions lib/syntax_tools/src/erl_syntax.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2650,7 +2650,7 @@ compact_list(Node) ->
copy_attrs(Node,
Node1));
_ ->
Node
Node
end
end;
_ ->
Expand Down Expand Up @@ -3172,7 +3172,7 @@ revert_attribute(Node) ->

revert_attribute_1(module, [M], Pos, Node) ->
case revert_module_name(M) of
{ok, A} ->
{ok, A} ->
{attribute, Pos, module, A};
error -> Node
end;
Expand All @@ -3189,7 +3189,7 @@ revert_attribute_1(module, [M, List], Pos, Node) ->
Node
end,
case revert_module_name(M) of
{ok, A} ->
{ok, A} ->
{attribute, Pos, module, {A, Vs}};
error -> Node
end;
Expand Down Expand Up @@ -7528,7 +7528,7 @@ subtrees(T) ->
Ts]
end;
binary_generator ->
[[binary_generator_pattern(T)],
[[binary_generator_pattern(T)],
[binary_generator_body(T)]];
bitstring_type ->
[[bitstring_type_m(T)],
Expand Down
26 changes: 20 additions & 6 deletions lib/syntax_tools/src/erl_syntax_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -494,6 +494,8 @@ vann(Tree, Env) ->
vann_generator(Tree, Env);
binary_generator ->
vann_binary_generator(Tree, Env);
map_generator ->
vann_map_generator(Tree, Env);
block_expr ->
vann_block_expr(Tree, Env);
macro ->
Expand Down Expand Up @@ -626,10 +628,12 @@ vann_list_comp(Tree, Env) ->
vann_list_comp_body_join() ->
fun (T, {Env, Bound, Free}) ->
{T1, Bound1, Free1} = case erl_syntax:type(T) of
binary_generator ->
vann_binary_generator(T,Env);
generator ->
generator ->
vann_generator(T, Env);
binary_generator ->
vann_binary_generator(T,Env);
map_generator ->
vann_map_generator(T,Env);
_ ->
%% Bindings in filters are not
%% exported to the rest of the
Expand Down Expand Up @@ -662,10 +666,12 @@ vann_binary_comp(Tree, Env) ->
vann_binary_comp_body_join() ->
fun (T, {Env, Bound, Free}) ->
{T1, Bound1, Free1} = case erl_syntax:type(T) of
binary_generator ->
vann_binary_generator(T, Env);
generator ->
generator ->
vann_generator(T, Env);
binary_generator ->
vann_binary_generator(T,Env);
map_generator ->
vann_map_generator(T,Env);
_ ->
%% Bindings in filters are not
%% exported to the rest of the
Expand Down Expand Up @@ -705,6 +711,14 @@ vann_binary_generator(Tree, Env) ->
Tree1 = rewrite(Tree, erl_syntax:binary_generator(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_map_generator(Tree, Env) ->
P = erl_syntax:map_generator_pattern(Tree),
{P1, Bound, _} = vann_pattern(P, []),
E = erl_syntax:map_generator_body(Tree),
{E1, _, Free} = vann(E, Env),
Tree1 = rewrite(Tree, erl_syntax:map_generator(P1, E1)),
{ann_bindings(Tree1, Env, Bound, Free), Bound, Free}.

vann_block_expr(Tree, Env) ->
Es = erl_syntax:block_expr_body(Tree),
{Es1, {Bound, Free}} = vann_body(Es, Env),
Expand Down
2 changes: 2 additions & 0 deletions lib/syntax_tools/test/syntax_tools_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -335,6 +335,8 @@ t_erl_parse_type(Config) when is_list(Config) ->
{"[catch V||V <- Vs]", list_comp,false},
{"<< <<B>> || <<B>> <= Bs>>", binary_comp,false},
{"<< (catch <<B>>) || <<B>> <= Bs>>", binary_comp,false},
{"#{K => V || {K,V} <- KVs}", map_comp,false},
{"#{K => (catch V) || {K,V} <- KVs}", map_comp,false},
{"#state{ a = A, b = B}", record_expr,false},
{"#state{}", record_expr,false},
{"#s{ a = #def{ a=A }, b = B}", record_expr,false},
Expand Down

0 comments on commit 0f0e375

Please sign in to comment.