aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/random_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/random_SUITE.erl')
-rw-r--r--lib/stdlib/test/random_SUITE.erl100
1 files changed, 44 insertions, 56 deletions
diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl
index 701a3e3f33..34b350e132 100644
--- a/lib/stdlib/test/random_SUITE.erl
+++ b/lib/stdlib/test/random_SUITE.erl
@@ -19,26 +19,23 @@
-module(random_SUITE).
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_testcase/2, end_per_testcase/2,
init_per_group/2,end_per_group/2]).
-export([interval_1/1, seed0/1, seed/1]).
--export([init_per_testcase/2, end_per_testcase/2]).
-include_lib("common_test/include/ct.hrl").
-% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
-
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
- [{watchdog, Dog} | Config].
-end_per_testcase(_Case, Config) ->
- Dog = ?config(watchdog, Config),
- test_server:timetrap_cancel(Dog),
+ Config.
+
+end_per_testcase(_Case, _Config) ->
ok.
-suite() -> [{ct_hooks,[ts_install_cth]}].
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
all() ->
[interval_1, seed0, seed].
@@ -59,59 +56,50 @@ end_per_group(_GroupName, Config) ->
Config.
-seed0(doc) ->
- ["Test that seed is set implicitly, and always the same."];
-seed0(suite) ->
- [];
+%% Test that seed is set implicitly, and always the same.
seed0(Config) when is_list(Config) ->
- ?line Self = self(),
- ?line _ = spawn(fun() -> Self ! random:uniform() end),
- ?line F1 = receive
- Fa -> Fa
- end,
- ?line _ = spawn(fun() -> random:seed(),
- Self ! random:uniform() end),
- ?line F2 = receive
- Fb -> Fb
- end,
- ?line F1 = F2,
+ Self = self(),
+ _ = spawn(fun() -> Self ! random:uniform() end),
+ F1 = receive
+ Fa -> Fa
+ end,
+ _ = spawn(fun() -> random:seed(),
+ Self ! random:uniform() end),
+ F2 = receive
+ Fb -> Fb
+ end,
+ F1 = F2,
ok.
-seed(doc) ->
- ["Test that seed/1 and seed/3 is equivalent."];
-seed(suite) ->
- [];
+%% Test that seed/1 and seed/3 are equivalent.
seed(Config) when is_list(Config) ->
- ?line Self = self(),
+ Self = self(),
Seed = {S1, S2, S3} = erlang:timestamp(),
- ?line _ = spawn(fun() ->
- random:seed(S1,S2,S3),
- Rands = lists:foldl(fun
- (_, Out) -> [random:uniform(10000)|Out]
- end, [], lists:seq(1,100)),
- Self ! {seed_test, Rands}
- end),
- ?line Rands1 = receive {seed_test, R1s} -> R1s end,
- ?line _ = spawn(fun() ->
- random:seed(Seed),
- Rands = lists:foldl(fun
- (_, Out) -> [random:uniform(10000)|Out]
- end, [], lists:seq(1,100)),
- Self ! {seed_test, Rands}
- end),
- ?line Rands2 = receive {seed_test, R2s} -> R2s end,
- ?line Rands1 = Rands2,
+ _ = spawn(fun() ->
+ random:seed(S1,S2,S3),
+ Rands = lists:foldl(fun
+ (_, Out) -> [random:uniform(10000)|Out]
+ end, [], lists:seq(1,100)),
+ Self ! {seed_test, Rands}
+ end),
+ Rands1 = receive {seed_test, R1s} -> R1s end,
+ _ = spawn(fun() ->
+ random:seed(Seed),
+ Rands = lists:foldl(fun
+ (_, Out) -> [random:uniform(10000)|Out]
+ end, [], lists:seq(1,100)),
+ Self ! {seed_test, Rands}
+ end),
+ Rands2 = receive {seed_test, R2s} -> R2s end,
+ Rands1 = Rands2,
ok.
-interval_1(doc) ->
- ["Check that uniform/1 returns values within the proper interval."];
-interval_1(suite) ->
- [];
+%% Check that uniform/1 returns values within the proper interval.
interval_1(Config) when is_list(Config) ->
- ?line Top = 7,
- ?line N = 10,
- ?line check_interval(N, Top),
+ Top = 7,
+ N = 10,
+ check_interval(N, Top),
ok.
check_interval(0, _) -> ok;
@@ -119,9 +107,9 @@ check_interval(N, Top) ->
X = random:uniform(Top),
if
X < 1 ->
- test_server:fail(too_small);
+ ct:fail(too_small);
X > Top ->
- test_server:fail(too_large);
+ ct:fail(too_large);
true ->
ok
end,