|
126 | 126 | -record(igen, {anno=#a{},acc_pat,acc_guard,
|
127 | 127 | skip_pat,tail,tail_pat,arg,
|
128 | 128 | refill={nomatch,ignore}}).
|
129 |
| --record(izip, {anno=#a{},len,acc_pats,acc_guard, |
| 129 | +-record(izip, {anno=#a{},acc_pats,acc_guard, |
130 | 130 | skip_pats,tails,tail_pats,pres,args,
|
131 | 131 | refill_pats,refill_as}).
|
132 | 132 | -record(isimple, {anno=#a{},term :: cerl:cerl()}).
|
@@ -1647,13 +1647,14 @@ lc_tq1(Line, E, [#igen{anno=#a{anno=GA}=GAnno,
|
1647 | 1647 |
|
1648 | 1648 | %% zip_tq(Line, Exp, [Qualifier], Mc, State, TqFun) -> {LetRec,[PreExp],State}.
|
1649 | 1649 |
|
1650 |
| -zip_tq(Line, E, #izip{anno=#a{anno=GA}=GAnno,len=NumGenerators, |
| 1650 | +zip_tq(Line, E, #izip{anno=#a{anno=GA}=GAnno, |
1651 | 1651 | acc_pats=AccPats,acc_guard=AccGuard,
|
1652 | 1652 | tails=TailVars,tail_pats=TailPats,
|
1653 | 1653 | skip_pats=SkipPats,refill_pats=RefillPats0,
|
1654 | 1654 | refill_as=RefillAs,pres=Pres,args=Args}, Mc, St0, Qs) ->
|
1655 | 1655 | {Name,St1} = new_fun_name("zlc", St0),
|
1656 | 1656 | LA = lineno_anno(Line, St1),
|
| 1657 | + NumGenerators = length(AccPats), |
1657 | 1658 |
|
1658 | 1659 | %% Generate new vars for each generator, 1 for the regular call, and 1 for
|
1659 | 1660 | %% the bad generator case.
|
@@ -1782,15 +1783,15 @@ bc_tq_build(Line, Pre0, #c_var{name=AccVar}, Elements0, St0) ->
|
1782 | 1783 | Anno = Anno0#a{anno=[compiler_generated,single_use|A]},
|
1783 | 1784 | {set_anno(E, Anno),Pre0++Pre,St}.
|
1784 | 1785 |
|
1785 |
| -bzip_tq1(Line, E, #izip{anno=GAnno,len=NumGenerators, |
| 1786 | +bzip_tq1(Line, E, #izip{anno=GAnno, |
1786 | 1787 | acc_pats=AccPats,acc_guard=AccGuard,
|
1787 | 1788 | tails=TailVars,tail_pats=TailPats,
|
1788 | 1789 | skip_pats=SkipPats,refill_pats=RefillPats0,
|
1789 | 1790 | refill_as=RefillAs,pres=Pres,args=Args}, Mc, St0, Qs) ->
|
1790 | 1791 | {Name,St1} = new_fun_name("bzip", St0),
|
1791 | 1792 | LA = lineno_anno(Line, St1),
|
1792 | 1793 | LAnno = #a{anno=LA},
|
1793 |
| - Arity = NumGenerators + 1, |
| 1794 | + Arity = length(AccPats) + 1, |
1794 | 1795 |
|
1795 | 1796 | %% Generate new vars for each generator, 1 for the regular call, and 1 for
|
1796 | 1797 | %% the bad generator case. last(CallVars) is used as the accumulator var
|
@@ -1848,29 +1849,6 @@ make_ignored(Ps, Vs) ->
|
1848 | 1849 | _ -> P
|
1849 | 1850 | end || {P, V} <- zip(Ps, Vs)].
|
1850 | 1851 |
|
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 |
| - |
1874 | 1852 | make_clause(Anno, [Pat|PatExtra], Guard, Body) ->
|
1875 | 1853 | make_clause(Anno, Pat, PatExtra, Guard, Body).
|
1876 | 1854 |
|
@@ -1927,19 +1905,19 @@ preprocess_quals(Line, Qs, St) ->
|
1927 | 1905 | preprocess_quals(Line, [{zip,Anno,Gens}|Qs], St, Acc) ->
|
1928 | 1906 | LAnno = #a{anno=lineno_anno(Anno, St)},
|
1929 | 1907 | {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), |
1932 | 1910 | [#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}, |
1943 | 1921 | preprocess_quals(Line, Qs, St1, [Zip|Acc]);
|
1944 | 1922 | preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
|
1945 | 1923 | case is_generator(Q) of
|
@@ -1969,6 +1947,25 @@ preprocess_quals(Line, [Q|Qs0], St0, Acc) ->
|
1969 | 1947 | preprocess_quals(_, [], St, Acc) ->
|
1970 | 1948 | {reverse(Acc),St}.
|
1971 | 1949 |
|
| 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 | + |
1972 | 1969 | is_generator({generate,_,_,_}) -> true;
|
1973 | 1970 | is_generator({b_generate,_,_,_}) -> true;
|
1974 | 1971 | is_generator({m_generate,_,_,_}) -> true;
|
|
0 commit comments