aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/stdlib_bench_SUITE.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2017-11-30 16:09:26 +0100
committerHans Bolinder <[email protected]>2017-11-30 16:30:53 +0100
commit7530b72480eb68cc9a5d700ee7f22c5069b61514 (patch)
treea80092a6918d5f28547c9a2578d33625f63d9a08 /lib/stdlib/test/stdlib_bench_SUITE.erl
parent2ead5d429fe87ffedf0134d918c3b404e9fa70fe (diff)
downloadotp-7530b72480eb68cc9a5d700ee7f22c5069b61514.tar.gz
otp-7530b72480eb68cc9a5d700ee7f22c5069b61514.tar.bz2
otp-7530b72480eb68cc9a5d700ee7f22c5069b61514.zip
stdlib: Add base64 benchmarks
Diffstat (limited to 'lib/stdlib/test/stdlib_bench_SUITE.erl')
-rw-r--r--lib/stdlib/test/stdlib_bench_SUITE.erl107
1 files changed, 104 insertions, 3 deletions
diff --git a/lib/stdlib/test/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl
index 8670e7029c..2a9981bb9e 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2012-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2012-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -28,13 +28,20 @@ suite() -> [{ct_hooks,[{ts_install_cth,[{nodenames,2}]}]}].
all() ->
- [{group,unicode}].
+ [{group,unicode}, {group,base64}].
groups() ->
[{unicode,[{repeat,5}],
[norm_nfc_list, norm_nfc_deep_l, norm_nfc_binary,
string_lexemes_list, string_lexemes_binary
- ]}].
+ ]},
+ {base64,[{repeat,5}],
+ [decode_binary, decode_binary_to_string,
+ decode_list, decode_list_to_string,
+ encode_binary, encode_binary_to_string,
+ encode_list, encode_list_to_string,
+ mime_binary_decode, mime_binary_decode_to_string,
+ mime_list_decode, mime_list_decode_to_string]}].
init_per_group(_GroupName, Config) ->
Config.
@@ -105,3 +112,97 @@ norm_data(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+decode_binary(_Config) ->
+ test(decode, encoded_binary()).
+
+decode_binary_to_string(_Config) ->
+ test(decode_to_string, encoded_binary()).
+
+decode_list(_Config) ->
+ test(decode, encoded_list()).
+
+decode_list_to_string(_Config) ->
+ test(decode_to_string, encoded_list()).
+
+encode_binary(_Config) ->
+ test(encode, binary()).
+
+encode_binary_to_string(_Config) ->
+ test(encode_to_string, binary()).
+
+encode_list(_Config) ->
+ test(encode, list()).
+
+encode_list_to_string(_Config) ->
+ test(encode_to_string, list()).
+
+mime_binary_decode(_Config) ->
+ test(mime_decode, encoded_binary()).
+
+mime_binary_decode_to_string(_Config) ->
+ test(mime_decode_to_string, encoded_binary()).
+
+mime_list_decode(_Config) ->
+ test(mime_decode, encoded_list()).
+
+mime_list_decode_to_string(_Config) ->
+ test(mime_decode_to_string, encoded_list()).
+
+-define(SIZE, 10000).
+-define(N, 1000).
+
+encoded_binary() ->
+ list_to_binary(encoded_list()).
+
+encoded_list() ->
+ L = random_byte_list(round(?SIZE*0.75)),
+ base64:encode_to_string(L).
+
+binary() ->
+ list_to_binary(list()).
+
+list() ->
+ random_byte_list(?SIZE).
+
+test(Func, Data) ->
+ F = fun() -> loop(?N, Func, Data) end,
+ {Time, ok} = timer:tc(fun() -> lspawn(F) end),
+ report_base64(Time).
+
+loop(0, _F, _D) -> garbage_collect(), ok;
+loop(N, F, D) ->
+ _ = base64:F(D),
+ loop(N - 1, F, D).
+
+lspawn(Fun) ->
+ {Pid, Ref} = spawn_monitor(fun() -> exit(Fun()) end),
+ receive
+ {'DOWN', Ref, process, Pid, Rep} -> Rep
+ end.
+
+report_base64(Time) ->
+ Tps = round((?N*1000000)/Time),
+ ct_event:notify(#event{name = benchmark_data,
+ data = [{suite, "stdlib_base64"},
+ {value, Tps}]}),
+ Tps.
+
+%% Copied from base64_SUITE.erl.
+
+random_byte_list(N) ->
+ random_byte_list(N, []).
+
+random_byte_list(0, Acc) ->
+ Acc;
+random_byte_list(N, Acc) ->
+ random_byte_list(N-1, [rand:uniform(255)|Acc]).
+
+make_big_binary(N) ->
+ list_to_binary(mbb(N, [])).
+
+mbb(N, Acc) when N > 256 ->
+ B = list_to_binary(lists:seq(0, 255)),
+ mbb(N - 256, [B | Acc]);
+mbb(N, Acc) ->
+ B = list_to_binary(lists:seq(0, N-1)),
+ lists:reverse(Acc, B).