Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
3504-Support-a-definition-with-non-zero-arity-i...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3504-Support-a-definition-with-non-zero-arity-in-letrecs.patch of Package erlang
From f546115ed4bdb0abcee2f4694c49860732585974 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Mon, 1 Nov 2021 06:20:24 +0100 Subject: [PATCH 04/12] Support a definition with non-zero arity in letrecs Teach the `v3_kernel` and `beam_kernel_to_ssa` passes to handle a `letrec` with the `letrec_goto` option, where the defined function has an arity of one or higher. Also update Dialyzer to handle such letrecs. This enhanced `letrec` will come in handy for implementing EEP 49 in the next commit. --- lib/compiler/src/beam_kernel_to_ssa.erl | 29 +++++++++++++------- lib/compiler/src/v3_kernel.erl | 34 +++++++++++++++--------- lib/compiler/src/v3_kernel.hrl | 4 +-- lib/compiler/src/v3_kernel_pp.erl | 7 ++--- lib/dialyzer/src/dialyzer_clean_core.erl | 7 +++-- 5 files changed, 53 insertions(+), 28 deletions(-) diff --git a/lib/compiler/src/beam_kernel_to_ssa.erl b/lib/compiler/src/beam_kernel_to_ssa.erl index 034130e5aa..52a68efbb6 100644 --- a/lib/compiler/src/beam_kernel_to_ssa.erl +++ b/lib/compiler/src/beam_kernel_to_ssa.erl @@ -133,20 +133,31 @@ cg(#k_return{args=[Ret0]}, St) -> cg(#k_break{args=Bs}, #cg{break=Br}=St) -> Args = ssa_args(Bs, St), {[#cg_break{args=Args,phi=Br}],St}; -cg(#k_letrec_goto{label=Label,first=First,then=Then,ret=Rs}, +cg(#k_letrec_goto{label=Label,vars=Vs0,first=First,then=Then,ret=Rs}, #cg{break=OldBreak,labels=Labels0}=St0) -> {Tf,St1} = new_label(St0), {B,St2} = new_label(St1), Labels = Labels0#{Label=>Tf}, - {Fis,St3} = cg(First, St2#cg{labels=Labels,break=B}), - {Sis,St4} = cg(Then, St3), - St5 = St4#cg{labels=Labels0}, - {BreakVars,St} = new_ssa_vars(Rs, St5), - Phi = #cg_phi{vars=BreakVars}, - {Fis ++ [{label,Tf}] ++ Sis ++ [{label,B},Phi],St#cg{break=OldBreak}}; -cg(#k_goto{label=Label}, #cg{labels=Labels}=St) -> + {Vs,St3} = new_ssa_vars(Vs0, St2), + {Fis,St4} = cg(First, St3#cg{labels=Labels,break=B}), + {Sis,St5} = cg(Then, St4), + St6 = St5#cg{labels=Labels0}, + {BreakVars,St} = new_ssa_vars(Rs, St6), + PostPhi = #cg_phi{vars=BreakVars}, + FailPhi = case Vs of + [] -> []; + [_|_] -> [#cg_phi{vars=Vs}] + end, + {Fis ++ [{label,Tf}] ++ FailPhi ++ Sis ++ [{label,B},PostPhi], + St#cg{break=OldBreak}}; +cg(#k_goto{label=Label,args=[]}, #cg{labels=Labels}=St) -> Branch = map_get(Label, Labels), - {[make_uncond_branch(Branch)],St}. + {[make_uncond_branch(Branch)],St}; +cg(#k_goto{label=Label,args=As0}, #cg{labels=Labels}=St) -> + As = ssa_args(As0, St), + Branch = map_get(Label, Labels), + Break = #cg_break{args=As,phi=Branch}, + {[Break],St}. %% match_cg(Matc, [Ret], State) -> {[Ainstr],State}. %% Generate code for a match. diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl index 6fe4da764a..b2ddf1afd5 100644 --- a/lib/compiler/src/v3_kernel.erl +++ b/lib/compiler/src/v3_kernel.erl @@ -385,19 +385,27 @@ letrec_local_function(A, Cfs, Cb, Sub0, St0) -> %% Implement letrec with the single definition as a label and each %% apply of it as a goto. -letrec_goto([{#c_var{name={Label,0}},Cfail}], Cb, Sub0, +letrec_goto([{#c_var{name={Label,_Arity}},Cfail}], Cb, Sub0, #kern{labels=Labels0}=St0) -> + #c_fun{vars=FunVars,body=FunBody} = Cfail, + {Kvars,{FunSub,St1}} = + mapfoldl(fun(#c_var{anno=A,name=V}, {SubInt,StInt0}) -> + {New,StInt1} = new_var_name(StInt0), + {#k_var{anno=A,name=New}, + {set_vsub(V, New, SubInt), + StInt1#kern{ds=sets:add_element(New, StInt1#kern.ds)}}} + end, {Sub0,St0}, FunVars), Labels = sets:add_element(Label, Labels0), - {Kb,Pb,St1} = body(Cb, Sub0, St0#kern{labels=Labels}), - #c_fun{body=FailBody} = Cfail, - {Kfail,Fb,St2} = body(FailBody, Sub0, St1), + {Kb,Pb,St2} = body(Cb, Sub0, St1#kern{labels=Labels}), + {Kfail,Fb,St3} = body(FunBody, FunSub, St2), case {Kb,Kfail,Fb} of {#k_goto{label=Label},#k_goto{}=InnerGoto,[]} -> - {InnerGoto,Pb,St2}; + {InnerGoto,Pb,St3}; {_,_,_} -> - St3 = St2#kern{labels=Labels0}, - Alt = #k_letrec_goto{label=Label,first=Kb,then=pre_seq(Fb, Kfail)}, - {Alt,Pb,St3} + St4 = St3#kern{labels=Labels0}, + Alt = #k_letrec_goto{label=Label,vars=Kvars, + first=Kb,then=pre_seq(Fb, Kfail)}, + {Alt,Pb,St4} end. %% translate_match_fail(Arg, Sub, Anno, St) -> {Kexpr,[PreKexpr],State}. @@ -561,10 +569,11 @@ match_vars(Ka, St0) -> %% Transform application. c_apply(A, #c_var{anno=Ra,name={F0,Ar}}, Cargs, Sub, #kern{labels=Labels}=St0) -> - case Ar =:= 0 andalso sets:is_element(F0, Labels) of + case sets:is_element(F0, Labels) of true -> %% This is a goto to a label in a letrec_goto construct. - {#k_goto{label=F0},[],St0}; + {Kargs,Ap,St1} = atomic_list(Cargs, Sub, St0), + {#k_goto{label=F0,args=Kargs},Ap,St1}; false -> {Kargs,Ap,St1} = atomic_list(Cargs, Sub, St0), F1 = get_fsub(F0, Ar, Sub), %Has it been rewritten @@ -2002,11 +2011,12 @@ uexpr(#k_local{anno=A,name=Name,arity=Arity}, {break,Rs}, St) -> args=[#k_local{name=Name,arity=Arity+FreeCount} | Fvs], ret=Rs}, {Bif,Free,St}; -uexpr(#k_letrec_goto{anno=A,first=F0,then=T0}=MatchAlt, Br, St0) -> +uexpr(#k_letrec_goto{anno=A,vars=Vs,first=F0,then=T0}=MatchAlt, Br, St0) -> Rs = break_rets(Br), + Ns = lit_list_vars(Vs), {F1,Fu,St1} = ubody(F0, Br, St0), {T1,Tu,St2} = ubody(T0, Br, St1), - Used = union(Fu, Tu), + Used = subtract(union(Fu, Tu), Ns), {MatchAlt#k_letrec_goto{anno=A,first=F1,then=T1,ret=Rs},Used,St2}; uexpr(Lit, {break,Rs0}, St0) -> %% Transform literals to puts here. diff --git a/lib/compiler/src/v3_kernel.hrl b/lib/compiler/src/v3_kernel.hrl index 76987640e8..8d3e5dd7e7 100644 --- a/lib/compiler/src/v3_kernel.hrl +++ b/lib/compiler/src/v3_kernel.hrl @@ -56,8 +56,8 @@ -record(k_try_enter, {anno=[],arg,vars,body,evars,handler}). -record(k_catch, {anno=[],body,ret=[]}). --record(k_letrec_goto, {anno=[],label,first,then,ret=[]}). --record(k_goto, {anno=[],label}). +-record(k_letrec_goto, {anno=[],label,vars=[],first,then,ret=[]}). +-record(k_goto, {anno=[],label,args=[]}). -record(k_match, {anno=[],body,ret=[]}). -record(k_alt, {anno=[],first,then}). diff --git a/lib/compiler/src/v3_kernel_pp.erl b/lib/compiler/src/v3_kernel_pp.erl index 2c2bd498a9..d1b075ce0f 100644 --- a/lib/compiler/src/v3_kernel_pp.erl +++ b/lib/compiler/src/v3_kernel_pp.erl @@ -173,10 +173,11 @@ format_1(#k_alt{first=O,then=T}, Ctxt) -> format(O, Ctxt1), nl_indent(Ctxt1), format(T, Ctxt1)]; -format_1(#k_letrec_goto{label=Label,first=First,then=Then,ret=Rs}, Ctxt) -> +format_1(#k_letrec_goto{label=Label,vars=Vs,first=First,then=Then,ret=Rs}, Ctxt) -> Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent), ["letrec_goto ", atom_to_list(Label), + format_args(Vs, Ctxt), nl_indent(Ctxt1), format(Then, Ctxt1), nl_indent(Ctxt1), @@ -185,8 +186,8 @@ format_1(#k_letrec_goto{label=Label,first=First,then=Then,ret=Rs}, Ctxt) -> "end", format_ret(Rs, Ctxt1) ]; -format_1(#k_goto{label=Label}, _Ctxt) -> - ["goto ",atom_to_list(Label)]; +format_1(#k_goto{label=Label,args=As}, Ctxt) -> + ["goto ",atom_to_list(Label),format_args(As, Ctxt)]; format_1(#k_select{var=V,types=Cs}, Ctxt) -> Ctxt1 = ctxt_bump_indent(Ctxt, 2), ["select ", diff --git a/lib/dialyzer/src/dialyzer_clean_core.erl b/lib/dialyzer/src/dialyzer_clean_core.erl index 071e2eccad..820ce19a06 100644 --- a/lib/dialyzer/src/dialyzer_clean_core.erl +++ b/lib/dialyzer/src/dialyzer_clean_core.erl @@ -109,6 +109,7 @@ clean_letrec(Tree) -> FunBody = cerl:fun_body(Fun), FunBody1 = clean(FunBody), Body = clean(cerl:letrec_body(Tree)), + FunVars = cerl:fun_vars(Fun), case dialyzer_ignore(Body) of true -> %% The body of the letrec directly transfer controls to @@ -152,8 +153,10 @@ clean_letrec(Tree) -> %% end %% PrimopUnknown = cerl:c_primop(cerl:abstract(dialyzer_unknown), []), - Clauses = [cerl:c_clause([cerl:abstract(a)], Body), - cerl:c_clause([cerl:abstract(b)], FunBody1)], + PatA = [cerl:abstract(a)], + PatB = [cerl:c_tuple([cerl:abstract(b)|FunVars])], + Clauses = [cerl:c_clause(PatA, Body), + cerl:c_clause(PatB, FunBody1)], cerl:c_case(PrimopUnknown, Clauses) end; false -> -- 2.34.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor