Skip to content

Commit

Permalink
refactoring in v3_core and erl_eval
Browse files Browse the repository at this point in the history
  • Loading branch information
lucioleKi committed Oct 13, 2024
1 parent cac4be3 commit 8da3330
Show file tree
Hide file tree
Showing 3 changed files with 58 additions and 67 deletions.
75 changes: 36 additions & 39 deletions lib/compiler/src/v3_core.erl
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@
-record(igen, {anno=#a{},acc_pat,acc_guard,
skip_pat,tail,tail_pat,arg,
refill={nomatch,ignore}}).
-record(izip, {anno=#a{},len,acc_pats,acc_guard,
-record(izip, {anno=#a{},acc_pats,acc_guard,
skip_pats,tails,tail_pats,pres,args,
refill_pats,refill_as}).
-record(isimple, {anno=#a{},term :: cerl:cerl()}).
Expand Down Expand Up @@ -1647,13 +1647,14 @@ lc_tq1(Line, E, [#igen{anno=#a{anno=GA}=GAnno,

%% zip_tq(Line, Exp, [Qualifier], Mc, State, TqFun) -> {LetRec,[PreExp],State}.

zip_tq(Line, E, #izip{anno=#a{anno=GA}=GAnno,len=NumGenerators,
zip_tq(Line, E, #izip{anno=#a{anno=GA}=GAnno,
acc_pats=AccPats,acc_guard=AccGuard,
tails=TailVars,tail_pats=TailPats,
skip_pats=SkipPats,refill_pats=RefillPats0,
refill_as=RefillAs,pres=Pres,args=Args}, Mc, St0, Qs) ->
{Name,St1} = new_fun_name("zlc", St0),
LA = lineno_anno(Line, St1),
NumGenerators = length(AccPats),

%% Generate new vars for each generator, 1 for the regular call, and 1 for
%% the bad generator case.
Expand Down Expand Up @@ -1782,15 +1783,15 @@ bc_tq_build(Line, Pre0, #c_var{name=AccVar}, Elements0, St0) ->
Anno = Anno0#a{anno=[compiler_generated,single_use|A]},
{set_anno(E, Anno),Pre0++Pre,St}.

bzip_tq1(Line, E, #izip{anno=GAnno,len=NumGenerators,
bzip_tq1(Line, E, #izip{anno=GAnno,
acc_pats=AccPats,acc_guard=AccGuard,
tails=TailVars,tail_pats=TailPats,
skip_pats=SkipPats,refill_pats=RefillPats0,
refill_as=RefillAs,pres=Pres,args=Args}, Mc, St0, Qs) ->
{Name,St1} = new_fun_name("bzip", St0),
LA = lineno_anno(Line, St1),
LAnno = #a{anno=LA},
Arity = NumGenerators + 1,
Arity = length(AccPats) + 1,

%% Generate new vars for each generator, 1 for the regular call, and 1 for
%% the bad generator case. last(CallVars) is used as the accumulator var
Expand Down Expand Up @@ -1848,29 +1849,6 @@ make_ignored(Ps, Vs) ->
_ -> P
end || {P, V} <- zip(Ps, Vs)].

%% Helper function that collects a record field from all generators of a zip,
%% depending on the first argument.
collect_for_zip(What, Qs) ->
F = case What of
args ->
fun(#igen{arg={_,Arg}}) -> Arg end;
tails ->
fun(#igen{tail=T}) -> T end;
accpats ->
fun(#igen{acc_pat=A}) -> A end;
tailpats ->
fun(#igen{tail_pat=Tp}) -> Tp end;
refillpats ->
fun(#igen{refill={R, _}}) -> R end;
refillas ->
fun(#igen{refill={_, R}}) -> R end;
pres ->
fun(#igen{arg={Pre, _}}) -> Pre end;
skip_pats ->
fun(#igen{skip_pat=S}) -> S end
end,
[F(Q) || #igen{} = Q <- Qs].

make_clause(Anno, [Pat|PatExtra], Guard, Body) ->
make_clause(Anno, Pat, PatExtra, Guard, Body).

Expand Down Expand Up @@ -1927,19 +1905,19 @@ preprocess_quals(Line, Qs, St) ->
preprocess_quals(Line, [{zip,Anno,Gens}|Qs], St, Acc) ->
LAnno = #a{anno=lineno_anno(Anno, St)},
{Gens1, St1} = preprocess_quals(Line, Gens, St, []),
Len = length(Gens1),
AccPats = collect_for_zip(accpats, Gens1),
{AccPats, TailVars, TailPats, SkipPats, RefillPats, RefillAs, Pres, Args}
= preprocess_zip_1(Gens1),
[#igen{acc_guard=AccGuard}|_] = Gens1,
TailVars = collect_for_zip(tails, Gens1),
TailPats = collect_for_zip(tailpats, Gens1),
SkipPats = collect_for_zip(skip_pats, Gens1),
RefillPats = collect_for_zip(refillpats, Gens1),
RefillAs = collect_for_zip(refillas, Gens1),
Pres = collect_for_zip(pres, Gens1),
Args = collect_for_zip(args, Gens1),
Zip = #izip{anno=LAnno,len=Len,acc_pats=AccPats,acc_guard=AccGuard,
skip_pats=SkipPats,tails=TailVars,tail_pats=TailPats,pres=Pres,
args=Args,refill_pats=RefillPats,refill_as=RefillAs},
Zip = #izip{anno=LAnno,
acc_pats=AccPats,
acc_guard=AccGuard,
skip_pats=SkipPats,
tails=TailVars,
tail_pats=TailPats,
pres=Pres,
args=Args,
refill_pats=RefillPats,
refill_as=RefillAs},
preprocess_quals(Line, Qs, St1, [Zip|Acc]);
preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
case is_generator(Q) of
Expand Down Expand Up @@ -1969,6 +1947,25 @@ preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
preprocess_quals(_, [], St, Acc) ->
{reverse(Acc),St}.

preprocess_zip_1([#igen{arg={Pre,Arg},
tail=Tail,
acc_pat=AccPat,
tail_pat=TailPat,
refill={RefillPat, RefillArg},
skip_pat=SkipPat} | Rest]) ->
{AccPats, TailVars, TailPats, SkipPats, RefillPats, RefillAs, Pres, Args}
= preprocess_zip_1(Rest),
{[AccPat | AccPats],
[Tail | TailVars],
[TailPat | TailPats],
[SkipPat | SkipPats],
[RefillPat | RefillPats],
[RefillArg | RefillAs],
[Pre | Pres],
[Arg | Args]};
preprocess_zip_1([]) ->
{[], [], [], [], [], [], [], []}.

is_generator({generate,_,_,_}) -> true;
is_generator({b_generate,_,_,_}) -> true;
is_generator({m_generate,_,_,_}) -> true;
Expand Down
25 changes: 11 additions & 14 deletions lib/debugger/src/dbg_ieval.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1986,22 +1986,19 @@ merge_bindings([], B2s, _Ieval) ->
B2s.

zip_add_bindings(Bs1, Bs2) when is_map(Bs1), is_map(Bs2) ->
lists:foldl(fun(Key, Acc) ->
case maps:find(Key, Bs1) of
{ok, Val} ->
case maps:find(Key, Bs2) of
{ok, Val} ->
Acc;
{ok, _Value} ->
nomatch
end;
error ->
maps:put(Key, maps:get(Key,Bs2), Acc)
end
end, Bs1, maps:keys(Bs2));
zip_add_bindings(Bs1, Bs2) ->
zip_add_bindings_map(maps:keys(Bs2), Bs1, Bs2);
zip_add_bindings(Bs1, Bs2) when is_list(Bs1), is_list(Bs2) ->
zip_add_bindings1(orddict:to_list(Bs1), Bs2).

zip_add_bindings_map([Key | Keys], Bs1, Bs2) ->
case {Bs1, Bs2} of
{#{Key := Same}, #{Key := Same}} -> zip_add_bindings_map(Keys, Bs1, Bs2);
{#{Key := _}, _} -> nomatch;
{_, #{Key := Value}} -> zip_add_bindings_map(Keys, Bs1, Bs2#{Key => Value})
end;
zip_add_bindings_map([], Bs1, Bs2) ->
maps:merge(Bs2, Bs1).

zip_add_bindings1([{Name,Val}|Bs1], Bs2) ->
case orddict:find(Name, Bs2) of
{ok, Val} ->
Expand Down
25 changes: 11 additions & 14 deletions lib/stdlib/src/erl_eval.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1779,22 +1779,19 @@ del_binding(Name, Bs) when is_map(Bs) -> maps:remove(Name, Bs);
del_binding(Name, Bs) when is_list(Bs) -> orddict:erase(Name, Bs).

zip_add_bindings(Bs1, Bs2) when is_map(Bs1), is_map(Bs2) ->
foldl(fun(Key, Acc) ->
case maps:find(Key, Bs1) of
{ok, Val} ->
case maps:find(Key, Bs2) of
{ok, Val} ->
Acc;
{ok, _Value} ->
nomatch
end;
error ->
maps:put(Key, maps:get(Key,Bs2), Acc)
end
end, Bs1, maps:keys(Bs2));
zip_add_bindings(Bs1, Bs2) ->
zip_add_bindings_map(maps:keys(Bs2), Bs1, Bs2);
zip_add_bindings(Bs1, Bs2) when is_list(Bs1), is_list(Bs2) ->
zip_add_bindings1(orddict:to_list(Bs1), Bs2).

zip_add_bindings_map([Key | Keys], Bs1, Bs2) ->
case {Bs1, Bs2} of
{#{Key := Same}, #{Key := Same}} -> zip_add_bindings_map(Keys, Bs1, Bs2);
{#{Key := _}, _} -> nomatch;
{_, #{Key := Value}} -> zip_add_bindings_map(Keys, Bs1, Bs2#{Key => Value})
end;
zip_add_bindings_map([], Bs1, Bs2) ->
maps:merge(Bs2, Bs1).

zip_add_bindings1([{Name,Val}|Bs1], Bs2) ->
case orddict:find(Name, Bs2) of
{ok, Val} ->
Expand Down

0 comments on commit 8da3330

Please sign in to comment.