Skip to content

Commit 8da3330

Browse files
committed
refactoring in v3_core and erl_eval
1 parent cac4be3 commit 8da3330

File tree

3 files changed

+58
-67
lines changed

3 files changed

+58
-67
lines changed

lib/compiler/src/v3_core.erl

Lines changed: 36 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -126,7 +126,7 @@
126126
-record(igen, {anno=#a{},acc_pat,acc_guard,
127127
skip_pat,tail,tail_pat,arg,
128128
refill={nomatch,ignore}}).
129-
-record(izip, {anno=#a{},len,acc_pats,acc_guard,
129+
-record(izip, {anno=#a{},acc_pats,acc_guard,
130130
skip_pats,tails,tail_pats,pres,args,
131131
refill_pats,refill_as}).
132132
-record(isimple, {anno=#a{},term :: cerl:cerl()}).
@@ -1647,13 +1647,14 @@ lc_tq1(Line, E, [#igen{anno=#a{anno=GA}=GAnno,
16471647

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

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

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

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

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

1851-
%% Helper function that collects a record field from all generators of a zip,
1852-
%% depending on the first argument.
1853-
collect_for_zip(What, Qs) ->
1854-
F = case What of
1855-
args ->
1856-
fun(#igen{arg={_,Arg}}) -> Arg end;
1857-
tails ->
1858-
fun(#igen{tail=T}) -> T end;
1859-
accpats ->
1860-
fun(#igen{acc_pat=A}) -> A end;
1861-
tailpats ->
1862-
fun(#igen{tail_pat=Tp}) -> Tp end;
1863-
refillpats ->
1864-
fun(#igen{refill={R, _}}) -> R end;
1865-
refillas ->
1866-
fun(#igen{refill={_, R}}) -> R end;
1867-
pres ->
1868-
fun(#igen{arg={Pre, _}}) -> Pre end;
1869-
skip_pats ->
1870-
fun(#igen{skip_pat=S}) -> S end
1871-
end,
1872-
[F(Q) || #igen{} = Q <- Qs].
1873-
18741852
make_clause(Anno, [Pat|PatExtra], Guard, Body) ->
18751853
make_clause(Anno, Pat, PatExtra, Guard, Body).
18761854

@@ -1927,19 +1905,19 @@ preprocess_quals(Line, Qs, St) ->
19271905
preprocess_quals(Line, [{zip,Anno,Gens}|Qs], St, Acc) ->
19281906
LAnno = #a{anno=lineno_anno(Anno, St)},
19291907
{Gens1, St1} = preprocess_quals(Line, Gens, St, []),
1930-
Len = length(Gens1),
1931-
AccPats = collect_for_zip(accpats, Gens1),
1908+
{AccPats, TailVars, TailPats, SkipPats, RefillPats, RefillAs, Pres, Args}
1909+
= preprocess_zip_1(Gens1),
19321910
[#igen{acc_guard=AccGuard}|_] = Gens1,
1933-
TailVars = collect_for_zip(tails, Gens1),
1934-
TailPats = collect_for_zip(tailpats, Gens1),
1935-
SkipPats = collect_for_zip(skip_pats, Gens1),
1936-
RefillPats = collect_for_zip(refillpats, Gens1),
1937-
RefillAs = collect_for_zip(refillas, Gens1),
1938-
Pres = collect_for_zip(pres, Gens1),
1939-
Args = collect_for_zip(args, Gens1),
1940-
Zip = #izip{anno=LAnno,len=Len,acc_pats=AccPats,acc_guard=AccGuard,
1941-
skip_pats=SkipPats,tails=TailVars,tail_pats=TailPats,pres=Pres,
1942-
args=Args,refill_pats=RefillPats,refill_as=RefillAs},
1911+
Zip = #izip{anno=LAnno,
1912+
acc_pats=AccPats,
1913+
acc_guard=AccGuard,
1914+
skip_pats=SkipPats,
1915+
tails=TailVars,
1916+
tail_pats=TailPats,
1917+
pres=Pres,
1918+
args=Args,
1919+
refill_pats=RefillPats,
1920+
refill_as=RefillAs},
19431921
preprocess_quals(Line, Qs, St1, [Zip|Acc]);
19441922
preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
19451923
case is_generator(Q) of
@@ -1969,6 +1947,25 @@ preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
19691947
preprocess_quals(_, [], St, Acc) ->
19701948
{reverse(Acc),St}.
19711949

1950+
preprocess_zip_1([#igen{arg={Pre,Arg},
1951+
tail=Tail,
1952+
acc_pat=AccPat,
1953+
tail_pat=TailPat,
1954+
refill={RefillPat, RefillArg},
1955+
skip_pat=SkipPat} | Rest]) ->
1956+
{AccPats, TailVars, TailPats, SkipPats, RefillPats, RefillAs, Pres, Args}
1957+
= preprocess_zip_1(Rest),
1958+
{[AccPat | AccPats],
1959+
[Tail | TailVars],
1960+
[TailPat | TailPats],
1961+
[SkipPat | SkipPats],
1962+
[RefillPat | RefillPats],
1963+
[RefillArg | RefillAs],
1964+
[Pre | Pres],
1965+
[Arg | Args]};
1966+
preprocess_zip_1([]) ->
1967+
{[], [], [], [], [], [], [], []}.
1968+
19721969
is_generator({generate,_,_,_}) -> true;
19731970
is_generator({b_generate,_,_,_}) -> true;
19741971
is_generator({m_generate,_,_,_}) -> true;

lib/debugger/src/dbg_ieval.erl

Lines changed: 11 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1986,22 +1986,19 @@ merge_bindings([], B2s, _Ieval) ->
19861986
B2s.
19871987

19881988
zip_add_bindings(Bs1, Bs2) when is_map(Bs1), is_map(Bs2) ->
1989-
lists:foldl(fun(Key, Acc) ->
1990-
case maps:find(Key, Bs1) of
1991-
{ok, Val} ->
1992-
case maps:find(Key, Bs2) of
1993-
{ok, Val} ->
1994-
Acc;
1995-
{ok, _Value} ->
1996-
nomatch
1997-
end;
1998-
error ->
1999-
maps:put(Key, maps:get(Key,Bs2), Acc)
2000-
end
2001-
end, Bs1, maps:keys(Bs2));
2002-
zip_add_bindings(Bs1, Bs2) ->
1989+
zip_add_bindings_map(maps:keys(Bs2), Bs1, Bs2);
1990+
zip_add_bindings(Bs1, Bs2) when is_list(Bs1), is_list(Bs2) ->
20031991
zip_add_bindings1(orddict:to_list(Bs1), Bs2).
20041992

1993+
zip_add_bindings_map([Key | Keys], Bs1, Bs2) ->
1994+
case {Bs1, Bs2} of
1995+
{#{Key := Same}, #{Key := Same}} -> zip_add_bindings_map(Keys, Bs1, Bs2);
1996+
{#{Key := _}, _} -> nomatch;
1997+
{_, #{Key := Value}} -> zip_add_bindings_map(Keys, Bs1, Bs2#{Key => Value})
1998+
end;
1999+
zip_add_bindings_map([], Bs1, Bs2) ->
2000+
maps:merge(Bs2, Bs1).
2001+
20052002
zip_add_bindings1([{Name,Val}|Bs1], Bs2) ->
20062003
case orddict:find(Name, Bs2) of
20072004
{ok, Val} ->

lib/stdlib/src/erl_eval.erl

Lines changed: 11 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1779,22 +1779,19 @@ del_binding(Name, Bs) when is_map(Bs) -> maps:remove(Name, Bs);
17791779
del_binding(Name, Bs) when is_list(Bs) -> orddict:erase(Name, Bs).
17801780

17811781
zip_add_bindings(Bs1, Bs2) when is_map(Bs1), is_map(Bs2) ->
1782-
foldl(fun(Key, Acc) ->
1783-
case maps:find(Key, Bs1) of
1784-
{ok, Val} ->
1785-
case maps:find(Key, Bs2) of
1786-
{ok, Val} ->
1787-
Acc;
1788-
{ok, _Value} ->
1789-
nomatch
1790-
end;
1791-
error ->
1792-
maps:put(Key, maps:get(Key,Bs2), Acc)
1793-
end
1794-
end, Bs1, maps:keys(Bs2));
1795-
zip_add_bindings(Bs1, Bs2) ->
1782+
zip_add_bindings_map(maps:keys(Bs2), Bs1, Bs2);
1783+
zip_add_bindings(Bs1, Bs2) when is_list(Bs1), is_list(Bs2) ->
17961784
zip_add_bindings1(orddict:to_list(Bs1), Bs2).
17971785

1786+
zip_add_bindings_map([Key | Keys], Bs1, Bs2) ->
1787+
case {Bs1, Bs2} of
1788+
{#{Key := Same}, #{Key := Same}} -> zip_add_bindings_map(Keys, Bs1, Bs2);
1789+
{#{Key := _}, _} -> nomatch;
1790+
{_, #{Key := Value}} -> zip_add_bindings_map(Keys, Bs1, Bs2#{Key => Value})
1791+
end;
1792+
zip_add_bindings_map([], Bs1, Bs2) ->
1793+
maps:merge(Bs2, Bs1).
1794+
17981795
zip_add_bindings1([{Name,Val}|Bs1], Bs2) ->
17991796
case orddict:find(Name, Bs2) of
18001797
{ok, Val} ->

0 commit comments

Comments
 (0)