1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1999-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21-module(bs_construct_SUITE).
22
23-export([all/0, suite/0,
24         init_per_suite/1, end_per_suite/1,
25	 test1/1, test2/1, test3/1, test4/1, test5/1, testf/1,
26	 not_used/1, in_guard/1,
27	 mem_leak/1, coerce_to_float/1, bjorn/1, append_empty_is_same/1,
28	 huge_float_field/1, system_limit/1, badarg/1,
29	 copy_writable_binary/1, kostis/1, dynamic/1, bs_add/1,
30	 otp_7422/1, zero_width/1, bad_append/1, bs_append_overflow/1,
31         reductions/1, fp16/1]).
32
33-include_lib("common_test/include/ct.hrl").
34
35suite() ->
36    [{ct_hooks,[ts_install_cth]},
37     {timetrap, {minutes, 1}}].
38
39all() ->
40    [test1, test2, test3, test4, test5, testf, not_used,
41     in_guard, mem_leak, coerce_to_float, bjorn, append_empty_is_same,
42     huge_float_field, system_limit, badarg,
43     copy_writable_binary, kostis, dynamic, bs_add, otp_7422, zero_width,
44     bad_append, bs_append_overflow, reductions, fp16].
45
46init_per_suite(Config) ->
47    Config.
48
49end_per_suite(_Config) ->
50    application:stop(os_mon).
51
52big(1) ->
53    57285702734876389752897683.
54
55i(X) -> X.
56
57r(L) ->
58    lists:reverse(L).
59
60-define(T(B, L), {B, ??B, L}).
61-define(N(B), {B, ??B, unknown}).
62
63-define(FAIL(Expr), fail_check(catch Expr, ??Expr, [])).
64
65-define(FAIL_VARS(Expr, Vars), fail_check(catch Expr, ??Expr, Vars)).
66
67l(I_13, I_big1) ->
68    [
69     ?T(<<-43>>,
70	[256-43]),
71     ?T(<<56>>,
72	[56]),
73     ?T(<<1,2>>,
74	[1, 2]),
75     ?T(<<4:4, 7:4>>,
76	[4*16+7]),
77     ?T(<<777:16/big>>,
78	[3, 9]),
79     ?T(<<777:16/little>>,
80	[9, 3]),
81     ?T(<<0.0:32/float>>,
82	[0,0,0,0]),
83     ?T(<<0.125:32/float>>,
84	[62,0,0,0]),
85     ?T(<<0.125:32/little-float>>,
86	[0,0,0,62]),
87     ?T(<<I_big1:32>>,
88	[138, 99, 0, 147]),
89     ?T(<<57285702734876389752897684:32>>,
90	[138, 99, 0, 148]),
91     ?T(<<I_big1:32/little>>,
92	r([138, 99, 0, 147])),
93     ?T(<<-1:17/unit:8>>,
94	lists:duplicate(17, 255)),
95
96     ?T(<<I_13>>,
97	[13]),
98
99     ?T(<<4:8/unit:2,5:2/unit:8>>,
100	[0, 4, 0, 5]),
101
102     ?T(<<1:1, 0:6, 1:1>>,
103	[129]),
104     ?T(<<1:1/little, 0:6/little, 1:1/little>>,
105	[129]),
106
107     ?T(<<<<1,2>>/binary>>,
108	[1, 2]),
109     ?T(<<<<1,2>>:1/binary>>,
110	[1]),
111     ?T(<<4,3,<<1,2>>:1/binary>>,
112	[4,3,1]),
113
114     ?T(<<(256*45+47)>>,
115	[47]),
116
117     ?T(<<57:0>>,
118	[]),
119
120     ?T(<<"apa">>,
121	"apa"),
122
123     ?T(<<1:3,"string",9:5>>,
124	[46,110,142,77,45,204,233]),
125
126     ?T(<<>>,
127	[]),
128
129     ?T(<<37.98:64/native-float>>,
130	native_3798()),
131
132     ?T(<<32978297842987249827298387697777669766334937:128/native-integer>>,
133	native_bignum()),
134
135     %% Unit tests.
136     ?T(<<<<5:3>>/bitstring>>, <<5:3>>),
137     ?T(<<42,<<7:4>>/binary-unit:4>>, <<42,7:4>>),
138     ?T(<<<<344:17>>/binary-unit:17>>, <<344:17>>),
139     ?T(<<<<42,3,7656:16>>/binary-unit:16>>, <<42,3,7656:16>>)
140
141     ].
142
143native_3798() ->
144    case <<1:16/native>> of
145	<<0,1>> -> [64,66,253,112,163,215,10,61];
146	<<1,0>> -> [61,10,215,163,112,253,66,64]
147    end.
148
149native_bignum() ->
150    case <<1:16/native>> of
151	<<0,1>> -> [129,205,18,177,1,213,170,101,39,231,109,128,176,11,73,217];
152	<<1,0>> -> [217,73,11,176,128,109,231,39,101,170,213,1,177,18,205,129]
153    end.
154
155evaluate(Str, Vars) ->
156    {ok,Tokens,_} =
157	erl_scan:string(Str ++ " . "),
158    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
159    case erl_eval:expr(Expr, Vars) of
160	{value, Result, _} ->
161	    Result
162    end.
163
164eval_list([], _Vars) ->
165    [];
166eval_list([{C_bin, Str, Bytes} | Rest], Vars) ->
167    case catch evaluate(Str, Vars) of
168	{'EXIT', Error} ->
169	    io:format("Evaluation error: ~p, ~p, ~p~n", [Str, Vars, Error]),
170	    exit(Error);
171	E_bin ->
172	    [{C_bin, E_bin, Str, Bytes} | eval_list(Rest, Vars)]
173    end.
174
175one_test({C_bin, E_bin, Str, Bytes}) when is_list(Bytes) ->
176    io:format("  ~s, ~p~n", [Str, Bytes]),
177    Bin = list_to_binary(Bytes),
178    if
179	C_bin == Bin ->
180	    ok;
181	true ->
182	    io:format("ERROR: Compiled: ~p. Expected ~p. Got ~p.~n",
183		      [Str, Bytes, binary_to_list(C_bin)]),
184	    ct:fail(comp)
185    end,
186    if
187	E_bin == Bin ->
188	    ok;
189	true ->
190	    io:format("ERROR: Interpreted: ~p. Expected ~p. Got ~p.~n",
191		      [Str, Bytes, binary_to_list(E_bin)]),
192	    ct:fail(comp)
193    end;
194one_test({C_bin, E_bin, Str, Result}) ->
195    io:format("  ~s ~p~n", [Str, C_bin]),
196    if
197	C_bin == E_bin ->
198	    ok;
199	true ->
200	    Arbitrary = case Result of
201			    unknown ->
202				size(C_bin);
203			    _ ->
204				Result
205			end,
206	    case equal_lists(binary_to_list(C_bin),
207			     binary_to_list(E_bin),
208			     Arbitrary) of
209		false ->
210		    io:format("ERROR: Compiled not equal to interpreted:"
211			      "~n ~p, ~p.~n",
212			      [binary_to_list(C_bin), binary_to_list(E_bin)]),
213		    ct:fail(comp);
214		0 ->
215		    ok;
216		%% For situations where the final bits may not matter, like
217		%% for floats:
218		N when is_integer(N) ->
219		    io:format("Info: compiled and interpreted differ in the"
220			      " last bytes:~n ~p, ~p.~n",
221			      [binary_to_list(C_bin), binary_to_list(E_bin)]),
222		    ok
223	    end
224    end.
225
226equal_lists([], [], _) ->
227    0;
228equal_lists([], _, _) ->
229    false;
230equal_lists(_, [], _) ->
231    false;
232equal_lists([A|AR], [A|BR], R) ->
233    equal_lists(AR, BR, R);
234equal_lists(A, B, R) ->
235    if
236	length(A) /= length(B) ->
237	    false;
238	length(A) =< R ->
239	    R;
240	true ->
241	    false
242    end.
243
244fail_check({'EXIT',{badarg,_}}, Str, Vars) ->
245    try	evaluate(Str, Vars) of
246	Res ->
247	    io:format("Interpreted result: ~p", [Res]),
248	    ct:fail(did_not_fail_in_intepreted_code)
249    catch
250	error:badarg ->
251	    ok
252    end;
253fail_check(Res, _, _) ->
254    io:format("Compiled result: ~p", [Res]),
255    ct:fail(did_not_fail_in_compiled_code).
256
257%%% Simple working cases
258test1(Config) when is_list(Config) ->
259    I_13 = i(13),
260    I_big1 = big(1),
261    Vars = [{'I_13', I_13},
262		  {'I_big1', I_big1}],
263    lists:foreach(fun one_test/1, eval_list(l(I_13, I_big1), Vars)).
264
265%%% Misc
266
267%%% <<A:S, A:(N-S)>>
268comp(N, A, S) ->
269    M1 = (1 bsl S) - 1,
270    M2 = (1 bsl (N-S)) - 1,
271    [((A band M1) bsl (N-S)) bor (A band M2)].
272
273gen(N, S, A) ->
274    [?T(<<A:S, A:(N-S)>>, comp(N, A, S))].
275
276gen_l(N, S, A) ->
277    [?T(<<A:S/little, A:(N-S)/little>>, comp(N, A, S))].
278
279test2(Config) when is_list(Config) ->
280    test2(0, 8, 2#10101010101010101),
281    test2(0, 8, 2#1111111111).
282
283test2(End, End, _) ->
284    ok;
285test2(I, End, A) ->
286    test2(I, A),
287    test2(I+1, End, A).
288
289test2(S, A) ->
290    N = 8,
291    Vars = [{'A',A}, {'N',N}, {'S',S}],
292    io:format("Vars: ~p\n", [Vars]),
293    lists:foreach(fun one_test/1, eval_list(gen(N, S, A), Vars)),
294    lists:foreach(fun one_test/1, eval_list(gen_l(N, S, A), Vars)).
295
296%%% Tests without facit
297
298t3() ->
299    [?N(<<4711:13, 9876:13, 3:6>>),
300     ?N(<<4.57:64/float>>),
301     ?N(<<4.57:32/float>>),
302
303     ?N(<<>>)
304    ].
305
306test3(Config) when is_list(Config) ->
307    Vars = [],
308    lists:foreach(fun one_test/1, eval_list(t3(), Vars)).
309
310gen_u(N, S, A) ->
311    [?N(<<A:S, A:(N-S)>>)].
312
313gen_u_l(N, S, A) ->
314    [?N(<<A:S/little, A:(N-S)/little>>)].
315
316test4(Config) when is_list(Config) ->
317    test4(0, 16, 2#10101010101010101),
318    test4(0, 16, 2#1111111111).
319
320test4(End, End, _) ->
321    ok;
322test4(I, End, A) ->
323    test4(I, A),
324    test4(I+1, End, A).
325
326test4(S, A) ->
327    N = 16,
328    Vars = [{'A', A}, {'N', 16}, {'S', S}],
329    lists:foreach(fun one_test/1, eval_list(gen_u(N, S, A), Vars)),
330    lists:foreach(fun one_test/1, eval_list(gen_u_l(N, S, A), Vars)).
331
332gen_b(N, S, A) ->
333    [?T(<<A:S/binary-unit:1, A:(N-S)/binary-unit:1>>,
334	binary_to_list(<<A:S/binary-unit:1, A:(N-S)/binary-unit:1>>))].
335
336%% OTP-3995
337test5(Config) when is_list(Config) ->
338    test5(0, 8, <<73>>),
339    test5(0, 8, <<68>>).
340
341test5(End, End, _) ->
342    ok;
343test5(I, End, A) ->
344    test5(I, A),
345    test5(I+1, End, A).
346
347test5(S, A) ->
348    N = 8,
349    Vars = [{'A', A}, {'N', 8}, {'S', S}],
350    lists:foreach(fun one_test/1, eval_list(gen_b(N, S, A), Vars)).
351
352%%% Failure cases
353testf(Config) when is_list(Config) ->
354    ?FAIL(<<3.14>>),
355    ?FAIL(<<<<1,2>>>>),
356
357    ?FAIL(<<2.71/binary>>),
358    ?FAIL(<<24334/binary>>),
359    ?FAIL(<<24334344294788947129487129487219847/binary>>),
360    BigInt = id(24334344294788947129487129487219847),
361    ?FAIL_VARS(<<BigInt/binary>>, [{'BigInt',BigInt}]),
362    ?FAIL_VARS(<<42,BigInt/binary>>, [{'BigInt',BigInt}]),
363    ?FAIL_VARS(<<BigInt:2/binary>>, [{'BigInt',BigInt}]),
364
365    %% One negative field size, but the sum of field sizes will be 1 byte.
366    %% Make sure that we reject that properly.
367    I_minus_777 = id(-777),
368    I_minus_2047 = id(-2047),
369    ?FAIL_VARS(<<I_minus_777:2048/unit:8,57:I_minus_2047/unit:8>>,
370		     ordsets:from_list([{'I_minus_777',I_minus_777},
371					{'I_minus_2047',I_minus_2047}])),
372    ?FAIL(<<<<1,2,3>>/float>>),
373
374    %% Negative field widths.
375    testf_1(-8, <<1,2,3,4,5>>),
376    ?FAIL(<<0:(-(1 bsl 100))>>),
377
378    ?FAIL(<<42:(-16)>>),
379    ?FAIL(<<3.14:(-8)/float>>),
380    ?FAIL(<<<<23,56,0,2>>:(-16)/binary>>),
381    ?FAIL(<<<<23,56,0,2>>:(2.5)/binary>>),
382    ?FAIL(<<<<23,56,0,2>>:(anka)>>),
383    ?FAIL(<<<<23,56,0,2>>:(anka)>>),
384
385    %% Unit failures.
386    ?FAIL(<<<<1:1>>/binary>>),
387    Sz = id(1),
388    ?FAIL_VARS(<<<<1:Sz>>/binary>>, [{'Sz',Sz}]),
389    {'EXIT',{badarg,_}} = (catch <<<<1:(id(1))>>/binary>>),
390    ?FAIL(<<<<7,8,9>>/binary-unit:16>>),
391    ?FAIL(<<<<7,8,9,3:7>>/binary-unit:16>>),
392    ?FAIL(<<<<7,8,9,3:7>>/binary-unit:17>>),
393
394    ok.
395
396testf_1(W, B) ->
397    Vars = [{'W',W}],
398    ?FAIL_VARS(<<42:W>>, Vars),
399    ?FAIL_VARS(<<3.14:W/float>>, Vars),
400    ?FAIL_VARS(<<B:W/binary>>, [{'B',B}|Vars]).
401
402%% Test that constructed binaries that are not used will still give an exception.
403not_used(Config) when is_list(Config) ->
404    ok = not_used1(3, <<"dum">>),
405    {'EXIT',{badarg,_}} = (catch not_used1(3, "dum")),
406    {'EXIT',{badarg,_}} = (catch not_used2(444, -2)),
407    {'EXIT',{badarg,_}} = (catch not_used2(444, anka)),
408    {'EXIT',{badarg,_}} = (catch not_used3(444)),
409    ok.
410
411not_used1(I, BinString) ->
412    <<I:32,BinString/binary>>,
413    ok.
414
415not_used2(I, Sz) ->
416    <<I:Sz>>,
417    ok.
418
419not_used3(I) ->
420    <<I:(-8)>>,
421    ok.
422
423in_guard(Config) when is_list(Config) ->
424    1 = in_guard(<<16#74ad:16>>, 16#e95, 5),
425    2 = in_guard(<<16#3A,16#F7,"hello">>, 16#3AF7, <<"hello">>),
426    3 = in_guard(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415),
427    3 = in_guard(<<16#FBCD:14,3/float,3:2>>, 16#FBCD, 3),
428    3 = in_guard(<<16#FBCD:14,(2 bsl 226)/float,3:2>>, 16#FBCD, 2 bsl 226),
429    nope = in_guard(<<1>>, 42, b),
430    nope = in_guard(<<1>>, a, b),
431    nope = in_guard(<<1,2>>, 1, 1),
432    nope = in_guard(<<4,5>>, 1, 2.71),
433    nope = in_guard(<<4,5>>, 1, <<12,13>>),
434    ok.
435
436in_guard(Bin, A, B) when <<A:13,B:3>> == Bin -> 1;
437in_guard(Bin, A, B) when <<A:16,B/binary>> == Bin -> 2;
438in_guard(Bin, A, B) when <<A:14,B/float,3:2>> == Bin -> 3;
439in_guard(Bin, A, B) when {a,b,<<A:14,B/float,3:2>>} == Bin -> cant_happen;
440in_guard(_, _, _) -> nope.
441
442%% Make sure that construction has no memory leak
443mem_leak(Config) when is_list(Config) ->
444    B = make_bin(16, <<0>>),
445    mem_leak(1024, B),
446    ok.
447
448mem_leak(0, _) -> ok;
449mem_leak(N, B) ->
450    big_bin(B, <<23>>),
451    {'EXIT',{badarg,_}} = (catch big_bin(B, bad)),
452    mem_leak(N-1, B).
453
454big_bin(B1, B2) ->
455    <<B1/binary,B1/binary,B1/binary,B1/binary,
456      B1/binary,B1/binary,B1/binary,B1/binary,
457      B1/binary,B1/binary,B1/binary,B1/binary,
458      B1/binary,B1/binary,B1/binary,B1/binary,
459      B2/binary>>.
460
461make_bin(0, Acc) -> Acc;
462make_bin(N, Acc) -> make_bin(N-1, <<Acc/binary,Acc/binary>>).
463
464-define(COF(Int0),
465	(fun(Int) ->
466		 true = <<Int:16/float>> =:= <<(float(Int)):16/float>>,
467		 true = <<Int:32/float>> =:= <<(float(Int)):32/float>>,
468		 true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
469	 end)(nonliteral(Int0)),
470	true = <<Int0:16/float>> =:= <<(float(Int0)):16/float>>,
471	true = <<Int0:32/float>> =:= <<(float(Int0)):32/float>>,
472	true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>).
473
474-define(COF32(Int0),
475	(fun(Int) ->
476		 true = <<Int:32/float>> =:= <<(float(Int)):32/float>>,
477		 true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
478	 end)(nonliteral(Int0)),
479	true = <<Int0:32/float>> =:= <<(float(Int0)):32/float>>,
480	true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>).
481
482-define(COF64(Int0),
483	(fun(Int) ->
484		 true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
485	 end)(nonliteral(Int0)),
486	true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>).
487
488nonliteral(X) -> X.
489
490coerce_to_float(Config) when is_list(Config) ->
491    ?COF(0),
492    ?COF(-1),
493    ?COF(1),
494    ?COF(42),
495    ?COF(255),
496    ?COF(-255),
497    ?COF(38474),
498    ?COF(65504),
499    ?COF(-65504),
500    ?COF32(387498738948729893849444444443),
501    ?COF32(-37489378937773899999999999999993),
502    ?COF64(298748888888888888888888888883478264866528467367364766666666666666663),
503    ?COF64(-367546729879999999999947826486652846736736476555566666663),
504    ok.
505
506bjorn(Config) when is_list(Config) ->
507    error = bjorn_1(),
508    ok.
509
510bjorn_1() ->
511    Bitstr = <<7:13>>,
512    try
513	do_something()
514    catch
515	throw:blurf ->
516	    ignore
517    end,
518    do_more(Bitstr, 13).
519
520do_more(Bin, Sz) ->
521    %% Previous bug in the bs_bits_to_bytes instruction: The exeption code
522    %% was not set - the previous exception (throw:blurf) would be used,
523    %% causing the catch to slip.
524    try <<Bin:Sz/binary>> of
525	_V -> ok
526    catch
527	error:_ ->
528	    error
529    end.
530
531do_something() ->
532    throw(blurf).
533
534append_empty_is_same(Config) when is_list(Config) ->
535    NonWritableBin = <<"123">>,
536    true = erts_debug:same(NonWritableBin, append(NonWritableBin, <<>>)),
537    WritableBin = <<(id(<<>>))/binary,0,1,2,3,4,5,6,7>>,
538    true = erts_debug:same(WritableBin, append(WritableBin, <<>>)),
539    ok.
540
541append(A, B) ->
542    <<A/binary, B/binary>>.
543
544huge_float_field(Config) when is_list(Config) ->
545    {'EXIT',{badarg,_}} = (catch <<0.0:9/float-unit:8>>),
546    huge_float_check(catch <<0.0:67108865/float-unit:64>>),
547    huge_float_check(catch <<0.0:((1 bsl 26)+1)/float-unit:64>>),
548    huge_float_check(catch <<0.0:(id(67108865))/float-unit:64>>),
549%%  huge_float_check(catch <<0.0:((1 bsl 60)+1)/float-unit:64>>),
550    huge_float_check(catch <<3839739387439387383739387987347983:((1 bsl 26)+1)/float-unit:64>>),
551%%  huge_float_check(catch <<3839739387439387383739387987347983:((1 bsl 60)+1)/float-unit:64>>),
552    ok.
553
554huge_float_check({'EXIT',{system_limit,_}}) -> ok;
555huge_float_check({'EXIT',{badarg,_}}) -> ok.
556
557system_limit(Config) when is_list(Config) ->
558    WordSize = erlang:system_info(wordsize),
559    BitsPerWord = WordSize * 8,
560    {'EXIT',{system_limit,_}} =
561	(catch <<0:(id(0)),42:(id(1 bsl BitsPerWord))>>),
562    {'EXIT',{system_limit,_}} =
563	(catch <<42:(id(1 bsl BitsPerWord)),0:(id(0))>>),
564    {'EXIT',{system_limit,_}} =
565	(catch <<(id(<<>>))/binary,0:(id(1 bsl 100))>>),
566
567    %% Would fail to load.
568    {'EXIT',{system_limit,_}} = (catch <<0:(1 bsl 67)>>),
569    {'EXIT',{system_limit,_}} = (catch <<0:((1 bsl 64)+1)>>),
570
571    case WordSize of
572	4 ->
573	    system_limit_32();
574	8 ->
575	    ok
576    end.
577
578system_limit_32() ->
579    {'EXIT',{badarg,_}} = (catch <<42:(-1)>>),
580    {'EXIT',{badarg,_}} = (catch <<42:(id(-1))>>),
581    {'EXIT',{badarg,_}} = (catch <<42:(id(-389739873536870912))/unit:8>>),
582    {'EXIT',{system_limit,_}} = (catch <<42:536870912/unit:8>>),
583    {'EXIT',{system_limit,_}} = (catch <<42:(id(536870912))/unit:8>>),
584    {'EXIT',{system_limit,_}} = (catch <<0:(id(8)),42:536870912/unit:8>>),
585    {'EXIT',{system_limit,_}} = (catch <<0:(id(8)),42:(id(536870912))/unit:8>>),
586
587    %% The size would be silently truncated, resulting in a crash.
588    {'EXIT',{system_limit,_}} = (catch <<0:(1 bsl 35)>>),
589    {'EXIT',{system_limit,_}} = (catch <<0:((1 bsl 32)+1)>>),
590
591    %% Would fail to load.
592    {'EXIT',{system_limit,_}} = (catch <<0:(1 bsl 43)>>),
593    {'EXIT',{system_limit,_}} = (catch <<0:((1 bsl 40)+1)>>),
594    ok.
595
596badarg(Config) when is_list(Config) ->
597    <<3:2>> = <<1:(id(1)),1:(id(1))>>,
598    {'EXIT',{badarg,_}} = (catch <<0:(id(1)),0:(id(-1))>>),
599    {'EXIT',{badarg,_}} = (catch <<0:(id(1)),0:(id(-(1 bsl 70)))>>),
600    {'EXIT',{badarg,_}} = (catch <<0:(id(-(1 bsl 70))),0:(id(1))>>),
601    {'EXIT',{badarg,_}} = (catch <<(id(<<>>))/binary,0:(id(-(1)))>>),
602    ok.
603
604copy_writable_binary(Config) when is_list(Config) ->
605    [copy_writable_binary_1(I) || I <- lists:seq(0, 256)],
606    ok.
607
608copy_writable_binary_1(_) ->
609    Bin0 = <<(id(<<>>))/binary,0,1,2,3,4,5,6,7>>,
610    SubBin = make_sub_bin(Bin0),
611    id(<<42,34,55,Bin0/binary>>),		%Make reallocation likelier.
612    Pid = spawn(fun() ->
613			      copy_writable_binary_holder(Bin0, SubBin)
614		      end),
615    Tab = ets:new(holder, []),
616    ets:insert(Tab, {17,Bin0}),
617    ets:insert(Tab, {42,SubBin}),
618    id(<<Bin0/binary,0:(64*1024*8)>>),
619    Pid ! self(),
620    [{17,Bin0}] = ets:lookup(Tab, 17),
621    [{42,Bin0}] = ets:lookup(Tab, 42),
622    receive
623	{Pid,Bin0,Bin0} -> ok;
624	Other ->
625	    ct:fail("Unexpected message: ~p", [Other])
626    end,
627    ok.
628
629copy_writable_binary_holder(Bin, SubBin) ->
630    receive
631	Pid ->
632	    Pid ! {self(),Bin,SubBin}
633    end.
634
635make_sub_bin(Bin0) ->
636    N = bit_size(Bin0),
637    <<_:17,Bin:N/bitstring,_:5>> = <<(-1):17,Bin0/bitstring,(-1):5>>,
638    Bin = Bin0,					%Assertion.
639    Bin.
640
641%% Make sure that bit syntax expression with huge field size are
642%% not constructed at compile time.
643
644kostis(Config) when is_list(Config) ->
645    case have_250_terabytes_of_ram() of
646	true ->
647	    Bin = <<0:800000000000>>,
648	    EmbeddedBin = <<0,(<<0:99999999999>>)/bitstring,1>>,
649	    Bin0 = list_to_binary([Bin,Bin,Bin,Bin,Bin]),
650	    Bin1 = list_to_binary([Bin0,Bin0,Bin0,Bin0,Bin0,Bin0]),
651	    Bin2 = list_to_binary([Bin1,Bin1]),
652	    id({EmbeddedBin,Bin0,Bin1,Bin2});
653	false ->
654	    ok
655    end.
656
657%% I'm not even certain how much 250 TB really is...
658%% but I'm sure I don't have it :-)
659
660have_250_terabytes_of_ram() -> false.
661
662%% Test that different ways of using bit syntax instructions
663%% give the same result.
664
665dynamic(Config) when is_list(Config) ->
666    dynamic_1(fun dynamic_big/5),
667    dynamic_1(fun dynamic_little/5),
668    ok.
669
670dynamic_1(Dynamic) ->
671    <<Lpad:128>> = erlang:md5([0]),
672    <<Rpad:128>> = erlang:md5([1]),
673    <<Int:128>> = erlang:md5([2]),
674    8385 = dynamic_2(0, {Int,Lpad,Rpad,Dynamic}, 0).
675
676dynamic_2(129, _, Count) -> Count;
677dynamic_2(Bef, Data, Count0) ->
678    Count = dynamic_3(Bef, 128-Bef, Data, Count0),
679    dynamic_2(Bef+1, Data, Count).
680
681dynamic_3(_, -1, _, Count) -> Count;
682dynamic_3(Bef, N, {Int0,Lpad,Rpad,Dynamic}=Data, Count) ->
683    Int1 = Int0 band ((1 bsl (N+3))-1),
684    Dynamic(Bef, N, Int1, Lpad, Rpad),
685    Dynamic(Bef, N, -Int1, Lpad, Rpad),
686
687    %% OTP-7085: Test a small number in a wide field.
688    Int2 = Int0 band 16#FFFFFF,
689    Dynamic(Bef, N, Int2, Lpad, Rpad),
690    Dynamic(Bef, N, -Int2, Lpad, Rpad),
691    dynamic_3(Bef, N-1, Data, Count+1).
692
693dynamic_big(Bef, N, Int, Lpad, Rpad) ->
694    NumBin = id(<<Int:N>>),
695    MaskedInt = Int band ((1 bsl N) - 1),
696    <<MaskedInt:N>> = NumBin,
697
698    %% Construct the binary in two different ways.
699    Bin = id(<<Lpad:Bef,NumBin/bitstring,Rpad:(128-Bef-N)>>),
700    Bin = <<Lpad:Bef,Int:N,Rpad:(128-Bef-N)>>,
701
702    %% Further verify the result by matching.
703    LpadMasked = Lpad band ((1 bsl Bef) - 1),
704    RpadMasked = Rpad band ((1 bsl (128-Bef-N)) - 1),
705    Rbits = (128-Bef-N),
706    <<LpadMasked:Bef,MaskedInt:N,RpadMasked:Rbits>> = id(Bin),
707    ok.
708
709dynamic_little(Bef, N, Int, Lpad, Rpad) ->
710    NumBin = id(<<Int:N/little>>),
711    MaskedInt = Int band ((1 bsl N) - 1),
712    <<MaskedInt:N/little>> = NumBin,
713
714    %% Construct the binary in two different ways.
715    Bin = id(<<Lpad:Bef/little,NumBin/bitstring,Rpad:(128-Bef-N)/little>>),
716    Bin = <<Lpad:Bef/little,Int:N/little,Rpad:(128-Bef-N)/little>>,
717
718    %% Further verify the result by matching.
719    LpadMasked = Lpad band ((1 bsl Bef) - 1),
720    RpadMasked = Rpad band ((1 bsl (128-Bef-N)) - 1),
721    Rbits = (128-Bef-N),
722    <<LpadMasked:Bef/little,MaskedInt:N/little,RpadMasked:Rbits/little>> = id(Bin),
723    ok.
724
725%% Test that the bs_add/5 instruction handles big numbers correctly.
726bs_add(Config) when is_list(Config) ->
727    Mod = bs_construct_bs_add,
728    N = 2000,
729    Code = [{module, Mod},
730	    {exports, [{bs_add,2}]},
731	    {labels, 2},
732
733	    %% bs_add(Number, -SmallestBig) -> Number + N
734	    {function, bs_add, 2, 2},
735	    {label,1},
736	    {func_info,{atom,Mod},{atom,bs_add},2},
737
738	    {label,2},
739	    {move,{x,0},{x,2}}] ++
740	lists:duplicate(N-1, {bs_add,{f,0},[{x,2},{integer,1},1],{x,2}}) ++
741	[{gc_bif,abs,{f,0},3,[{x,1}],{x,4}},	%Force GC, ignore result.
742	 {gc_bif,'+',{f,0},3,[{x,2},{integer,1}],{x,0}}, %Safe result in {x,0}
743	 return],
744
745    %% Write assembly file and assemble it.
746    PrivDir = proplists:get_value(priv_dir, Config),
747    RootName = filename:join(PrivDir, atom_to_list(Mod)),
748    AsmFile = RootName ++ ".S",
749    {ok,Fd} = file:open(AsmFile, [write]),
750    [io:format(Fd, "~p. \n", [T]) || T <- Code],
751    ok = file:close(Fd),
752    {ok,Mod} = compile:file(AsmFile, [from_asm,report,{outdir,PrivDir}]),
753    LoadRc = code:load_abs(RootName),
754    {module,_Module} = LoadRc,
755
756    %% Find smallest positive bignum.
757    SmallestBig = smallest_big(),
758    io:format("~p\n", [SmallestBig]),
759    DoTest = fun() ->
760		     exit(Mod:bs_add(SmallestBig, -SmallestBig))
761	     end,
762    {Pid,Mref} = spawn_monitor(DoTest),
763    receive
764	{'DOWN',Mref,process,Pid,Res} -> ok
765    end,
766
767    case erlang:system_info(wordsize) of
768        8 ->
769            %% bignum-sized binaries must system_limit on 64-bit platforms
770            {system_limit, _} = Res;
771        4 ->
772            Res = SmallestBig + N
773    end,
774
775    %% Clean up.
776    ok = file:delete(AsmFile),
777    ok = file:delete(code:which(Mod)),
778    ok.
779
780
781smallest_big() ->
782    smallest_big_1(1 bsl 24).
783
784smallest_big_1(N) ->
785    case erts_debug:flat_size(N) of
786	0 -> smallest_big_1(N+N);
787	_  -> N
788    end.
789
790otp_7422(Config) when is_list(Config) ->
791    otp_7422_int(0),
792    otp_7422_bin(0).
793
794otp_7422_int(N) when N < 512 ->
795    T = erlang:make_tuple(N, []),
796    spawn_link(fun() ->
797		       id(T),
798		       %% A size of field 0 would write one byte beyond
799		       %% the current position in the binary. It could
800		       %% overwrite the continuation pointer stored on
801		       %% the stack if HTOP was equal to E (the stack pointer).
802		       id(<<0:(id(0))>>)
803	       end),
804    otp_7422_int(N+1);
805otp_7422_int(_) -> ok.
806
807otp_7422_bin(N) when N < 512 ->
808    T = erlang:make_tuple(N, []),
809    Z = id(<<>>),
810    spawn_link(fun() ->
811		       id(T),
812		       id(<<Z:(id(0))/bits>>)
813	       end),
814    otp_7422_bin(N+1);
815otp_7422_bin(_) -> ok.
816
817zero_width(Config) when is_list(Config) ->
818    Z = id(0),
819    Small = id(42),
820    Big = id(1 bsl 128),
821    <<>> = <<Small:Z>>,
822    <<>> = <<Small:0>>,
823    <<>> = <<Big:Z>>,
824    <<>> = <<Big:0>>,
825
826    {'EXIT',{badarg,_}} = (catch <<not_a_number:0>>),
827    {'EXIT',{badarg,_}} = (catch <<(id(not_a_number)):Z>>),
828    {'EXIT',{badarg,_}} = (catch <<(id(not_a_number)):0>>),
829
830    ok.
831
832bad_append(_) ->
833    do_bad_append(<<127:1>>, fun append_unit_3/1),
834    do_bad_append(<<127:2>>, fun append_unit_3/1),
835    do_bad_append(<<127:17>>, fun append_unit_3/1),
836
837    do_bad_append(<<127:3>>, fun append_unit_4/1),
838    do_bad_append(<<127:5>>, fun append_unit_4/1),
839    do_bad_append(<<127:7>>, fun append_unit_4/1),
840    do_bad_append(<<127:199>>, fun append_unit_4/1),
841
842    do_bad_append(<<127:7>>, fun append_unit_8/1),
843    do_bad_append(<<127:9>>, fun append_unit_8/1),
844
845    do_bad_append(<<0:8>>, fun append_unit_16/1),
846    do_bad_append(<<0:15>>, fun append_unit_16/1),
847    do_bad_append(<<0:17>>, fun append_unit_16/1),
848    ok.
849
850do_bad_append(Bin0, Appender) ->
851    {'EXIT',{badarg,_}} = (catch Appender(Bin0)),
852
853    Bin1 = id(<<0:3,Bin0/bitstring>>),
854    <<_:3,Bin2/bitstring>> = Bin1,
855    {'EXIT',{badarg,_}} = (catch Appender(Bin2)),
856
857    %% Create a writable binary.
858    Empty = id(<<>>),
859    Bin3 = <<Empty/bitstring,Bin0/bitstring>>,
860    {'EXIT',{badarg,_}} = (catch Appender(Bin3)),
861    ok.
862
863append_unit_3(Bin) ->
864    <<Bin/binary-unit:3,0:1>>.
865
866append_unit_4(Bin) ->
867    <<Bin/binary-unit:4,0:1>>.
868
869append_unit_8(Bin) ->
870    <<Bin/binary,0:1>>.
871
872append_unit_16(Bin) ->
873    <<Bin/binary-unit:16,0:1>>.
874
875%% Test that the bs_append instruction will correctly check for
876%% overflow by producing a binary whose total size would exceed the
877%% maximum allowed size for a binary on a 32-bit computer.
878
879bs_append_overflow(_Config) ->
880    Memsize = memsize(),
881    io:format("Memsize = ~w Bytes~n", [Memsize]),
882    case erlang:system_info(wordsize) of
883	8 ->
884            %% Not possible to test on a 64-bit computer.
885	    {skip, "64-bit architecture"};
886        _ when Memsize < (2 bsl 30) ->
887	    {skip, "Less than 2 GB of memory"};
888	4 ->
889            {'EXIT', {system_limit, _}} = (catch bs_append_overflow_signed()),
890            erlang:garbage_collect(),
891            {'EXIT', {system_limit, _}} = (catch bs_append_overflow_unsigned()),
892            erlang:garbage_collect(),
893	    ok
894    end.
895
896bs_append_overflow_signed() ->
897    %% Produce a large binary that, if cast to signed int, would
898    %% overflow into a negative number that fits a smallnum.
899    Large = <<0:((1 bsl 30)-1)>>,
900    <<Large/bits, Large/bits, Large/bits, Large/bits,
901      Large/bits, Large/bits, Large/bits, Large/bits,
902      Large/bits>>.
903
904bs_append_overflow_unsigned() ->
905    %% The following would succeed but would produce an incorrect result
906    %% where B =:= C!
907    A = <<0:((1 bsl 32)-8)>>,
908    B = <<2, 3>>,
909    C = <<A/binary,1,B/binary>>,
910    true = byte_size(B) < byte_size(C).
911
912reductions(_Config) ->
913    TwoMeg = <<0:(2_000*1024)/unit:8>>,
914    reds_at_least(2000, fun() -> <<0:8,TwoMeg/binary>> end),
915    reds_at_least(4000, fun() -> <<0:8,TwoMeg/binary,TwoMeg/binary>> end),
916    reds_at_least(1000, fun() -> <<0:8,TwoMeg:(1000*1024)/binary>> end),
917
918    %% Here we expect about 500 reductions in the bs_append
919    %% instruction for setting up a writable binary and about 2000
920    %% reductions in the bs_put_binary instruction for copying the
921    %% binary data.
922    reds_at_least(2500, fun() -> <<TwoMeg/binary,TwoMeg:(2000*1024)/binary>> end),
923    ok.
924
925reds_at_least(N, Fun) ->
926    receive after 1 -> ok end,
927    {reductions,Red0} = process_info(self(), reductions),
928    _ = Fun(),
929    {reductions,Red1} = process_info(self(), reductions),
930    Diff = Red1 - Red0,
931    io:format("Expected at least ~p; got ~p\n", [N,Diff]),
932    if
933        Diff >= N ->
934            ok;
935        Diff ->
936            ct:fail({expected,N,got,Diff})
937    end.
938
939id(I) -> I.
940
941memsize() ->
942    application:ensure_all_started(os_mon),
943    {Tot,_Used,_}  = memsup:get_memory_data(),
944    Tot.
945
946-define(FP16(EncodedInt, Float),
947        (fun(NlInt, NlFloat) ->
948                 {0, true} = {0, <<NlInt:16>> =:= <<NlFloat:16/float>>},
949                 {1, true} = {1, <<(NlInt+16#8000):16>> =:= <<-NlFloat:16/float>>},
950                 {2, true} = {2, <<NlInt:16/little>> =:= <<NlFloat:16/float-little>>},
951                 {3, true} = {3, <<(NlInt+16#8000):16/little>> =:= <<-NlFloat:16/float-little>>},
952                 {4, true} = {4, <<NlInt:16/native>> =:= <<NlFloat:16/float-native>>},
953                 {5, true} = {5, <<(NlInt+16#8000):16/native>> =:= <<-NlFloat:16/float-native>>}
954         end)(nonliteral(EncodedInt), nonliteral(Float)),
955        {a, true} = {a, <<EncodedInt:16>> =:= <<Float:16/float>>},
956        {b, true} = {b, <<(EncodedInt+16#8000):16>> =:= <<-Float:16/float>>},
957        {c, true} = {c, <<EncodedInt:16/little>> =:= <<Float:16/float-little>>},
958        {d, true} = {d, <<(EncodedInt+16#8000):16/little>> =:= <<-Float:16/float-little>>},
959        {e, true} = {e, <<EncodedInt:16/native>> =:= <<Float:16/float-native>>},
960        {f, true} = {f, <<(EncodedInt+16#8000):16/native>> =:= <<-Float:16/float-native>>}).
961
962fp16(_Config) ->
963    %% smallest positive subnormal number
964    ?FP16(16#0001, 0.000000059604645),
965    %% largest positive subnormal number
966    ?FP16(16#03ff, 0.000060975552),
967    %% smallest positive normal number
968    ?FP16(16#0400, 0.00006103515625),
969    %% largest normal number
970    ?FP16(16#7bff, 65504),
971    ?FP16(16#7bff, 65504.0),
972    %% largest number less than one
973    ?FP16(16#3bff, 0.99951172),
974    %% zero
975    ?FP16(16#0000, 0.0),
976    %% one
977    ?FP16(16#3c00, 1),
978    ?FP16(16#3c00, 1.0),
979    %% smallest number larger than one
980    ?FP16(16#3c01, 1.00097656),
981    %% rounding of 1/3 to nearest
982    ?FP16(16#3555, 0.33325195),
983    %% others
984    ?FP16(16#4000, 2),
985    ?FP16(16#4000, 2.0),
986    ok.
987