Skip to content

Commit

Permalink
[EEP 78] Implement multi comprehensions in compiler
Browse files Browse the repository at this point in the history
  • Loading branch information
michalmuskala committed Feb 3, 2025
1 parent dfe64f8 commit 1531a18
Show file tree
Hide file tree
Showing 4 changed files with 51 additions and 24 deletions.
44 changes: 26 additions & 18 deletions lib/compiler/src/v3_core.erl
Original file line number Diff line number Diff line change
Expand Up @@ -710,12 +710,12 @@ expr({cons,L,H0,T0}, St0) ->
{annotate_cons(A, H1, T1, St1),Eps,St1};
expr({lc,L,E,Qs0}, St0) ->
{Qs1,St1} = preprocess_quals(L, Qs0, St0),
lc_tq(L, E, Qs1, #c_literal{anno=lineno_anno(L, St1),val=[]}, St1);
lc_tq(L, wrap_list(E), Qs1, #c_literal{anno=lineno_anno(L, St1),val=[]}, St1);
expr({bc,L,E,Qs}, St) ->
bc_tq(L, E, Qs, St);
expr({mc,L,E,Qs0}, St0) ->
{Qs1,St1} = preprocess_quals(L, Qs0, St0),
mc_tq(L, E, Qs1, #c_literal{anno=lineno_anno(L, St1),val=[]}, St1);
mc_tq(L, wrap_list(E), Qs1, #c_literal{anno=lineno_anno(L, St1),val=[]}, St1);
expr({tuple,L,Es0}, St0) ->
{Es1,Eps,St1} = safe_list(Es0, St0),
A = record_anno(L, St1),
Expand Down Expand Up @@ -967,7 +967,7 @@ expr({op,_,'++',{lc,Llc,E,Qs0},More}, St0) ->
%% number variables in the environment for letrec.
{Mc,Mps,St1} = safe(More, St0),
{Qs,St2} = preprocess_quals(Llc, Qs0, St1),
{Y,Yps,St} = lc_tq(Llc, E, Qs, Mc, St2),
{Y,Yps,St} = lc_tq(Llc, wrap_list(E), Qs, Mc, St2),
{Y,Mps++Yps,St};
expr({op,_,'andalso',_,_}=E0, St0) ->
{op,L,'andalso',E1,E2} = right_assoc(E0, 'andalso'),
Expand Down Expand Up @@ -1623,21 +1623,29 @@ fun_tq(Cs0, L, St0, NameInfo) ->
vars=Args,clauses=Cs1,fc=Fc,name=NameInfo},
{Fun,[],St4}.

%% lc_tq(Line, Exp, [Qualifier], Mc, State) -> {LetRec,[PreExp],State}.
wrap_list(List) when is_list(List) -> List;
wrap_list(Other) -> [Other].

%% lc_tq(Line, Exprs, [Qualifier], Mc, State) -> {LetRec,[PreExp],State}.
%% This TQ from Simon PJ pp 127-138.

lc_tq(Line, E, [#igen{}|_T] = Qs, Mc, St) ->
lc_tq1(Line, E, Qs, Mc, St);
lc_tq(Line, E, [#izip{}=Zip|Qs], Mc, St) ->
zip_tq(Line, E, Zip, Mc, St, Qs);
lc_tq(Line, E, [#ifilter{}=Filter|Qs], Mc, St) ->
filter_tq(Line, E, Filter, Mc, St, Qs, fun lc_tq/5);
lc_tq(Line, E0, [], Mc0, St0) ->
{H1,Hps,St1} = safe(E0, St0),
lc_tq(Line, Es, [#igen{}|_T] = Qs, Mc, St) ->
lc_tq1(Line, Es, Qs, Mc, St);
lc_tq(Line, Es, [#izip{}=Zip|Qs], Mc, St) ->
zip_tq(Line, Es, Zip, Mc, St, Qs);
lc_tq(Line, Es, [#ifilter{}=Filter|Qs], Mc, St) ->
filter_tq(Line, Es, Filter, Mc, St, Qs, fun lc_tq/5);
lc_tq(Line, Es0, [], Mc0, St0) ->
{Hs1,Hps,St1} = safe_list(Es0, St0),
{T1,Tps,St} = force_safe(Mc0, St1),
Anno = lineno_anno(Line, St),
E = ann_c_cons(Anno, H1, T1),
{set_anno(E, [compiler_generated|Anno]),Hps ++ Tps,St}.
Anno = lineno_anno(erl_anno:set_generated(true, Line), St),
E = ann_c_cons_all(Anno, Hs1, T1),
{E,Hps ++ Tps,St}.

ann_c_cons_all(Anno, [H | Hs], T) ->
ann_c_cons(Anno, H, ann_c_cons_all(Anno, Hs, T));
ann_c_cons_all(_Anno, [], T) ->
T.

lc_tq1(Line, E, [#igen{anno=#a{anno=GA}=GAnno,
acc_pat=AccPat,acc_guard=AccGuard,
Expand Down Expand Up @@ -1924,9 +1932,9 @@ bzip_tq1(Line, E, #izip{anno=#a{anno=_GA}=GAnno,
body=append(Pres) ++
[#iapply{anno=LAnno,op=F,args=Args++[Mc]}]},[],St4}.

mc_tq(Line, {map_field_assoc,Lf,K,V}, Qs, Mc, St0) ->
E = {tuple,Lf,[K,V]},
{Lc,Pre0,St1} = lc_tq(Line, E, Qs, Mc, St0),
mc_tq(Line, Es0, Qs, Mc, St0) ->
Es = map(fun({map_field_assoc,Lf,K,V}) -> {tuple,Lf,[K,V]} end, Es0),
{Lc,Pre0,St1} = lc_tq(Line, Es, Qs, Mc, St0),
{LcVar,St2} = new_var(St1),
Pre = Pre0 ++ [#iset{var=LcVar,arg=Lc}],
Call = #icall{module=#c_literal{val=maps},
Expand Down
9 changes: 7 additions & 2 deletions lib/compiler/test/lc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@
init_per_testcase/2,end_per_testcase/2,
basic/1,deeply_nested/1,no_generator/1,
empty_generator/1,no_export/1,shadow/1,
effect/1]).
effect/1,multi/1]).

-include_lib("common_test/include/ct.hrl").

Expand All @@ -43,7 +43,8 @@ groups() ->
empty_generator,
no_export,
shadow,
effect
effect,
multi
]}].

init_per_suite(Config) ->
Expand Down Expand Up @@ -284,6 +285,10 @@ do_effect(Lc, L) ->
ok = Lc(F, L),
lists:reverse(erase(?MODULE)).

multi(Config) when is_list(Config) ->
[true, false] = [true, false || true],
[1, 2, 5, 6] = [X, X + 1 || X <- [1, 5]].

id(I) -> I.

-file("bad_lc.erl", 1).
Expand Down
13 changes: 11 additions & 2 deletions lib/compiler/test/mc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
-export([all/0,suite/0,groups/0,init_per_suite/1,end_per_suite/1,
init_per_group/2,end_per_group/2,
basic/1,duplicate_keys/1,mixed/1,
shadow/1,bad_generators/1]).
shadow/1,bad_generators/1,multi/1]).

-include_lib("common_test/include/ct.hrl").

Expand All @@ -40,7 +40,8 @@ groups() ->
duplicate_keys,
mixed,
shadow,
bad_generators]}].
bad_generators,
multi]}].

init_per_suite(Config) ->
test_lib:recompile(?MODULE),
Expand Down Expand Up @@ -298,6 +299,14 @@ bad_generators(_Config) ->
end,
ok.

multi(_Config) ->
Exp = #{true => 1, false => 2},
Exp = #{true => 1, false => 2 || true},
Exp2 = #{1 => 1, 2 => 2, 5 => 5, 6 => 6},
Exp2 = #{X => X, X + 1 => X + 1 || X <- [1, 5]},
Exp3 = #{1 => 4, 5 => 8},
Exp3 = #{X => X+1, X => X+3 || X <- [1, 5]}.

id(I) -> I.

-file("bad_mc.erl", 1).
Expand Down
9 changes: 7 additions & 2 deletions lib/stdlib/src/erl_expand_records.erl
Original file line number Diff line number Diff line change
Expand Up @@ -276,6 +276,11 @@ record_test_in_body(Anno, Expr, Name, St0) ->
{atom,NAnno,is_record}},
[Var,{atom,Anno,Name},{integer,Anno,length(Fs)+1}]}]}, St).

