aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/c_SUITE.erl53
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl41
-rw-r--r--lib/stdlib/test/shell_SUITE.erl50
3 files changed, 134 insertions, 10 deletions
diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl
index 4bd32a30f8..f01988478c 100644
--- a/lib/stdlib/test/c_SUITE.erl
+++ b/lib/stdlib/test/c_SUITE.erl
@@ -21,7 +21,9 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2]).
-export([c_1/1, c_2/1, c_3/1, c_4/1, nc_1/1, nc_2/1, nc_3/1, nc_4/1,
- ls/1, memory/1]).
+ c_default_outdir_1/1, c_default_outdir_2/1,
+ nc_default_outdir_1/1, nc_default_outdir_2/1,
+ ls/1, memory/1]).
-include_lib("common_test/include/ct.hrl").
@@ -30,7 +32,10 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [c_1, c_2, c_3, c_4, nc_1, nc_2, nc_3, nc_4, ls, memory].
+ [c_1, c_2, c_3, c_4, nc_1, nc_2, nc_3, nc_4,
+ c_default_outdir_1, c_default_outdir_2,
+ nc_default_outdir_1, nc_default_outdir_2,
+ ls, memory].
groups() ->
[].
@@ -124,6 +129,50 @@ nc_4(Config) when is_list(Config) ->
Result = nc(R,[{outdir,W}]),
{ok, m} = Result.
+c_default_outdir_1(Config) ->
+ R = filename:join(proplists:get_value(data_dir, Config), "m.erl"),
+ W = proplists:get_value(priv_dir, Config),
+ file:set_cwd(W),
+ Obj = "m" ++ code:objfile_extension(),
+ _ = file:delete(Obj),
+ false = filelib:is_file(Obj),
+ Result = c:c(R),
+ {ok, m} = Result,
+ true = filelib:is_file(Obj).
+
+c_default_outdir_2(Config) ->
+ R = filename:join(proplists:get_value(data_dir, Config), "m"),
+ W = proplists:get_value(priv_dir, Config),
+ file:set_cwd(W),
+ Obj = "m" ++ code:objfile_extension(),
+ _ = file:delete(Obj),
+ false = filelib:is_file(Obj),
+ Result = c:c(R),
+ {ok, m} = Result,
+ true = filelib:is_file(Obj).
+
+nc_default_outdir_1(Config) ->
+ R = filename:join(proplists:get_value(data_dir, Config), "m.erl"),
+ W = proplists:get_value(priv_dir, Config),
+ file:set_cwd(W),
+ Obj = "m" ++ code:objfile_extension(),
+ _ = file:delete(Obj),
+ false = filelib:is_file(Obj),
+ Result = c:nc(R),
+ {ok, m} = Result,
+ true = filelib:is_file(Obj).
+
+nc_default_outdir_2(Config) ->
+ R = filename:join(proplists:get_value(data_dir, Config), "m"),
+ W = proplists:get_value(priv_dir, Config),
+ file:set_cwd(W),
+ Obj = "m" ++ code:objfile_extension(),
+ _ = file:delete(Obj),
+ false = filelib:is_file(Obj),
+ Result = c:nc(R),
+ {ok, m} = Result,
+ true = filelib:is_file(Obj).
+
ls(Config) when is_list(Config) ->
Directory = proplists:get_value(data_dir, Config),
ok = c:ls(Directory),
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 029e6286e4..c4fafe82a4 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -28,7 +28,7 @@
init_per_group/2,end_per_group/2,
crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1,
spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, '\x{447}'/0,
- hibernate/1, stop/1, t_format/1]).
+ hibernate/1, stop/1, t_format/1, t_format_arbitrary/1]).
-export([ otp_6345/1, init_dont_hang/1]).
-export([hib_loop/1, awaken/1]).
@@ -51,7 +51,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[crash, stacktrace, {group, sync_start}, spawn_opt, hibernate,
- {group, tickets}, stop, t_format].
+ {group, tickets}, stop, t_format, t_format_arbitrary].
groups() ->
[{tickets, [], [otp_6345, init_dont_hang]},
@@ -78,6 +78,14 @@ end_per_group(_GroupName, Config) ->
%% synchronous, and we want to test that the crash report is ok.
%%-----------------------------------------------------------------
crash(Config) when is_list(Config) ->
+ ok = application:unset_env(kernel, error_logger_format_depth),
+ crash_1(Config),
+ ok = application:set_env(kernel, error_logger_format_depth, 30),
+ crash_1(Config),
+ ok = application:unset_env(kernel, error_logger_format_depth),
+ ok.
+
+crash_1(_Config) ->
error_logger:add_report_handler(?MODULE, self()),
%% Make sure that we don't get a crash report if a process
@@ -562,9 +570,32 @@ t_format() ->
ok.
+t_format_arbitrary(_Config) ->
+ error_logger:tty(false),
+ try
+ t_format_arbitrary()
+ after
+ error_logger:tty(true)
+ end,
+ ok.
+
+t_format_arbitrary() ->
+ A = list_to_atom([1024]),
+ do_test_format([fake_report, A], unlimited),
+ do_test_format([fake_report, A], 20),
+
+ do_test_format([fake_report, foo], unlimited),
+ do_test_format([fake_report, foo], 20),
+ do_test_format([fake_report, []], unlimited),
+ do_test_format([fake_report, []], 20).
+
do_test_format(Report, Depth) ->
- io:format("*** Depth = ~p", [Depth]),
- S0 = proc_lib:format(Report, latin1, Depth),
+ do_test_format(Report, latin1, Depth),
+ do_test_format(Report, unicode, Depth).
+
+do_test_format(Report, Encoding, Depth) ->
+ io:format("*** Depth = ~p, Encoding = ~p", [Depth, Encoding]),
+ S0 = proc_lib:format(Report, Encoding, Depth),
S = lists:flatten(S0),
io:put_chars(S),
length(S).
@@ -584,7 +615,7 @@ init(Tester) ->
{ok, Tester}.
handle_event({error_report, _GL, {Pid, crash_report, Report}}, Tester) ->
- io:format("~s\n", [proc_lib:format(Report)]),
+ io:format("~ts\n", [proc_lib:format(Report)]),
Tester ! {crash_report, Pid, Report},
{ok, Tester};
handle_event(_Event, State) ->
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 4f0fdc4c6a..217e8cc252 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -31,7 +31,7 @@
progex_lc/1, progex_funs/1,
otp_5990/1, otp_6166/1, otp_6554/1,
otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1, otp_13719/1,
- otp_14285/1, otp_14296/1]).
+ otp_14285/1, otp_14296/1, typed_records/1]).
-export([ start_restricted_from_shell/1,
start_restricted_on_command_line/1,restricted_local/1]).
@@ -74,10 +74,10 @@ suite() ->
{timetrap,{minutes,10}}].
all() ->
- [forget, records, known_bugs, otp_5226, otp_5327,
+ [forget, known_bugs, otp_5226, otp_5327,
otp_5435, otp_5195, otp_5915, otp_5916, {group, bits},
{group, refman}, {group, progex}, {group, tickets},
- {group, restricted}].
+ {group, restricted}, {group, records}].
groups() ->
[{restricted, [],
@@ -86,6 +86,8 @@ groups() ->
{bits, [],
[bs_match_misc_SUITE, bs_match_tail_SUITE,
bs_match_bin_SUITE, bs_construct_SUITE]},
+ {records, [],
+ [records, typed_records]},
{refman, [], [refman_bit_syntax]},
{progex, [],
[progex_bit_syntax, progex_records, progex_lc,
@@ -486,6 +488,48 @@ records(Config) when is_list(Config) ->
ok.
+%% Test of typed record support.
+typed_records(Config) when is_list(Config) ->
+ Test = filename:join(proplists:get_value(priv_dir, Config), "test.hrl"),
+ Contents = <<"-module(test).
+ -record(r0,{f :: any()}).
+ -record(r1,{f1 :: #r1{} | undefined, f2 :: #r0{} | atom()}).
+ -record(r2,{f :: #r2{} | undefined}).
+ ">>,
+ ok = file:write_file(Test, Contents),
+
+ RR1 = "rr(\"" ++ Test ++ "\"),
+ #r1{} = (#r1{f1=#r1{f1=undefined, f2=x}, f2 = #r0{}})#r1.f1,
+ ok.",
+ RR2 = "rr(\"" ++ Test ++ "\"),
+ #r0{} = (#r1{f1=#r1{f1=undefined, f2=x}, f2 = #r0{}})#r1.f2,
+ ok. ",
+ RR3 = "rr(\"" ++ Test ++ "\"),
+ #r1{f2=#r0{}} = (#r1{f1=#r1{f1=undefined, f2=#r0{}}, f2 = x})#r1.f1,
+ ok.",
+ RR4 = "rr(\"" ++ Test ++ "\"),
+ (#r1{f2 = #r0{}})#r1{f2 = x},
+ ok. ",
+ RR5 = "rr(\"" ++ Test ++ "\"),
+ (#r1{f2 = #r0{}})#r1{f1 = #r1{}},
+ ok. ",
+ RR6 = "rr(\"" ++ Test ++ "\"),
+ (#r2{f=#r2{f=undefined}})#r2.f,
+ ok.",
+ RR7 = "rr(\"" ++ Test ++ "\"),
+ #r2{} = (#r2{f=#r2{f=undefined}})#r2.f,
+ ok.",
+ [ok] = scan(RR1),
+ [ok] = scan(RR2),
+ [ok] = scan(RR3),
+ [ok] = scan(RR4),
+ [ok] = scan(RR5),
+ [ok] = scan(RR6),
+ [ok] = scan(RR7),
+
+ file:delete(Test),
+ ok.
+
%% Known bugs.
known_bugs(Config) when is_list(Config) ->
%% erl_eval:merge_bindings/2 cannot handle _removal_ of bindings.