aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--.travis.yml10
-rw-r--r--lib/compiler/src/v3_kernel.erl228
-rw-r--r--lib/compiler/test/bs_match_SUITE.erl162
-rw-r--r--lib/jinterface/java_src/com/ericsson/otp/erlang/OtpOutputStream.java8
-rw-r--r--lib/os_mon/c_src/cpu_sup.c2
-rwxr-xr-xscripts/build-otp2
6 files changed, 333 insertions, 79 deletions
diff --git a/.travis.yml b/.travis.yml
index 00fe85fc04..51453639b0 100644
--- a/.travis.yml
+++ b/.travis.yml
@@ -5,6 +5,8 @@ sudo: false
os:
- linux
+dist: xenial
+
addons:
apt:
packages:
@@ -12,10 +14,8 @@ addons:
- libncurses-dev
- build-essential
- libssl-dev
- - libwxgtk2.8-dev
- - libgl1-mesa-dev
+ - libwxgtk3.0-dev
- libglu1-mesa-dev
- - libpng3
- default-jdk
- g++
- xsltproc
@@ -64,9 +64,7 @@ matrix:
- build-essential
- libssl-dev
- libwxgtk3.0-dev
- - libgl1-mesa-dev
- libglu1-mesa-dev
- - libpng3
- default-jdk
- g++
- xsltproc
@@ -80,7 +78,7 @@ matrix:
repo: erlang/cd
target-branch: master
skip-cleanup: true
- keep-history: true
+ keep-history: false
verbose: true
github-token: $ERLANG_CD_GITHUB_TOKEN
on:
diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl
index 6fd1790c1a..49fb66126f 100644
--- a/lib/compiler/src/v3_kernel.erl
+++ b/lib/compiler/src/v3_kernel.erl
@@ -91,6 +91,7 @@
-include("core_parse.hrl").
-include("v3_kernel.hrl").
+-define(EXPAND_MAX_SIZE_SEGMENT, 1024).
%% These are not defined in v3_kernel.hrl.
get_kanno(Kthing) -> element(2, Kthing).
@@ -1170,7 +1171,7 @@ validate_bin_element_size(#k_int{val=V}) when V >= 0 -> ok;
validate_bin_element_size(#k_atom{val=all}) -> ok;
validate_bin_element_size(#k_atom{val=undefined}) -> ok;
validate_bin_element_size(_) -> throw(bad_element_size).
-
+
%% atomic_list([Cexpr], Sub, State) -> {[Kexpr],[PreKexpr],State}.
atomic_list(Ces, Sub, St) ->
@@ -1296,14 +1297,63 @@ pattern_bin_1([#c_bitstr{anno=A,val=E0,size=S0,unit=U,type=T,flags=Fs}|Es0],
_ -> Isub0
end,
{Es,{Isub,Osub},St3} = pattern_bin_1(Es0, Isub1, Osub1, St2),
- {#k_bin_seg{anno=A,size=S,
- unit=U0,
- type=cerl:concrete(T),
- flags=Fs0,
- seg=E,next=Es},
- {Isub,Osub},St3};
+ {build_bin_seg(A, S, U0, cerl:concrete(T), Fs0, E, Es),{Isub,Osub},St3};
pattern_bin_1([], Isub, Osub, St) -> {#k_bin_end{},{Isub,Osub},St}.
+%% build_bin_seg(Anno, Size, Unit, Type, Flags, Seg, Next) -> #k_bin_seg{}.
+%% This function normalizes literal integers with size > 8 and literal
+%% utf8 segments into integers with size = 8 (and potentially an integer
+%% with size less than 8 at the end). This is so further optimizations
+%% have a normalized view of literal integers, allowing us to generate
+%% more literals and group more clauses. Those integers may be "squeezed"
+%% later into the largest integer possible.
+%%
+build_bin_seg(A, #k_int{val=Bits} = Sz, U, integer=Type, [unsigned,big]=Flags, #k_literal{val=Int}=Seg, Next) ->
+ Size = Bits * U,
+ case integer_fits_and_is_expandable(Int, Size) of
+ true -> build_bin_seg_integer_recur(A, Size, Int, Next);
+ false -> #k_bin_seg{anno=A,size=Sz,unit=U,type=Type,flags=Flags,seg=Seg,next=Next}
+ end;
+build_bin_seg(A, Sz, U, utf8=Type, [unsigned,big]=Flags, #k_literal{val=Utf8} = Seg, Next) ->
+ case utf8_fits(Utf8) of
+ {Int, Bits} -> build_bin_seg_integer_recur(A, Bits, Int, Next);
+ error -> #k_bin_seg{anno=A,size=Sz,unit=U,type=Type,flags=Flags,seg=Seg,next=Next}
+ end;
+build_bin_seg(A, Sz, U, Type, Flags, Seg, Next) ->
+ #k_bin_seg{anno=A,size=Sz,unit=U,type=Type,flags=Flags,seg=Seg,next=Next}.
+
+build_bin_seg_integer_recur(A, Bits, Val, Next) when Bits > 8 ->
+ NextBits = Bits - 8,
+ NextVal = Val band ((1 bsl NextBits) - 1),
+ Last = build_bin_seg_integer_recur(A, NextBits, NextVal, Next),
+ build_bin_seg_integer(A, 8, Val bsr NextBits, Last);
+
+build_bin_seg_integer_recur(A, Bits, Val, Next) ->
+ build_bin_seg_integer(A, Bits, Val, Next).
+
+build_bin_seg_integer(A, Bits, Val, Next) ->
+ Sz = #k_int{anno=A,val=Bits},
+ Seg = #k_literal{anno=A,val=Val},
+ #k_bin_seg{anno=A,size=Sz,unit=1,type=integer,flags=[unsigned,big],seg=Seg,next=Next}.
+
+integer_fits_and_is_expandable(Int, Size) when 0 < Size, Size =< ?EXPAND_MAX_SIZE_SEGMENT ->
+ case <<Int:Size>> of
+ <<Int:Size>> -> true;
+ _ -> false
+ end;
+integer_fits_and_is_expandable(_Int, _Size) ->
+ false.
+
+utf8_fits(Utf8) ->
+ try
+ Bin = <<Utf8/utf8>>,
+ Bits = bit_size(Bin),
+ <<Int:Bits>> = Bin,
+ {Int, Bits}
+ catch
+ _:_ -> error
+ end.
+
%% pattern_list([Cexpr], Sub, State) -> {[Kexpr],Sub,State}.
pattern_list(Ces, Sub, St) ->
@@ -1553,7 +1603,7 @@ maybe_add_warning(Ke, MatchAnno, St) ->
get_line([Line|_]) when is_integer(Line) -> Line;
get_line([_|T]) -> get_line(T);
get_line([]) -> none.
-
+
get_file([{file,File}|_]) -> File;
get_file([_|T]) -> get_file(T);
get_file([]) -> "no_file". % should not happen
@@ -1761,27 +1811,10 @@ do_combine_lit_pat(#k_tuple{anno=A,es=Es0}) ->
do_combine_lit_pat(_) ->
throw(not_possible).
-combine_bin_segs(#k_bin_seg{size=Size0,unit=Unit,type=integer,
- flags=[unsigned,big],seg=Seg,next=Next}) ->
- #k_literal{val=Size1} = do_combine_lit_pat(Size0),
- #k_literal{val=Int} = do_combine_lit_pat(Seg),
- Size = Size1 * Unit,
- if
- 0 < Size, Size < 64 ->
- Bin = <<Int:Size>>,
- case Bin of
- <<Int:Size>> ->
- NextBin = combine_bin_segs(Next),
- <<Bin/bits,NextBin/bits>>;
- _ ->
- %% The integer Int does not fit in the segment,
- %% thus it will not match.
- throw(not_possible)
- end;
- true ->
- %% Avoid creating huge binary literals.
- throw(not_possible)
- end;
+combine_bin_segs(#k_bin_seg{size=#k_int{val=8},unit=1,type=integer,
+ flags=[unsigned,big],seg=#k_literal{val=Int},next=Next})
+ when is_integer(Int), 0 =< Int, Int =< 255 ->
+ <<Int,(combine_bin_segs(Next))/bits>>;
combine_bin_segs(#k_bin_end{}) ->
<<>>;
combine_bin_segs(_) ->
@@ -1851,11 +1884,10 @@ handle_bin_con_not_possible([]) -> [].
select_bin_int([#iclause{pats=[#k_bin_seg{anno=A,type=integer,
size=#k_int{val=Bits0}=Sz,unit=U,
flags=Fl,seg=#k_literal{val=Val},
- next=N}|Ps]}=C|Cs0])
- when is_integer(Val) ->
+ next=N}|Ps]}=C|Cs0]) ->
Bits = U * Bits0,
if
- Bits > 1024 -> throw(not_possible); %Expands the code too much.
+ Bits > ?EXPAND_MAX_SIZE_SEGMENT -> throw(not_possible); %Expands the code too much.
true -> ok
end,
select_assert_match_possible(Bits, Val, Fl),
@@ -1866,16 +1898,6 @@ select_bin_int([#iclause{pats=[#k_bin_seg{anno=A,type=integer,
end,
Cs = select_bin_int_1(Cs0, Bits, Fl, Val),
[{k_bin_int,[C#iclause{pats=[P|Ps]}|Cs]}];
-select_bin_int([#iclause{pats=[#k_bin_seg{anno=A,type=utf8,
- flags=[unsigned,big]=Fl,
- seg=#k_literal{val=Val0},
- next=N}|Ps]}=C|Cs0])
- when is_integer(Val0) ->
- {Val,Bits} = select_utf8(Val0),
- P = #k_bin_int{anno=A,size=#k_int{val=Bits},unit=1,
- flags=Fl,val=Val,next=N},
- Cs = select_bin_int_1(Cs0, Bits, Fl, Val),
- [{k_bin_int,[C#iclause{pats=[P|Ps]}|Cs]}];
select_bin_int(_) -> throw(not_possible).
select_bin_int_1([#iclause{pats=[#k_bin_seg{anno=A,type=integer,
@@ -1890,18 +1912,6 @@ select_bin_int_1([#iclause{pats=[#k_bin_seg{anno=A,type=integer,
end,
P = #k_bin_int{anno=A,size=Sz,unit=U,flags=Fl,val=Val,next=N},
[C#iclause{pats=[P|Ps]}|select_bin_int_1(Cs, Bits, Fl, Val)];
-select_bin_int_1([#iclause{pats=[#k_bin_seg{anno=A,type=utf8,
- flags=Fl,
- seg=#k_literal{val=Val0},
- next=N}|Ps]}=C|Cs],
- Bits, Fl, Val) when is_integer(Val0) ->
- case select_utf8(Val0) of
- {Val,Bits} -> ok;
- {_,_} -> throw(not_possible)
- end,
- P = #k_bin_int{anno=A,size=#k_int{val=Bits},unit=1,
- flags=[unsigned,big],val=Val,next=N},
- [C#iclause{pats=[P|Ps]}|select_bin_int_1(Cs, Bits, Fl, Val)];
select_bin_int_1([], _, _, _) -> [];
select_bin_int_1(_, _, _, _) -> throw(not_possible).
@@ -1927,17 +1937,6 @@ match_fun(Val) ->
{match,Bs}
end.
-select_utf8(Val0) ->
- try
- Bin = <<Val0/utf8>>,
- Size = bit_size(Bin),
- <<Val:Size>> = Bin,
- {Val,Size}
- catch
- error:_ ->
- throw(not_possible)
- end.
-
%% match_value([Var], Con, [Clause], Default, State) -> {SelectExpr,State}.
%% At this point all the clauses have the same constructor, we must
%% now separate them according to value.
@@ -2057,7 +2056,8 @@ match_clause([U|Us], [C|_]=Cs0, Def, St0) ->
{Match0,Vs,St1} = get_match(get_con(Cs0), St0),
Match = sub_size_var(Match0, Cs0),
{Cs1,St2} = new_clauses(Cs0, U, St1),
- {B,St3} = match(Vs ++ Us, Cs1, Def, St2),
+ Cs2 = squeeze_clauses_by_bin_integer_count(Cs1, []),
+ {B,St3} = match(Vs ++ Us, Cs2, Def, St2),
{#k_val_clause{anno=Anno,val=Match,body=B},St3}.
sub_size_var(#k_bin_seg{size=#k_var{name=Name}=Kvar}=BinSeg, [#iclause{isub=Sub}|_]) ->
@@ -2127,6 +2127,102 @@ new_clauses(Cs0, U, St) ->
end, Cs0),
{Cs1,St}.
+%% group and squeeze
+%% The goal of those functions is to group subsequent integer k_bin_seg
+%% literals by count so we can leverage bs_get_integer_16 whenever possible.
+%%
+%% The priority is to create large groups. So if we have three clauses matching
+%% on 16-bits/16-bits/8-bits, we will first have a single 8-bits match for all
+%% three clauses instead of clauses (one with 16 and another with 8). But note
+%% the algorithm is recursive, so the remaining 8-bits for the first two clauses
+%% will be grouped next.
+%%
+%% We also try to not create too large groups. If we have too many clauses,
+%% it is preferrable to match on 8-bits, select a branch, then match on the
+%% next 8-bits, rather than match on 16-bits which would force us to have
+%% to select to many values at the same time, which would not be efficient.
+%%
+%% Another restriction is that we create groups only if the end of the
+%% group is a variadic clause or the end of the binary. That's because
+%% if we have 16-bits/16-bits/catch-all, breaking it into a 16-bits lookup
+%% will make the catch-all more expensive.
+%%
+%% Clauses are grouped in reverse when squeezing and then flattened and
+%% re-reversed at the end.
+squeeze_clauses_by_bin_integer_count([Clause | Clauses], Acc) ->
+ case clause_count_bin_integer_segments(Clause) of
+ {literal, N} -> squeeze_clauses_by_bin_integer_count(Clauses, N, 1, [Clause], Acc);
+ _ -> squeeze_clauses_by_bin_integer_count(Clauses, [[Clause] | Acc])
+ end;
+squeeze_clauses_by_bin_integer_count(_, Acc) ->
+ flat_reverse(Acc, []).
+
+squeeze_clauses_by_bin_integer_count([], N, Count, GroupAcc, Acc) ->
+ Squeezed = squeeze_clauses(GroupAcc, fix_count_without_variadic_segment(N), Count),
+ flat_reverse([Squeezed | Acc], []);
+squeeze_clauses_by_bin_integer_count([#iclause{pats=[#k_bin_end{} | _]} = Clause], N, Count, GroupAcc, Acc) ->
+ Squeezed = squeeze_clauses(GroupAcc, fix_count_without_variadic_segment(N), Count),
+ flat_reverse([[Clause | Squeezed] | Acc], []);
+squeeze_clauses_by_bin_integer_count([Clause | Clauses], N, Count, GroupAcc, Acc) ->
+ case clause_count_bin_integer_segments(Clause) of
+ {literal, NewN} ->
+ squeeze_clauses_by_bin_integer_count(Clauses, min(N, NewN), Count + 1, [Clause | GroupAcc], Acc);
+
+ {variadic, NewN} when NewN =< N ->
+ Squeezed = squeeze_clauses(GroupAcc, NewN, Count),
+ squeeze_clauses_by_bin_integer_count(Clauses, [[Clause | Squeezed] | Acc]);
+
+ _ ->
+ squeeze_clauses_by_bin_integer_count(Clauses, [[Clause | GroupAcc] | Acc])
+ end.
+
+clause_count_bin_integer_segments(#iclause{pats=[#k_bin_seg{seg=#k_literal{}} = BinSeg | _]}) ->
+ count_bin_integer_segments(BinSeg, 0);
+clause_count_bin_integer_segments(#iclause{pats=[#k_bin_seg{size=#k_int{val=Size},unit=Unit,
+ type=integer,flags=[unsigned,big], seg=#k_var{}} | _]})
+ when ((Size * Unit) rem 8) =:= 0 ->
+ {variadic, (Size * Unit) div 8};
+clause_count_bin_integer_segments(_) ->
+ error.
+
+count_bin_integer_segments(#k_bin_seg{size=#k_int{val=8},unit=1,type=integer,flags=[unsigned,big],
+ seg=#k_literal{val=Int},next=Next}, Count) when is_integer(Int), 0 =< Int, Int =< 255 ->
+ count_bin_integer_segments(Next, Count + 1);
+count_bin_integer_segments(_, Count) when Count > 0 ->
+ {literal, Count};
+count_bin_integer_segments(_, _Count) ->
+ error.
+
+%% Since 4 bytes in on 32-bits systems are bignums, we convert
+%% anything more than 3 into 2 bytes lookup. The goal is to convert
+%% any multi-clause segment into 2-byte lookups with a potential
+%% 3 byte lookup at the end.
+fix_count_without_variadic_segment(N) when N > 3 -> 2;
+fix_count_without_variadic_segment(N) -> N.
+
+%% If we have more than 16 clauses, then it is better
+%% to branch multiple times than getting a large integer.
+%% We also abort if we have nothing to squeeze.
+squeeze_clauses(Clauses, Size, Count) when Count >= 16; Size == 1 -> Clauses;
+squeeze_clauses(Clauses, Size, _Count) -> squeeze_clauses(Clauses, Size).
+
+squeeze_clauses([#iclause{pats=[#k_bin_seg{seg=#k_literal{}} = BinSeg | Pats]} = Clause | Clauses], Size) ->
+ [Clause#iclause{pats=[squeeze_segments(BinSeg, 0, 0, Size) | Pats]} |
+ squeeze_clauses(Clauses, Size)];
+squeeze_clauses([], _Size) ->
+ [].
+
+squeeze_segments(#k_bin_seg{size=Sz, seg=#k_literal{val=Val}=Lit} = BinSeg, Acc, Size, 1) ->
+ BinSeg#k_bin_seg{size=Sz#k_int{val=Size + 8}, seg=Lit#k_literal{val=(Acc bsl 8) bor Val}};
+squeeze_segments(#k_bin_seg{seg=#k_literal{val=Val},next=Next}, Acc, Size, Count) ->
+ squeeze_segments(Next, (Acc bsl 8) bor Val, Size + 8, Count - 1).
+
+flat_reverse([Head | Tail], Acc) -> flat_reverse(Tail, flat_reverse_1(Head, Acc));
+flat_reverse([], Acc) -> Acc.
+
+flat_reverse_1([Head | Tail], Acc) -> flat_reverse_1(Tail, [Head | Acc]);
+flat_reverse_1([], Acc) -> Acc.
+
%% build_guard([GuardClause]) -> GuardExpr.
build_guard([]) -> fail;
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 145a50f4ad..0dc1d64eeb 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -24,7 +24,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
init_per_testcase/2,end_per_testcase/2,
- verify_highest_opcode/1,
+ verify_highest_opcode/1, expand_and_squeeze/1,
size_shadow/1,int_float/1,otp_5269/1,null_fields/1,wiger/1,
bin_tail/1,save_restore/1,
partitioned_bs_match/1,function_clause/1,
@@ -64,7 +64,7 @@ groups() ->
[{p,[],
[verify_highest_opcode,
size_shadow,int_float,otp_5269,null_fields,wiger,
- bin_tail,save_restore,
+ bin_tail,save_restore,expand_and_squeeze,
partitioned_bs_match,function_clause,unit,
shared_sub_bins,bin_and_float,dec_subidentifiers,
skip_optional_tag,decode_integer,wfbm,degenerated_match,bs_sum,
@@ -2021,3 +2021,161 @@ do_exceptions_after_match_failure(Other) ->
ok.
id(I) -> I.
+
+expand_and_squeeze(Config) when is_list(Config) ->
+ %% UTF8 literals are expanded and then squeezed into integer16
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,16}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<$á/utf8,_/binary>>"),
+ ?Q("<<$é/utf8,_/binary>>")
+ ]),
+
+ %% Sized integers are expanded and then squeezed into integer16
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,16}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<0:32,_/binary>>"),
+ ?Q("<<\"bbbb\",_/binary>>")
+ ]),
+
+ %% Groups of 8 bits are squeezed into integer16
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,16}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<\"aaaa\",_/binary>>"),
+ ?Q("<<\"bbbb\",_/binary>>")
+ ]),
+
+ %% Groups of 8 bits with empty binary are also squeezed
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,16}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<\"aaaa\",_/binary>>"),
+ ?Q("<<\"bbbb\",_/binary>>"),
+ ?Q("<<>>")
+ ]),
+
+ %% Groups of 8 bits with float lookup are not squeezed
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,8}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<\"aaaa\",_/binary>>"),
+ ?Q("<<\"bbbb\",_/binary>>"),
+ ?Q("<<_/float>>")
+ ]),
+
+ %% Groups of diverse bits go with minimum possible
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,8}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<\"aa\",_/binary>>"),
+ ?Q("<<\"bb\",_/binary>>"),
+ ?Q("<<\"c\",_/binary>>")
+ ]),
+
+ %% Groups of diverse bits go with minimum possible but are recursive...
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,8}|_],_}
+ | RestDiverse
+ ] = binary_match_to_asm([
+ ?Q("<<\"aaa\",_/binary>>"),
+ ?Q("<<\"abb\",_/binary>>"),
+ ?Q("<<\"c\",_/binary>>")
+ ]),
+
+ %% so we still perform a 16 bits lookup for the remaining
+ true = lists:any(fun({test,bs_get_integer2,_,_,[_,{integer,16}|_],_}) -> true;
+ (_) -> false end, RestDiverse),
+
+ %% Large match is kept as is if there is a sized match later
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,64}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<255,255,255,255,255,255,255,255>>"),
+ ?Q("<<_:64>>")
+ ]),
+
+ %% Large match is kept as is with large matches before and after
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,32}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<A:32,_:A>>"),
+ ?Q("<<0:32>>"),
+ ?Q("<<_:32>>")
+ ]),
+
+ %% Large match is kept as is with large matches before and after
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,32}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<A:32,_:A>>"),
+ ?Q("<<0,0,0,0>>"),
+ ?Q("<<_:32>>")
+ ]),
+
+ %% Large match is kept as is with smaller but still large matches before and after
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,32}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<A:32, _:A>>"),
+ ?Q("<<0:64>>"),
+ ?Q("<<_:32>>")
+ ]),
+
+ %% There is no squeezing for groups with more than 16 matches
+ [
+ {test,bs_get_integer2,_,_,[_,{integer,8}|_],_}
+ | _
+ ] = binary_match_to_asm([
+ ?Q("<<\"aa\", _/binary>>"),
+ ?Q("<<\"bb\", _/binary>>"),
+ ?Q("<<\"cc\", _/binary>>"),
+ ?Q("<<\"dd\", _/binary>>"),
+ ?Q("<<\"ee\", _/binary>>"),
+ ?Q("<<\"ff\", _/binary>>"),
+ ?Q("<<\"gg\", _/binary>>"),
+ ?Q("<<\"hh\", _/binary>>"),
+ ?Q("<<\"ii\", _/binary>>"),
+ ?Q("<<\"jj\", _/binary>>"),
+ ?Q("<<\"kk\", _/binary>>"),
+ ?Q("<<\"ll\", _/binary>>"),
+ ?Q("<<\"mm\", _/binary>>"),
+ ?Q("<<\"nn\", _/binary>>"),
+ ?Q("<<\"oo\", _/binary>>"),
+ ?Q("<<\"pp\", _/binary>>")
+ ]),
+
+ ok.
+
+binary_match_to_asm(Matches) ->
+ Clauses = [
+ begin
+ Ann = element(2, Match),
+ {clause,Ann,[Match],[],[{integer,Ann,Return}]}
+ end || {Match,Return} <- lists:zip(Matches, lists:seq(1, length(Matches)))
+ ],
+
+ Module = [
+ {attribute,1,module,match_to_asm},
+ {attribute,2,export,[{example,1}]},
+ {function,3,example,1,Clauses}
+ ],
+
+ {ok,match_to_asm,{match_to_asm,_Exports,_Attrs,Funs,_},_} =
+ compile:forms(Module, [return, to_asm]),
+
+ [{function,example,1,2,AllInstructions}|_] = Funs,
+ [{label,_},{line,_},{func_info,_,_,_},{label,_},{'%',_},
+ {test,bs_start_match3,_,_,_,_},{bs_get_position,_,_,_}|Instructions] = AllInstructions,
+ Instructions.
diff --git a/lib/jinterface/java_src/com/ericsson/otp/erlang/OtpOutputStream.java b/lib/jinterface/java_src/com/ericsson/otp/erlang/OtpOutputStream.java
index a3b089c1da..917e5baf3a 100644
--- a/lib/jinterface/java_src/com/ericsson/otp/erlang/OtpOutputStream.java
+++ b/lib/jinterface/java_src/com/ericsson/otp/erlang/OtpOutputStream.java
@@ -106,9 +106,9 @@ public class OtpOutputStream extends ByteArrayOutputStream {
}
/**
- * Trims the capacity of this <tt>OtpOutputStream</tt> instance to be the
+ * Trims the capacity of this <code>OtpOutputStream</code> instance to be the
* buffer's current size. An application can use this operation to minimize
- * the storage of an <tt>OtpOutputStream</tt> instance.
+ * the storage of an <code>OtpOutputStream</code> instance.
*/
public void trimToSize() {
resize(super.count);
@@ -125,7 +125,7 @@ public class OtpOutputStream extends ByteArrayOutputStream {
}
/**
- * Increases the capacity of this <tt>OtpOutputStream</tt> instance, if
+ * Increases the capacity of this <code>OtpOutputStream</code> instance, if
* necessary, to ensure that it can hold at least the number of elements
* specified by the minimum capacity argument.
*
@@ -909,7 +909,7 @@ public class OtpOutputStream extends ByteArrayOutputStream {
* @param o
* the Erlang term to write.
* @param level
- * the compression level (<tt>0..9</tt>)
+ * the compression level (<code>0..9</code>)
*/
public void write_compressed(final OtpErlangObject o, final int level) {
@SuppressWarnings("resource")
diff --git a/lib/os_mon/c_src/cpu_sup.c b/lib/os_mon/c_src/cpu_sup.c
index c96a5c9f7c..98a2526aab 100644
--- a/lib/os_mon/c_src/cpu_sup.c
+++ b/lib/os_mon/c_src/cpu_sup.c
@@ -359,7 +359,7 @@ static cpu_t *read_procstat(FILE *fp, cpu_t *cpu) {
memset(cpu, 0, sizeof(cpu_t));
return cpu;
}
- sscanf(buffer, "cpu%u %Lu %Lu %Lu %Lu %Lu %Lu %Lu %Lu",
+ sscanf(buffer, "cpu%u %llu %llu %llu %llu %llu %llu %llu %llu",
&(cpu->id),
&(cpu->user),
&(cpu->nice_user),
diff --git a/scripts/build-otp b/scripts/build-otp
index abf8d5d67f..55023ba7d8 100755
--- a/scripts/build-otp
+++ b/scripts/build-otp
@@ -44,6 +44,8 @@ fi
do_and_log "Autoconfing" ./otp_build autoconf
do_and_log "Configuring" ./otp_build configure
+echo Configure result:
+tail -n 20 $log
do_and_log "Building OTP" ./otp_build boot -a
if [ "$1" = "release" ]; then