expr_or_exprs(Es, St) when is_list(Es) ->
exprs(Es, St);
expr_or_exprs(E, St) ->
expr(E, St).

exprs([E0 | Es0], St0) ->
{E,St1} = expr(E0, St0),
{Es,St2} = exprs(Es0, St1),
Expand All @@ -302,15 +307,15 @@ expr({cons,Anno,H0,T0}, St0) ->
{{cons,Anno,H,T},St2};
expr({lc,Anno,E0,Qs0}, St0) ->
{Qs1,St1} = lc_tq(Anno, Qs0, St0),
{E1,St2} = expr(E0, St1),
{E1,St2} = expr_or_exprs(E0, St1),
{{lc,Anno,E1,Qs1},St2};
expr({bc,Anno,E0,Qs0}, St0) ->
{Qs1,St1} = lc_tq(Anno, Qs0, St0),
{E1,St2} = expr(E0, St1),
{{bc,Anno,E1,Qs1},St2};
expr({mc,Anno,E0,Qs0}, St0) ->
{Qs1,St1} = lc_tq(Anno, Qs0, St0),
{E1,St2} = expr(E0, St1),
{E1,St2} = expr_or_exprs(E0, St1),
{{mc,Anno,E1,Qs1},St2};
expr({tuple,Anno,Es0}, St0) ->
{Es1,St1} = expr_list(Es0, St0),
Expand Down

0 comments on commit 1531a18

Please sign in to comment.