aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2016-03-02 06:50:54 +0100
committerBjörn Gustavsson <[email protected]>2016-03-09 13:22:59 +0100
commit33b414783b37dc0c242c729fa3fa843cd648e3e0 (patch)
tree7d4f40be30fca15fa09efdc89334246f4a0c7da9 /lib/stdlib/test
parent477f490820a28e479527e93d420f26ea23fdf3e3 (diff)
downloadotp-33b414783b37dc0c242c729fa3fa843cd648e3e0.tar.gz
otp-33b414783b37dc0c242c729fa3fa843cd648e3e0.tar.bz2
otp-33b414783b37dc0c242c729fa3fa843cd648e3e0.zip
Remove ?line macros
While we are it, also re-ident the files.
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/array_SUITE.erl12
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl688
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl1152
-rw-r--r--lib/stdlib/test/c_SUITE.erl114
-rw-r--r--lib/stdlib/test/calendar_SUITE.erl169
-rw-r--r--lib/stdlib/test/digraph_SUITE.erl380
-rw-r--r--lib/stdlib/test/digraph_utils_SUITE.erl310
-rw-r--r--lib/stdlib/test/epp_SUITE.erl305
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl860
-rw-r--r--lib/stdlib/test/erl_expand_records_SUITE.erl70
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl160
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl202
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl462
-rw-r--r--lib/stdlib/test/escript_SUITE.erl634
-rw-r--r--lib/stdlib/test/ets_SUITE.erl4100
-rw-r--r--lib/stdlib/test/ets_tough_SUITE.erl42
-rw-r--r--lib/stdlib/test/file_sorter_SUITE.erl1242
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl210
-rw-r--r--lib/stdlib/test/fixtable_SUITE.erl428
-rw-r--r--lib/stdlib/test/format_SUITE.erl4
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl1184
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl314
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl710
-rw-r--r--lib/stdlib/test/io_SUITE.erl1317
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl1338
-rw-r--r--lib/stdlib/test/lists_SUITE.erl2024
-rw-r--r--lib/stdlib/test/log_mf_h_SUITE.erl35
-rw-r--r--lib/stdlib/test/ms_transform_SUITE.erl466
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl54
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl292
-rw-r--r--lib/stdlib/test/queue_SUITE.erl378
-rw-r--r--lib/stdlib/test/random_SUITE.erl64
-rw-r--r--lib/stdlib/test/re_SUITE.erl456
-rw-r--r--lib/stdlib/test/select_SUITE.erl434
-rw-r--r--lib/stdlib/test/shell_SUITE.erl3114
-rw-r--r--lib/stdlib/test/slave_SUITE.erl152
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl2848
-rw-r--r--lib/stdlib/test/string_SUITE.erl456
-rw-r--r--lib/stdlib/test/supervisor_bridge_SUITE.erl48
-rw-r--r--lib/stdlib/test/sys_SUITE.erl50
-rw-r--r--lib/stdlib/test/tar_SUITE.erl544
-rw-r--r--lib/stdlib/test/timer_SUITE.erl34
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl212
-rw-r--r--lib/stdlib/test/unicode_SUITE.erl610
-rw-r--r--lib/stdlib/test/win32reg_SUITE.erl8
-rw-r--r--lib/stdlib/test/y2k_SUITE.erl97
-rw-r--r--lib/stdlib/test/zip_SUITE.erl56
47 files changed, 14413 insertions, 14426 deletions
diff --git a/lib/stdlib/test/array_SUITE.erl b/lib/stdlib/test/array_SUITE.erl
index dc949b53cd..8d031ed490 100644
--- a/lib/stdlib/test/array_SUITE.erl
+++ b/lib/stdlib/test/array_SUITE.erl
@@ -105,19 +105,19 @@ end_per_testcase(_Case, _Config) ->
}).
-define(_assert(What),
- begin ?line true = What end
+ begin true = What end
).
-define(_assertNot(What),
- begin ?line false = What end
+ begin false = What end
).
-define(_assertMatch(Res,What),
begin
- ?line case What of Res -> ok end
+ case What of Res -> ok end
end
).
-define(_assertError(Reas,What),
- begin ?line fun() ->
+ begin fun() ->
try What of
A_Success -> exit({test_error, A_Success})
catch error:Reas -> ok end
@@ -125,9 +125,9 @@ end_per_testcase(_Case, _Config) ->
end
).
--define(LET(Var,Expr, Test), begin ?line fun() -> Var = Expr, Test end() end).
+-define(LET(Var,Expr, Test), begin fun() -> Var = Expr, Test end() end).
--define(_test(Expr), begin ?line Expr end).
+-define(_test(Expr), begin Expr end).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Some helpers to be able to run the tests without testserver
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index e5329da749..bb56efb11e 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -72,67 +72,67 @@ end_per_testcase(_Case, _Config) ->
%% Read correct beam file.
normal(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
- ?line Simple = filename:join(PrivDir, "simple"),
- ?line Source = Simple ++ ".erl",
- ?line BeamFile = Simple ++ ".beam",
- ?line simple_file(Source),
+ PrivDir = ?privdir,
+ Simple = filename:join(PrivDir, "simple"),
+ Source = Simple ++ ".erl",
+ BeamFile = Simple ++ ".beam",
+ simple_file(Source),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
CompileFlags = [{outdir,PrivDir}, debug_info],
- ?line {ok,_} = compile:file(Source, CompileFlags),
- ?line {ok, Binary} = file:read_file(BeamFile),
+ {ok,_} = compile:file(Source, CompileFlags),
+ {ok, Binary} = file:read_file(BeamFile),
- ?line do_normal(BeamFile),
- ?line do_normal(Binary),
+ do_normal(BeamFile),
+ do_normal(Binary),
- ?line {ok,_} = compile:file(Source, [{outdir,PrivDir}, no_debug_info]),
- ?line {ok, {simple, [{abstract_code, no_abstract_code}]}} =
+ {ok,_} = compile:file(Source, [{outdir,PrivDir}, no_debug_info]),
+ {ok, {simple, [{abstract_code, no_abstract_code}]}} =
beam_lib:chunks(BeamFile, [abstract_code]),
- %% ?line {ok,_} = compile:file(Source, [compressed | CompileFlags]),
- %% ?line do_normal(BeamFile),
+ %% {ok,_} = compile:file(Source, [compressed | CompileFlags]),
+ %% do_normal(BeamFile),
- ?line file:delete(BeamFile),
- ?line file:delete(Source),
- ?line NoOfTables = length(ets:all()),
- ?line true = (P0 == pps()),
+ file:delete(BeamFile),
+ file:delete(Source),
+ NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
ok.
do_normal(BeamFile) ->
- ?line Imports = {imports, [{erlang, get_module_info, 1},
- {erlang, get_module_info, 2},
- {lists, member, 2}]},
- ?line Exports = {exports, [{module_info, 0}, {module_info, 1}, {t, 0}]},
- ?line Local = {locals, [{t, 1}]},
- ?line {ok, {simple, [Imports]}} = beam_lib:chunks(BeamFile, [imports]),
- ?line {ok, {simple, [{"ImpT",_Bin}]}} =
+ Imports = {imports, [{erlang, get_module_info, 1},
+ {erlang, get_module_info, 2},
+ {lists, member, 2}]},
+ Exports = {exports, [{module_info, 0}, {module_info, 1}, {t, 0}]},
+ Local = {locals, [{t, 1}]},
+ {ok, {simple, [Imports]}} = beam_lib:chunks(BeamFile, [imports]),
+ {ok, {simple, [{"ImpT",_Bin}]}} =
beam_lib:chunks(BeamFile, ["ImpT"]),
- ?line {ok, {simple, [Exports]}} = beam_lib:chunks(BeamFile, [exports]),
- ?line {ok, {simple, [{attributes, [{vsn, [_]}]}]}} =
+ {ok, {simple, [Exports]}} = beam_lib:chunks(BeamFile, [exports]),
+ {ok, {simple, [{attributes, [{vsn, [_]}]}]}} =
beam_lib:chunks(BeamFile, [attributes]),
- ?line {ok, {simple, [{compile_info, _}=CompileInfo]}} =
+ {ok, {simple, [{compile_info, _}=CompileInfo]}} =
beam_lib:chunks(BeamFile, [compile_info]),
- ?line {ok, {simple, [Local]}} = beam_lib:chunks(BeamFile, [locals]),
- ?line {ok, {simple, [{attributes, [{vsn, [_]}]}, CompileInfo,
- Exports, Imports, Local]}} =
+ {ok, {simple, [Local]}} = beam_lib:chunks(BeamFile, [locals]),
+ {ok, {simple, [{attributes, [{vsn, [_]}]}, CompileInfo,
+ Exports, Imports, Local]}} =
beam_lib:chunks(BeamFile, [attributes, compile_info, exports, imports, locals]),
- ?line {ok, {simple, [{atoms, _Atoms}]}} =
+ {ok, {simple, [{atoms, _Atoms}]}} =
beam_lib:chunks(BeamFile, [atoms]),
- ?line {ok, {simple, [{labeled_exports, _LExports}]}} =
+ {ok, {simple, [{labeled_exports, _LExports}]}} =
beam_lib:chunks(BeamFile, [labeled_exports]),
- ?line {ok, {simple, [{labeled_locals, _LLocals}]}} =
+ {ok, {simple, [{labeled_locals, _LLocals}]}} =
beam_lib:chunks(BeamFile, [labeled_locals]),
- ?line {ok, {simple, [_Vsn]}} = beam_lib:version(BeamFile),
- ?line {ok, {simple, [{abstract_code, _}]}} =
+ {ok, {simple, [_Vsn]}} = beam_lib:version(BeamFile),
+ {ok, {simple, [{abstract_code, _}]}} =
beam_lib:chunks(BeamFile, [abstract_code]),
-
+
%% Test reading optional chunks.
All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT"],
- ?line {ok,{simple,Chunks}} = beam_lib:chunks(BeamFile, All, [allow_missing_chunks]),
- ?line verify_simple(Chunks).
+ {ok,{simple,Chunks}} = beam_lib:chunks(BeamFile, All, [allow_missing_chunks]),
+ verify_simple(Chunks).
verify_simple([{"Atom", AtomBin},
{"Code", CodeBin},
@@ -147,59 +147,59 @@ verify_simple([{"Atom", AtomBin},
%% Read invalid beam files.
error(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
- ?line Simple = filename:join(PrivDir, "simple"),
- ?line Source = Simple ++ ".erl",
- ?line BeamFile = Simple ++ ".beam",
- ?line WrongFile = Simple ++ "foo.beam",
- ?line simple_file(Source),
-
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
- ?line {ok,_} = compile:file(Source, [{outdir,PrivDir},debug_info]),
- ?line ACopy = filename:join(PrivDir, "a_copy.beam"),
- ?line copy_file(BeamFile, ACopy),
-
- ?line {ok, Binary} = file:read_file(BeamFile),
-
- ?line copy_file(ACopy, WrongFile),
- ?line verify(file_error, beam_lib:info("./does_simply_not_exist")),
-
- ?line do_error(BeamFile, ACopy),
- ?line do_error(Binary, ACopy),
-
- ?line copy_file(ACopy, BeamFile),
- ?line verify(unknown_chunk, beam_lib:chunks(BeamFile, [not_a_chunk])),
-
- ?line ok = file:write_file(BeamFile, <<>>),
- ?line verify(not_a_beam_file, beam_lib:info(BeamFile)),
- ?line verify(not_a_beam_file, beam_lib:info(<<>>)),
- ?line ok = file:write_file(BeamFile, <<"short">>),
- ?line verify(not_a_beam_file, beam_lib:info(BeamFile)),
- ?line verify(not_a_beam_file, beam_lib:info(<<"short">>)),
-
- ?line {Binary1, _} = split_binary(Binary, byte_size(Binary)-10),
+ PrivDir = ?privdir,
+ Simple = filename:join(PrivDir, "simple"),
+ Source = Simple ++ ".erl",
+ BeamFile = Simple ++ ".beam",
+ WrongFile = Simple ++ "foo.beam",
+ simple_file(Source),
+
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
+ {ok,_} = compile:file(Source, [{outdir,PrivDir},debug_info]),
+ ACopy = filename:join(PrivDir, "a_copy.beam"),
+ copy_file(BeamFile, ACopy),
+
+ {ok, Binary} = file:read_file(BeamFile),
+
+ copy_file(ACopy, WrongFile),
+ verify(file_error, beam_lib:info("./does_simply_not_exist")),
+
+ do_error(BeamFile, ACopy),
+ do_error(Binary, ACopy),
+
+ copy_file(ACopy, BeamFile),
+ verify(unknown_chunk, beam_lib:chunks(BeamFile, [not_a_chunk])),
+
+ ok = file:write_file(BeamFile, <<>>),
+ verify(not_a_beam_file, beam_lib:info(BeamFile)),
+ verify(not_a_beam_file, beam_lib:info(<<>>)),
+ ok = file:write_file(BeamFile, <<"short">>),
+ verify(not_a_beam_file, beam_lib:info(BeamFile)),
+ verify(not_a_beam_file, beam_lib:info(<<"short">>)),
+
+ {Binary1, _} = split_binary(Binary, byte_size(Binary)-10),
LastChunk = last_chunk(Binary),
- ?line verify(chunk_too_big, beam_lib:chunks(Binary1, [LastChunk])),
- ?line Chunks = chunk_info(Binary),
- ?line {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
- ?line {Binary2, _} = split_binary(Binary, AbstractStart),
- ?line verify(chunk_too_big, beam_lib:chunks(Binary2, ["Abst"])),
- ?line {Binary3, _} = split_binary(Binary, AbstractStart-4),
- ?line verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Abst"])),
+ verify(chunk_too_big, beam_lib:chunks(Binary1, [LastChunk])),
+ Chunks = chunk_info(Binary),
+ {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
+ {Binary2, _} = split_binary(Binary, AbstractStart),
+ verify(chunk_too_big, beam_lib:chunks(Binary2, ["Abst"])),
+ {Binary3, _} = split_binary(Binary, AbstractStart-4),
+ verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Abst"])),
%% Instead of the 5:32 field below, there used to be control characters
%% (including zero bytes) directly in the string. Because inferior programs
%% such as sed and clearcasediff don't like zero bytes in text files,
%% we have eliminated them.
- ?line ok = file:write_file(BeamFile, <<"FOR1",5:32,"BEAMfel">>),
-
- ?line NoOfTables = length(ets:all()),
- ?line true = (P0 == pps()),
- ?line file:delete(Source),
- ?line file:delete(WrongFile),
- ?line file:delete(BeamFile),
- ?line file:delete(ACopy),
+ ok = file:write_file(BeamFile, <<"FOR1",5:32,"BEAMfel">>),
+
+ NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
+ file:delete(Source),
+ file:delete(WrongFile),
+ file:delete(BeamFile),
+ file:delete(ACopy),
ok.
last_chunk(Bin) ->
@@ -210,80 +210,80 @@ last_chunk(Bin) ->
do_error(BeamFile, ACopy) ->
%% evil tests
- ?line Chunks = chunk_info(BeamFile),
- ?line {value, {_, AtomStart, _}} = lists:keysearch("Atom", 1, Chunks),
- ?line {value, {_, ImportStart, _}} = lists:keysearch("ImpT", 1, Chunks),
- ?line {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
- ?line {value, {_, AttributesStart, _}} =
+ Chunks = chunk_info(BeamFile),
+ {value, {_, AtomStart, _}} = lists:keysearch("Atom", 1, Chunks),
+ {value, {_, ImportStart, _}} = lists:keysearch("ImpT", 1, Chunks),
+ {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
+ {value, {_, AttributesStart, _}} =
lists:keysearch("Attr", 1, Chunks),
- ?line {value, {_, CompileInfoStart, _}} =
+ {value, {_, CompileInfoStart, _}} =
lists:keysearch("CInf", 1, Chunks),
- ?line verify(missing_chunk, beam_lib:chunks(BeamFile, ["__"])),
- ?line BF2 = set_byte(ACopy, BeamFile, ImportStart+4, 17),
- ?line verify(invalid_chunk, beam_lib:chunks(BF2, [imports])),
- ?line BF3 = set_byte(ACopy, BeamFile, AtomStart-6, 17),
- ?line verify(missing_chunk, beam_lib:chunks(BF3, [imports])),
- ?line BF4 = set_byte(ACopy, BeamFile, AbstractStart+10, 17),
- ?line verify(invalid_chunk, beam_lib:chunks(BF4, [abstract_code])),
- ?line BF5 = set_byte(ACopy, BeamFile, AttributesStart+10, 17),
- ?line verify(invalid_chunk, beam_lib:chunks(BF5, [attributes])),
-
- ?line BF6 = set_byte(ACopy, BeamFile, 1, 17),
- ?line verify(not_a_beam_file, beam_lib:info(BF6)),
- ?line BF7 = set_byte(ACopy, BeamFile, 9, 17),
- ?line verify(not_a_beam_file, beam_lib:info(BF7)),
-
- ?line BF8 = set_byte(ACopy, BeamFile, 13, 17),
- ?line verify(missing_chunk, beam_lib:chunks(BF8, ["Atom"])),
-
- ?line BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+10, 17),
- ?line verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])).
-
+ verify(missing_chunk, beam_lib:chunks(BeamFile, ["__"])),
+ BF2 = set_byte(ACopy, BeamFile, ImportStart+4, 17),
+ verify(invalid_chunk, beam_lib:chunks(BF2, [imports])),
+ BF3 = set_byte(ACopy, BeamFile, AtomStart-6, 17),
+ verify(missing_chunk, beam_lib:chunks(BF3, [imports])),
+ BF4 = set_byte(ACopy, BeamFile, AbstractStart+10, 17),
+ verify(invalid_chunk, beam_lib:chunks(BF4, [abstract_code])),
+ BF5 = set_byte(ACopy, BeamFile, AttributesStart+10, 17),
+ verify(invalid_chunk, beam_lib:chunks(BF5, [attributes])),
+
+ BF6 = set_byte(ACopy, BeamFile, 1, 17),
+ verify(not_a_beam_file, beam_lib:info(BF6)),
+ BF7 = set_byte(ACopy, BeamFile, 9, 17),
+ verify(not_a_beam_file, beam_lib:info(BF7)),
+
+ BF8 = set_byte(ACopy, BeamFile, 13, 17),
+ verify(missing_chunk, beam_lib:chunks(BF8, ["Atom"])),
+
+ BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+10, 17),
+ verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])).
+
%% Compare contents of BEAM files and directories.
cmp(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
+ PrivDir = ?privdir,
- ?line Dir1 = filename:join(PrivDir, "dir1"),
- ?line Dir2 = filename:join(PrivDir, "dir2"),
+ Dir1 = filename:join(PrivDir, "dir1"),
+ Dir2 = filename:join(PrivDir, "dir2"),
ok = file:make_dir(Dir1),
ok = file:make_dir(Dir2),
- ?line {SourceD1, BeamFileD1} = make_beam(Dir1, simple, member),
- ?line {Source2D1, BeamFile2D1} = make_beam(Dir1, simple2, concat),
- ?line {SourceD2, BeamFileD2} = make_beam(Dir2, simple, concat),
+ {SourceD1, BeamFileD1} = make_beam(Dir1, simple, member),
+ {Source2D1, BeamFile2D1} = make_beam(Dir1, simple2, concat),
+ {SourceD2, BeamFileD2} = make_beam(Dir2, simple, concat),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
%% cmp
- ?line ok = beam_lib:cmp(BeamFileD1, BeamFileD1),
- ?line ver(modules_different, beam_lib:cmp(BeamFileD1, BeamFile2D1)),
- ?line ver(chunks_different, beam_lib:cmp(BeamFileD1, BeamFileD2)),
- ?line verify(file_error, beam_lib:cmp(foo, bar)),
-
- ?line {ok, B1} = file:read_file(BeamFileD1),
- ?line ok = beam_lib:cmp(B1, BeamFileD1),
- ?line {ok, B2} = file:read_file(BeamFileD2),
- ?line ver(chunks_different, beam_lib:cmp(B1, B2)),
+ ok = beam_lib:cmp(BeamFileD1, BeamFileD1),
+ ver(modules_different, beam_lib:cmp(BeamFileD1, BeamFile2D1)),
+ ver(chunks_different, beam_lib:cmp(BeamFileD1, BeamFileD2)),
+ verify(file_error, beam_lib:cmp(foo, bar)),
+
+ {ok, B1} = file:read_file(BeamFileD1),
+ ok = beam_lib:cmp(B1, BeamFileD1),
+ {ok, B2} = file:read_file(BeamFileD2),
+ ver(chunks_different, beam_lib:cmp(B1, B2)),
%% cmp_dirs
- ?line {[],[],[]} = beam_lib:cmp_dirs(Dir1, Dir1),
- ?line true = {[BeamFile2D1], [], [{BeamFileD1,BeamFileD2}]} ==
- beam_lib:cmp_dirs(Dir1, Dir2),
- ?line true = {[], [BeamFile2D1], [{BeamFileD2,BeamFileD1}]} ==
- beam_lib:cmp_dirs(Dir2, Dir1),
- ?line ver(not_a_directory, beam_lib:cmp_dirs(foo, bar)),
-
+ {[],[],[]} = beam_lib:cmp_dirs(Dir1, Dir1),
+ true = {[BeamFile2D1], [], [{BeamFileD1,BeamFileD2}]} ==
+ beam_lib:cmp_dirs(Dir1, Dir2),
+ true = {[], [BeamFile2D1], [{BeamFileD2,BeamFileD1}]} ==
+ beam_lib:cmp_dirs(Dir2, Dir1),
+ ver(not_a_directory, beam_lib:cmp_dirs(foo, bar)),
+
%% diff_dirs
- ?line ok = beam_lib:diff_dirs(Dir1, Dir1),
- ?line ver(not_a_directory, beam_lib:diff_dirs(foo, bar)),
+ ok = beam_lib:diff_dirs(Dir1, Dir1),
+ ver(not_a_directory, beam_lib:diff_dirs(foo, bar)),
- ?line true = (P0 == pps()),
- ?line NoOfTables = length(ets:all()),
- ?line delete_files([SourceD1, BeamFileD1, Source2D1,
- BeamFile2D1, SourceD2, BeamFileD2]),
+ true = (P0 == pps()),
+ NoOfTables = length(ets:all()),
+ delete_files([SourceD1, BeamFileD1, Source2D1,
+ BeamFile2D1, SourceD2, BeamFileD2]),
file:del_dir(Dir1),
file:del_dir(Dir2),
@@ -291,33 +291,33 @@ cmp(Conf) when is_list(Conf) ->
%% Compare contents of BEAM files having literals.
cmp_literals(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
+ PrivDir = ?privdir,
- ?line Dir1 = filename:join(PrivDir, "dir1"),
- ?line Dir2 = filename:join(PrivDir, "dir2"),
+ Dir1 = filename:join(PrivDir, "dir1"),
+ Dir2 = filename:join(PrivDir, "dir2"),
ok = file:make_dir(Dir1),
ok = file:make_dir(Dir2),
- ?line {SourceD1, BeamFileD1} = make_beam(Dir1, simple, constant),
- ?line {SourceD2, BeamFileD2} = make_beam(Dir2, simple, constant2),
+ {SourceD1, BeamFileD1} = make_beam(Dir1, simple, constant),
+ {SourceD2, BeamFileD2} = make_beam(Dir2, simple, constant2),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
%% cmp
- ?line ok = beam_lib:cmp(BeamFileD1, BeamFileD1),
- ?line ver(chunks_different, beam_lib:cmp(BeamFileD1, BeamFileD2)),
-
- ?line {ok, B1} = file:read_file(BeamFileD1),
- ?line ok = beam_lib:cmp(B1, BeamFileD1),
- ?line {ok, B2} = file:read_file(BeamFileD2),
- ?line ver(chunks_different, beam_lib:cmp(B1, B2)),
+ ok = beam_lib:cmp(BeamFileD1, BeamFileD1),
+ ver(chunks_different, beam_lib:cmp(BeamFileD1, BeamFileD2)),
- ?line true = (P0 == pps()),
- ?line NoOfTables = length(ets:all()),
+ {ok, B1} = file:read_file(BeamFileD1),
+ ok = beam_lib:cmp(B1, BeamFileD1),
+ {ok, B2} = file:read_file(BeamFileD2),
+ ver(chunks_different, beam_lib:cmp(B1, B2)),
- ?line delete_files([SourceD1, BeamFileD1, SourceD2, BeamFileD2]),
+ true = (P0 == pps()),
+ NoOfTables = length(ets:all()),
+
+ delete_files([SourceD1, BeamFileD1, SourceD2, BeamFileD2]),
file:del_dir(Dir1),
file:del_dir(Dir2),
@@ -325,94 +325,94 @@ cmp_literals(Conf) when is_list(Conf) ->
%% Strip BEAM files.
strip(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
- ?line {SourceD1, BeamFileD1} = make_beam(PrivDir, simple, member),
- ?line {Source2D1, BeamFile2D1} = make_beam(PrivDir, simple2, concat),
- ?line {Source3D1, BeamFile3D1} = make_beam(PrivDir, make_fun, make_fun),
- ?line {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant),
- ?line {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines),
+ PrivDir = ?privdir,
+ {SourceD1, BeamFileD1} = make_beam(PrivDir, simple, member),
+ {Source2D1, BeamFile2D1} = make_beam(PrivDir, simple2, concat),
+ {Source3D1, BeamFile3D1} = make_beam(PrivDir, make_fun, make_fun),
+ {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant),
+ {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
%% strip binary
- ?line verify(not_a_beam_file, beam_lib:strip(<<>>)),
- ?line {ok, B1} = file:read_file(BeamFileD1),
- ?line {ok, {simple, NB1}} = beam_lib:strip(B1),
- ?line BId1 = chunk_ids(B1),
- ?line NBId1 = chunk_ids(NB1),
- ?line true = length(BId1) > length(NBId1),
- ?line compare_chunks(B1, NB1, NBId1),
+ verify(not_a_beam_file, beam_lib:strip(<<>>)),
+ {ok, B1} = file:read_file(BeamFileD1),
+ {ok, {simple, NB1}} = beam_lib:strip(B1),
+ BId1 = chunk_ids(B1),
+ NBId1 = chunk_ids(NB1),
+ true = length(BId1) > length(NBId1),
+ compare_chunks(B1, NB1, NBId1),
%% strip file
- ?line verify(file_error, beam_lib:strip(foo)),
- ?line {ok, {simple, _}} = beam_lib:strip(BeamFileD1),
- ?line compare_chunks(NB1, BeamFileD1, NBId1),
+ verify(file_error, beam_lib:strip(foo)),
+ {ok, {simple, _}} = beam_lib:strip(BeamFileD1),
+ compare_chunks(NB1, BeamFileD1, NBId1),
%% strip_files
- ?line {ok, B2} = file:read_file(BeamFile2D1),
- ?line {ok, [{simple,_},{simple2,_}]} = beam_lib:strip_files([B1, B2]),
- ?line {ok, [{simple,_},{simple2,_},{make_fun,_},{constant,_}]} =
+ {ok, B2} = file:read_file(BeamFile2D1),
+ {ok, [{simple,_},{simple2,_}]} = beam_lib:strip_files([B1, B2]),
+ {ok, [{simple,_},{simple2,_},{make_fun,_},{constant,_}]} =
beam_lib:strip_files([BeamFileD1, BeamFile2D1, BeamFile3D1, BeamFile4D1]),
%% check that each module can be loaded.
- ?line {module, simple} = code:load_abs(filename:rootname(BeamFileD1)),
- ?line {module, simple2} = code:load_abs(filename:rootname(BeamFile2D1)),
- ?line {module, make_fun} = code:load_abs(filename:rootname(BeamFile3D1)),
- ?line {module, constant} = code:load_abs(filename:rootname(BeamFile4D1)),
+ {module, simple} = code:load_abs(filename:rootname(BeamFileD1)),
+ {module, simple2} = code:load_abs(filename:rootname(BeamFile2D1)),
+ {module, make_fun} = code:load_abs(filename:rootname(BeamFile3D1)),
+ {module, constant} = code:load_abs(filename:rootname(BeamFile4D1)),
%% check that line number information is still present after stripping
- ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
- ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
(catch lines:t(atom)),
- ?line true = code:delete(lines),
- ?line false = code:purge(lines),
- ?line {ok, {lines,BeamFile5D1}} = beam_lib:strip(BeamFile5D1),
- ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
- ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ true = code:delete(lines),
+ false = code:purge(lines),
+ {ok, {lines,BeamFile5D1}} = beam_lib:strip(BeamFile5D1),
+ {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
(catch lines:t(atom)),
- ?line true = (P0 == pps()),
- ?line NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
+ NoOfTables = length(ets:all()),
- ?line delete_files([SourceD1, BeamFileD1,
- Source2D1, BeamFile2D1,
- Source3D1, BeamFile3D1,
- Source4D1, BeamFile4D1,
- Source5D1, BeamFile5D1]),
+ delete_files([SourceD1, BeamFileD1,
+ Source2D1, BeamFile2D1,
+ Source3D1, BeamFile3D1,
+ Source4D1, BeamFile4D1,
+ Source5D1, BeamFile5D1]),
ok.
otp_6711(Conf) when is_list(Conf) ->
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:info(3)}),
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:chunks(a, b)}),
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:chunks(a,b,c)}),
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:all_chunks(3)}),
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:cmp(3,4)}),
- ?line {'EXIT',{function_clause,_}} = (catch {a, beam_lib:strip(3)}),
- ?line {'EXIT',{function_clause,_}} =
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:info(3)}),
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:chunks(a, b)}),
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:chunks(a,b,c)}),
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:all_chunks(3)}),
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:cmp(3,4)}),
+ {'EXIT',{function_clause,_}} = (catch {a, beam_lib:strip(3)}),
+ {'EXIT',{function_clause,_}} =
(catch {a, beam_lib:strip_files([3])}),
- ?line PrivDir = ?privdir,
- ?line Dir = filename:join(PrivDir, "dir"),
- ?line Lib = filename:join(Dir, "lib"),
- ?line App = filename:join(Lib, "app"),
- ?line EBin = filename:join(App, "ebin"),
+ PrivDir = ?privdir,
+ Dir = filename:join(PrivDir, "dir"),
+ Lib = filename:join(Dir, "lib"),
+ App = filename:join(Lib, "app"),
+ EBin = filename:join(App, "ebin"),
ok = file:make_dir(Dir),
ok = file:make_dir(Lib),
ok = file:make_dir(App),
ok = file:make_dir(EBin),
-
- ?line {SourceD, BeamFileD} = make_beam(EBin, simple, member),
+
+ {SourceD, BeamFileD} = make_beam(EBin, simple, member),
unwritable(BeamFileD),
%% There is no way that strip_release can fail with
%% function_clause or something like that...
- ?line {error,_,{file_error,_,_}} = beam_lib:strip_release(Dir),
+ {error,_,{file_error,_,_}} = beam_lib:strip_release(Dir),
- ?line delete_files([SourceD, BeamFileD]),
+ delete_files([SourceD, BeamFileD]),
file:del_dir(EBin),
file:del_dir(App),
file:del_dir(Lib),
@@ -428,56 +428,56 @@ unwritable(Fname) ->
%% Testing building of BEAM files.
building(Conf) when is_list(Conf) ->
- ?line PrivDir = ?privdir,
+ PrivDir = ?privdir,
- ?line Dir1 = filename:join(PrivDir, "b_dir1"),
- ?line Dir2 = filename:join(PrivDir, "b_dir2"),
+ Dir1 = filename:join(PrivDir, "b_dir1"),
+ Dir2 = filename:join(PrivDir, "b_dir2"),
ok = file:make_dir(Dir1),
ok = file:make_dir(Dir2),
- ?line {SourceD1, BeamFileD1} = make_beam(Dir1, building, member),
+ {SourceD1, BeamFileD1} = make_beam(Dir1, building, member),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
%% read all chunks
- ?line ChunkIds = chunk_ids(BeamFileD1),
- ?line {ok, _Mod, Chunks} = beam_lib:all_chunks(BeamFileD1),
- ?line ChunkIds = lists:map(fun ({Id, Data}) when is_binary(Data) -> Id
- end, Chunks),
+ ChunkIds = chunk_ids(BeamFileD1),
+ {ok, _Mod, Chunks} = beam_lib:all_chunks(BeamFileD1),
+ ChunkIds = lists:map(fun ({Id, Data}) when is_binary(Data) -> Id
+ end, Chunks),
%% write a new beam file, with reversed chunk order
- ?line BeamFileD2 = filename:join(Dir2, "building.beam"),
- ?line {ok,RevBeam} = beam_lib:build_module(lists:reverse(Chunks)),
- ?line file:write_file(BeamFileD2, RevBeam),
+ BeamFileD2 = filename:join(Dir2, "building.beam"),
+ {ok,RevBeam} = beam_lib:build_module(lists:reverse(Chunks)),
+ file:write_file(BeamFileD2, RevBeam),
%% compare files
- ?line compare_chunks(BeamFileD1, BeamFileD2, ChunkIds),
+ compare_chunks(BeamFileD1, BeamFileD2, ChunkIds),
%% test that we can retrieve a chunk before the atom table
%% (actually, try to retrieve all chunks)
- ?line lists:foreach(fun(Id) ->
- {ok, {building, [{Id, _Data}]}} =
- beam_lib:chunks(BeamFileD1, [Id])
- end, ChunkIds),
- ?line lists:foreach(fun(Id) ->
- {ok, {building, [{Id, _Data}]}} =
- beam_lib:chunks(BeamFileD2, [Id])
- end, ChunkIds),
+ lists:foreach(fun(Id) ->
+ {ok, {building, [{Id, _Data}]}} =
+ beam_lib:chunks(BeamFileD1, [Id])
+ end, ChunkIds),
+ lists:foreach(fun(Id) ->
+ {ok, {building, [{Id, _Data}]}} =
+ beam_lib:chunks(BeamFileD2, [Id])
+ end, ChunkIds),
- ?line true = (P0 == pps()),
- ?line NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
+ NoOfTables = length(ets:all()),
- ?line delete_files([SourceD1, BeamFileD1, BeamFileD2]),
+ delete_files([SourceD1, BeamFileD1, BeamFileD2]),
file:del_dir(Dir1),
file:del_dir(Dir2),
ok.
%% Compare beam_lib:md5/1 and code:module_md5/1.
md5(Conf) when is_list(Conf) ->
- ?line Beams = collect_beams(),
+ Beams = collect_beams(),
io:format("Found ~w beam files", [length(Beams)]),
md5_1(Beams).
@@ -488,7 +488,7 @@ md5_1([N|Ns]) ->
{Mod,MD5} = {Mod,code:module_md5(Beam)},
md5_1(Ns);
md5_1([]) -> ok.
-
+
collect_beams() ->
SuperDir = filename:dirname(filename:dirname(code:which(?MODULE))),
TestDirs = filelib:wildcard(filename:join([SuperDir,"*_test"])),
@@ -507,84 +507,84 @@ encrypted_abstr(Conf) when is_list(Conf) ->
run_if_crypto_works(fun() -> encrypted_abstr_1(Conf) end).
encrypted_abstr_1(Conf) ->
- ?line PrivDir = ?privdir,
- ?line Simple = filename:join(PrivDir, "simple"),
- ?line Source = Simple ++ ".erl",
- ?line BeamFile = Simple ++ ".beam",
- ?line simple_file(Source),
+ PrivDir = ?privdir,
+ Simple = filename:join(PrivDir, "simple"),
+ Source = Simple ++ ".erl",
+ BeamFile = Simple ++ ".beam",
+ simple_file(Source),
%% Avoid getting an extra port when crypto starts erl_ddll.
- ?line erl_ddll:start(),
+ erl_ddll:start(),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
Key = "#a_crypto_key",
CompileFlags = [{outdir,PrivDir}, debug_info, {debug_info_key,Key}],
- ?line {ok,_} = compile:file(Source, CompileFlags),
- ?line {ok, Binary} = file:read_file(BeamFile),
+ {ok,_} = compile:file(Source, CompileFlags),
+ {ok, Binary} = file:read_file(BeamFile),
- ?line do_encrypted_abstr(BeamFile, Key),
- ?line do_encrypted_abstr(Binary, Key),
+ do_encrypted_abstr(BeamFile, Key),
+ do_encrypted_abstr(Binary, Key),
- ?line ok = crypto:stop(), %To get rid of extra ets tables.
- ?line file:delete(BeamFile),
- ?line file:delete(Source),
- ?line NoOfTables = length(ets:all()),
- ?line true = (P0 == pps()),
+ ok = crypto:stop(), %To get rid of extra ets tables.
+ file:delete(BeamFile),
+ file:delete(Source),
+ NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
ok.
do_encrypted_abstr(Beam, Key) ->
- ?line verify(key_missing_or_invalid, beam_lib:chunks(Beam, [abstract_code])),
+ verify(key_missing_or_invalid, beam_lib:chunks(Beam, [abstract_code])),
%% The raw chunk "Abst" can still be read even without a key.
- ?line {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
- ?line <<0:8,8:8,"des3_cbc",_/binary>> = Abst,
+ {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
+ <<0:8,8:8,"des3_cbc",_/binary>> = Abst,
%% Try som invalid funs.
- ?line bad_fun(badfun, fun() -> ok end),
- ?line bad_fun(badfun, {a,b}),
- ?line bad_fun(blurf),
- ?line {function_clause,_} = bad_fun(fun(glurf) -> ok end),
+ bad_fun(badfun, fun() -> ok end),
+ bad_fun(badfun, {a,b}),
+ bad_fun(blurf),
+ {function_clause,_} = bad_fun(fun(glurf) -> ok end),
%% Funs that return something strange.
- ?line bad_fun(badfun, fun(init) -> {ok,fun() -> ok end} end),
- ?line glurf = bad_fun(fun(init) -> {error,glurf} end),
+ bad_fun(badfun, fun(init) -> {ok,fun() -> ok end} end),
+ glurf = bad_fun(fun(init) -> {error,glurf} end),
%% Try clearing (non-existing fun).
- ?line undefined = beam_lib:clear_crypto_key_fun(),
+ undefined = beam_lib:clear_crypto_key_fun(),
%% Install a fun which cannot retrieve a key.
- ?line ok = beam_lib:crypto_key_fun(fun(init) -> ok end),
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+ ok = beam_lib:crypto_key_fun(fun(init) -> ok end),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
%% Install a fun which returns an incorrect key.
- ?line {ok,_} = beam_lib:clear_crypto_key_fun(),
- ?line ok = beam_lib:crypto_key_fun(simple_crypto_fun("wrong key...")),
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
-
+ {ok,_} = beam_lib:clear_crypto_key_fun(),
+ ok = beam_lib:crypto_key_fun(simple_crypto_fun("wrong key...")),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+
%% Installing a new key fun is not possible without clearing the old.
- ?line verify(exists, beam_lib:crypto_key_fun(simple_crypto_fun(Key))),
+ verify(exists, beam_lib:crypto_key_fun(simple_crypto_fun(Key))),
%% Install the simplest possible working key fun.
- ?line {ok,_} = beam_lib:clear_crypto_key_fun(),
- ?line ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)),
- ?line verify_abstract(Beam),
- ?line {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
+ {ok,_} = beam_lib:clear_crypto_key_fun(),
+ ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)),
+ verify_abstract(Beam),
+ {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
%% Installing a new key fun is not possible without clearing the old.
verify(exists, beam_lib:crypto_key_fun(ets_crypto_fun(Key))),
%% Install a key using an ets table.
- ?line {ok,_} = beam_lib:clear_crypto_key_fun(),
- ?line ok = beam_lib:crypto_key_fun(ets_crypto_fun(Key)),
- ?line verify_abstract(Beam),
- ?line {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
+ {ok,_} = beam_lib:clear_crypto_key_fun(),
+ ok = beam_lib:crypto_key_fun(ets_crypto_fun(Key)),
+ verify_abstract(Beam),
+ {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
- ?line {ok,cleared} = beam_lib:clear_crypto_key_fun(),
+ {ok,cleared} = beam_lib:clear_crypto_key_fun(),
%% Try to force a stop/start race.
- ?line start_stop_race(10000),
+ start_stop_race(10000),
ok.
@@ -630,62 +630,62 @@ encrypted_abstr_file(Conf) when is_list(Conf) ->
run_if_crypto_works(fun() -> encrypted_abstr_file_1(Conf) end).
encrypted_abstr_file_1(Conf) ->
- ?line PrivDir = ?privdir,
- ?line Simple = filename:join(PrivDir, "simple"),
- ?line Source = Simple ++ ".erl",
- ?line BeamFile = Simple ++ ".beam",
- ?line simple_file(Source),
+ PrivDir = ?privdir,
+ Simple = filename:join(PrivDir, "simple"),
+ Source = Simple ++ ".erl",
+ BeamFile = Simple ++ ".beam",
+ simple_file(Source),
%% Avoid getting an extra port when crypto starts erl_ddll.
- ?line erl_ddll:start(),
+ erl_ddll:start(),
- ?line NoOfTables = length(ets:all()),
- ?line P0 = pps(),
+ NoOfTables = length(ets:all()),
+ P0 = pps(),
Key = "Long And niCe 99Krypto Key",
CompileFlags = [{outdir,PrivDir}, debug_info, {debug_info_key,Key}],
- ?line {ok,_} = compile:file(Source, CompileFlags),
- ?line {ok, Binary} = file:read_file(BeamFile),
-
- ?line {ok,OldCwd} = file:get_cwd(),
- ?line ok = file:set_cwd(PrivDir),
- ?line do_encrypted_abstr_file(BeamFile, Key),
- ?line do_encrypted_abstr_file(Binary, Key),
- ?line ok = file:set_cwd(OldCwd),
-
- ?line ok = crypto:stop(), %To get rid of extra ets tables.
- ?line file:delete(filename:join(PrivDir, ".erlang.crypt")),
- ?line file:delete(BeamFile),
- ?line file:delete(Source),
- ?line NoOfTables = length(ets:all()),
- ?line true = (P0 == pps()),
+ {ok,_} = compile:file(Source, CompileFlags),
+ {ok, Binary} = file:read_file(BeamFile),
+
+ {ok,OldCwd} = file:get_cwd(),
+ ok = file:set_cwd(PrivDir),
+ do_encrypted_abstr_file(BeamFile, Key),
+ do_encrypted_abstr_file(Binary, Key),
+ ok = file:set_cwd(OldCwd),
+
+ ok = crypto:stop(), %To get rid of extra ets tables.
+ file:delete(filename:join(PrivDir, ".erlang.crypt")),
+ file:delete(BeamFile),
+ file:delete(Source),
+ NoOfTables = length(ets:all()),
+ true = (P0 == pps()),
ok.
do_encrypted_abstr_file(Beam, Key) ->
%% No key.
- ?line write_crypt_file(""),
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+ write_crypt_file(""),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
%% A wrong key.
- ?line write_crypt_file(["[{debug_info,des3_cbc,simple,\"A Wrong Key\"}].\n"]),
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+ write_crypt_file(["[{debug_info,des3_cbc,simple,\"A Wrong Key\"}].\n"]),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
%% Write correct key...
- ?line write_crypt_file(["[{debug_info,des3_cbc,simple,\"",Key,"\"}].\n"]),
+ write_crypt_file(["[{debug_info,des3_cbc,simple,\"",Key,"\"}].\n"]),
%% ... but the fun with the wrong key is still there.
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
%% Clear the fun. Now it should work.
- ?line {ok,_} = beam_lib:clear_crypto_key_fun(),
- ?line verify_abstract(Beam),
- ?line verify_abstract(Beam),
- ?line ok = file:delete(".erlang.crypt"),
- ?line verify_abstract(Beam),
+ {ok,_} = beam_lib:clear_crypto_key_fun(),
+ verify_abstract(Beam),
+ verify_abstract(Beam),
+ ok = file:delete(".erlang.crypt"),
+ verify_abstract(Beam),
%% Clear, otherwise the second pass will fail.
- ?line {ok,_} = beam_lib:clear_crypto_key_fun(),
- ?line {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
+ {ok,_} = beam_lib:clear_crypto_key_fun(),
+ {error,beam_lib,Error} = beam_lib:chunks(Beam, [abstract_code]),
ok.
write_crypt_file(Contents0) ->
@@ -694,44 +694,44 @@ write_crypt_file(Contents0) ->
ok = file:write_file(".erlang.crypt", Contents).
compare_chunks(File1, File2, ChunkIds) ->
- ?line {ok, {_, Chunks1}} = beam_lib:chunks(File1, ChunkIds),
- ?line {ok, {_, Chunks2}} = beam_lib:chunks(File2, ChunkIds),
- ?line true = Chunks1 == Chunks2.
+ {ok, {_, Chunks1}} = beam_lib:chunks(File1, ChunkIds),
+ {ok, {_, Chunks2}} = beam_lib:chunks(File2, ChunkIds),
+ true = Chunks1 == Chunks2.
chunk_ids(File) ->
- ?line lists:map(fun({Id,_Start,_Size}) -> Id end, chunk_info(File)).
-
+ lists:map(fun({Id,_Start,_Size}) -> Id end, chunk_info(File)).
+
chunk_info(File) ->
- ?line {value, {chunks, Chunks}} =
+ {value, {chunks, Chunks}} =
lists:keysearch(chunks, 1, beam_lib:info(File)),
Chunks.
-
+
make_beam(Dir, Module, F) ->
- ?line FileBase = filename:join(Dir, atom_to_list(Module)),
- ?line Source = FileBase ++ ".erl",
- ?line BeamFile = FileBase ++ ".beam",
- ?line simple_file(Source, Module, F),
- ?line {ok, _} = compile:file(Source, [{outdir,Dir}, debug_info, report]),
+ FileBase = filename:join(Dir, atom_to_list(Module)),
+ Source = FileBase ++ ".erl",
+ BeamFile = FileBase ++ ".beam",
+ simple_file(Source, Module, F),
+ {ok, _} = compile:file(Source, [{outdir,Dir}, debug_info, report]),
{Source, BeamFile}.
set_byte(_Backup, Binary, Pos, Byte) when is_binary(Binary) ->
- ?line <<B1:Pos/binary, _:1/binary, B2/binary>> = Binary,
+ <<B1:Pos/binary, _:1/binary, B2/binary>> = Binary,
NB = <<B1/binary, Byte:8, B2/binary>>,
NB;
set_byte(Backup, File, Pos, Byte) ->
- ?line copy_file(Backup, File),
- ?line set_byte(File, Pos, Byte),
+ copy_file(Backup, File),
+ set_byte(File, Pos, Byte),
File.
set_byte(File, Pos, Byte) ->
- ?line {ok, Fd} = file:open(File, [read, write]),
- ?line {ok, _} = file:position(Fd, Pos),
- ?line ok = file:write(Fd, [Byte]),
- ?line file:close(Fd).
+ {ok, Fd} = file:open(File, [read, write]),
+ {ok, _} = file:position(Fd, Pos),
+ ok = file:write(Fd, [Byte]),
+ file:close(Fd).
copy_file(Src, Dest) ->
- ?line {ok, _} = file:copy(Src, Dest),
- ?line ok = file:change_mode(Dest, 8#0666).
+ {ok, _} = file:copy(Src, Dest),
+ ok = file:change_mode(Dest, 8#0666).
delete_files(Files) ->
lists:foreach(fun(F) -> file:delete(F) end, Files).
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 7a106e3538..285740d3e0 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -67,196 +67,196 @@ end_per_group(_GroupName, Config) ->
%% Test various badarg exceptions in the module.
badargs(Config) when is_list(Config) ->
- ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3:3>>])),
- ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3>>|<<1,2>>])),
- ?line badarg = ?MASK_ERROR(binary:compile_pattern(<<1,2,3:3>>)),
- ?line badarg = ?MASK_ERROR(binary:compile_pattern(<<>>)),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3:3>>,<<1>>)),
- ?line badarg = ?MASK_ERROR(binary:matches(<<1,2,3:3>>,<<1>>)),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
- [{scope,{0,1},1}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
- [{scape,{0,1}}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
- [{scope,{0,1,1}}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,0,1}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,[0,1]}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
- [{scope,{0.1,1}}])),
- ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
- [{scope,{1,1.1}}])),
- ?line badarg =
+ badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3:3>>])),
+ badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3>>|<<1,2>>])),
+ badarg = ?MASK_ERROR(binary:compile_pattern(<<1,2,3:3>>)),
+ badarg = ?MASK_ERROR(binary:compile_pattern(<<>>)),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3:3>>,<<1>>)),
+ badarg = ?MASK_ERROR(binary:matches(<<1,2,3:3>>,<<1>>)),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0,1},1}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scape,{0,1}}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0,1,1}}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,0,1}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,[0,1]}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0.1,1}}])),
+ badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{1,1.1}}])),
+ badarg =
?MASK_ERROR(
binary:match(<<1,2,3>>,<<1>>,
[{scope,{16#FF,
16#FFFFFFFFFFFFFFFF}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:match(<<1,2,3>>,<<1>>,
[{scope,{16#FFFFFFFFFFFFFFFF,
-16#7FFFFFFFFFFFFFFF-1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:match(<<1,2,3>>,<<1>>,
[{scope,{16#FFFFFFFFFFFFFFFF,
16#7FFFFFFFFFFFFFFF}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:part(<<1,2,3>>,{16#FF,
- 16#FFFFFFFFFFFFFFFF})),
- ?line badarg =
+ 16#FFFFFFFFFFFFFFFF})),
+ badarg =
?MASK_ERROR(
binary:part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
- -16#7FFFFFFFFFFFFFFF-1})),
- ?line badarg =
+ -16#7FFFFFFFFFFFFFFF-1})),
+ badarg =
?MASK_ERROR(
binary:part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
- 16#7FFFFFFFFFFFFFFF})),
- ?line badarg =
+ 16#7FFFFFFFFFFFFFFF})),
+ badarg =
?MASK_ERROR(
binary:part(make_unaligned(<<1,2,3>>),{1,1,1})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{1,1,1})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFF,
- -16#7FFFFFFFFFFFFFFF-1})),
- ?line badarg =
+ -16#7FFFFFFFFFFFFFFF-1})),
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{16#FF,
- 16#FFFFFFFFFFFFFFFF})),
- ?line badarg =
+ 16#FFFFFFFFFFFFFFFF})),
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFF,
- 16#7FFFFFFFFFFFFFFF})),
- ?line badarg =
+ 16#7FFFFFFFFFFFFFFF})),
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFFFF,
- -16#7FFF})),
- ?line badarg =
+ -16#7FFF})),
+ badarg =
?MASK_ERROR(
binary_part(make_unaligned(<<1,2,3>>),{16#FF,
- -16#7FFF})),
- ?line badarg =
+ -16#7FFF})),
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{16#FF,
- 16#FFFFFFFFFFFFFFFF})),
- ?line badarg =
+ 16#FFFFFFFFFFFFFFFF})),
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
- -16#7FFFFFFFFFFFFFFF-1})),
- ?line badarg =
+ -16#7FFFFFFFFFFFFFFF-1})),
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
- 16#7FFFFFFFFFFFFFFF})),
- ?line [1,2,3] =
+ 16#7FFFFFFFFFFFFFFF})),
+ [1,2,3] =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,[])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{1,2,3})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{1.0,1})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3>>,{1,1.0})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3:3>>,{1,1})),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list(<<1,2,3:3>>)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:bin_to_list([1,2,3])),
- ?line nomatch =
+ nomatch =
?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,{0,0}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:match(<<1,2,3>>,{bm,<<>>},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:match(<<1,2,3>>,[],[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:match(<<1,2,3>>,{ac,<<>>},[{scope,{0,1}}])),
- ?line {bm,BMMagic} = binary:compile_pattern([<<1,2,3>>]),
- ?line {ac,ACMagic} = binary:compile_pattern([<<1,2,3>>,<<4,5>>]),
- ?line badarg =
+ {bm,BMMagic} = binary:compile_pattern([<<1,2,3>>]),
+ {ac,ACMagic} = binary:compile_pattern([<<1,2,3>>,<<4,5>>]),
+ badarg =
?MASK_ERROR(binary:match(<<1,2,3>>,{bm,ACMagic},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:match(<<1,2,3>>,{ac,BMMagic},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:match(<<1,2,3>>,
{bm,ets:match_spec_compile([{'_',[],['$_']}])},
[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:match(<<1,2,3>>,
{ac,ets:match_spec_compile([{'_',[],['$_']}])},
[{scope,{0,1}}])),
- ?line [] =
+ [] =
?MASK_ERROR(binary:matches(<<1,2,3>>,<<1>>,[{scope,{0,0}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:matches(<<1,2,3>>,{bm,<<>>},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:matches(<<1,2,3>>,[],[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:matches(<<1,2,3>>,{ac,<<>>},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:matches(<<1,2,3>>,{bm,ACMagic},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:matches(<<1,2,3>>,{ac,BMMagic},[{scope,{0,1}}])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:matches(<<1,2,3>>,
- {bm,ets:match_spec_compile([{'_',[],['$_']}])},
- [{scope,{0,1}}])),
- ?line badarg =
+ {bm,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
+ badarg =
?MASK_ERROR(
binary:matches(<<1,2,3>>,
- {ac,ets:match_spec_compile([{'_',[],['$_']}])},
- [{scope,{0,1}}])),
+ {ac,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
%% OTP-11350
badarg = ?MASK_ERROR(
binary:matches(<<"foo">>,
[<<>>, <<"f">>])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:longest_common_prefix(
[<<0:10000,1,2,4,1:3>>,
<<0:10000,1,2,3>>])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:longest_common_suffix(
[<<0:10000,1,2,4,1:3>>,
<<0:10000,1,2,3>>])),
- ?line badarg =
+ badarg =
?MASK_ERROR(binary:encode_unsigned(-1)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:encode_unsigned(-16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:first(<<1,2,4,1:3>>)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:first([1,2,4])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:last(<<1,2,4,1:3>>)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:last([1,2,4])),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:at(<<1,2,4,1:3>>,2)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:at(<<>>,2)),
- ?line badarg =
+ badarg =
?MASK_ERROR(
binary:at([1,2,4],2)),
ok.
@@ -264,95 +264,95 @@ badargs(Config) when is_list(Config) ->
%% Whitebox test to force special trap conditions in
%% longest_common_{prefix,suffix}.
longest_common_trap(Config) when is_list(Config) ->
- ?line erts_debug:set_internal_state(available_internal_state,true),
- ?line io:format("oldlimit: ~p~n",
- [erts_debug:set_internal_state(binary_loop_limit,10)]),
+ erts_debug:set_internal_state(available_internal_state,true),
+ io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,10)]),
erlang:bump_reductions(10000000),
- ?line _ = binary:longest_common_prefix(
- [<<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0:10000,1,3,3>>,
- <<0:10000,1,2,4>>]),
- ?line _ = binary:longest_common_prefix(
- [<<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
- <<0:10000,1,2,4>>]),
+ _ = binary:longest_common_prefix(
+ [<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>]),
+ _ = binary:longest_common_prefix(
+ [<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<0:10000,1,2,4>>]),
erlang:bump_reductions(10000000),
- ?line _ = binary:longest_common_suffix(
- [<<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,3,3,0:10000,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
- <<1,2,4,0:10000>>]),
- ?line _ = binary:longest_common_suffix(
- [<<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<1,2,4,0:10000>>,
- <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
- <<1,2,4,0:10000>>]),
+ _ = binary:longest_common_suffix(
+ [<<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,3,3,0:10000,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<1,2,4,0:10000>>]),
+ _ = binary:longest_common_suffix(
+ [<<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<1,2,4,0:10000>>]),
Subj = subj(),
Len = byte_size(Subj),
- ?line Len = binary:longest_common_suffix(
- [Subj,Subj,Subj]),
- ?line io:format("limit was: ~p~n",
- [erts_debug:set_internal_state(binary_loop_limit,
- default)]),
- ?line erts_debug:set_internal_state(available_internal_state,false),
+ Len = binary:longest_common_suffix(
+ [Subj,Subj,Subj]),
+ io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ erts_debug:set_internal_state(available_internal_state,false),
ok.
subj() ->
- Me = self(),
- spawn(fun() ->
- X0 = iolist_to_binary([
- "1234567890",
- lists:duplicate(100, $x)
- ]),
- Me ! X0,
- receive X -> X end
- end),
- X0 = receive A -> A end,
- <<X1:32/binary,_/binary>> = X0,
- Subject= <<X1/binary>>,
- Subject.
+ Me = self(),
+ spawn(fun() ->
+ X0 = iolist_to_binary([
+ "1234567890",
+ lists:duplicate(100, $x)
+ ]),
+ Me ! X0,
+ receive X -> X end
+ end),
+ X0 = receive A -> A end,
+ <<X1:32/binary,_/binary>> = X0,
+ Subject= <<X1/binary>>,
+ Subject.
%% Test correct return values for scopes (OTP-9701).
@@ -364,8 +364,8 @@ scope_return(Config) when is_list(Config) ->
scope_loop(_,N,N) ->
ok;
scope_loop(Bin,N,M) ->
- ?line {N,1} = binary:match(Bin,<<"a">>,[{scope,{N,1}}]),
- ?line {N,1} = binary:match(Bin,[<<"a">>,<<"b">>],[{scope,{N,1}}]),
+ {N,1} = binary:match(Bin,<<"a">>,[{scope,{N,1}}]),
+ {N,1} = binary:match(Bin,[<<"a">>,<<"b">>],[{scope,{N,1}}]),
scope_loop(Bin,N+1,M).
%% Try some interesting patterns.
@@ -374,352 +374,352 @@ interesting(Config) when is_list(Config) ->
X = do_interesting(binref).
do_interesting(Module) ->
- ?line {0,4} = Module:match(<<"123456">>,
+ {0,4} = Module:match(<<"123456">>,
Module:compile_pattern([<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>,<<"6">>])),
- ?line [{0,4},{5,1}] = Module:matches(<<"123456">>,
+ [{0,4},{5,1}] = Module:matches(<<"123456">>,
Module:compile_pattern([<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>,<<"6">>])),
- ?line [{0,4}] = Module:matches(<<"123456">>,
+ [{0,4}] = Module:matches(<<"123456">>,
Module:compile_pattern([<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>])),
- ?line [{0,2},{2,2}] = Module:matches(<<"123456">>,
- Module:compile_pattern([<<"12">>,
- <<"23">>,<<"3">>,
- <<"34">>,<<"456">>,
- <<"45">>])),
- ?line {1,4} = Module:match(<<"123456">>,
+ [{0,2},{2,2}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"12">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>])),
+ {1,4} = Module:match(<<"123456">>,
Module:compile_pattern([<<"34">>,<<"34">>,
<<"12347">>,<<"2345">>])),
- ?line [{1,4}] = Module:matches(<<"123456">>,
+ [{1,4}] = Module:matches(<<"123456">>,
Module:compile_pattern([<<"34">>,<<"34">>,
<<"12347">>,<<"2345">>])),
- ?line [{2,2}] = Module:matches(<<"123456">>,
+ [{2,2}] = Module:matches(<<"123456">>,
Module:compile_pattern([<<"34">>,<<"34">>,
<<"12347">>,<<"2346">>])),
- ?line {0,4} = Module:match(<<"123456">>,
+ {0,4} = Module:match(<<"123456">>,
[<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>,<<"6">>]),
- ?line [{0,4},{5,1}] = Module:matches(<<"123456">>,
+ [{0,4},{5,1}] = Module:matches(<<"123456">>,
[<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>,<<"6">>]),
- ?line [{0,4}] = Module:matches(<<"123456">>,
+ [{0,4}] = Module:matches(<<"123456">>,
[<<"12">>,<<"1234">>,
<<"23">>,<<"3">>,
<<"34">>,<<"456">>,
<<"45">>]),
- ?line [{0,2},{2,2}] = Module:matches(<<"123456">>,
- [<<"12">>,
- <<"23">>,<<"3">>,
- <<"34">>,<<"456">>,
- <<"45">>]),
- ?line {1,4} = Module:match(<<"123456">>,
- [<<"34">>,<<"34">>,
- <<"12347">>,<<"2345">>]),
- ?line [{1,4}] = Module:matches(<<"123456">>,
- [<<"34">>,<<"34">>,
- <<"12347">>,<<"2345">>]),
- ?line [{2,2}] = Module:matches(<<"123456">>,
- [<<"34">>,<<"34">>,
- <<"12347">>,<<"2346">>]),
- ?line nomatch = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
- ?line {1,1} = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,2}}]),
- ?line nomatch = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
- ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
- ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
- ?line badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<2,3>>,
- [{scope,{0,5}}])),
- ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
- ?line {0,3} = Module:match(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
- ?line {0,4} = Module:match(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
- ?line badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<1,2,3,4>>,
- [{scope,{3,-4}}])),
- ?line [] = Module:matches(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
- ?line [{1,1}] = Module:matches(<<1,2,3,4>>,[<<2>>,<<3>>],[{scope,{0,2}}]),
- ?line [] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
- ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
- ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
- ?line [{1,2}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
- [{scope,{0,3}}]),
- ?line [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
- [{scope,{0,4}}]),
- ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<2,3>>,
- [{scope,{0,5}}])),
- ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
- ?line [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
- [{scope,{4,-4}}]),
- ?line [{0,3}] = Module:matches(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
- ?line [{0,4}] = Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
- ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,
- [{scope,{3,-4}}])),
- ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,[<<1,2,3,4>>],
- [{scope,{3,-4}}])),
- ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,<<4,5>>),
- ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>]),
- ?line [<<1,2,3>>,<<6>>,<<8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>],[global]),
- ?line [<<1,2,3>>,<<6>>,<<>>,<<>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],
- [global]),
- ?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],
- [global,trim]),
- ?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],
- [global,trim_all]),
- ?line [<<1,2,3,4,5,6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],
- [global,trim,{scope,{0,4}}]),
- ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [{0,2},{2,2}] = Module:matches(<<"123456">>,
+ [<<"12">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>]),
+ {1,4} = Module:match(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>]),
+ [{1,4}] = Module:matches(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>]),
+ [{2,2}] = Module:matches(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2346">>]),
+ nomatch = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
+ {1,1} = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,2}}]),
+ nomatch = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
+ {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
+ {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
+ badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<2,3>>,
+ [{scope,{0,5}}])),
+ {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
+ {0,3} = Module:match(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
+ {0,4} = Module:match(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
+ badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<1,2,3,4>>,
+ [{scope,{3,-4}}])),
+ [] = Module:matches(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
+ [{1,1}] = Module:matches(<<1,2,3,4>>,[<<2>>,<<3>>],[{scope,{0,2}}]),
+ [] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
+ [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
+ [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
+ [{1,2}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{0,3}}]),
+ [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{0,4}}]),
+ badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<2,3>>,
+ [{scope,{0,5}}])),
+ [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
+ [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{4,-4}}]),
+ [{0,3}] = Module:matches(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
+ [{0,4}] = Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
+ badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,
+ [{scope,{3,-4}}])),
+ badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,[<<1,2,3,4>>],
+ [{scope,{3,-4}}])),
+ [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,<<4,5>>),
+ [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>]),
+ [<<1,2,3>>,<<6>>,<<8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>],[global]),
+ [<<1,2,3>>,<<6>>,<<>>,<<>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
- [global,trim,{scope,{0,5}}]),
-
- ?line [<<>>,<<>>,<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<1>>,<<2>>,<<4,5>>],
- [global,trim]),
- ?line [<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<1>>,<<2>>,<<4,5>>],
- [global,trim_all]),
-
- ?line [<<1,2,3>>,<<>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<6>>],
- [global,trim]),
- ?line [<<1,2,3>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<6>>],
- [global,trim_all]),
- ?line [<<>>,<<>>,<<3>>,<<>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
- [global,trim]),
- ?line [<<3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
- [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
- [global,trim_all]),
+ [global]),
+ [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim]),
+ [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim_all]),
+ [<<1,2,3,4,5,6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim,{scope,{0,4}}]),
+ [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim,{scope,{0,5}}]),
+
+ [<<>>,<<>>,<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim]),
+ [<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim_all]),
+
+ [<<1,2,3>>,<<>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim]),
+ [<<1,2,3>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim_all]),
+ [<<>>,<<>>,<<3>>,<<>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim]),
+ [<<3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim_all]),
[<<>>] = binary:split(<<>>, <<",">>, []),
[] = binary:split(<<>>, <<",">>, [trim]),
[] = binary:split(<<>>, <<",">>, [trim_all]),
[] = binary:split(<<>>, <<",">>, [global,trim]),
[] = binary:split(<<>>, <<",">>, [global,trim_all]),
- ?line badarg = ?MASK_ERROR(
- Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,trim,{scope,{0,5}}])),
- ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,[]),
- ?line <<1,2,3,99,6,99,99>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global]),
- ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,{scope,{0,5}}]),
- ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,{scope,{0,5}}]),
- ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,{scope,{0,5}}]),
- ?line badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,{scope,{0,5}},
- {insert,1}])),
- ?line <<1,2,3,99,4,5,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<99>>,
- [global,{scope,{0,5}},
- {insert_replaced,1}]),
- ?line <<1,2,3,9,4,5,9,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],
- <<9,9>>,
- [global,{scope,{0,5}},
- {insert_replaced,1}]),
- ?line badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
- [<<4,5>>,<<7>>,<<8>>],<<>>,
- [global,{scope,{0,5}},
- {insert_replaced,1}])),
- ?line 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>]),
- ?line 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2>>]),
- ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1>>]),
- ?line 0 = Module:longest_common_prefix([<<1,2,4>>,<<>>]),
- ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>]),
- ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>,<<1,2,4>>]),
- ?line 1251 = Module:longest_common_prefix([<<0:10000,1,2,4>>,
- <<0:10000,1,2,3>>,
- <<0:10000,1,3,3>>,
- <<0:10000,1,2,4>>]),
- ?line 12501 = Module:longest_common_prefix([<<0:100000,1,2,4>>,
- <<0:100000,1,2,3>>,
- <<0:100000,1,3,3>>,
- <<0:100000,1,2,4>>]),
- ?line 1251 = Module:longest_common_prefix(
- [make_unaligned(<<0:10000,1,2,4>>),
- <<0:10000,1,2,3>>,
- make_unaligned(<<0:10000,1,3,3>>),
- <<0:10000,1,2,4>>]),
- ?line 12501 = Module:longest_common_prefix(
- [<<0:100000,1,2,4>>,
- make_unaligned(<<0:100000,1,2,3>>),
- <<0:100000,1,3,3>>,
- make_unaligned(<<0:100000,1,2,4>>)]),
- ?line 1250001 = Module:longest_common_prefix([<<0:10000000,1,2,4>>,
- <<0:10000000,1,2,3>>,
- <<0:10000000,1,3,3>>,
- <<0:10000000,1,2,4>>]),
+ badarg = ?MASK_ERROR(
+ Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,trim,{scope,{0,5}}])),
+ <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,[]),
+ <<1,2,3,99,6,99,99>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global]),
+ <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}},
+ {insert,1}])),
+ <<1,2,3,99,4,5,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}]),
+ <<1,2,3,9,4,5,9,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ <<9,9>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}]),
+ badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}])),
+ 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>]),
+ 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2>>]),
+ 1 = Module:longest_common_prefix([<<1,2,4>>,<<1>>]),
+ 0 = Module:longest_common_prefix([<<1,2,4>>,<<>>]),
+ 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>]),
+ 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>,<<1,2,4>>]),
+ 1251 = Module:longest_common_prefix([<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>]),
+ 12501 = Module:longest_common_prefix([<<0:100000,1,2,4>>,
+ <<0:100000,1,2,3>>,
+ <<0:100000,1,3,3>>,
+ <<0:100000,1,2,4>>]),
+ 1251 = Module:longest_common_prefix(
+ [make_unaligned(<<0:10000,1,2,4>>),
+ <<0:10000,1,2,3>>,
+ make_unaligned(<<0:10000,1,3,3>>),
+ <<0:10000,1,2,4>>]),
+ 12501 = Module:longest_common_prefix(
+ [<<0:100000,1,2,4>>,
+ make_unaligned(<<0:100000,1,2,3>>),
+ <<0:100000,1,3,3>>,
+ make_unaligned(<<0:100000,1,2,4>>)]),
+ 1250001 = Module:longest_common_prefix([<<0:10000000,1,2,4>>,
+ <<0:10000000,1,2,3>>,
+ <<0:10000000,1,3,3>>,
+ <<0:10000000,1,2,4>>]),
if % Too cruel for the reference implementation
Module =:= binary ->
- ?line erts_debug:set_internal_state(available_internal_state,true),
- ?line io:format("oldlimit: ~p~n",
- [erts_debug:set_internal_state(
- binary_loop_limit,100)]),
- ?line 1250001 = Module:longest_common_prefix(
- [<<0:10000000,1,2,4>>,
- <<0:10000000,1,2,3>>,
- <<0:10000000,1,3,3>>,
- <<0:10000000,1,2,4>>]),
- ?line io:format("limit was: ~p~n",
- [erts_debug:set_internal_state(binary_loop_limit,
- default)]),
- ?line erts_debug:set_internal_state(available_internal_state,
- false);
+ erts_debug:set_internal_state(available_internal_state,true),
+ io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(
+ binary_loop_limit,100)]),
+ 1250001 = Module:longest_common_prefix(
+ [<<0:10000000,1,2,4>>,
+ <<0:10000000,1,2,3>>,
+ <<0:10000000,1,3,3>>,
+ <<0:10000000,1,2,4>>]),
+ io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ erts_debug:set_internal_state(available_internal_state,
+ false);
true ->
ok
end,
- ?line 1 = Module:longest_common_suffix([<<0:100000000,1,2,4,5>>,
- <<0:100000000,1,2,3,5>>,
- <<0:100000000,1,3,3,5>>,
- <<0:100000000,1,2,4,5>>]),
- ?line 1 = Module:longest_common_suffix([<<1,2,4,5>>,
- <<0:100000000,1,2,3,5>>,
- <<0:100000000,1,3,3,5>>,
- <<0:100000000,1,2,4,5>>]),
- ?line 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
- <<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5>>]),
- ?line 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
- <<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4>>]),
- ?line 2 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
- <<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5>>,
- <<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<>>,
- <<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 2 = Module:longest_common_suffix([<<5,5>>,<<0:100000000,1,3,3,5,5>>,
- <<0:100000000,1,2,4,5,5>>]),
- ?line 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<4,5,5>>]),
- ?line 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<5,5>>]),
- ?line 3 = Module:longest_common_suffix([<<4,5,5>>,<<4,5,5>>,<<4,5,5>>]),
- ?line 0 = Module:longest_common_suffix([<<>>]),
- ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([apa])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<>>]])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<0>>,
- <<1:9>>]])),
- ?line 0 = Module:longest_common_prefix([<<>>]),
- ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([apa])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<>>]])),
- ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<0>>,
- <<1:9>>]])),
-
- ?line <<1:6,Bin:3/binary,_:2>> = <<1:6,1,2,3,1:2>>,
- ?line <<1,2,3>> = Bin,
- ?line 1 = Module:first(Bin),
- ?line 1 = Module:first(<<1>>),
- ?line 1 = Module:first(<<1,2,3>>),
- ?line badarg = ?MASK_ERROR(Module:first(<<>>)),
- ?line badarg = ?MASK_ERROR(Module:first(apa)),
- ?line 3 = Module:last(Bin),
- ?line 1 = Module:last(<<1>>),
- ?line 3 = Module:last(<<1,2,3>>),
- ?line badarg = ?MASK_ERROR(Module:last(<<>>)),
- ?line badarg = ?MASK_ERROR(Module:last(apa)),
- ?line 1 = Module:at(Bin,0),
- ?line 1 = Module:at(<<1>>,0),
- ?line 1 = Module:at(<<1,2,3>>,0),
- ?line 2 = Module:at(<<1,2,3>>,1),
- ?line 3 = Module:at(<<1,2,3>>,2),
- ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,3)),
- ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,-1)),
- ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,apa)),
- ?line "hejsan" = [ Module:at(<<"hejsan">>,I) || I <- lists:seq(0,5) ],
-
- ?line badarg = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-4)),
- ?line [1,2,3] = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-3)),
-
- ?line badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,big)),
- ?line badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,little)),
- ?line badarg = ?MASK_ERROR(Module:decode_unsigned(apa)),
- ?line badarg = ?MASK_ERROR(Module:decode_unsigned(125,little)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,little)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,big)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,little)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,big)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),
- little)),
- ?line 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),big)),
- ?line badarg = ?MASK_ERROR(Module:encode_unsigned(apa)),
- ?line badarg = ?MASK_ERROR(Module:encode_unsigned(125.3,little)),
- ?line badarg = ?MASK_ERROR(Module:encode_unsigned({1},little)),
- ?line badarg = ?MASK_ERROR(Module:encode_unsigned([1],little)),
- ?line <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,little)),
- ?line <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,big)),
+ 1 = Module:longest_common_suffix([<<0:100000000,1,2,4,5>>,
+ <<0:100000000,1,2,3,5>>,
+ <<0:100000000,1,3,3,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ 1 = Module:longest_common_suffix([<<1,2,4,5>>,
+ <<0:100000000,1,2,3,5>>,
+ <<0:100000000,1,3,3,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4>>]),
+ 2 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 2 = Module:longest_common_suffix([<<5,5>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<4,5,5>>]),
+ 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<5,5>>]),
+ 3 = Module:longest_common_suffix([<<4,5,5>>,<<4,5,5>>,<<4,5,5>>]),
+ 0 = Module:longest_common_suffix([<<>>]),
+ badarg = ?MASK_ERROR(Module:longest_common_suffix([])),
+ badarg = ?MASK_ERROR(Module:longest_common_suffix([apa])),
+ badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<>>]])),
+ badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<0>>,
+ <<1:9>>]])),
+ 0 = Module:longest_common_prefix([<<>>]),
+ badarg = ?MASK_ERROR(Module:longest_common_prefix([])),
+ badarg = ?MASK_ERROR(Module:longest_common_prefix([apa])),
+ badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<>>]])),
+ badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<0>>,
+ <<1:9>>]])),
+
+ <<1:6,Bin:3/binary,_:2>> = <<1:6,1,2,3,1:2>>,
+ <<1,2,3>> = Bin,
+ 1 = Module:first(Bin),
+ 1 = Module:first(<<1>>),
+ 1 = Module:first(<<1,2,3>>),
+ badarg = ?MASK_ERROR(Module:first(<<>>)),
+ badarg = ?MASK_ERROR(Module:first(apa)),
+ 3 = Module:last(Bin),
+ 1 = Module:last(<<1>>),
+ 3 = Module:last(<<1,2,3>>),
+ badarg = ?MASK_ERROR(Module:last(<<>>)),
+ badarg = ?MASK_ERROR(Module:last(apa)),
+ 1 = Module:at(Bin,0),
+ 1 = Module:at(<<1>>,0),
+ 1 = Module:at(<<1,2,3>>,0),
+ 2 = Module:at(<<1,2,3>>,1),
+ 3 = Module:at(<<1,2,3>>,2),
+ badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,3)),
+ badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,-1)),
+ badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,apa)),
+ "hejsan" = [ Module:at(<<"hejsan">>,I) || I <- lists:seq(0,5) ],
+
+ badarg = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-4)),
+ [1,2,3] = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-3)),
+
+ badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,big)),
+ badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,little)),
+ badarg = ?MASK_ERROR(Module:decode_unsigned(apa)),
+ badarg = ?MASK_ERROR(Module:decode_unsigned(125,little)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,little)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,big)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,little)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,big)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),
+ little)),
+ 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),big)),
+ badarg = ?MASK_ERROR(Module:encode_unsigned(apa)),
+ badarg = ?MASK_ERROR(Module:encode_unsigned(125.3,little)),
+ badarg = ?MASK_ERROR(Module:encode_unsigned({1},little)),
+ badarg = ?MASK_ERROR(Module:encode_unsigned([1],little)),
+ <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,little)),
+ <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,big)),
ok.
%% Test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2.
encode_decode(Config) when is_list(Config) ->
rand:seed(exsplus, {1271,769940,559934}),
- ?line ok = encode_decode_loop({1,200},1000), % Need to be long enough
- % to create offheap binaries
+ ok = encode_decode_loop({1,200},1000), % Need to be long enough
+ % to create offheap binaries
ok.
encode_decode_loop(_Range,0) ->
ok;
encode_decode_loop(Range, X) ->
- ?line N = random_number(Range),
- ?line A = binary:encode_unsigned(N),
- ?line B = binary:encode_unsigned(N,big),
- ?line C = binref:encode_unsigned(N),
- ?line D = binref:encode_unsigned(N,big),
- ?line E = binary:encode_unsigned(N,little),
- ?line F = binref:encode_unsigned(N,little),
- ?line G = binary:decode_unsigned(A),
- ?line H = binary:decode_unsigned(A,big),
- ?line I = binref:decode_unsigned(A),
- ?line J = binary:decode_unsigned(E,little),
- ?line K = binref:decode_unsigned(E,little),
- ?line L = binary:decode_unsigned(make_unaligned(A)),
- ?line M = binary:decode_unsigned(make_unaligned(E),little),
- ?line PaddedBig = <<0:48,A/binary>>,
- ?line PaddedLittle = <<E/binary,0:48>>,
- ?line O = binary:decode_unsigned(PaddedBig),
- ?line P = binary:decode_unsigned(make_unaligned(PaddedBig)),
- ?line Q = binary:decode_unsigned(PaddedLittle,little),
- ?line R = binary:decode_unsigned(make_unaligned(PaddedLittle),little),
- ?line S = binref:decode_unsigned(PaddedLittle,little),
- ?line T = binref:decode_unsigned(PaddedBig),
+ N = random_number(Range),
+ A = binary:encode_unsigned(N),
+ B = binary:encode_unsigned(N,big),
+ C = binref:encode_unsigned(N),
+ D = binref:encode_unsigned(N,big),
+ E = binary:encode_unsigned(N,little),
+ F = binref:encode_unsigned(N,little),
+ G = binary:decode_unsigned(A),
+ H = binary:decode_unsigned(A,big),
+ I = binref:decode_unsigned(A),
+ J = binary:decode_unsigned(E,little),
+ K = binref:decode_unsigned(E,little),
+ L = binary:decode_unsigned(make_unaligned(A)),
+ M = binary:decode_unsigned(make_unaligned(E),little),
+ PaddedBig = <<0:48,A/binary>>,
+ PaddedLittle = <<E/binary,0:48>>,
+ O = binary:decode_unsigned(PaddedBig),
+ P = binary:decode_unsigned(make_unaligned(PaddedBig)),
+ Q = binary:decode_unsigned(PaddedLittle,little),
+ R = binary:decode_unsigned(make_unaligned(PaddedLittle),little),
+ S = binref:decode_unsigned(PaddedLittle,little),
+ T = binref:decode_unsigned(PaddedBig),
case (((A =:= B) and (B =:= C) and (C =:= D)) and
- ((E =:= F)) and
- ((N =:= G) and (G =:= H) and (H =:= I) and
- (I =:= J) and (J =:= K) and (K =:= L) and (L =:= M)) and
- ((M =:= O) and (O =:= P) and (P =:= Q) and (Q =:= R) and
- (R =:= S) and (S =:= T)))of
+ ((E =:= F)) and
+ ((N =:= G) and (G =:= H) and (H =:= I) and
+ (I =:= J) and (J =:= K) and (K =:= L) and (L =:= M)) and
+ ((M =:= O) and (O =:= P) and (P =:= Q) and (Q =:= R) and
+ (R =:= S) and (S =:= T)))of
true ->
encode_decode_loop(Range,X-1);
_ ->
@@ -734,26 +734,26 @@ guard(Config) when is_list(Config) ->
%% Test referenced_byte_size/1 bif.
referenced(Config) when is_list(Config) ->
- ?line badarg = ?MASK_ERROR(binary:referenced_byte_size([])),
- ?line badarg = ?MASK_ERROR(binary:referenced_byte_size(apa)),
- ?line badarg = ?MASK_ERROR(binary:referenced_byte_size({})),
- ?line badarg = ?MASK_ERROR(binary:referenced_byte_size(1)),
- ?line A = <<1,2,3>>,
- ?line B = binary:copy(A,1000),
- ?line 3 = binary:referenced_byte_size(A),
- ?line 3000 = binary:referenced_byte_size(B),
- ?line <<_:8,C:2/binary>> = A,
- ?line 3 = binary:referenced_byte_size(C),
- ?line 2 = binary:referenced_byte_size(binary:copy(C)),
- ?line <<_:7,D:2/binary,_:1>> = A,
- ?line 2 = binary:referenced_byte_size(binary:copy(D)),
- ?line 3 = binary:referenced_byte_size(D),
- ?line <<_:8,E:2/binary,_/binary>> = B,
- ?line 3000 = binary:referenced_byte_size(E),
- ?line 2 = binary:referenced_byte_size(binary:copy(E)),
- ?line <<_:7,F:2/binary,_:1,_/binary>> = B,
- ?line 2 = binary:referenced_byte_size(binary:copy(F)),
- ?line 3000 = binary:referenced_byte_size(F),
+ badarg = ?MASK_ERROR(binary:referenced_byte_size([])),
+ badarg = ?MASK_ERROR(binary:referenced_byte_size(apa)),
+ badarg = ?MASK_ERROR(binary:referenced_byte_size({})),
+ badarg = ?MASK_ERROR(binary:referenced_byte_size(1)),
+ A = <<1,2,3>>,
+ B = binary:copy(A,1000),
+ 3 = binary:referenced_byte_size(A),
+ 3000 = binary:referenced_byte_size(B),
+ <<_:8,C:2/binary>> = A,
+ 3 = binary:referenced_byte_size(C),
+ 2 = binary:referenced_byte_size(binary:copy(C)),
+ <<_:7,D:2/binary,_:1>> = A,
+ 2 = binary:referenced_byte_size(binary:copy(D)),
+ 3 = binary:referenced_byte_size(D),
+ <<_:8,E:2/binary,_/binary>> = B,
+ 3000 = binary:referenced_byte_size(E),
+ 2 = binary:referenced_byte_size(binary:copy(E)),
+ <<_:7,F:2/binary,_:1,_/binary>> = B,
+ 2 = binary:referenced_byte_size(binary:copy(F)),
+ 3000 = binary:referenced_byte_size(F),
ok.
@@ -761,53 +761,53 @@ referenced(Config) when is_list(Config) ->
%% Test list_to_bin/1 BIF.
list_to_bin(Config) when is_list(Config) ->
%% Just some smoke_tests first, then go nuts with random cases
- ?line badarg = ?MASK_ERROR(binary:list_to_bin({})),
- ?line badarg = ?MASK_ERROR(binary:list_to_bin(apa)),
- ?line badarg = ?MASK_ERROR(binary:list_to_bin(<<"apa">>)),
+ badarg = ?MASK_ERROR(binary:list_to_bin({})),
+ badarg = ?MASK_ERROR(binary:list_to_bin(apa)),
+ badarg = ?MASK_ERROR(binary:list_to_bin(<<"apa">>)),
F1 = fun(L) ->
?MASK_ERROR(binref:list_to_bin(L))
end,
F2 = fun(L) ->
?MASK_ERROR(binary:list_to_bin(L))
end,
- ?line random_iolist:run(1000,F1,F2),
+ random_iolist:run(1000,F1,F2),
ok.
%% Test copy/1,2 BIFs.
copy(Config) when is_list(Config) ->
- ?line <<1,2,3>> = binary:copy(<<1,2,3>>),
- ?line RS = random_string({1,10000}),
- ?line RS = RS2 = binary:copy(RS),
- ?line false = erts_debug:same(RS,RS2),
- ?line <<>> = ?MASK_ERROR(binary:copy(<<1,2,3>>,0)),
- ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3:3>>,2)),
- ?line badarg = ?MASK_ERROR(binary:copy([],0)),
- ?line <<>> = ?MASK_ERROR(binary:copy(<<>>,0)),
- ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,1.0)),
- ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,
- 16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
- ?line <<>> = binary:copy(<<>>,10000),
+ <<1,2,3>> = binary:copy(<<1,2,3>>),
+ RS = random_string({1,10000}),
+ RS = RS2 = binary:copy(RS),
+ false = erts_debug:same(RS,RS2),
+ <<>> = ?MASK_ERROR(binary:copy(<<1,2,3>>,0)),
+ badarg = ?MASK_ERROR(binary:copy(<<1,2,3:3>>,2)),
+ badarg = ?MASK_ERROR(binary:copy([],0)),
+ <<>> = ?MASK_ERROR(binary:copy(<<>>,0)),
+ badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,1.0)),
+ badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,
+ 16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
+ <<>> = binary:copy(<<>>,10000),
rand:seed(exsplus, {1271,769940,559934}),
- ?line ok = random_copy(3000),
- ?line erts_debug:set_internal_state(available_internal_state,true),
- ?line io:format("oldlimit: ~p~n",
- [erts_debug:set_internal_state(binary_loop_limit,10)]),
- ?line Subj = subj(),
- ?line XX = binary:copy(Subj,1000),
- ?line XX = binref:copy(Subj,1000),
- ?line ok = random_copy(1000),
- ?line kill_copy_loop(1000),
- ?line io:format("limit was: ~p~n",
- [erts_debug:set_internal_state(binary_loop_limit,
- default)]),
- ?line erts_debug:set_internal_state(available_internal_state,false),
+ ok = random_copy(3000),
+ erts_debug:set_internal_state(available_internal_state,true),
+ io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,10)]),
+ Subj = subj(),
+ XX = binary:copy(Subj,1000),
+ XX = binref:copy(Subj,1000),
+ ok = random_copy(1000),
+ kill_copy_loop(1000),
+ io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ erts_debug:set_internal_state(available_internal_state,false),
ok.
kill_copy_loop(0) ->
ok;
kill_copy_loop(N) ->
{Pid,Ref} = spawn_monitor(fun() ->
- ok = random_copy(1000)
+ ok = random_copy(1000)
end),
receive
after 10 ->
@@ -843,30 +843,30 @@ random_copy(N) ->
%% Test bin_to_list/1,2,3 BIFs.
bin_to_list(Config) when is_list(Config) ->
%% Just some smoke_tests first, then go nuts with random cases
- ?line X = <<1,2,3,4,0:1000000,5>>,
- ?line Y = make_unaligned(X),
- ?line LX = binary:bin_to_list(X),
- ?line LX = binary:bin_to_list(X,0,byte_size(X)),
- ?line LX = binary:bin_to_list(X,byte_size(X),-byte_size(X)),
- ?line LX = binary:bin_to_list(X,{0,byte_size(X)}),
- ?line LX = binary:bin_to_list(X,{byte_size(X),-byte_size(X)}),
- ?line LY = binary:bin_to_list(Y),
- ?line LY = binary:bin_to_list(Y,0,byte_size(Y)),
- ?line LY = binary:bin_to_list(Y,byte_size(Y),-byte_size(Y)),
- ?line LY = binary:bin_to_list(Y,{0,byte_size(Y)}),
- ?line LY = binary:bin_to_list(Y,{byte_size(Y),-byte_size(Y)}),
- ?line 1 = hd(LX),
- ?line 5 = lists:last(LX),
- ?line 1 = hd(LY),
- ?line 5 = lists:last(LY),
- ?line X = list_to_binary(LY),
- ?line Y = list_to_binary(LY),
- ?line X = list_to_binary(LY),
- ?line [5] = lists:nthtail(byte_size(X)-1,LX),
- ?line [0,5] = lists:nthtail(byte_size(X)-2,LX),
- ?line [0,5] = lists:nthtail(byte_size(Y)-2,LY),
+ X = <<1,2,3,4,0:1000000,5>>,
+ Y = make_unaligned(X),
+ LX = binary:bin_to_list(X),
+ LX = binary:bin_to_list(X,0,byte_size(X)),
+ LX = binary:bin_to_list(X,byte_size(X),-byte_size(X)),
+ LX = binary:bin_to_list(X,{0,byte_size(X)}),
+ LX = binary:bin_to_list(X,{byte_size(X),-byte_size(X)}),
+ LY = binary:bin_to_list(Y),
+ LY = binary:bin_to_list(Y,0,byte_size(Y)),
+ LY = binary:bin_to_list(Y,byte_size(Y),-byte_size(Y)),
+ LY = binary:bin_to_list(Y,{0,byte_size(Y)}),
+ LY = binary:bin_to_list(Y,{byte_size(Y),-byte_size(Y)}),
+ 1 = hd(LX),
+ 5 = lists:last(LX),
+ 1 = hd(LY),
+ 5 = lists:last(LY),
+ X = list_to_binary(LY),
+ Y = list_to_binary(LY),
+ X = list_to_binary(LY),
+ [5] = lists:nthtail(byte_size(X)-1,LX),
+ [0,5] = lists:nthtail(byte_size(X)-2,LX),
+ [0,5] = lists:nthtail(byte_size(Y)-2,LY),
rand:seed(exsplus, {1271,769940,559934}),
- ?line ok = random_bin_to_list(5000),
+ ok = random_bin_to_list(5000),
ok.
random_bin_to_list(0) ->
@@ -877,10 +877,10 @@ random_bin_to_list(N) ->
Parts1 = Parts0 ++ [ {X+Y,-Y} || {X,Y} <- Parts0 ],
[ begin
try
- true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
- ?MASK_ERROR(binref:bin_to_list(Str,Z)),
- true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
- ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),Z))
+ true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
+ ?MASK_ERROR(binref:bin_to_list(Str,Z)),
+ true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
+ ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),Z))
catch
_:_ ->
io:format("Error, Str = <<\"~s\">>.~nZ = ~p.~n",
@@ -890,10 +890,10 @@ random_bin_to_list(N) ->
end || Z <- Parts1 ],
[ begin
try
- true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
- ?MASK_ERROR(binref:bin_to_list(Str,A,B)),
- true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
- ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),A,B))
+ true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
+ ?MASK_ERROR(binref:bin_to_list(Str,A,B)),
+ true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
+ ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),A,B))
catch
_:_ ->
io:format("Error, Str = <<\"~s\">>.~nA = ~p.~nB = ~p.~n",
@@ -906,33 +906,33 @@ random_bin_to_list(N) ->
%% Test the part/2,3 BIFs.
parts(Config) when is_list(Config) ->
%% Some simple smoke tests to begin with
- ?line Simple = <<1,2,3,4,5,6,7,8>>,
- ?line <<1,2>> = binary:part(Simple,0,2),
- ?line <<1,2>> = binary:part(Simple,{0,2}),
- ?line Simple = binary:part(Simple,0,8),
- ?line Simple = binary:part(Simple,{0,8}),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,0,9)),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{0,9})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,1,8)),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{1,8})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{3,-4})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{3.0,1})),
- ?line badarg = ?MASK_ERROR(
- binary:part(Simple,{16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFF
- ,1})),
- ?line <<2,3,4,5,6,7,8>> = binary:part(Simple,{1,7}),
- ?line <<2,3,4,5,6,7,8>> = binary:part(Simple,{8,-7}),
- ?line Simple = binary:part(Simple,{8,-8}),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{1,-8})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{8,-9})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{0,-1})),
- ?line <<>> = binary:part(Simple,{8,0}),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{9,0})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{-1,0})),
- ?line badarg = ?MASK_ERROR(binary:part(Simple,{7,2})),
- ?line <<8>> = binary:part(Simple,{7,1}),
+ Simple = <<1,2,3,4,5,6,7,8>>,
+ <<1,2>> = binary:part(Simple,0,2),
+ <<1,2>> = binary:part(Simple,{0,2}),
+ Simple = binary:part(Simple,0,8),
+ Simple = binary:part(Simple,{0,8}),
+ badarg = ?MASK_ERROR(binary:part(Simple,0,9)),
+ badarg = ?MASK_ERROR(binary:part(Simple,{0,9})),
+ badarg = ?MASK_ERROR(binary:part(Simple,1,8)),
+ badarg = ?MASK_ERROR(binary:part(Simple,{1,8})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{3,-4})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{3.0,1})),
+ badarg = ?MASK_ERROR(
+ binary:part(Simple,{16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFF
+ ,1})),
+ <<2,3,4,5,6,7,8>> = binary:part(Simple,{1,7}),
+ <<2,3,4,5,6,7,8>> = binary:part(Simple,{8,-7}),
+ Simple = binary:part(Simple,{8,-8}),
+ badarg = ?MASK_ERROR(binary:part(Simple,{1,-8})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{8,-9})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{0,-1})),
+ <<>> = binary:part(Simple,{8,0}),
+ badarg = ?MASK_ERROR(binary:part(Simple,{9,0})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{-1,0})),
+ badarg = ?MASK_ERROR(binary:part(Simple,{7,2})),
+ <<8>> = binary:part(Simple,{7,1}),
rand:seed(exsplus, {1271,769940,559934}),
- ?line random_parts(5000),
+ random_parts(5000),
ok.
@@ -1009,11 +1009,11 @@ random_ref_sr_comp(Config) when is_list(Config) ->
%% Test pseudorandomly generated cases against reference implementation
%% of split and replace.
random_ref_fla_comp(Config) when is_list(Config) ->
- ?line put(success_counter,0),
+ put(success_counter,0),
rand:seed(exsplus, {1271,769940,559934}),
- ?line do_random_first_comp(5000,{1,1000}),
- ?line do_random_last_comp(5000,{1,1000}),
- ?line do_random_at_comp(5000,{1,1000}),
+ do_random_first_comp(5000,{1,1000}),
+ do_random_last_comp(5000,{1,1000}),
+ do_random_at_comp(5000,{1,1000}),
io:format("Number of successes: ~p~n",[get(success_counter)]),
ok.
@@ -1293,7 +1293,7 @@ do_random_replace_comp(N,NeedleRange,HaystackRange) ->
true = do_replace_comp(Needle,Haystack,Repl,[]),
true = do_replace_comp(Needle,Haystack,Repl,[global]),
true = do_replace_comp(Needle,Haystack,Repl,
- [global,{insert_replaced,Insertat}]),
+ [global,{insert_replaced,Insertat}]),
do_random_replace_comp(N-1,NeedleRange,HaystackRange).
do_random_replace_comp2(0,_,_) ->
ok;
@@ -1307,7 +1307,7 @@ do_random_replace_comp2(N,NeedleRange,HaystackRange) ->
true = do_replace_comp(Needles,Haystack,Repl,[]),
true = do_replace_comp(Needles,Haystack,Repl,[global]),
true = do_replace_comp(Needles,Haystack,Repl,
- [global,{insert_replaced,Insertat}]),
+ [global,{insert_replaced,Insertat}]),
do_random_replace_comp2(N-1,NeedleRange,HaystackRange).
do_replace_comp(N,H,R,Opts) ->
@@ -1343,7 +1343,7 @@ one_random(N) ->
$Ä,$Ö,$0,$1,$2,$3,$4,$5,$6,$7,$8,$9}).
random_number({Min,Max}) -> % Min and Max are *length* of number in
- % decimal positions
+ % decimal positions
X = rand:uniform(Max - Min + 1) + Min - 1,
list_to_integer([one_random_number(rand:uniform(10)) || _ <- lists:seq(1,X)]).
diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl
index 0843fcc0de..c46434f599 100644
--- a/lib/stdlib/test/c_SUITE.erl
+++ b/lib/stdlib/test/c_SUITE.erl
@@ -52,17 +52,17 @@ end_per_group(_GroupName, Config) ->
%% OTP-1209: Check that c:c/2 works also with option 'outdir'.
c_1(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m.erl"),
- ?line W = ?config(priv_dir, Config),
- ?line Result = c(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m.erl"),
+ W = ?config(priv_dir, Config),
+ Result = c(R,[{outdir,W}]),
+ {ok, m} = Result.
%% OTP-1209: Check that c:c/2 works also with option 'outdir'.
c_2(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m"),
- ?line W = ?config(priv_dir, Config),
- ?line Result = c(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m"),
+ W = ?config(priv_dir, Config),
+ Result = c(R,[{outdir,W}]),
+ {ok, m} = Result.
%%% Put results in current directory (or rather, change current dir
@@ -71,36 +71,36 @@ c_2(Config) when is_list(Config) ->
%% OTP-1209: Check that c:c/2 works also with option 'outdir'
%% (same as current directory).
c_3(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m.erl"),
- ?line W = ?config(priv_dir, Config),
- ?line file:set_cwd(W),
- ?line Result = c(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m.erl"),
+ W = ?config(priv_dir, Config),
+ file:set_cwd(W),
+ Result = c(R,[{outdir,W}]),
+ {ok, m} = Result.
%% OTP-1209: Check that c:c/2 works also with option 'outdir'
%% (same as current directory).
c_4(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m"),
- ?line W = ?config(priv_dir, Config),
- ?line file:set_cwd(W),
- ?line Result = c(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m"),
+ W = ?config(priv_dir, Config),
+ file:set_cwd(W),
+ Result = c(R,[{outdir,W}]),
+ {ok, m} = Result.
%%% Write output to a directory other than current directory:
%% Check that c:nc/2 works also with option 'outdir'.
nc_1(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m.erl"),
- ?line W = ?config(priv_dir, Config),
- ?line Result = nc(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m.erl"),
+ W = ?config(priv_dir, Config),
+ Result = nc(R,[{outdir,W}]),
+ {ok, m} = Result.
%% Check that c:nc/2 works also with option 'outdir'.
nc_2(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m"),
- ?line W = ?config(priv_dir, Config),
- ?line Result = nc(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m"),
+ W = ?config(priv_dir, Config),
+ Result = nc(R,[{outdir,W}]),
+ {ok, m} = Result.
%%% Put results in current directory (or rather, change current dir
@@ -109,20 +109,20 @@ nc_2(Config) when is_list(Config) ->
%% Check that c:nc/2 works also with option 'outdir'
%% (same as current directory).
nc_3(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m.erl"),
- ?line W = ?config(priv_dir, Config),
- ?line file:set_cwd(W),
- ?line Result = nc(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m.erl"),
+ W = ?config(priv_dir, Config),
+ file:set_cwd(W),
+ Result = nc(R,[{outdir,W}]),
+ {ok, m} = Result.
%% Check that c:nc/2 works also with option 'outdir'
%% (same as current directory).
nc_4(Config) when is_list(Config) ->
- ?line R = filename:join(?config(data_dir, Config), "m"),
- ?line W = ?config(priv_dir, Config),
- ?line file:set_cwd(W),
- ?line Result = nc(R,[{outdir,W}]),
- ?line {ok, m} = Result.
+ R = filename:join(?config(data_dir, Config), "m"),
+ W = ?config(priv_dir, Config),
+ file:set_cwd(W),
+ Result = nc(R,[{outdir,W}]),
+ {ok, m} = Result.
ls(Config) when is_list(Config) ->
Directory = ?config(data_dir, Config),
@@ -134,33 +134,33 @@ ls(Config) when is_list(Config) ->
%% Check that c:memory/[0,1] returns consistent results.
memory(Config) when is_list(Config) ->
try
- ?line ML = c:memory(),
- ?line T = mget(total, ML),
- ?line P = mget(processes, ML),
- ?line S = mget(system, ML),
- ?line A = mget(atom, ML),
- ?line AU = mget(atom_used, ML),
- ?line B = mget(binary, ML),
- ?line C = mget(code, ML),
- ?line E = mget(ets, ML),
- ?line T = P + S,
- ?line if S >= A + B + C + E -> ok end,
- ?line if A >= AU -> ok end,
- ?line ok
+ ML = c:memory(),
+ T = mget(total, ML),
+ P = mget(processes, ML),
+ S = mget(system, ML),
+ A = mget(atom, ML),
+ AU = mget(atom_used, ML),
+ B = mget(binary, ML),
+ C = mget(code, ML),
+ E = mget(ets, ML),
+ T = P + S,
+ if S >= A + B + C + E -> ok end,
+ if A >= AU -> ok end,
+ ok
catch
error:notsup ->
- ?line {skipped,
- "erlang:memory/[0,1] and c:memory/[0,1] not supported"}
+ {skipped,
+ "erlang:memory/[0,1] and c:memory/[0,1] not supported"}
end.
%% Help function for c_SUITE:memory/1
mget(K, L) ->
- ?line {value,{K,V}} = lists:keysearch(K, 1, L),
- ?line test_v(c:memory(K)), % Check that c:memory/1 also accept this
- % argument and returns an integer (usally
- % *not* the same as V).
- ?line test_v(V).
+ {value,{K,V}} = lists:keysearch(K, 1, L),
+ test_v(c:memory(K)), % Check that c:memory/1 also accept this
+ % argument and returns an integer (usally
+ % *not* the same as V).
+ test_v(V).
%% Help function for c_SUITE:memory/1
test_v(V) when is_integer(V) ->
- ?line V.
+ V.
diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl
index d3e56fc314..7372288492 100644
--- a/lib/stdlib/test/calendar_SUITE.erl
+++ b/lib/stdlib/test/calendar_SUITE.erl
@@ -61,42 +61,42 @@ end_per_group(_GroupName, Config) ->
%% are each others inverses from ?START_YEAR-01-01 up to ?END_YEAR-01-01.
%% At the same time valid_date is tested.
gregorian_days(Config) when is_list(Config) ->
- ?line Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
- ?line MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
- ?line check_gregorian_days(Days, MaxDays).
+ Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
+ MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
+ check_gregorian_days(Days, MaxDays).
%% Tests that datetime_to_gregorian_seconds and
%% gregorian_seconds_to_date are each others inverses for a sampled
%% number of seconds from ?START_YEAR-01-01 up to ?END_YEAR-01-01: We check
%% every 2 days + 1 second.
gregorian_seconds(Config) when is_list(Config) ->
- ?line Secs = calendar:datetime_to_gregorian_seconds({{?START_YEAR, 1, 1},
- {0, 0, 0}}),
- ?line MaxSecs = calendar:datetime_to_gregorian_seconds({{?END_YEAR, 1, 1},
- {0, 0, 0}}),
- ?line check_gregorian_seconds(Secs, MaxSecs).
+ Secs = calendar:datetime_to_gregorian_seconds({{?START_YEAR, 1, 1},
+ {0, 0, 0}}),
+ MaxSecs = calendar:datetime_to_gregorian_seconds({{?END_YEAR, 1, 1},
+ {0, 0, 0}}),
+ check_gregorian_seconds(Secs, MaxSecs).
%% Tests that day_of_the_week reports correctly the day of the week from
%% year ?START_YEAR up to ?END_YEAR.
day_of_the_week(Config) when is_list(Config) ->
- ?line Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
- ?line MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
- ?line DayNumber = calendar:day_of_the_week({?START_YEAR, 1, 1}),
- ?line check_day_of_the_week(Days, MaxDays, DayNumber).
+ Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
+ MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
+ DayNumber = calendar:day_of_the_week({?START_YEAR, 1, 1}),
+ check_day_of_the_week(Days, MaxDays, DayNumber).
%% Tests that day_of_the_week for 1997-11-11 is Tuesday (2).
day_of_the_week_calibrate(Config) when is_list(Config) ->
- ?line 2 = calendar:day_of_the_week({1997, 11, 11}).
+ 2 = calendar:day_of_the_week({1997, 11, 11}).
%% Tests that is_leap_year reports correctly the leap years from
%% year ?START_YEAR up to ?END_YEAR.
leap_years(Config) when is_list(Config) ->
- ?line check_leap_years(?START_YEAR, ?END_YEAR).
+ check_leap_years(?START_YEAR, ?END_YEAR).
%% Tests that last_day_of_the_month reports correctly from
%% year ?START_YEAR up to ?END_YEAR.
last_day_of_the_month(Config) when is_list(Config) ->
- ?line check_last_day_of_the_month({?START_YEAR, 1}, {?END_YEAR, 1}).
+ check_last_day_of_the_month({?START_YEAR, 1}, {?END_YEAR, 1}).
%% Tests local_time_to_universal_time_dst for MET.
local_time_to_universal_time_dst(Config) when is_list(Config) ->
@@ -113,35 +113,35 @@ local_time_to_universal_time_dst(Config) when is_list(Config) ->
end.
local_time_to_universal_time_dst_x(Config) when is_list(Config) ->
%% Assumes MET (UTC+1 / UTC+2(dst)
- ?line LtW = {{2003,01,15},{14,00,00}}, % Winter
- ?line UtW = {{2003,01,15},{13,00,00}}, %
- ?line UtWd = {{2003,01,15},{12,00,00}}, % dst
- ?line LtS = {{2003,07,15},{14,00,00}}, % Summer
- ?line UtS = {{2003,07,15},{13,00,00}}, %
- ?line UtSd = {{2003,07,15},{12,00,00}}, % dst
- ?line LtWS = {{2003,03,30},{02,30,00}}, % Winter->Summer
- ?line UtWS = {{2003,03,30},{01,30,00}}, %
- ?line UtWSd = {{2003,03,30},{00,30,00}}, % dst
- ?line LtSW = {{2003,10,26},{02,30,00}}, % Summer->Winter
- ?line UtSW = {{2003,10,26},{01,30,00}}, %
- ?line UtSWd = {{2003,10,26},{00,30,00}}, % dst
+ LtW = {{2003,01,15},{14,00,00}}, % Winter
+ UtW = {{2003,01,15},{13,00,00}}, %
+ UtWd = {{2003,01,15},{12,00,00}}, % dst
+ LtS = {{2003,07,15},{14,00,00}}, % Summer
+ UtS = {{2003,07,15},{13,00,00}}, %
+ UtSd = {{2003,07,15},{12,00,00}}, % dst
+ LtWS = {{2003,03,30},{02,30,00}}, % Winter->Summer
+ UtWS = {{2003,03,30},{01,30,00}}, %
+ UtWSd = {{2003,03,30},{00,30,00}}, % dst
+ LtSW = {{2003,10,26},{02,30,00}}, % Summer->Winter
+ UtSW = {{2003,10,26},{01,30,00}}, %
+ UtSWd = {{2003,10,26},{00,30,00}}, % dst
%%
- ?line UtW = calendar:local_time_to_universal_time(LtW, false),
- ?line UtWd = calendar:local_time_to_universal_time(LtW, true),
- ?line UtW = calendar:local_time_to_universal_time(LtW, undefined),
+ UtW = calendar:local_time_to_universal_time(LtW, false),
+ UtWd = calendar:local_time_to_universal_time(LtW, true),
+ UtW = calendar:local_time_to_universal_time(LtW, undefined),
%%
- ?line UtS = calendar:local_time_to_universal_time(LtS, false),
- ?line UtSd = calendar:local_time_to_universal_time(LtS, true),
- ?line UtSd = calendar:local_time_to_universal_time(LtS, undefined),
+ UtS = calendar:local_time_to_universal_time(LtS, false),
+ UtSd = calendar:local_time_to_universal_time(LtS, true),
+ UtSd = calendar:local_time_to_universal_time(LtS, undefined),
%%
case calendar:local_time_to_universal_time(LtWS, false) of
UtWS ->
- ?line UtWSd = calendar:local_time_to_universal_time(LtWS, true),
- ?line [] = calendar:local_time_to_universal_time_dst(LtWS),
+ UtWSd = calendar:local_time_to_universal_time(LtWS, true),
+ [] = calendar:local_time_to_universal_time_dst(LtWS),
%%
- ?line UtSW = calendar:local_time_to_universal_time(LtSW, false),
- ?line UtSWd = calendar:local_time_to_universal_time(LtSW, true),
- ?line [UtSWd, UtSW] = calendar:local_time_to_universal_time_dst(LtSW),
+ UtSW = calendar:local_time_to_universal_time(LtSW, false),
+ UtSWd = calendar:local_time_to_universal_time(LtSW, true),
+ [UtSWd, UtSW] = calendar:local_time_to_universal_time_dst(LtSW),
ok;
{{1969,12,31},{23,59,59}} ->
%% It seems that Apple has no intention of fixing this bug in
@@ -155,7 +155,7 @@ local_time_to_universal_time_dst_x(Config) when is_list(Config) ->
%% when the date falls on a week within the given year and finally,
%% when the date falls on the first week of the next year.
iso_week_number(Config) when is_list(Config) ->
- ?line check_iso_week_number().
+ check_iso_week_number().
%%
%% LOCAL FUNCTIONS
@@ -164,10 +164,10 @@ iso_week_number(Config) when is_list(Config) ->
%% check_gregorian_days
%%
check_gregorian_days(Days, MaxDays) when Days < MaxDays ->
- ?line Date = calendar:gregorian_days_to_date(Days),
- ?line true = calendar:valid_date(Date),
- ?line Days = calendar:date_to_gregorian_days(Date),
- ?line check_gregorian_days(Days + 1, MaxDays);
+ Date = calendar:gregorian_days_to_date(Days),
+ true = calendar:valid_date(Date),
+ Days = calendar:date_to_gregorian_days(Date),
+ check_gregorian_days(Days + 1, MaxDays);
check_gregorian_days(_Days, _MaxDays) ->
ok.
@@ -176,9 +176,9 @@ check_gregorian_days(_Days, _MaxDays) ->
%% We increment with something prime (172801 = 2 days + 1 second).
%%
check_gregorian_seconds(Secs, MaxSecs) when Secs < MaxSecs ->
- ?line DateTime = calendar:gregorian_seconds_to_datetime(Secs),
- ?line Secs = calendar:datetime_to_gregorian_seconds(DateTime),
- ?line check_gregorian_seconds(Secs + 172801, MaxSecs);
+ DateTime = calendar:gregorian_seconds_to_datetime(Secs),
+ Secs = calendar:datetime_to_gregorian_seconds(DateTime),
+ check_gregorian_seconds(Secs + 172801, MaxSecs);
check_gregorian_seconds(_Secs, _MaxSecs) ->
ok.
@@ -186,10 +186,10 @@ check_gregorian_seconds(_Secs, _MaxSecs) ->
%% check_day_of_the_week
%%
check_day_of_the_week(Days, MaxDays, DayNumber) when Days < MaxDays ->
- ?line Date = calendar:gregorian_days_to_date(Days),
- ?line DayNumber = calendar:day_of_the_week(Date),
- ?line check_day_of_the_week(Days + 1, MaxDays,
- ((DayNumber rem 7) + 1));
+ Date = calendar:gregorian_days_to_date(Days),
+ DayNumber = calendar:day_of_the_week(Date),
+ check_day_of_the_week(Days + 1, MaxDays,
+ ((DayNumber rem 7) + 1));
check_day_of_the_week(_Days, _MaxDays, _DayNumber) ->
ok.
@@ -198,59 +198,56 @@ check_day_of_the_week(_Days, _MaxDays, _DayNumber) ->
%% SYr must be larger than 1800, and EYr must be less than ?END_YEAR.
%%
check_leap_years(SYr, EYr) when SYr < EYr ->
- ?line Rem = SYr rem 4,
+ Rem = SYr rem 4,
case Rem of
0 ->
case SYr of
1900 ->
- ?line false = calendar:is_leap_year(SYr);
+ false = calendar:is_leap_year(SYr);
2000 ->
- ?line true = calendar:is_leap_year(SYr);
+ true = calendar:is_leap_year(SYr);
_ ->
- ?line true = calendar:is_leap_year(SYr)
+ true = calendar:is_leap_year(SYr)
end;
_ ->
- ?line false = calendar:is_leap_year(SYr)
+ false = calendar:is_leap_year(SYr)
end,
check_leap_years(SYr + 1, EYr);
check_leap_years(_SYr, _EYr) ->
ok.
check_last_day_of_the_month({SYr, SMon}, {EYr, EMon}) when SYr < EYr ->
- ?line LastDay = calendar:last_day_of_the_month(SYr, SMon),
- ?line LastDay = case SMon of
- 1 -> 31;
- 2 ->
- case calendar:is_leap_year(SYr) of
- true -> 29;
- false -> 28
- end;
- 3 -> 31;
- 4 -> 30;
- 5 -> 31;
- 6 -> 30;
- 7 -> 31;
- 8 -> 31;
- 9 -> 30;
- 10 -> 31;
- 11 -> 30;
- 12 -> 31
- end,
- ?line NYr = case SMon of
- 12 -> SYr + 1;
- _ -> SYr
- end,
- ?line check_last_day_of_the_month({NYr, (SMon rem 12) + 1},
- {EYr, EMon});
+ LastDay = calendar:last_day_of_the_month(SYr, SMon),
+ LastDay = case SMon of
+ 1 -> 31;
+ 2 ->
+ case calendar:is_leap_year(SYr) of
+ true -> 29;
+ false -> 28
+ end;
+ 3 -> 31;
+ 4 -> 30;
+ 5 -> 31;
+ 6 -> 30;
+ 7 -> 31;
+ 8 -> 31;
+ 9 -> 30;
+ 10 -> 31;
+ 11 -> 30;
+ 12 -> 31
+ end,
+ NYr = case SMon of
+ 12 -> SYr + 1;
+ _ -> SYr
+ end,
+ check_last_day_of_the_month({NYr, (SMon rem 12) + 1},
+ {EYr, EMon});
check_last_day_of_the_month(_, _) ->
ok.
%% check_iso_week_number
%%
check_iso_week_number() ->
- ?line {2004, 53} = calendar:iso_week_number({2005, 1, 1}),
- ?line {2007, 1} = calendar:iso_week_number({2007, 1, 1}),
- ?line {2009, 1} = calendar:iso_week_number({2008, 12, 29}).
-
-
-
+ {2004, 53} = calendar:iso_week_number({2005, 1, 1}),
+ {2007, 1} = calendar:iso_week_number({2007, 1, 1}),
+ {2009, 1} = calendar:iso_week_number({2008, 12, 29}).
diff --git a/lib/stdlib/test/digraph_SUITE.erl b/lib/stdlib/test/digraph_SUITE.erl
index 9c8c11e403..8825d3fc15 100644
--- a/lib/stdlib/test/digraph_SUITE.erl
+++ b/lib/stdlib/test/digraph_SUITE.erl
@@ -64,98 +64,98 @@ end_per_group(_GroupName, Config) ->
opts(Config) when is_list(Config) ->
%% OTP-5985: the 'public' option has been removed
- ?line {'EXIT',{badarg,_}} = (catch digraph:new([public])),
- ?line {P2,G2} = spawn_graph([private]),
- ?line {'EXIT',{badarg,_}} = (catch digraph:add_vertex(G2, x)),
- ?line kill_graph(P2),
- ?line {P3,G3} = spawn_graph([protected]),
- ?line {'EXIT',{badarg,_}} = (catch digraph:add_vertex(G3, x)),
- ?line kill_graph(P3),
- ?line Template = [{v1,[v2]}, {v2,[v3]}, {v3,[v4]}, {v4,[]}],
- ?line G4 = build_graph([], Template),
- ?line e = digraph:add_edge(G4, e, v4, v1, []),
- ?line digraph:delete(G4),
- ?line G5 = build_graph([cyclic], Template),
- ?line e = digraph:add_edge(G5, e, v4, v1, []),
- ?line digraph:delete(G5),
- ?line G6 = build_graph([acyclic], Template),
- ?line acyclic = info(G6, cyclicity),
- ?line {error, {bad_edge,_}} = digraph:add_edge(G6, v4, v1),
- ?line digraph:delete(G6),
+ {'EXIT',{badarg,_}} = (catch digraph:new([public])),
+ {P2,G2} = spawn_graph([private]),
+ {'EXIT',{badarg,_}} = (catch digraph:add_vertex(G2, x)),
+ kill_graph(P2),
+ {P3,G3} = spawn_graph([protected]),
+ {'EXIT',{badarg,_}} = (catch digraph:add_vertex(G3, x)),
+ kill_graph(P3),
+ Template = [{v1,[v2]}, {v2,[v3]}, {v3,[v4]}, {v4,[]}],
+ G4 = build_graph([], Template),
+ e = digraph:add_edge(G4, e, v4, v1, []),
+ digraph:delete(G4),
+ G5 = build_graph([cyclic], Template),
+ e = digraph:add_edge(G5, e, v4, v1, []),
+ digraph:delete(G5),
+ G6 = build_graph([acyclic], Template),
+ acyclic = info(G6, cyclicity),
+ {error, {bad_edge,_}} = digraph:add_edge(G6, v4, v1),
+ digraph:delete(G6),
ok.
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
degree(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x1,[]}, {x2,[x1]}, {x3,[x1,x2]},
- {x4,[x1,x2,x3]}, {x5,[x1,x2,x3,x4]}]),
+ G = build_graph([], [{x1,[]}, {x2,[x1]}, {x3,[x1,x2]},
+ {x4,[x1,x2,x3]}, {x5,[x1,x2,x3,x4]}]),
%% out degree
- ?line 0 = digraph:out_degree(G, x1),
- ?line 1 = digraph:out_degree(G, x2),
- ?line 2 = digraph:out_degree(G, x3),
- ?line 3 = digraph:out_degree(G, x4),
- ?line 4 = digraph:out_degree(G, x5),
+ 0 = digraph:out_degree(G, x1),
+ 1 = digraph:out_degree(G, x2),
+ 2 = digraph:out_degree(G, x3),
+ 3 = digraph:out_degree(G, x4),
+ 4 = digraph:out_degree(G, x5),
%% out neighbours
- ?line [] = check(digraph:out_neighbours(G, x1), []),
- ?line [] = check(digraph:out_neighbours(G, x2), [x1]),
- ?line [] = check(digraph:out_neighbours(G, x3), [x1,x2]),
- ?line [] = check(digraph:out_neighbours(G, x4), [x1,x2,x3]),
- ?line [] = check(digraph:out_neighbours(G, x5), [x1,x2,x3,x4]),
+ [] = check(digraph:out_neighbours(G, x1), []),
+ [] = check(digraph:out_neighbours(G, x2), [x1]),
+ [] = check(digraph:out_neighbours(G, x3), [x1,x2]),
+ [] = check(digraph:out_neighbours(G, x4), [x1,x2,x3]),
+ [] = check(digraph:out_neighbours(G, x5), [x1,x2,x3,x4]),
%% in degree
- ?line 4 = digraph:in_degree(G, x1),
- ?line 3 = digraph:in_degree(G, x2),
- ?line 2 = digraph:in_degree(G, x3),
- ?line 1 = digraph:in_degree(G, x4),
- ?line 0 = digraph:in_degree(G, x5),
+ 4 = digraph:in_degree(G, x1),
+ 3 = digraph:in_degree(G, x2),
+ 2 = digraph:in_degree(G, x3),
+ 1 = digraph:in_degree(G, x4),
+ 0 = digraph:in_degree(G, x5),
%% in neighbours
- ?line [] = check(digraph:in_neighbours(G, x1), [x2,x3,x4,x5]),
- ?line [] = check(digraph:in_neighbours(G, x2), [x3,x4,x5]),
- ?line [] = check(digraph:in_neighbours(G, x3), [x4,x5]),
- ?line [] = check(digraph:in_neighbours(G, x4), [x5]),
- ?line [] = check(digraph:in_neighbours(G, x5), []),
+ [] = check(digraph:in_neighbours(G, x1), [x2,x3,x4,x5]),
+ [] = check(digraph:in_neighbours(G, x2), [x3,x4,x5]),
+ [] = check(digraph:in_neighbours(G, x3), [x4,x5]),
+ [] = check(digraph:in_neighbours(G, x4), [x5]),
+ [] = check(digraph:in_neighbours(G, x5), []),
digraph:delete(G),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
path(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]},
- {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7]}]),
- ?line Vi = case digraph:get_path(G, x1, x7) of
- [x1,x2,x4,x5,x7] -> digraph:del_vertex(G, x5), x6;
- [x1,x2,x4,x6,x7] -> digraph:del_vertex(G, x6), x5;
- [x1,x3,x4,x5,x7] -> digraph:del_vertex(G, x5), x6;
- [x1,x3,x4,x6,x7] -> digraph:del_vertex(G, x6), x5
- end,
- ?line Vj = case digraph:get_path(G, x1, x7) of
- [x1,x2,x4,Vi,x7] -> digraph:del_vertex(G,x2), x3;
- [x1,x3,x4,Vi,x7] -> digraph:del_vertex(G,x3), x2
- end,
- ?line [x1,Vj,x4,Vi,x7] = digraph:get_path(G, x1, x7),
- ?line digraph:del_vertex(G, Vj),
- ?line false = digraph:get_path(G, x1, x7),
- ?line [] = check(digraph:vertices(G), [x1,x4,Vi,x7]),
+ G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]},
+ {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7]}]),
+ Vi = case digraph:get_path(G, x1, x7) of
+ [x1,x2,x4,x5,x7] -> digraph:del_vertex(G, x5), x6;
+ [x1,x2,x4,x6,x7] -> digraph:del_vertex(G, x6), x5;
+ [x1,x3,x4,x5,x7] -> digraph:del_vertex(G, x5), x6;
+ [x1,x3,x4,x6,x7] -> digraph:del_vertex(G, x6), x5
+ end,
+ Vj = case digraph:get_path(G, x1, x7) of
+ [x1,x2,x4,Vi,x7] -> digraph:del_vertex(G,x2), x3;
+ [x1,x3,x4,Vi,x7] -> digraph:del_vertex(G,x3), x2
+ end,
+ [x1,Vj,x4,Vi,x7] = digraph:get_path(G, x1, x7),
+ digraph:del_vertex(G, Vj),
+ false = digraph:get_path(G, x1, x7),
+ [] = check(digraph:vertices(G), [x1,x4,Vi,x7]),
digraph:delete(G),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
cycle(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]},
- {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7,x8]},
- {x8,[x3,x8]}]),
- ?line false = digraph:get_cycle(G, x1),
- ?line false = digraph:get_cycle(G, x2),
- ?line false = digraph:get_cycle(G, x5),
- ?line false = digraph:get_cycle(G, x7),
- ?line [x3,x4,x6,x8,x3] = digraph:get_cycle(G, x3),
- ?line [x4,x6,x8,x3,x4] = digraph:get_cycle(G, x4),
- ?line [x6,x8,x3,x4,x6] = digraph:get_cycle(G, x6),
- ?line [x8,x3,x4,x6,x8] = digraph:get_cycle(G, x8),
- ?line digraph:del_vertex(G, x4),
- ?line [x8] = digraph:get_cycle(G, x8),
+ G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]},
+ {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7,x8]},
+ {x8,[x3,x8]}]),
+ false = digraph:get_cycle(G, x1),
+ false = digraph:get_cycle(G, x2),
+ false = digraph:get_cycle(G, x5),
+ false = digraph:get_cycle(G, x7),
+ [x3,x4,x6,x8,x3] = digraph:get_cycle(G, x3),
+ [x4,x6,x8,x3,x4] = digraph:get_cycle(G, x4),
+ [x6,x8,x3,x4,x6] = digraph:get_cycle(G, x6),
+ [x8,x3,x4,x6,x8] = digraph:get_cycle(G, x8),
+ digraph:del_vertex(G, x4),
+ [x8] = digraph:get_cycle(G, x8),
digraph:delete(G),
ok.
@@ -164,54 +164,54 @@ cycle(Config) when is_list(Config) ->
vertices(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x,[]}, {y,[]}]),
- ?line [] = check(digraph:vertices(G), [x,y]),
- ?line digraph:del_vertices(G, [x,y]),
- ?line [] = digraph:vertices(G),
- ?line digraph:delete(G),
+ G = build_graph([], [{x,[]}, {y,[]}]),
+ [] = check(digraph:vertices(G), [x,y]),
+ digraph:del_vertices(G, [x,y]),
+ [] = digraph:vertices(G),
+ digraph:delete(G),
ok.
edges(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x, [{exy,y},{exx,x}]},
- {y, [{eyx,x}]}
- ]),
- ?line [] = check(digraph:edges(G), [exy, eyx, exx]),
- ?line [] = check(digraph:out_edges(G, x), [exy,exx]),
- ?line [] = check(digraph:in_edges(G, x), [eyx,exx]),
- ?line [] = check(digraph:out_edges(G, y), [eyx]),
- ?line [] = check(digraph:in_edges(G, y), [exy]),
- ?line true = digraph:del_edges(G, [exy, eyx, does_not_exist]),
- ?line [exx] = digraph:edges(G),
- ?line [] = check(digraph:out_edges(G, x), [exx]),
- ?line [] = check(digraph:in_edges(G, x), [exx]),
- ?line [] = check(digraph:out_edges(G, y), []),
- ?line [] = check(digraph:in_edges(G, y), []),
- ?line digraph:del_vertices(G, [x,y]),
- ?line [] = digraph:edges(G),
- ?line [] = digraph:vertices(G),
- ?line digraph:delete(G),
+ G = build_graph([], [{x, [{exy,y},{exx,x}]},
+ {y, [{eyx,x}]}
+ ]),
+ [] = check(digraph:edges(G), [exy, eyx, exx]),
+ [] = check(digraph:out_edges(G, x), [exy,exx]),
+ [] = check(digraph:in_edges(G, x), [eyx,exx]),
+ [] = check(digraph:out_edges(G, y), [eyx]),
+ [] = check(digraph:in_edges(G, y), [exy]),
+ true = digraph:del_edges(G, [exy, eyx, does_not_exist]),
+ [exx] = digraph:edges(G),
+ [] = check(digraph:out_edges(G, x), [exx]),
+ [] = check(digraph:in_edges(G, x), [exx]),
+ [] = check(digraph:out_edges(G, y), []),
+ [] = check(digraph:in_edges(G, y), []),
+ digraph:del_vertices(G, [x,y]),
+ [] = digraph:edges(G),
+ [] = digraph:vertices(G),
+ digraph:delete(G),
ok.
data(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x, [{exy, y}]}, {y, []}]),
-
- ?line {x,[]} = digraph:vertex(G, x),
- ?line {y,[]} = digraph:vertex(G, y),
- ?line {exy,x,y,[]} = digraph:edge(G, exy),
-
- ?line digraph:add_edge(G, exy, x, y, {data,x,y}),
- ?line E = digraph:add_edge(G, x, y, {data,y,x}),
- ?line digraph:add_vertex(G, x, {any}),
- ?line digraph:add_vertex(G, y, '_'),
-
- ?line {x,{any}} = digraph:vertex(G, x),
- ?line {y,'_'} = digraph:vertex(G, y),
- ?line {exy,x,y,{data,x,y}} = digraph:edge(G, exy),
- ?line {E,x,y,{data,y,x}} = digraph:edge(G, E),
- ?line true = digraph:del_edge(G, E),
- ?line false = digraph:edge(G, E),
- ?line true = sane(G),
- ?line digraph:delete(G),
+ G = build_graph([], [{x, [{exy, y}]}, {y, []}]),
+
+ {x,[]} = digraph:vertex(G, x),
+ {y,[]} = digraph:vertex(G, y),
+ {exy,x,y,[]} = digraph:edge(G, exy),
+
+ digraph:add_edge(G, exy, x, y, {data,x,y}),
+ E = digraph:add_edge(G, x, y, {data,y,x}),
+ digraph:add_vertex(G, x, {any}),
+ digraph:add_vertex(G, y, '_'),
+
+ {x,{any}} = digraph:vertex(G, x),
+ {y,'_'} = digraph:vertex(G, y),
+ {exy,x,y,{data,x,y}} = digraph:edge(G, exy),
+ {E,x,y,{data,y,x}} = digraph:edge(G, E),
+ true = digraph:del_edge(G, E),
+ false = digraph:edge(G, E),
+ true = sane(G),
+ digraph:delete(G),
ok.
@@ -220,64 +220,64 @@ data(Config) when is_list(Config) ->
otp_3522(Config) when is_list(Config) ->
- ?line G1 = build_graph([acyclic], [{x, []}]),
- ?line {error, {bad_edge,_}} = digraph:add_edge(G1, x, x),
- ?line true = digraph:delete(G1),
-
- ?line G = digraph:new(),
- ?line 0 = digraph:no_vertices(G),
- ?line 0 = digraph:no_edges(G),
- ?line V1 = digraph:add_vertex(G),
- ?line '$vid' = digraph:add_vertex(G, '$vid'),
- ?line V2 = digraph:add_vertex(G),
- ?line '$eid' = digraph:add_edge(G, '$eid', V1, V2, []),
- ?line E = digraph:add_edge(G, V1, V2),
- ?line 3 = digraph:no_vertices(G),
- ?line 2 = digraph:no_edges(G),
- ?line cyclic = info(G, cyclicity),
- ?line protected = info(G, protection),
-
- ?line [] = check(digraph:in_edges(G, V2), ['$eid', E]),
- ?line [] = check(digraph:out_edges(G, V1), ['$eid', E]),
- ?line [] = check(digraph:vertices(G), [V1,V2,'$vid']),
- ?line [] = check(digraph:edges(G), [E, '$eid']),
- ?line true = sane(G),
- ?line true = digraph:delete(G),
+ G1 = build_graph([acyclic], [{x, []}]),
+ {error, {bad_edge,_}} = digraph:add_edge(G1, x, x),
+ true = digraph:delete(G1),
+
+ G = digraph:new(),
+ 0 = digraph:no_vertices(G),
+ 0 = digraph:no_edges(G),
+ V1 = digraph:add_vertex(G),
+ '$vid' = digraph:add_vertex(G, '$vid'),
+ V2 = digraph:add_vertex(G),
+ '$eid' = digraph:add_edge(G, '$eid', V1, V2, []),
+ E = digraph:add_edge(G, V1, V2),
+ 3 = digraph:no_vertices(G),
+ 2 = digraph:no_edges(G),
+ cyclic = info(G, cyclicity),
+ protected = info(G, protection),
+
+ [] = check(digraph:in_edges(G, V2), ['$eid', E]),
+ [] = check(digraph:out_edges(G, V1), ['$eid', E]),
+ [] = check(digraph:vertices(G), [V1,V2,'$vid']),
+ [] = check(digraph:edges(G), [E, '$eid']),
+ true = sane(G),
+ true = digraph:delete(G),
ok.
otp_3630(Config) when is_list(Config) ->
- ?line G = build_graph([], [{x, [{exy,y},{exx,x}]},
- {y, [{eyy,y},{eyx,x}]}
- ]),
- ?line [x,y] = digraph:get_path(G, x, y),
- ?line [y,x] = digraph:get_path(G, y, x),
-
- ?line [x,x] = digraph:get_short_path(G, x, x),
- ?line [y,y] = digraph:get_short_path(G, y, y),
- ?line true = digraph:delete(G),
-
- ?line G1 = build_graph([], [{1, [{12,2},{13,3},{11,1}]},
- {2, [{23,3}]},
- {3, [{34,4},{35,5}]},
- {4, [{45,5}]},
- {5, [{56,6},{57,7}]},
- {6, [{67,7}]},
- {7, [{71,1}]}
- ]),
-
- ?line [1,3,5,7] = digraph:get_short_path(G1, 1, 7),
- ?line [3,5,7,1,3] = digraph:get_short_cycle(G1, 3),
- ?line [1,1] = digraph:get_short_cycle(G1, 1),
- ?line true = digraph:delete(G1),
+ G = build_graph([], [{x, [{exy,y},{exx,x}]},
+ {y, [{eyy,y},{eyx,x}]}
+ ]),
+ [x,y] = digraph:get_path(G, x, y),
+ [y,x] = digraph:get_path(G, y, x),
+
+ [x,x] = digraph:get_short_path(G, x, x),
+ [y,y] = digraph:get_short_path(G, y, y),
+ true = digraph:delete(G),
+
+ G1 = build_graph([], [{1, [{12,2},{13,3},{11,1}]},
+ {2, [{23,3}]},
+ {3, [{34,4},{35,5}]},
+ {4, [{45,5}]},
+ {5, [{56,6},{57,7}]},
+ {6, [{67,7}]},
+ {7, [{71,1}]}
+ ]),
+
+ [1,3,5,7] = digraph:get_short_path(G1, 1, 7),
+ [3,5,7,1,3] = digraph:get_short_cycle(G1, 3),
+ [1,1] = digraph:get_short_cycle(G1, 1),
+ true = digraph:delete(G1),
F = 0.0, I = round(F),
- ?line G2 = digraph:new([acyclic]),
- ?line digraph:add_vertex(G2, F),
- ?line digraph:add_vertex(G2, I),
- ?line E = digraph:add_edge(G2, F, I),
- ?line true = not is_tuple(E),
- ?line true = sane(G2),
- ?line true = digraph:delete(G2),
+ G2 = digraph:new([acyclic]),
+ digraph:add_vertex(G2, F),
+ digraph:add_vertex(G2, I),
+ E = digraph:add_edge(G2, F, I),
+ true = not is_tuple(E),
+ true = sane(G2),
+ true = digraph:delete(G2),
ok.
@@ -287,13 +287,13 @@ otp_8066(Config) when is_list(Config) ->
V1 = digraph:add_vertex(D),
V2 = digraph:add_vertex(D),
_ = digraph:add_edge(D, V1, V2),
- ?line [V1, V2] = digraph:get_path(D, V1, V2),
- ?line true = sane(D),
- ?line true = digraph:del_path(D, V1, V2),
- ?line true = sane(D),
- ?line false = digraph:get_path(D, V1, V2),
- ?line true = digraph:del_path(D, V1, V2),
- ?line true = digraph:delete(D)
+ [V1, V2] = digraph:get_path(D, V1, V2),
+ true = sane(D),
+ true = digraph:del_path(D, V1, V2),
+ true = sane(D),
+ false = digraph:get_path(D, V1, V2),
+ true = digraph:del_path(D, V1, V2),
+ true = digraph:delete(D)
end(),
fun() ->
@@ -304,15 +304,15 @@ otp_8066(Config) when is_list(Config) ->
_ = digraph:add_edge(D, V1, V2),
_ = digraph:add_edge(D, V1, V1),
_ = digraph:add_edge(D, V2, V2),
- ?line [V1, V2] = digraph:get_path(D, V1, V2),
- ?line true = sane(D),
- ?line true = digraph:del_path(D, V1, V2),
- ?line false = digraph:get_short_path(D, V2, V1),
-
- ?line true = sane(D),
- ?line false = digraph:get_path(D, V1, V2),
- ?line true = digraph:del_path(D, V1, V2),
- ?line true = digraph:delete(D)
+ [V1, V2] = digraph:get_path(D, V1, V2),
+ true = sane(D),
+ true = digraph:del_path(D, V1, V2),
+ false = digraph:get_short_path(D, V2, V1),
+
+ true = sane(D),
+ false = digraph:get_path(D, V1, V2),
+ true = digraph:del_path(D, V1, V2),
+ true = digraph:delete(D)
end(),
fun() ->
@@ -322,18 +322,18 @@ otp_8066(Config) when is_list(Config) ->
W3 = digraph:add_vertex(G),
W4 = digraph:add_vertex(G),
_ = digraph:add_edge(G,['$e'|0], W1, W2, {}),
- ?line {error,{bad_vertex, bv}} =
+ {error,{bad_vertex, bv}} =
digraph:add_edge(G, edge, bv, W1, {}),
- ?line {error,{bad_vertex, bv}} =
+ {error,{bad_vertex, bv}} =
digraph:add_edge(G, edge, W1, bv, {}),
- ?line false = digraph:get_short_cycle(G, W1),
- ?line {error, {bad_edge,_}} =
+ false = digraph:get_short_cycle(G, W1),
+ {error, {bad_edge,_}} =
digraph:add_edge(G,['$e'|0], W3, W4, {}),
- ?line true = sane(G),
- ?line true = digraph:delete(G)
+ true = sane(G),
+ true = digraph:delete(G)
end(),
ok.
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -402,7 +402,7 @@ sane1(G) ->
end
end, OutEs)
end, Vs),
-
+
InEs = lists:flatmap(fun(V) -> digraph:in_edges(G, V) end, Vs),
OutEs = lists:flatmap(fun(V) -> digraph:out_edges(G, V) end, Vs),
lists:foreach(
@@ -430,7 +430,7 @@ sane1(G) ->
end,
Edges = [digraph:edge(G, E) || E <- Es],
EVs = lists:usort([V || {_, V, _, _} <- Edges] ++
- [V || {_, _, V, _} <- Edges]),
+ [V || {_, _, V, _} <- Edges]),
lists:foreach(
fun(V) ->
case digraph:vertex(G, V) of
diff --git a/lib/stdlib/test/digraph_utils_SUITE.erl b/lib/stdlib/test/digraph_utils_SUITE.erl
index 743da8da1a..23520072f8 100644
--- a/lib/stdlib/test/digraph_utils_SUITE.erl
+++ b/lib/stdlib/test/digraph_utils_SUITE.erl
@@ -60,191 +60,191 @@ end_per_group(_GroupName, Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
simple(Config) when is_list(Config) ->
- ?line G = digraph:new(),
- ?line add_vertices(G, [a]),
- ?line add_edges(G, [{b,c},{b,d},{e,f},{f,g},{g,e},{h,h},{i,i},{i,j}]),
- ?line 10 = length(digraph_utils:postorder(G)),
- ?line 10 = length(digraph_utils:preorder(G)),
- ?line ok = evall(digraph_utils:components(G),
- [[a],[b,c,d],[e,f,g],[h],[i,j]]),
- ?line ok = evall(digraph_utils:strong_components(G),
+ G = digraph:new(),
+ add_vertices(G, [a]),
+ add_edges(G, [{b,c},{b,d},{e,f},{f,g},{g,e},{h,h},{i,i},{i,j}]),
+ 10 = length(digraph_utils:postorder(G)),
+ 10 = length(digraph_utils:preorder(G)),
+ ok = evall(digraph_utils:components(G),
+ [[a],[b,c,d],[e,f,g],[h],[i,j]]),
+ ok = evall(digraph_utils:strong_components(G),
[[a],[b],[c],[d],[e,f,g],[h],[i],[j]]),
- ?line ok = evall(digraph_utils:cyclic_strong_components(G),
- [[e,f,g],[h],[i]]),
- ?line true = path(G, e, e),
- ?line false = path(G, e, j),
- ?line false = path(G, a, a),
- ?line false = digraph_utils:topsort(G),
- ?line false = digraph_utils:is_acyclic(G),
- ?line ok = eval(digraph_utils:loop_vertices(G), [h,i]),
- ?line ok = eval(digraph_utils:reaching([e], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reaching_neighbours([e], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reachable([e], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reachable_neighbours([e], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reaching([b], G), [b]),
- ?line ok = eval(digraph_utils:reaching_neighbours([b], G), []),
- ?line ok = eval(digraph_utils:reachable([b], G), [b,c,d]),
- ?line ok = eval(digraph_utils:reachable_neighbours([b], G), [c,d]),
- ?line ok = eval(digraph_utils:reaching([h], G), [h]),
- ?line ok = eval(digraph_utils:reaching_neighbours([h], G), [h]),
- ?line ok = eval(digraph_utils:reachable([h], G), [h]),
- ?line ok = eval(digraph_utils:reachable_neighbours([h], G), [h]),
- ?line ok = eval(digraph_utils:reachable([e,f], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reachable_neighbours([e,f], G), [e,f,g]),
- ?line ok = eval(digraph_utils:reachable([h,h,h], G), [h]),
- ?line true = digraph:delete(G),
+ ok = evall(digraph_utils:cyclic_strong_components(G),
+ [[e,f,g],[h],[i]]),
+ true = path(G, e, e),
+ false = path(G, e, j),
+ false = path(G, a, a),
+ false = digraph_utils:topsort(G),
+ false = digraph_utils:is_acyclic(G),
+ ok = eval(digraph_utils:loop_vertices(G), [h,i]),
+ ok = eval(digraph_utils:reaching([e], G), [e,f,g]),
+ ok = eval(digraph_utils:reaching_neighbours([e], G), [e,f,g]),
+ ok = eval(digraph_utils:reachable([e], G), [e,f,g]),
+ ok = eval(digraph_utils:reachable_neighbours([e], G), [e,f,g]),
+ ok = eval(digraph_utils:reaching([b], G), [b]),
+ ok = eval(digraph_utils:reaching_neighbours([b], G), []),
+ ok = eval(digraph_utils:reachable([b], G), [b,c,d]),
+ ok = eval(digraph_utils:reachable_neighbours([b], G), [c,d]),
+ ok = eval(digraph_utils:reaching([h], G), [h]),
+ ok = eval(digraph_utils:reaching_neighbours([h], G), [h]),
+ ok = eval(digraph_utils:reachable([h], G), [h]),
+ ok = eval(digraph_utils:reachable_neighbours([h], G), [h]),
+ ok = eval(digraph_utils:reachable([e,f], G), [e,f,g]),
+ ok = eval(digraph_utils:reachable_neighbours([e,f], G), [e,f,g]),
+ ok = eval(digraph_utils:reachable([h,h,h], G), [h]),
+ true = digraph:delete(G),
ok.
loop(Config) when is_list(Config) ->
- ?line G = digraph:new(),
- ?line add_vertices(G, [a,b]),
- ?line add_edges(G, [{a,a},{b,b}]),
- ?line ok = evall(digraph_utils:components(G), [[a],[b]]),
- ?line ok = evall(digraph_utils:strong_components(G), [[a],[b]]),
- ?line ok = evall(digraph_utils:cyclic_strong_components(G), [[a],[b]]),
- ?line [_,_] = digraph_utils:topsort(G),
- ?line false = digraph_utils:is_acyclic(G),
- ?line ok = eval(digraph_utils:loop_vertices(G), [a,b]),
- ?line [_,_] = digraph_utils:preorder(G),
- ?line [_,_] = digraph_utils:postorder(G),
- ?line ok = eval(digraph_utils:reaching([b], G), [b]),
- ?line ok = eval(digraph_utils:reaching_neighbours([b], G), [b]),
- ?line ok = eval(digraph_utils:reachable([b], G), [b]),
- ?line ok = eval(digraph_utils:reachable_neighbours([b], G), [b]),
- ?line true = path(G, a, a),
- ?line true = digraph:delete(G),
+ G = digraph:new(),
+ add_vertices(G, [a,b]),
+ add_edges(G, [{a,a},{b,b}]),
+ ok = evall(digraph_utils:components(G), [[a],[b]]),
+ ok = evall(digraph_utils:strong_components(G), [[a],[b]]),
+ ok = evall(digraph_utils:cyclic_strong_components(G), [[a],[b]]),
+ [_,_] = digraph_utils:topsort(G),
+ false = digraph_utils:is_acyclic(G),
+ ok = eval(digraph_utils:loop_vertices(G), [a,b]),
+ [_,_] = digraph_utils:preorder(G),
+ [_,_] = digraph_utils:postorder(G),
+ ok = eval(digraph_utils:reaching([b], G), [b]),
+ ok = eval(digraph_utils:reaching_neighbours([b], G), [b]),
+ ok = eval(digraph_utils:reachable([b], G), [b]),
+ ok = eval(digraph_utils:reachable_neighbours([b], G), [b]),
+ true = path(G, a, a),
+ true = digraph:delete(G),
ok.
isolated(Config) when is_list(Config) ->
- ?line G = digraph:new(),
- ?line add_vertices(G, [a,b]),
- ?line ok = evall(digraph_utils:components(G), [[a],[b]]),
- ?line ok = evall(digraph_utils:strong_components(G), [[a],[b]]),
- ?line ok = evall(digraph_utils:cyclic_strong_components(G), []),
- ?line [_,_] = digraph_utils:topsort(G),
- ?line true = digraph_utils:is_acyclic(G),
- ?line ok = eval(digraph_utils:loop_vertices(G), []),
- ?line [_,_] = digraph_utils:preorder(G),
- ?line [_,_] = digraph_utils:postorder(G),
- ?line ok = eval(digraph_utils:reaching([b], G), [b]),
- ?line ok = eval(digraph_utils:reaching_neighbours([b], G), []),
- ?line ok = eval(digraph_utils:reachable([b], G), [b]),
- ?line ok = eval(digraph_utils:reachable_neighbours([b], G), []),
- ?line false = path(G, a, a),
- ?line true = digraph:delete(G),
+ G = digraph:new(),
+ add_vertices(G, [a,b]),
+ ok = evall(digraph_utils:components(G), [[a],[b]]),
+ ok = evall(digraph_utils:strong_components(G), [[a],[b]]),
+ ok = evall(digraph_utils:cyclic_strong_components(G), []),
+ [_,_] = digraph_utils:topsort(G),
+ true = digraph_utils:is_acyclic(G),
+ ok = eval(digraph_utils:loop_vertices(G), []),
+ [_,_] = digraph_utils:preorder(G),
+ [_,_] = digraph_utils:postorder(G),
+ ok = eval(digraph_utils:reaching([b], G), [b]),
+ ok = eval(digraph_utils:reaching_neighbours([b], G), []),
+ ok = eval(digraph_utils:reachable([b], G), [b]),
+ ok = eval(digraph_utils:reachable_neighbours([b], G), []),
+ false = path(G, a, a),
+ true = digraph:delete(G),
ok.
topsort(Config) when is_list(Config) ->
- ?line G = digraph:new(),
- ?line add_edges(G, [{a,b},{b,c},{c,d},{d,e},{e,f}]),
- ?line ok = eval(digraph_utils:topsort(G), [a,b,c,d,e,f]),
- ?line true = digraph:delete(G),
+ G = digraph:new(),
+ add_edges(G, [{a,b},{b,c},{c,d},{d,e},{e,f}]),
+ ok = eval(digraph_utils:topsort(G), [a,b,c,d,e,f]),
+ true = digraph:delete(G),
ok.
subgraph(Config) when is_list(Config) ->
- ?line G = digraph:new([acyclic]),
- ?line add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e},
- {h,h},{i,i},{i,j}]),
- ?line add_vertices(G, [{b,bl},{f,fl}]),
- ?line SG = digraph_utils:subgraph(G, [u1,b,c,u2,f,g,i,u3]),
- ?line [b,c,f,g,i] = lists:sort(digraph:vertices(SG)),
- ?line {b,bl} = digraph:vertex(SG, b),
- ?line {c,[]} = digraph:vertex(SG, c),
- ?line {fg,f,g,fgl} = digraph:edge(SG, fg),
- ?line {fg2,f,g,fgl2} = digraph:edge(SG, fg2),
- ?line {_, {_, acyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG)),
- ?line true = digraph:delete(SG),
-
- ?line SG1 = digraph_utils:subgraph(G, [f, g, h],
- [{type, []}, {keep_labels, false}]),
- ?line [f,g,h] = lists:sort(digraph:vertices(SG1)),
- ?line {f,[]} = digraph:vertex(SG1, f),
- ?line {fg,f,g,[]} = digraph:edge(SG1, fg),
- ?line {_, {_, cyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG1)),
- ?line true = digraph:delete(SG1),
-
- ?line SG2 = digraph_utils:subgraph(G, [f, g, h],
- [{type, [acyclic]},
- {keep_labels, true}]),
- ?line [f,g,h] = lists:sort(digraph:vertices(SG2)),
- ?line {f,fl} = digraph:vertex(SG2, f),
- ?line {fg,f,g,fgl} = digraph:edge(SG2, fg),
- ?line {_, {_, acyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG2)),
- ?line true = digraph:delete(SG2),
-
- ?line {'EXIT',{badarg,_}} =
+ G = digraph:new([acyclic]),
+ add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e},
+ {h,h},{i,i},{i,j}]),
+ add_vertices(G, [{b,bl},{f,fl}]),
+ SG = digraph_utils:subgraph(G, [u1,b,c,u2,f,g,i,u3]),
+ [b,c,f,g,i] = lists:sort(digraph:vertices(SG)),
+ {b,bl} = digraph:vertex(SG, b),
+ {c,[]} = digraph:vertex(SG, c),
+ {fg,f,g,fgl} = digraph:edge(SG, fg),
+ {fg2,f,g,fgl2} = digraph:edge(SG, fg2),
+ {_, {_, acyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG)),
+ true = digraph:delete(SG),
+
+ SG1 = digraph_utils:subgraph(G, [f, g, h],
+ [{type, []}, {keep_labels, false}]),
+ [f,g,h] = lists:sort(digraph:vertices(SG1)),
+ {f,[]} = digraph:vertex(SG1, f),
+ {fg,f,g,[]} = digraph:edge(SG1, fg),
+ {_, {_, cyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG1)),
+ true = digraph:delete(SG1),
+
+ SG2 = digraph_utils:subgraph(G, [f, g, h],
+ [{type, [acyclic]},
+ {keep_labels, true}]),
+ [f,g,h] = lists:sort(digraph:vertices(SG2)),
+ {f,fl} = digraph:vertex(SG2, f),
+ {fg,f,g,fgl} = digraph:edge(SG2, fg),
+ {_, {_, acyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG2)),
+ true = digraph:delete(SG2),
+
+ {'EXIT',{badarg,_}} =
(catch digraph_utils:subgraph(G, [f], [{invalid, opt}])),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch digraph_utils:subgraph(G, [f], [{keep_labels, not_Bool}])),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch digraph_utils:subgraph(G, [f], [{type, not_type}])),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch digraph_utils:subgraph(G, [f], [{type, [not_type]}])),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch digraph_utils:subgraph(G, [f], not_a_list)),
- ?line true = digraph:delete(G),
+ true = digraph:delete(G),
ok.
condensation(Config) when is_list(Config) ->
- ?line G = digraph:new([]),
- ?line add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e},
- {h,h},{j,i},{i,j}]),
- ?line add_vertices(G, [q]),
- ?line CG = digraph_utils:condensation(G),
- ?line Vs = sort_2(digraph:vertices(CG)),
- ?line [[b],[c],[d],[e,f,g],[h],[i,j],[q]] = Vs,
- ?line Fun = fun(E) ->
- {_E, V1, V2, _L} = digraph:edge(CG, E),
- {lists:sort(V1), lists:sort(V2)}
- end,
- ?line Es = lists:map(Fun, digraph:edges(CG)),
- ?line [{[b],[c]},{[b],[d]}] = lists:sort(Es),
- ?line true = digraph:delete(CG),
- ?line true = digraph:delete(G),
+ G = digraph:new([]),
+ add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e},
+ {h,h},{j,i},{i,j}]),
+ add_vertices(G, [q]),
+ CG = digraph_utils:condensation(G),
+ Vs = sort_2(digraph:vertices(CG)),
+ [[b],[c],[d],[e,f,g],[h],[i,j],[q]] = Vs,
+ Fun = fun(E) ->
+ {_E, V1, V2, _L} = digraph:edge(CG, E),
+ {lists:sort(V1), lists:sort(V2)}
+ end,
+ Es = lists:map(Fun, digraph:edges(CG)),
+ [{[b],[c]},{[b],[d]}] = lists:sort(Es),
+ true = digraph:delete(CG),
+ true = digraph:delete(G),
ok.
%% OTP-7081
tree(Config) when is_list(Config) ->
- ?line false = is_tree([], []),
- ?line true = is_tree([a], []),
- ?line false = is_tree([a,b], []),
- ?line true = is_tree([{a,b}]),
- ?line false = is_tree([{a,b},{b,a}]),
- ?line true = is_tree([{a,b},{a,c},{b,d},{b,e}]),
- ?line false = is_tree([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
- ?line false = is_tree([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
- ?line true = is_tree([{a,c},{c,b}]),
- ?line true = is_tree([{b,a},{c,a}]),
+ false = is_tree([], []),
+ true = is_tree([a], []),
+ false = is_tree([a,b], []),
+ true = is_tree([{a,b}]),
+ false = is_tree([{a,b},{b,a}]),
+ true = is_tree([{a,b},{a,c},{b,d},{b,e}]),
+ false = is_tree([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
+ false = is_tree([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
+ true = is_tree([{a,c},{c,b}]),
+ true = is_tree([{b,a},{c,a}]),
%% Parallel edges. Acyclic and with one componets
%% (according to the digraph module).
- ?line false = is_tree([{a,b},{a,b}]),
-
- ?line no = arborescence_root([], []),
- ?line {yes, a} = arborescence_root([a], []),
- ?line no = arborescence_root([a,b], []),
- ?line {yes, a} = arborescence_root([{a,b}]),
- ?line no = arborescence_root([{a,b},{b,a}]),
- ?line {yes, a} = arborescence_root([{a,b},{a,c},{b,d},{b,e}]),
- ?line no = arborescence_root([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
- ?line no = arborescence_root([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
- ?line {yes, a} = arborescence_root([{a,c},{c,b}]),
- ?line no = arborescence_root([{b,a},{c,a}]),
-
- ?line false = is_arborescence([], []),
- ?line true = is_arborescence([a], []),
- ?line false = is_arborescence([a,b], []),
- ?line true = is_arborescence([{a,b}]),
- ?line false = is_arborescence([{a,b},{b,a}]),
- ?line true = is_arborescence([{a,b},{a,c},{b,d},{b,e}]),
- ?line false = is_arborescence([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
- ?line false = is_arborescence([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
- ?line true = is_arborescence([{a,c},{c,b}]),
- ?line false = is_arborescence([{b,a},{c,a}]),
+ false = is_tree([{a,b},{a,b}]),
+
+ no = arborescence_root([], []),
+ {yes, a} = arborescence_root([a], []),
+ no = arborescence_root([a,b], []),
+ {yes, a} = arborescence_root([{a,b}]),
+ no = arborescence_root([{a,b},{b,a}]),
+ {yes, a} = arborescence_root([{a,b},{a,c},{b,d},{b,e}]),
+ no = arborescence_root([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
+ no = arborescence_root([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
+ {yes, a} = arborescence_root([{a,c},{c,b}]),
+ no = arborescence_root([{b,a},{c,a}]),
+
+ false = is_arborescence([], []),
+ true = is_arborescence([a], []),
+ false = is_arborescence([a,b], []),
+ true = is_arborescence([{a,b}]),
+ false = is_arborescence([{a,b},{b,a}]),
+ true = is_arborescence([{a,b},{a,c},{b,d},{b,e}]),
+ false = is_arborescence([{a,b},{a,c},{b,d},{b,e}, {d,e}]),
+ false = is_arborescence([{a,b},{a,c},{b,d},{b,e}, {b,e}]),
+ true = is_arborescence([{a,c},{c,b}]),
+ false = is_arborescence([{b,a},{c,a}]),
%% Parallel edges.
- ?line false = is_arborescence([{a,b},{a,b}]),
+ false = is_arborescence([{a,b},{a,b}]),
ok.
@@ -312,7 +312,7 @@ eval(L, E) ->
evall(L, E) ->
F = fun(L1) -> lists:sort(L1) end,
Fun = fun(LL) -> F(lists:map(F, LL)) end,
-
+
Expected = Fun(E),
Got = Fun(L),
if
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 447480a1bd..d18f99acf5 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -87,24 +87,24 @@ end_per_group(_GroupName, Config) ->
%% Recursive macros hang or crash epp (OTP-1398).
rec_1(Config) when is_list(Config) ->
- ?line File = filename:join(?config(data_dir, Config), "mac.erl"),
- ?line {ok, List} = epp_parse_file(File, [], []),
+ File = filename:join(?config(data_dir, Config), "mac.erl"),
+ {ok, List} = epp_parse_file(File, [], []),
%% we should encounter errors
- ?line {value, _} = lists:keysearch(error, 1, List),
- ?line check_errors(List),
+ {value, _} = lists:keysearch(error, 1, List),
+ check_errors(List),
ok.
include_local(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line File = filename:join(DataDir, "include_local.erl"),
+ DataDir = ?config(data_dir, Config),
+ File = filename:join(DataDir, "include_local.erl"),
FooHrl = filename:join([DataDir,"include","foo.hrl"]),
BarHrl = filename:join([DataDir,"include","bar.hrl"]),
%% include_local.erl includes include/foo.hrl which
%% includes bar.hrl (also in include/) without requiring
%% any additional include path, and overriding any file
%% of the same name that the path points to
- ?line {ok, List} = epp:parse_file(File, [DataDir], []),
- ?line {value, {attribute,_,a,{true,true}}} =
+ {ok, List} = epp:parse_file(File, [DataDir], []),
+ {value, {attribute,_,a,{true,true}}} =
lists:keysearch(a,3,List),
[{File,1},{FooHrl,1},{BarHrl,1},{FooHrl,5},{File,5}] =
[ FileLine || {attribute,_,file,FileLine} <- List ],
@@ -160,55 +160,55 @@ epp_parse_erl_form(Epp, Parent) ->
check_errors([]) ->
ok;
check_errors([{error, Info} | Rest]) ->
- ?line {Line, Mod, Desc} = Info,
- ?line case Line of
- I when is_integer(I) -> ok;
- {L,C} when is_integer(L), is_integer(C), C >= 1 -> ok
- end,
- ?line Str = lists:flatten(Mod:format_error(Desc)),
- ?line [Str] = io_lib:format("~s", [Str]),
+ {Line, Mod, Desc} = Info,
+ case Line of
+ I when is_integer(I) -> ok;
+ {L,C} when is_integer(L), is_integer(C), C >= 1 -> ok
+ end,
+ Str = lists:flatten(Mod:format_error(Desc)),
+ [Str] = io_lib:format("~s", [Str]),
check_errors(Rest);
check_errors([_ | Rest]) ->
check_errors(Rest).
upcase_mac_1(Config) when is_list(Config) ->
- ?line File = filename:join(?config(data_dir, Config), "mac2.erl"),
- ?line {ok, List} = epp:parse_file(File, [], []),
- ?line [_, {attribute, _, plupp, Tuple} | _] = List,
- ?line Tuple = {1, 1, 3, 3},
+ File = filename:join(?config(data_dir, Config), "mac2.erl"),
+ {ok, List} = epp:parse_file(File, [], []),
+ [_, {attribute, _, plupp, Tuple} | _] = List,
+ Tuple = {1, 1, 3, 3},
ok.
upcase_mac_2(Config) when is_list(Config) ->
- ?line File = filename:join(?config(data_dir, Config), "mac2.erl"),
- ?line {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]),
- ?line [_, {attribute, _, plupp, Tuple} | _] = List,
- ?line Tuple = {5, 5, 6, 6},
+ File = filename:join(?config(data_dir, Config), "mac2.erl"),
+ {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]),
+ [_, {attribute, _, plupp, Tuple} | _] = List,
+ Tuple = {5, 5, 6, 6},
ok.
predef_mac(Config) when is_list(Config) ->
- ?line File = filename:join(?config(data_dir, Config), "mac3.erl"),
- ?line {ok, List} = epp:parse_file(File, [], []),
- ?line [_,
- {attribute, Anno, l, Line1},
- {attribute, _, f, File},
- {attribute, _, machine1, _},
- {attribute, _, module, mac3},
- {attribute, _, m, mac3},
- {attribute, _, ms, "mac3"},
- {attribute, _, machine2, _}
- | _] = List,
+ File = filename:join(?config(data_dir, Config), "mac3.erl"),
+ {ok, List} = epp:parse_file(File, [], []),
+ [_,
+ {attribute, Anno, l, Line1},
+ {attribute, _, f, File},
+ {attribute, _, machine1, _},
+ {attribute, _, module, mac3},
+ {attribute, _, m, mac3},
+ {attribute, _, ms, "mac3"},
+ {attribute, _, machine2, _}
+ | _] = List,
Line1 = erl_anno:line(Anno),
ok.
variable_1(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line File = filename:join(DataDir, "variable_1.erl"),
- ?line true = os:putenv("VAR", DataDir),
+ DataDir = ?config(data_dir, Config),
+ File = filename:join(DataDir, "variable_1.erl"),
+ true = os:putenv("VAR", DataDir),
%% variable_1.erl includes variable_1_include.hrl and
%% variable_1_include_dir.hrl.
- ?line {ok, List} = epp:parse_file(File, [], []),
- ?line {value, {attribute,_,a,{value1,value2}}} =
+ {ok, List} = epp:parse_file(File, [], []),
+ {value, {attribute,_,a,{value1,value2}}} =
lists:keysearch(a,3,List),
ok.
@@ -218,28 +218,28 @@ otp_4870(Config) when is_list(Config) ->
<<"-undef(foo).
">>,
[]}],
- ?line [] = check(Config, Ts),
+ [] = check(Config, Ts),
ok.
%% crashing erl_scan
otp_4871(Config) when is_list(Config) ->
- ?line Dir = ?config(priv_dir, Config),
- ?line File = filename:join(Dir, "otp_4871.erl"),
- ?line ok = file:write_file(File, "-module(otp_4871)."),
+ Dir = ?config(priv_dir, Config),
+ File = filename:join(Dir, "otp_4871.erl"),
+ ok = file:write_file(File, "-module(otp_4871)."),
%% Testing crash in erl_scan. Unfortunately there currently is
%% no known way to crash erl_scan so it is emulated by killing the
%% file io server. This assumes lots of things about how
%% the processes are started and how monitors are set up,
%% so there are some sanity checks before killing.
- ?line {ok,Epp} = epp:open(File, []),
+ {ok,Epp} = epp:open(File, []),
timer:sleep(1),
- ?line true = current_module(Epp, epp),
- ?line {monitored_by,[Io]} = process_info(Epp, monitored_by),
- ?line true = current_module(Io, file_io_server),
- ?line exit(Io, emulate_crash),
+ true = current_module(Epp, epp),
+ {monitored_by,[Io]} = process_info(Epp, monitored_by),
+ true = current_module(Io, file_io_server),
+ exit(Io, emulate_crash),
timer:sleep(1),
- ?line {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp),
- ?line epp:close(Epp),
+ {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp),
+ epp:close(Epp),
ok.
current_module(Pid, Mod) ->
@@ -282,12 +282,12 @@ otp_5362(Config) when is_list(Config) ->
Incl3 = <<"glurk(Foo) -> % line 1
bar.
">>,
- ?line ok = file:write_file(File_Incl, Incl),
- ?line ok = file:write_file(File_Incl2, Incl2),
- ?line ok = file:write_file(File_Incl3, Incl3),
+ ok = file:write_file(File_Incl, Incl),
+ ok = file:write_file(File_Incl2, Incl2),
+ ok = file:write_file(File_Incl3, Incl3),
- ?line {ok, incl_5362, InclWarnings} = compile:file(File_Incl, Copts),
- ?line true = message_compare(
+ {ok, incl_5362, InclWarnings} = compile:file(File_Incl, Copts),
+ true = message_compare(
[{File_Incl3,[{{1,1},erl_lint,{unused_function,{glurk,1}}},
{{1,7},erl_lint,{unused_var,'Foo'}}]},
{File_Incl,[{{7,15},erl_lint,{unused_function,{hi,1}}},
@@ -317,11 +317,11 @@ otp_5362(Config) when is_list(Config) ->
-file(\"">>,File_Back,<<"\", 2).
">>],
- ?line ok = file:write_file(File_Back, Back),
- ?line ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)),
+ ok = file:write_file(File_Back, Back),
+ ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)),
- ?line {ok, back_5362, BackWarnings} = compile:file(File_Back, Copts),
- ?line true = message_compare(
+ {ok, back_5362, BackWarnings} = compile:file(File_Back, Copts),
+ true = message_compare(
[{File_Back,[{{4,19},erl_lint,{unused_var,'V'}}]}],
BackWarnings),
file:delete(File_Back),
@@ -345,11 +345,11 @@ otp_5362(Config) when is_list(Config) ->
foo.
">>],
- ?line ok = file:write_file(File_Change, list_to_binary(Change)),
+ ok = file:write_file(File_Change, list_to_binary(Change)),
- ?line {ok, change_5362, ChangeWarnings} =
+ {ok, change_5362, ChangeWarnings} =
compile:file(File_Change, Copts),
- ?line true = message_compare(
+ true = message_compare(
[{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]},
{"other.file",[{{105,21},erl_lint,{unused_var,'A'}}]}],
lists:usort(ChangeWarnings)),
@@ -377,9 +377,9 @@ otp_5362(Config) when is_list(Config) ->
-file(?FILE, ?LINE). c(C) -> % line 47
3.
">>,
- ?line ok = file:write_file(File_Blank, Blank),
- ?line {ok, blank_5362, BlankWarnings} = compile:file(File_Blank, Copts),
- ?line true = message_compare(
+ ok = file:write_file(File_Blank, Blank),
+ {ok, blank_5362, BlankWarnings} = compile:file(File_Blank, Copts),
+ true = message_compare(
[{File_Blank,[{{18,3},erl_lint,{unused_var,'Q'}},
{{20,18},erl_lint,{unused_var,'A'}},
{{44,18},erl_lint,{unused_var,'B'}},
@@ -403,16 +403,16 @@ otp_5362(Config) when is_list(Config) ->
FILE1 = <<"ii() -> ?FILE.
">>,
FILE_Mod = file_5362,
- ?line ok = file:write_file(FILE_incl, FILE),
- ?line ok = file:write_file(FILE_incl1, FILE1),
+ ok = file:write_file(FILE_incl, FILE),
+ ok = file:write_file(FILE_incl1, FILE1),
FILE_Copts = [return, {i,Dir},{outdir,Dir}],
- ?line {ok, file_5362, []} = compile:file(FILE_incl, FILE_Copts),
+ {ok, file_5362, []} = compile:file(FILE_incl, FILE_Copts),
AbsFile = filename:rootname(FILE_incl, ".erl"),
- ?line {module, FILE_Mod} = code:load_abs(AbsFile, FILE_Mod),
- ?line II = FILE_Mod:ii(),
- ?line "file_incl_5362.erl" = filename:basename(II),
- ?line FF = FILE_Mod:ff(),
- ?line "other_file" = filename:basename(FF),
+ {module, FILE_Mod} = code:load_abs(AbsFile, FILE_Mod),
+ II = FILE_Mod:ii(),
+ "file_incl_5362.erl" = filename:basename(II),
+ FF = FILE_Mod:ff(),
+ "other_file" = filename:basename(FF),
code:purge(file_5362),
file:delete(FILE_incl),
@@ -421,12 +421,12 @@ otp_5362(Config) when is_list(Config) ->
ok.
pmod(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line Pmod = filename:join(DataDir, "pmod.erl"),
- ?line case epp:parse_file([Pmod], [], []) of
+ DataDir = ?config(data_dir, Config),
+ Pmod = filename:join(DataDir, "pmod.erl"),
+ case epp:parse_file([Pmod], [], []) of
{ok,Forms} ->
- %% ?line io:format("~p\n", [Forms]),
- ?line [] = [F || {error,_}=F <- Forms],
+ %% io:format("~p\n", [Forms]),
+ [] = [F || {error,_}=F <- Forms],
ok
end,
ok.
@@ -439,14 +439,14 @@ not_circular(Config) when is_list(Config) ->
<<"-define(S(S), ??S).\n"
"t() -> \"string\" = ?S(string), ok.\n">>,
ok}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Skip some bytes in the beginning of the file.
skip_header(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
- ?line File = filename:join([PrivDir, "epp_test_skip_header.erl"]),
- ?line ok = file:write_file(File,
+ PrivDir = ?config(priv_dir, Config),
+ File = filename:join([PrivDir, "epp_test_skip_header.erl"]),
+ ok = file:write_file(File,
<<"some bytes
in the beginning of the file
that should be skipped
@@ -456,16 +456,16 @@ skip_header(Config) when is_list(Config) ->
main(_) -> ?MODULE.
">>),
- ?line {ok, Fd} = file:open(File, [read]),
- ?line io:get_line(Fd, ''),
- ?line io:get_line(Fd, ''),
- ?line io:get_line(Fd, ''),
- ?line {ok, Epp} = epp:open(list_to_atom(File), Fd, 4, [], []),
-
- ?line Forms = epp:parse_file(Epp),
- ?line [] = [Reason || {error, Reason} <- Forms],
- ?line ok = epp:close(Epp),
- ?line ok = file:close(Fd),
+ {ok, Fd} = file:open(File, [read]),
+ io:get_line(Fd, ''),
+ io:get_line(Fd, ''),
+ io:get_line(Fd, ''),
+ {ok, Epp} = epp:open(list_to_atom(File), Fd, 4, [], []),
+
+ Forms = epp:parse_file(Epp),
+ [] = [Reason || {error, Reason} <- Forms],
+ ok = epp:close(Epp),
+ ok = file:close(Fd),
ok.
@@ -477,7 +477,7 @@ otp_6277(Config) when is_list(Config) ->
?ASSERT().">>,
[{error,{{4,16},epp,{undefined,'MODULE', none}}}]}],
- ?line [] = check(Config, Ts),
+ [] = check(Config, Ts),
ok.
%% OTP-7702. Wrong line number in stringifying macro expansion.
@@ -498,8 +498,8 @@ otp_7702(Config) when is_list(Config) ->
end).
t() ->
?RECEIVE(foo, bar).">>,
- ?line ok = file:write_file(File, Contents),
- ?line {ok, file_7702, []} =
+ ok = file:write_file(File, Contents),
+ {ok, file_7702, []} =
compile:file(File, [debug_info,return,{outdir,Dir}]),
BeamFile = filename:join(Dir, "file_7702.beam"),
@@ -507,8 +507,7 @@ otp_7702(Config) when is_list(Config) ->
{file_7702,[{abstract_code,{_,Forms}}]} = AC,
Forms2 = unopaque_forms(Forms),
- ?line
- [{attribute,1,file,_},
+ [{attribute,1,file,_},
_,
_,
{function,_,t,0,
@@ -642,7 +641,7 @@ otp_8130(Config) when is_list(Config) ->
{1,1}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
Cs = [{otp_8130_c1,
<<"-define(M1(A), if\n"
@@ -776,7 +775,7 @@ otp_8130(Config) when is_list(Config) ->
{{3,19},epp,{undefined,'A',none}}],[]}}
],
- ?line [] = compile(Config, Cs),
+ [] = compile(Config, Cs),
Cks = [{otp_check_1,
<<"\n-include_lib(\"epp_test.erl\").\n">>,
@@ -786,25 +785,25 @@ otp_8130(Config) when is_list(Config) ->
<<"\n-include(\"epp_test.erl\").\n">>,
[{error,{{2,2},epp,{depth,"include"}}}]}
],
- ?line [] = check(Config, Cks),
+ [] = check(Config, Cks),
- ?line Dir = ?config(priv_dir, Config),
- ?line File = filename:join(Dir, "otp_8130.erl"),
- ?line ok = file:write_file(File,
+ Dir = ?config(priv_dir, Config),
+ File = filename:join(Dir, "otp_8130.erl"),
+ ok = file:write_file(File,
"-module(otp_8130).\n"
"-define(a, 3.14).\n"
"t() -> ?a.\n"),
- ?line {ok,Epp} = epp:open(File, []),
+ {ok,Epp} = epp:open(File, []),
PreDefMacs = macs(Epp),
['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE',
'FUNCTION_ARITY','FUNCTION_NAME',
'LINE','MACHINE','MODULE','MODULE_STRING'] = PreDefMacs,
- ?line {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp),
- ?line {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp),
- ?line {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp),
- ?line {eof,_} = epp:scan_erl_form(Epp),
+ {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp),
+ {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp),
+ {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp),
+ {eof,_} = epp:scan_erl_form(Epp),
[a] = macs(Epp) -- PreDefMacs,
- ?line epp:close(Epp),
+ epp:close(Epp),
%% escript
ModuleStr = "any_name",
@@ -813,27 +812,27 @@ otp_8130(Config) when is_list(Config) ->
PreDefMacros = [{'MODULE', Module, redefine},
{'MODULE_STRING', ModuleStr, redefine},
a, {b,2}],
- ?line {ok,Epp2} = epp:open(File, [], PreDefMacros),
- ?line [{atom,_,true}] = macro(Epp2, a),
- ?line [{integer,_,2}] = macro(Epp2, b),
- ?line false = macro(Epp2, c),
- ?line epp:close(Epp2)
+ {ok,Epp2} = epp:open(File, [], PreDefMacros),
+ [{atom,_,true}] = macro(Epp2, a),
+ [{integer,_,2}] = macro(Epp2, b),
+ false = macro(Epp2, c),
+ epp:close(Epp2)
end(),
fun() ->
PreDefMacros = [{a,b,c}],
- ?line {error,{bad,{a,b,c}}} = epp:open(File, [], PreDefMacros)
+ {error,{bad,{a,b,c}}} = epp:open(File, [], PreDefMacros)
end(),
fun() ->
PreDefMacros = [a, {a,1}],
- ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
+ {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
end(),
fun() ->
PreDefMacros = [{a,1},a],
- ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
+ {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
end(),
- ?line {error,enoent} = epp:open("no such file", []),
- ?line {error,enoent} = epp:parse_file("no such file", [], []),
+ {error,enoent} = epp:open("no such file", []),
+ {error,enoent} = epp:parse_file("no such file", [], []),
_ = ifdef(Config),
@@ -973,7 +972,7 @@ ifdef(Config) ->
"t() -> a.\n">>,
{errors,[{{2,2},epp,{'NYI','if'}}],[]}}
],
- ?line [] = compile(Config, Cs),
+ [] = compile(Config, Cs),
Ts = [{ifdef_1,
<<"-ifdef(a).\n"
@@ -1054,7 +1053,7 @@ ifdef(Config) ->
ok}
],
- ?line [] = run(Config, Ts).
+ [] = run(Config, Ts).
@@ -1089,7 +1088,7 @@ overload_mac(Config) when is_list(Config) ->
"t() -> ?A(1).">>,
{errors,[{{4,9},epp,{mismatch,'A'}}],[]}}
],
- ?line [] = compile(Config, Cs),
+ [] = compile(Config, Cs),
Ts = [
{overload_mac_r1,
@@ -1113,24 +1112,24 @@ overload_mac(Config) when is_list(Config) ->
"t() -> ?A(1).">>,
1}
],
- ?line [] = run(Config, Ts).
+ [] = run(Config, Ts).
%% OTP-8388. More tests on overloaded macros.
otp_8388(Config) when is_list(Config) ->
Dir = ?config(priv_dir, Config),
- ?line File = filename:join(Dir, "otp_8388.erl"),
- ?line ok = file:write_file(File, <<"-module(otp_8388)."
+ File = filename:join(Dir, "otp_8388.erl"),
+ ok = file:write_file(File, <<"-module(otp_8388)."
"-define(LINE, a).">>),
fun() ->
PreDefMacros = [{'LINE', a}],
- ?line {error,{redefine_predef,'LINE'}} =
+ {error,{redefine_predef,'LINE'}} =
epp:open(File, [], PreDefMacros)
end(),
fun() ->
PreDefMacros = ['LINE'],
- ?line {error,{redefine_predef,'LINE'}} =
+ {error,{redefine_predef,'LINE'}} =
epp:open(File, [], PreDefMacros)
end(),
@@ -1160,7 +1159,7 @@ otp_8388(Config) when is_list(Config) ->
"test() -> ?BAR(1).\n">>,
{errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}}
],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% OTP-8470. Bugfix (one request - two replies).
@@ -1168,11 +1167,11 @@ otp_8470(Config) when is_list(Config) ->
Dir = ?config(priv_dir, Config),
C = <<"-file(\"erl_parse.yrl\", 486).\n"
"-file(\"erl_parse.yrl\", 488).\n">>,
- ?line File = filename:join(Dir, "otp_8470.erl"),
- ?line ok = file:write_file(File, C),
- ?line {ok, _List} = epp:parse_file(File, [], []),
+ File = filename:join(Dir, "otp_8470.erl"),
+ ok = file:write_file(File, C),
+ {ok, _List} = epp:parse_file(File, [], []),
file:delete(File),
- ?line receive _ -> fail() after 0 -> ok end,
+ receive _ -> fail() after 0 -> ok end,
ok.
%% OTP-8562. Record with no fields is considered typed.
@@ -1183,7 +1182,7 @@ otp_8562(Config) when is_list(Config) ->
{errors,[{{1,60},epp,missing_parenthesis},
{{2,13},epp,missing_parenthesis}], []}}
],
- ?line [] = compile(Config, Cs),
+ [] = compile(Config, Cs),
ok.
%% OTP-8911. -file and file inclusion bug.
@@ -1195,8 +1194,8 @@ otp_8911(Config) when is_list(Config) ->
do_otp_8911(Config)
end.
do_otp_8911(Config) ->
- ?line {ok, CWD} = file:get_cwd(),
- ?line ok = file:set_cwd(?config(priv_dir, Config)),
+ {ok, CWD} = file:get_cwd(),
+ ok = file:set_cwd(?config(priv_dir, Config)),
File = "i.erl",
Cont = <<"-module(i).
@@ -1206,22 +1205,22 @@ do_otp_8911(Config) ->
t() ->
a.
">>,
- ?line ok = file:write_file(File, Cont),
+ ok = file:write_file(File, Cont),
Incl = <<"-file(\"fil2\", 35).
t1() ->
b.
">>,
File1 = "i1.erl",
- ?line ok = file:write_file(File1, Incl),
+ ok = file:write_file(File1, Incl),
- ?line {ok, i} = cover:compile(File),
- ?line a = i:t(),
- ?line {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
- ?line cover:stop(),
+ {ok, i} = cover:compile(File),
+ a = i:t(),
+ {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
+ cover:stop(),
file:delete(File),
file:delete(File1),
- ?line file:set_cwd(CWD),
+ file:set_cwd(CWD),
ok.
%% OTP-8665. Bugfix premature end.
@@ -1230,7 +1229,7 @@ otp_8665(Config) when is_list(Config) ->
<<"-define(A, a)\n">>,
{errors,[{{1,54},epp,premature_end}],[]}}
],
- ?line [] = compile(Config, Cs),
+ [] = compile(Config, Cs),
ok.
%% OTP-10302. Unicode characters scanner/parser.
@@ -1543,9 +1542,9 @@ check_test(Config, Test) ->
compile_test(Config, Test0) ->
Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
Filename = "epp_test.erl",
- ?line PrivDir = ?config(priv_dir, Config),
- ?line File = filename:join(PrivDir, Filename),
- ?line ok = file:write_file(File, Test),
+ PrivDir = ?config(priv_dir, Config),
+ File = filename:join(PrivDir, Filename),
+ ok = file:write_file(File, Test),
Opts = [export_all,return,nowarn_unused_record,{outdir,PrivDir}],
case compile_file(File, Opts) of
{ok, Ws} -> warnings(File, Ws);
@@ -1597,14 +1596,14 @@ unopaque_forms(Forms) ->
run_test(Config, Test0) ->
Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
Filename = "epp_test.erl",
- ?line PrivDir = ?config(priv_dir, Config),
- ?line File = filename:join(PrivDir, Filename),
- ?line ok = file:write_file(File, Test),
+ PrivDir = ?config(priv_dir, Config),
+ File = filename:join(PrivDir, Filename),
+ ok = file:write_file(File, Test),
Opts = [return, {i,PrivDir},{outdir,PrivDir}],
- ?line {ok, epp_test, []} = compile:file(File, Opts),
+ {ok, epp_test, []} = compile:file(File, Opts),
AbsFile = filename:rootname(File, ".erl"),
- ?line {module, epp_test} = code:load_abs(AbsFile, epp_test),
- ?line Reply = epp_test:t(),
+ {module, epp_test} = code:load_abs(AbsFile, epp_test),
+ Reply = epp_test:t(),
code:purge(epp_test),
Reply.
@@ -1643,5 +1642,5 @@ ln2(M) ->
%% +fnu means a peer node has to be started; slave will not do
start_node(Name, Xargs) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
+ PA = filename:dirname(code:which(?MODULE)),
test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]).
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index 84e9f8bb15..c3ef4eb051 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -104,11 +104,11 @@ end_per_group(_GroupName, Config) ->
%% OTP-2405
guard_1(Config) when is_list(Config) ->
- ?line {ok,Tokens ,_} =
+ {ok,Tokens ,_} =
erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
- ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
- ?line no = guard_1_compiled(),
- ?line {value, no, []} = erl_eval:expr(Expr, []),
+ {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
+ no = guard_1_compiled(),
+ {value, no, []} = erl_eval:expr(Expr, []),
ok.
guard_1_compiled() ->
@@ -116,11 +116,11 @@ guard_1_compiled() ->
%% Similar to guard_1, but type-correct.
guard_2(Config) when is_list(Config) ->
- ?line {ok,Tokens ,_} =
+ {ok,Tokens ,_} =
erl_scan:string("if 6+4 == 4 -> yes; true -> no end. "),
- ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
- ?line no = guard_2_compiled(),
- ?line {value, no, []} = erl_eval:expr(Expr, []),
+ {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
+ no = guard_2_compiled(),
+ {value, no, []} = erl_eval:expr(Expr, []),
ok.
guard_2_compiled() ->
@@ -128,70 +128,70 @@ guard_2_compiled() ->
%% OTP-3069: syntactic sugar string ++ ...
string_plusplus(Config) when is_list(Config) ->
- ?line check(fun() -> case "abc" of "ab" ++ L -> L end end,
- "case \"abc\" of \"ab\" ++ L -> L end. ",
- "c"),
- ?line check(fun() -> case "abcde" of "ab" ++ "cd" ++ L -> L end end,
- "case \"abcde\" of \"ab\" ++ \"cd\" ++ L -> L end. ",
- "e"),
- ?line check(fun() -> case "abc" of [97, 98] ++ L -> L end end,
- "case \"abc\" of [97, 98] ++ L -> L end. ",
- "c"),
+ check(fun() -> case "abc" of "ab" ++ L -> L end end,
+ "case \"abc\" of \"ab\" ++ L -> L end. ",
+ "c"),
+ check(fun() -> case "abcde" of "ab" ++ "cd" ++ L -> L end end,
+ "case \"abcde\" of \"ab\" ++ \"cd\" ++ L -> L end. ",
+ "e"),
+ check(fun() -> case "abc" of [97, 98] ++ L -> L end end,
+ "case \"abc\" of [97, 98] ++ L -> L end. ",
+ "c"),
ok.
%% OTP-2983: match operator in pattern.
match_pattern(Config) when is_list(Config) ->
- ?line check(fun() -> case {a, b} of {a, _X}=Y -> {x,Y} end end,
- "case {a, b} of {a, X}=Y -> {x,Y} end. ",
- {x, {a, b}}),
- ?line check(fun() -> case {a, b} of Y={a, _X} -> {x,Y} end end,
- "case {a, b} of Y={a, X} -> {x,Y} end. ",
- {x, {a, b}}),
- ?line check(fun() -> case {a, b} of Y={a, _X}=Z -> {Z,Y} end end,
- "case {a, b} of Y={a, X}=Z -> {Z,Y} end. ",
- {{a, b}, {a, b}}),
- ?line check(fun() -> A = 4, B = 28, <<13:(A+(X=B))>>, X end,
- "begin A = 4, B = 28, <<13:(A+(X=B))>>, X end.",
- 28),
+ check(fun() -> case {a, b} of {a, _X}=Y -> {x,Y} end end,
+ "case {a, b} of {a, X}=Y -> {x,Y} end. ",
+ {x, {a, b}}),
+ check(fun() -> case {a, b} of Y={a, _X} -> {x,Y} end end,
+ "case {a, b} of Y={a, X} -> {x,Y} end. ",
+ {x, {a, b}}),
+ check(fun() -> case {a, b} of Y={a, _X}=Z -> {Z,Y} end end,
+ "case {a, b} of Y={a, X}=Z -> {Z,Y} end. ",
+ {{a, b}, {a, b}}),
+ check(fun() -> A = 4, B = 28, <<13:(A+(X=B))>>, X end,
+ "begin A = 4, B = 28, <<13:(A+(X=B))>>, X end.",
+ 28),
ok.
%% Binary match problems.
match_bin(Config) when is_list(Config) ->
- ?line check(fun() -> <<"abc">> = <<"abc">> end,
- "<<\"abc\">> = <<\"abc\">>. ",
- <<"abc">>),
- ?line check(fun() ->
- <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>,
- {Size,B,Rest}
- end,
- "begin <<Size,B:Size/binary,Rest/binary>> = <<2,\"AB\",\"CD\">>, "
- "{Size,B,Rest} end. ",
- {2,<<"AB">>,<<"CD">>}),
+ check(fun() -> <<"abc">> = <<"abc">> end,
+ "<<\"abc\">> = <<\"abc\">>. ",
+ <<"abc">>),
+ check(fun() ->
+ <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>,
+ {Size,B,Rest}
+ end,
+ "begin <<Size,B:Size/binary,Rest/binary>> = <<2,\"AB\",\"CD\">>, "
+ "{Size,B,Rest} end. ",
+ {2,<<"AB">>,<<"CD">>}),
ok.
%% OTP-3144: compile-time expressions in pattern.
pattern_expr(Config) when is_list(Config) ->
- ?line check(fun() -> case 4 of 2+2 -> ok end end,
- "case 4 of 2+2 -> ok end. ",
- ok),
- ?line check(fun() -> case 2 of +2 -> ok end end,
- "case 2 of +2 -> ok end. ",
- ok),
+ check(fun() -> case 4 of 2+2 -> ok end end,
+ "case 4 of 2+2 -> ok end. ",
+ ok),
+ check(fun() -> case 2 of +2 -> ok end end,
+ "case 2 of +2 -> ok end. ",
+ ok),
ok.
%% OTP-4518.
guard_3(Config) when is_list(Config) ->
- ?line check(fun() -> if false -> false; true -> true end end,
- "if false -> false; true -> true end.",
- true),
- ?line check(fun() -> if <<"hej">> == <<"hopp">> -> true;
- true -> false end end,
- "begin if <<\"hej\">> == <<\"hopp\">> -> true;
+ check(fun() -> if false -> false; true -> true end end,
+ "if false -> false; true -> true end.",
+ true),
+ check(fun() -> if <<"hej">> == <<"hopp">> -> true;
+ true -> false end end,
+ "begin if <<\"hej\">> == <<\"hopp\">> -> true;
true -> false end end.",
false),
- ?line check(fun() -> if <<"hej">> == <<"hej">> -> true;
- true -> false end end,
- "begin if <<\"hej\">> == <<\"hej\">> -> true;
+ check(fun() -> if <<"hej">> == <<"hej">> -> true;
+ true -> false end end,
+ "begin if <<\"hej\">> == <<\"hej\">> -> true;
true -> false end end.",
true),
ok.
@@ -205,25 +205,25 @@ guard_4(Config) when is_list(Config) ->
end,
"if erlang:is_integer(3) -> true ; true -> false end.",
true),
- ?line check(fun() -> [X || X <- [1,2,3], erlang:is_integer(X)] end,
- "[X || X <- [1,2,3], erlang:is_integer(X)].",
- [1,2,3]),
- ?line check(fun() -> if is_atom(is_integer(a)) -> true ; true -> false end
- end,
- "if is_atom(is_integer(a)) -> true ; true -> false end.",
- true),
+ check(fun() -> [X || X <- [1,2,3], erlang:is_integer(X)] end,
+ "[X || X <- [1,2,3], erlang:is_integer(X)].",
+ [1,2,3]),
+ check(fun() -> if is_atom(is_integer(a)) -> true ; true -> false end
+ end,
+ "if is_atom(is_integer(a)) -> true ; true -> false end.",
+ true),
check(fun() -> if erlang:is_atom(erlang:is_integer(a)) -> true;
true -> false end end,
"if erlang:is_atom(erlang:is_integer(a)) -> true; "
"true -> false end.",
true),
- ?line check(fun() -> if is_atom(3+a) -> true ; true -> false end end,
- "if is_atom(3+a) -> true ; true -> false end.",
- false),
- ?line check(fun() -> if erlang:is_atom(3+a) -> true ; true -> false end
- end,
- "if erlang:is_atom(3+a) -> true ; true -> false end.",
- false),
+ check(fun() -> if is_atom(3+a) -> true ; true -> false end end,
+ "if is_atom(3+a) -> true ; true -> false end.",
+ false),
+ check(fun() -> if erlang:is_atom(3+a) -> true ; true -> false end
+ end,
+ "if erlang:is_atom(3+a) -> true ; true -> false end.",
+ false),
ok.
%% Guards with erlang:'=='/2.
@@ -240,276 +240,276 @@ guard_5_compiled() ->
%% OTP-4518.
lc(Config) when is_list(Config) ->
- ?line check(fun() -> X = 32, [X || X <- [1,2,3]] end,
- "begin X = 32, [X || X <- [1,2,3]] end.",
- [1,2,3]),
- ?line check(fun() -> X = 32,
- [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end,
- %% "binsize variable" ^
- "begin X = 32,
+ check(fun() -> X = 32, [X || X <- [1,2,3]] end,
+ "begin X = 32, [X || X <- [1,2,3]] end.",
+ [1,2,3]),
+ check(fun() -> X = 32,
+ [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end,
+ %% "binsize variable" ^
+ "begin X = 32,
[X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end.",
[1,2]),
- ?line check(fun() -> Y = 13,[X || {X,Y} <- [{1,2}]] end,
- "begin Y = 13,[X || {X,Y} <- [{1,2}]] end.",
- [1]),
- ?line error_check("begin [A || X <- [{1,2}], 1 == A] end.",
- {unbound_var,'A'}),
- ?line error_check("begin X = 32,
+ check(fun() -> Y = 13,[X || {X,Y} <- [{1,2}]] end,
+ "begin Y = 13,[X || {X,Y} <- [{1,2}]] end.",
+ [1]),
+ error_check("begin [A || X <- [{1,2}], 1 == A] end.",
+ {unbound_var,'A'}),
+ error_check("begin X = 32,
[{Y,W} || X <- [1,2,32,Y=4], Z <- [1,2,W=3]] end.",
{unbound_var,'Y'}),
- ?line error_check("begin X = 32,<<A:B>> = <<100:X>> end.",
- {unbound_var,'B'}),
- ?line check(fun() -> [X || X <- [1,2,3,4], not (X < 2)] end,
- "begin [X || X <- [1,2,3,4], not (X < 2)] end.",
- [2,3,4]),
- ?line check(fun() -> [X || X <- [true,false], X] end,
- "[X || X <- [true,false], X].", [true]),
+ error_check("begin X = 32,<<A:B>> = <<100:X>> end.",
+ {unbound_var,'B'}),
+ check(fun() -> [X || X <- [1,2,3,4], not (X < 2)] end,
+ "begin [X || X <- [1,2,3,4], not (X < 2)] end.",
+ [2,3,4]),
+ check(fun() -> [X || X <- [true,false], X] end,
+ "[X || X <- [true,false], X].", [true]),
ok.
%% Simple cases, just to cover some code.
simple_cases(Config) when is_list(Config) ->
- ?line check(fun() -> A = $C end, "A = $C.", $C),
- %% ?line check(fun() -> A = 3.14 end, "A = 3.14.", 3.14),
- ?line check(fun() -> self() ! a, A = receive a -> true end end,
- "begin self() ! a, A = receive a -> true end end.",
- true),
- ?line check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
- receive b -> b end,
- {messages, [a,c]} =
- erlang:process_info(self(), messages),
- c:flush() end,
- "begin c:flush(), self() ! a, self() ! b, self() ! c,"
- "receive b -> b end,"
- "{messages, [a,c]} ="
- " erlang:process_info(self(), messages), c:flush() end.",
- ok),
- ?line check(fun() -> self() ! a, A = receive a -> true
- after 0 -> false end end,
- "begin self() ! a, A = receive a -> true"
- " after 0 -> false end end.",
- true),
- ?line check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
- receive b -> b after 0 -> true end,
- {messages, [a,c]} =
- erlang:process_info(self(), messages),
- c:flush() end,
- "begin c:flush(), self() ! a, self() ! b, self() ! c,"
- "receive b -> b after 0 -> true end,"
- "{messages, [a,c]} ="
- " erlang:process_info(self(), messages), c:flush() end.",
- ok),
- ?line check(fun() -> receive _ -> true after 10 -> false end end,
- "receive _ -> true after 10 -> false end.",
- false),
- ?line check(fun() -> F = fun(A) -> A end, true = 3 == F(3) end,
- "begin F = fun(A) -> A end, true = 3 == F(3) end.",
- true),
- ?line check(fun() -> F = fun(A) -> A end, true = 3 == apply(F, [3]) end,
- "begin F = fun(A) -> A end, true = 3 == apply(F,[3]) end.",
- true),
- ?line check(fun() -> catch throw(a) end, "catch throw(a).", a),
- ?line check(fun() -> catch a end, "catch a.", a),
- ?line check(fun() -> 4 == 3 end, "4 == 3.", false),
- ?line check(fun() -> not true end, "not true.", false),
- ?line check(fun() -> -3 end, "-3.", -3),
-
- ?line error_check("3.0 = 4.0.", {badmatch,4.0}),
- ?line check(fun() -> <<(3.0+2.0):32/float>> = <<5.0:32/float>> end,
- "<<(3.0+2.0):32/float>> = <<5.0:32/float>>.",
- <<5.0:32/float>>),
-
- ?line check(fun() -> false andalso kludd end, "false andalso kludd.",
- false),
- ?line check(fun() -> true andalso true end, "true andalso true.",
- true),
- ?line check(fun() -> true andalso false end, "true andalso false.",
- false),
- ?line check(fun() -> true andalso kludd end, "true andalso kludd.",
- kludd),
- ?line error_check("kladd andalso kludd.", {badarg,kladd}),
-
- ?line check(fun() -> if false andalso kludd -> a; true -> b end end,
- "if false andalso kludd -> a; true -> b end.",
- b),
- ?line check(fun() -> if true andalso true -> a; true -> b end end,
- "if true andalso true -> a; true -> b end.",
- a),
- ?line check(fun() -> if true andalso false -> a; true -> b end end,
- "if true andalso false -> a; true -> b end.",
- b),
-
- ?line check(fun() -> true orelse kludd end,
- "true orelse kludd.", true),
- ?line check(fun() -> false orelse false end,
- "false orelse false.", false),
- ?line check(fun() -> false orelse true end,
- "false orelse true.", true),
- ?line check(fun() -> false orelse kludd end,
- "false orelse kludd.", kludd),
- ?line error_check("kladd orelse kludd.", {badarg,kladd}),
- ?line error_check("[X || X <- [1,2,3], begin 1 end].",{bad_filter,1}),
- ?line error_check("[X || X <- a].",{bad_generator,a}),
-
- ?line check(fun() -> if true orelse kludd -> a; true -> b end end,
- "if true orelse kludd -> a; true -> b end.", a),
- ?line check(fun() -> if false orelse false -> a; true -> b end end,
- "if false orelse false -> a; true -> b end.", b),
- ?line check(fun() -> if false orelse true -> a; true -> b end end,
- "if false orelse true -> a; true -> b end.", a),
-
- ?line check(fun() -> [X || X <- [1,2,3], X+2] end,
- "[X || X <- [1,2,3], X+2].", []),
-
- ?line check(fun() -> [X || X <- [1,2,3], [X] == [X || X <- [2]]] end,
- "[X || X <- [1,2,3], [X] == [X || X <- [2]]].",
- [2]),
- ?line check(fun() -> F = fun(1) -> ett; (2) -> zwei end,
- ett = F(1), zwei = F(2) end,
- "begin F = fun(1) -> ett; (2) -> zwei end,
+ check(fun() -> A = $C end, "A = $C.", $C),
+ %% check(fun() -> A = 3.14 end, "A = 3.14.", 3.14),
+ check(fun() -> self() ! a, A = receive a -> true end end,
+ "begin self() ! a, A = receive a -> true end end.",
+ true),
+ check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
+ receive b -> b end,
+ {messages, [a,c]} =
+ erlang:process_info(self(), messages),
+ c:flush() end,
+ "begin c:flush(), self() ! a, self() ! b, self() ! c,"
+ "receive b -> b end,"
+ "{messages, [a,c]} ="
+ " erlang:process_info(self(), messages), c:flush() end.",
+ ok),
+ check(fun() -> self() ! a, A = receive a -> true
+ after 0 -> false end end,
+ "begin self() ! a, A = receive a -> true"
+ " after 0 -> false end end.",
+ true),
+ check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
+ receive b -> b after 0 -> true end,
+ {messages, [a,c]} =
+ erlang:process_info(self(), messages),
+ c:flush() end,
+ "begin c:flush(), self() ! a, self() ! b, self() ! c,"
+ "receive b -> b after 0 -> true end,"
+ "{messages, [a,c]} ="
+ " erlang:process_info(self(), messages), c:flush() end.",
+ ok),
+ check(fun() -> receive _ -> true after 10 -> false end end,
+ "receive _ -> true after 10 -> false end.",
+ false),
+ check(fun() -> F = fun(A) -> A end, true = 3 == F(3) end,
+ "begin F = fun(A) -> A end, true = 3 == F(3) end.",
+ true),
+ check(fun() -> F = fun(A) -> A end, true = 3 == apply(F, [3]) end,
+ "begin F = fun(A) -> A end, true = 3 == apply(F,[3]) end.",
+ true),
+ check(fun() -> catch throw(a) end, "catch throw(a).", a),
+ check(fun() -> catch a end, "catch a.", a),
+ check(fun() -> 4 == 3 end, "4 == 3.", false),
+ check(fun() -> not true end, "not true.", false),
+ check(fun() -> -3 end, "-3.", -3),
+
+ error_check("3.0 = 4.0.", {badmatch,4.0}),
+ check(fun() -> <<(3.0+2.0):32/float>> = <<5.0:32/float>> end,
+ "<<(3.0+2.0):32/float>> = <<5.0:32/float>>.",
+ <<5.0:32/float>>),
+
+ check(fun() -> false andalso kludd end, "false andalso kludd.",
+ false),
+ check(fun() -> true andalso true end, "true andalso true.",
+ true),
+ check(fun() -> true andalso false end, "true andalso false.",
+ false),
+ check(fun() -> true andalso kludd end, "true andalso kludd.",
+ kludd),
+ error_check("kladd andalso kludd.", {badarg,kladd}),
+
+ check(fun() -> if false andalso kludd -> a; true -> b end end,
+ "if false andalso kludd -> a; true -> b end.",
+ b),
+ check(fun() -> if true andalso true -> a; true -> b end end,
+ "if true andalso true -> a; true -> b end.",
+ a),
+ check(fun() -> if true andalso false -> a; true -> b end end,
+ "if true andalso false -> a; true -> b end.",
+ b),
+
+ check(fun() -> true orelse kludd end,
+ "true orelse kludd.", true),
+ check(fun() -> false orelse false end,
+ "false orelse false.", false),
+ check(fun() -> false orelse true end,
+ "false orelse true.", true),
+ check(fun() -> false orelse kludd end,
+ "false orelse kludd.", kludd),
+ error_check("kladd orelse kludd.", {badarg,kladd}),
+ error_check("[X || X <- [1,2,3], begin 1 end].",{bad_filter,1}),
+ error_check("[X || X <- a].",{bad_generator,a}),
+
+ check(fun() -> if true orelse kludd -> a; true -> b end end,
+ "if true orelse kludd -> a; true -> b end.", a),
+ check(fun() -> if false orelse false -> a; true -> b end end,
+ "if false orelse false -> a; true -> b end.", b),
+ check(fun() -> if false orelse true -> a; true -> b end end,
+ "if false orelse true -> a; true -> b end.", a),
+
+ check(fun() -> [X || X <- [1,2,3], X+2] end,
+ "[X || X <- [1,2,3], X+2].", []),
+
+ check(fun() -> [X || X <- [1,2,3], [X] == [X || X <- [2]]] end,
+ "[X || X <- [1,2,3], [X] == [X || X <- [2]]].",
+ [2]),
+ check(fun() -> F = fun(1) -> ett; (2) -> zwei end,
+ ett = F(1), zwei = F(2) end,
+ "begin F = fun(1) -> ett; (2) -> zwei end,
ett = F(1), zwei = F(2) end.",
zwei),
- ?line check(fun() -> F = fun(X) when X == 1 -> ett;
- (X) when X == 2 -> zwei end,
- ett = F(1), zwei = F(2) end,
- "begin F = fun(X) when X == 1 -> ett;
+ check(fun() -> F = fun(X) when X == 1 -> ett;
+ (X) when X == 2 -> zwei end,
+ ett = F(1), zwei = F(2) end,
+ "begin F = fun(X) when X == 1 -> ett;
(X) when X == 2 -> zwei end,
- ett = F(1), zwei = F(2) end.",
+ ett = F(1), zwei = F(2) end.",
zwei),
- ?line error_check("begin F = fun(1) -> ett end, zwei = F(2) end.",
- function_clause),
- ?line check(fun() -> if length([1]) == 1 -> yes;
- true -> no end end,
- "if length([1]) == 1 -> yes;
+ error_check("begin F = fun(1) -> ett end, zwei = F(2) end.",
+ function_clause),
+ check(fun() -> if length([1]) == 1 -> yes;
+ true -> no end end,
+ "if length([1]) == 1 -> yes;
true -> no end.",
yes),
- ?line check(fun() -> if is_integer(3) -> true; true -> false end end,
- "if is_integer(3) -> true; true -> false end.", true),
- ?line check(fun() -> if integer(3) -> true; true -> false end end,
- "if integer(3) -> true; true -> false end.", true),
- ?line check(fun() -> if is_float(3) -> true; true -> false end end,
- "if is_float(3) -> true; true -> false end.", false),
- ?line check(fun() -> if float(3) -> true; true -> false end end,
- "if float(3) -> true; true -> false end.", false),
- ?line check(fun() -> if is_number(3) -> true; true -> false end end,
- "if is_number(3) -> true; true -> false end.", true),
- ?line check(fun() -> if number(3) -> true; true -> false end end,
- "if number(3) -> true; true -> false end.", true),
- ?line check(fun() -> if is_atom(a) -> true; true -> false end end,
- "if is_atom(a) -> true; true -> false end.", true),
- ?line check(fun() -> if atom(a) -> true; true -> false end end,
- "if atom(a) -> true; true -> false end.", true),
- ?line check(fun() -> if is_list([]) -> true; true -> false end end,
- "if is_list([]) -> true; true -> false end.", true),
- ?line check(fun() -> if list([]) -> true; true -> false end end,
- "if list([]) -> true; true -> false end.", true),
- ?line check(fun() -> if is_tuple({}) -> true; true -> false end end,
- "if is_tuple({}) -> true; true -> false end.", true),
- ?line check(fun() -> if tuple({}) -> true; true -> false end end,
- "if tuple({}) -> true; true -> false end.", true),
- ?line check(fun() -> if is_pid(self()) -> true; true -> false end end,
- "if is_pid(self()) -> true; true -> false end.", true),
- ?line check(fun() -> if pid(self()) -> true; true -> false end end,
- "if pid(self()) -> true; true -> false end.", true),
- ?line check(fun() -> R = make_ref(), if is_reference(R) -> true;
- true -> false end end,
- "begin R = make_ref(), if is_reference(R) -> true;"
- "true -> false end end.", true),
- ?line check(fun() -> R = make_ref(), if reference(R) -> true;
- true -> false end end,
- "begin R = make_ref(), if reference(R) -> true;"
- "true -> false end end.", true),
- ?line check(fun() -> if is_port(a) -> true; true -> false end end,
- "if is_port(a) -> true; true -> false end.", false),
- ?line check(fun() -> if port(a) -> true; true -> false end end,
- "if port(a) -> true; true -> false end.", false),
- ?line check(fun() -> if is_function(a) -> true; true -> false end end,
- "if is_function(a) -> true; true -> false end.", false),
- ?line check(fun() -> if function(a) -> true; true -> false end end,
- "if function(a) -> true; true -> false end.", false),
- ?line check(fun() -> if is_binary(<<>>) -> true; true -> false end end,
- "if is_binary(<<>>) -> true; true -> false end.", true),
- ?line check(fun() -> if binary(<<>>) -> true; true -> false end end,
- "if binary(<<>>) -> true; true -> false end.", true),
- ?line check(fun() -> if is_integer(a) == true -> yes;
- true -> no end end,
- "if is_integer(a) == true -> yes;
+ check(fun() -> if is_integer(3) -> true; true -> false end end,
+ "if is_integer(3) -> true; true -> false end.", true),
+ check(fun() -> if integer(3) -> true; true -> false end end,
+ "if integer(3) -> true; true -> false end.", true),
+ check(fun() -> if is_float(3) -> true; true -> false end end,
+ "if is_float(3) -> true; true -> false end.", false),
+ check(fun() -> if float(3) -> true; true -> false end end,
+ "if float(3) -> true; true -> false end.", false),
+ check(fun() -> if is_number(3) -> true; true -> false end end,
+ "if is_number(3) -> true; true -> false end.", true),
+ check(fun() -> if number(3) -> true; true -> false end end,
+ "if number(3) -> true; true -> false end.", true),
+ check(fun() -> if is_atom(a) -> true; true -> false end end,
+ "if is_atom(a) -> true; true -> false end.", true),
+ check(fun() -> if atom(a) -> true; true -> false end end,
+ "if atom(a) -> true; true -> false end.", true),
+ check(fun() -> if is_list([]) -> true; true -> false end end,
+ "if is_list([]) -> true; true -> false end.", true),
+ check(fun() -> if list([]) -> true; true -> false end end,
+ "if list([]) -> true; true -> false end.", true),
+ check(fun() -> if is_tuple({}) -> true; true -> false end end,
+ "if is_tuple({}) -> true; true -> false end.", true),
+ check(fun() -> if tuple({}) -> true; true -> false end end,
+ "if tuple({}) -> true; true -> false end.", true),
+ check(fun() -> if is_pid(self()) -> true; true -> false end end,
+ "if is_pid(self()) -> true; true -> false end.", true),
+ check(fun() -> if pid(self()) -> true; true -> false end end,
+ "if pid(self()) -> true; true -> false end.", true),
+ check(fun() -> R = make_ref(), if is_reference(R) -> true;
+ true -> false end end,
+ "begin R = make_ref(), if is_reference(R) -> true;"
+ "true -> false end end.", true),
+ check(fun() -> R = make_ref(), if reference(R) -> true;
+ true -> false end end,
+ "begin R = make_ref(), if reference(R) -> true;"
+ "true -> false end end.", true),
+ check(fun() -> if is_port(a) -> true; true -> false end end,
+ "if is_port(a) -> true; true -> false end.", false),
+ check(fun() -> if port(a) -> true; true -> false end end,
+ "if port(a) -> true; true -> false end.", false),
+ check(fun() -> if is_function(a) -> true; true -> false end end,
+ "if is_function(a) -> true; true -> false end.", false),
+ check(fun() -> if function(a) -> true; true -> false end end,
+ "if function(a) -> true; true -> false end.", false),
+ check(fun() -> if is_binary(<<>>) -> true; true -> false end end,
+ "if is_binary(<<>>) -> true; true -> false end.", true),
+ check(fun() -> if binary(<<>>) -> true; true -> false end end,
+ "if binary(<<>>) -> true; true -> false end.", true),
+ check(fun() -> if is_integer(a) == true -> yes;
+ true -> no end end,
+ "if is_integer(a) == true -> yes;
true -> no end.",
no),
- ?line check(fun() -> if [] -> true; true -> false end end,
- "if [] -> true; true -> false end.", false),
- ?line error_check("if lists:member(1,[1]) -> true; true -> false end.",
- illegal_guard_expr),
- ?line error_check("if false -> true end.", if_clause),
- ?line check(fun() -> if a+b -> true; true -> false end end,
- "if a + b -> true; true -> false end.", false),
- ?line check(fun() -> if + b -> true; true -> false end end,
- "if + b -> true; true -> false end.", false),
- ?line error_check("case foo of bar -> true end.", {case_clause,foo}),
- ?line error_check("case 4 of 2+a -> true; _ -> false end.",
- illegal_pattern),
- ?line error_check("case 4 of +a -> true; _ -> false end.",
- illegal_pattern),
- ?line check(fun() -> case a of
- X when X == b -> one;
- X when X == a -> two
- end end,
- "begin case a of
+ check(fun() -> if [] -> true; true -> false end end,
+ "if [] -> true; true -> false end.", false),
+ error_check("if lists:member(1,[1]) -> true; true -> false end.",
+ illegal_guard_expr),
+ error_check("if false -> true end.", if_clause),
+ check(fun() -> if a+b -> true; true -> false end end,
+ "if a + b -> true; true -> false end.", false),
+ check(fun() -> if + b -> true; true -> false end end,
+ "if + b -> true; true -> false end.", false),
+ error_check("case foo of bar -> true end.", {case_clause,foo}),
+ error_check("case 4 of 2+a -> true; _ -> false end.",
+ illegal_pattern),
+ error_check("case 4 of +a -> true; _ -> false end.",
+ illegal_pattern),
+ check(fun() -> case a of
+ X when X == b -> one;
+ X when X == a -> two
+ end end,
+ "begin case a of
X when X == b -> one;
- X when X == a -> two
- end end.", two),
- ?line error_check("3 = 4.", {badmatch,4}),
- ?line error_check("a = 3.", {badmatch,3}),
- %% ?line error_check("3.1 = 2.7.",{badmatch,2.7}),
- ?line error_check("$c = 4.", {badmatch,4}),
- ?line check(fun() -> $c = $c end, "$c = $c.", $c),
- ?line check(fun() -> _ = bar end, "_ = bar.", bar),
- ?line check(fun() -> A = 14, A = 14 end,
+ X when X == a -> two
+ end end.", two),
+ error_check("3 = 4.", {badmatch,4}),
+ error_check("a = 3.", {badmatch,3}),
+ %% error_check("3.1 = 2.7.",{badmatch,2.7}),
+ error_check("$c = 4.", {badmatch,4}),
+ check(fun() -> $c = $c end, "$c = $c.", $c),
+ check(fun() -> _ = bar end, "_ = bar.", bar),
+ check(fun() -> A = 14, A = 14 end,
"begin A = 14, A = 14 end.", 14),
- ?line error_check("begin A = 14, A = 16 end.", {badmatch,16}),
- ?line error_check("\"hej\" = \"san\".", {badmatch,"san"}),
- ?line check(fun() -> "hej" = "hej" end,
+ error_check("begin A = 14, A = 16 end.", {badmatch,16}),
+ error_check("\"hej\" = \"san\".", {badmatch,"san"}),
+ check(fun() -> "hej" = "hej" end,
"\"hej\" = \"hej\".", "hej"),
- ?line error_check("[] = [a].", {badmatch,[a]}),
- ?line check(fun() -> [] = [] end, "[] = [].", []),
- ?line error_check("[a] = [].", {badmatch,[]}),
- ?line error_check("{a,b} = 34.", {badmatch,34}),
- ?line check(fun() -> <<X:7>> = <<8:7>>, X end,
+ error_check("[] = [a].", {badmatch,[a]}),
+ check(fun() -> [] = [] end, "[] = [].", []),
+ error_check("[a] = [].", {badmatch,[]}),
+ error_check("{a,b} = 34.", {badmatch,34}),
+ check(fun() -> <<X:7>> = <<8:7>>, X end,
"begin <<X:7>> = <<8:7>>, X end.", 8),
- ?line error_check("<<34:32>> = \"hej\".", {badmatch,"hej"}),
- ?line check(fun() -> trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end,
+ error_check("<<34:32>> = \"hej\".", {badmatch,"hej"}),
+ check(fun() -> trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end,
"begin trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end.", 0),
- ?line check(fun() -> (2#101 band 2#10101) bor (2#110 bxor 2#010) end,
+ check(fun() -> (2#101 band 2#10101) bor (2#110 bxor 2#010) end,
"(2#101 band 2#10101) bor (2#110 bxor 2#010).", 5),
- ?line check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
+ check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
"(2#1 bsl 4) + (2#10000 bsr 3).", 18),
- ?line check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
+ check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
"((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2).", false),
- ?line check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
+ check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
"(a /= b) or (2 > 4) or (3 >= 3).", true),
- ?line check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
+ check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
"\"hej\" ++ \"san\" =/= \"hejsan\" -- \"san\".", true),
- ?line check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true),
- ok.
+ check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true),
+ ok.
%% OTP-4929. Unary plus rejects non-numbers.
unary_plus(Config) when is_list(Config) ->
- ?line check(fun() -> F = fun(X) -> + X end,
- true = -1 == F(-1) end,
- "begin F = fun(X) -> + X end,"
- " true = -1 == F(-1) end.", true, ['F'], none, none),
- ?line error_check("+a.", badarith),
+ check(fun() -> F = fun(X) -> + X end,
+ true = -1 == F(-1) end,
+ "begin F = fun(X) -> + X end,"
+ " true = -1 == F(-1) end.", true, ['F'], none, none),
+ error_check("+a.", badarith),
ok.
%% OTP-5064. Can no longer apply atoms.
apply_atom(Config) when is_list(Config) ->
- ?line error_check("[X || X <- [[1],[2]],
+ error_check("[X || X <- [[1],[2]],
begin L = length, L(X) =:= 1 end].",
{badfun,length}),
ok.
%% OTP-5269. Bugs in the bit syntax.
otp_5269(Config) when is_list(Config) ->
- ?line check(fun() -> L = 8,
+ check(fun() -> L = 8,
F = fun(<<A:L,B:A>>) -> B end,
F(<<16:8, 7:16>>)
end,
@@ -517,7 +517,7 @@ otp_5269(Config) when is_list(Config) ->
L = 8, F = fun(<<A:L,B:A>>) -> B end, F(<<16:8, 7:16>>)
end.",
7),
- ?line check(fun() -> L = 8,
+ check(fun() -> L = 8,
F = fun(<<L:L,B:L>>) -> B end,
F(<<16:8, 7:16>>)
end,
@@ -525,31 +525,31 @@ otp_5269(Config) when is_list(Config) ->
L = 8, F = fun(<<L:L,B:L>>) -> B end, F(<<16:8, 7:16>>)
end.",
7),
- ?line check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end,
+ check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end,
"begin L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end.",
7),
- ?line error_check("begin L = 8, <<L:L,B:L>> = <<16:8, 7:16>> end.",
+ error_check("begin L = 8, <<L:L,B:L>> = <<16:8, 7:16>> end.",
{badmatch,<<16:8,7:16>>}),
- ?line error_check("begin <<L:16,L:L>> = <<16:16,8:16>>, L end.",
+ error_check("begin <<L:16,L:L>> = <<16:16,8:16>>, L end.",
{badmatch, <<16:16,8:16>>}),
- ?line check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end,
+ check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end,
"begin U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end.",
32),
- ?line check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end,
+ check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end,
"begin U = 8, [U || <<U:U>> <- [<<32:8>>]] end.",
[32]),
- ?line error_check("(fun({3,<<A:32,A:32>>}) -> a end)
+ error_check("(fun({3,<<A:32,A:32>>}) -> a end)
({3,<<17:32,19:32>>}).",
function_clause),
- ?line check(fun() -> [X || <<A:8,
+ check(fun() -> [X || <<A:8,
B:A>> <- [<<16:8,19:16>>],
<<X:8>> <- [<<B:8>>]] end,
"[X || <<A:8,
B:A>> <- [<<16:8,19:16>>],
<<X:8>> <- [<<B:8>>]].",
[19]),
- ?line check(fun() ->
+ check(fun() ->
(fun (<<A:1/binary, B:8/integer, _C:B/binary>>) ->
case A of
B -> wrong;
@@ -564,7 +564,7 @@ otp_5269(Config) when is_list(Config) ->
%% OTP-6539. try/catch bugs.
otp_6539(Config) when is_list(Config) ->
- ?line check(fun() ->
+ check(fun() ->
F = fun(A,B) ->
try A+B
catch _:_ -> dontthinkso
@@ -585,147 +585,147 @@ otp_6539(Config) when is_list(Config) ->
%% OTP-6543. bitlevel binaries.
otp_6543(Config) when is_list(Config) ->
- ?line check(fun() ->
+ check(fun() ->
<< <<X>> || <<X>> <- [1,2,3] >>
end,
"<< <<X>> || <<X>> <- [1,2,3] >>.",
<<>>),
- ?line check(fun() ->
+ check(fun() ->
<< <<X>> || X <- [1,2,3] >>
end,
"<< <<X>> || X <- [1,2,3] >>.",
<<1,2,3>>),
- ?line check(fun() ->
+ check(fun() ->
<< <<X:8>> || <<X:2>> <= <<"hej">> >>
end,
"<< <<X:8>> || <<X:2>> <= <<\"hej\">> >>.",
<<1,2,2,0,1,2,1,1,1,2,2,2>>),
- ?line check(fun() ->
+ check(fun() ->
<< <<X:8>> ||
<<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>
end,
"<< <<X:8>> ||
<<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>.",
<<7,3>>),
- ?line check(fun() -> <<34:18/big>> end,
+ check(fun() -> <<34:18/big>> end,
"<<34:18/big>>.",
<<0,8,2:2>>),
- ?line check(fun() -> <<34:18/big-unit:2>> end,
+ check(fun() -> <<34:18/big-unit:2>> end,
"<<34:18/big-unit:2>>.",
<<0,0,0,2,2:4>>),
- ?line check(fun() -> <<34:18/little>> end,
+ check(fun() -> <<34:18/little>> end,
"<<34:18/little>>.",
<<34,0,0:2>>),
- ?line case eval_string("<<34:18/native>>.") of
+ case eval_string("<<34:18/native>>.") of
<<0,8,2:2>> -> ok;
<<34,0,0:2>> -> ok
end,
- ?line check(fun() -> <<34:18/big-signed>> end,
+ check(fun() -> <<34:18/big-signed>> end,
"<<34:18/big-signed>>.",
<<0,8,2:2>>),
- ?line check(fun() -> <<34:18/little-signed>> end,
+ check(fun() -> <<34:18/little-signed>> end,
"<<34:18/little-signed>>.",
<<34,0,0:2>>),
- ?line case eval_string("<<34:18/native-signed>>.") of
+ case eval_string("<<34:18/native-signed>>.") of
<<0,8,2:2>> -> ok;
<<34,0,0:2>> -> ok
end,
- ?line check(fun() -> <<34:18/big-unsigned>> end,
+ check(fun() -> <<34:18/big-unsigned>> end,
"<<34:18/big-unsigned>>.",
<<0,8,2:2>>),
- ?line check(fun() -> <<34:18/little-unsigned>> end,
+ check(fun() -> <<34:18/little-unsigned>> end,
"<<34:18/little-unsigned>>.",
<<34,0,0:2>>),
- ?line case eval_string("<<34:18/native-unsigned>>.") of
+ case eval_string("<<34:18/native-unsigned>>.") of
<<0,8,2:2>> -> ok;
<<34,0,0:2>> -> ok
end,
- ?line check(fun() -> <<3.14:32/float-big>> end,
+ check(fun() -> <<3.14:32/float-big>> end,
"<<3.14:32/float-big>>.",
<<64,72,245,195>>),
- ?line check(fun() -> <<3.14:32/float-little>> end,
+ check(fun() -> <<3.14:32/float-little>> end,
"<<3.14:32/float-little>>.",
<<195,245,72,64>>),
- ?line case eval_string("<<3.14:32/float-native>>.") of
+ case eval_string("<<3.14:32/float-native>>.") of
<<64,72,245,195>> -> ok;
<<195,245,72,64>> -> ok
end,
- ?line error_check("<<(<<17,3:2>>)/binary>>.", badarg),
- ?line check(fun() -> <<(<<17,3:2>>)/bitstring>> end,
+ error_check("<<(<<17,3:2>>)/binary>>.", badarg),
+ check(fun() -> <<(<<17,3:2>>)/bitstring>> end,
"<<(<<17,3:2>>)/bitstring>>.",
<<17,3:2>>),
- ?line check(fun() -> <<(<<17,3:2>>):10/bitstring>> end,
+ check(fun() -> <<(<<17,3:2>>):10/bitstring>> end,
"<<(<<17,3:2>>):10/bitstring>>.",
<<17,3:2>>),
- ?line check(fun() -> <<<<344:17>>/binary-unit:17>> end,
+ check(fun() -> <<<<344:17>>/binary-unit:17>> end,
"<<<<344:17>>/binary-unit:17>>.",
<<344:17>>),
- ?line check(fun() -> <<X:18/big>> = <<34:18/big>>, X end,
+ check(fun() -> <<X:18/big>> = <<34:18/big>>, X end,
"begin <<X:18/big>> = <<34:18/big>>, X end.",
34),
- ?line check(fun() -> <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end,
+ check(fun() -> <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end,
"begin <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end.",
34),
- ?line check(fun() -> <<X:18/little>> = <<34:18/little>>, X end,
+ check(fun() -> <<X:18/little>> = <<34:18/little>>, X end,
"begin <<X:18/little>> = <<34:18/little>>, X end.",
34),
- ?line check(fun() -> <<X:18/native>> = <<34:18/native>>, X end,
+ check(fun() -> <<X:18/native>> = <<34:18/native>>, X end,
"begin <<X:18/native>> = <<34:18/native>>, X end.",
34),
- ?line check(fun() -> <<X:18/big-signed>> = <<34:18/big-signed>>, X end,
+ check(fun() -> <<X:18/big-signed>> = <<34:18/big-signed>>, X end,
"begin <<X:18/big-signed>> = <<34:18/big-signed>>, X end.",
34),
- ?line check(fun() -> <<X:18/little-signed>> = <<34:18/little-signed>>,
+ check(fun() -> <<X:18/little-signed>> = <<34:18/little-signed>>,
X end,
"begin <<X:18/little-signed>> = <<34:18/little-signed>>,
X end.",
34),
- ?line check(fun() -> <<X:18/native-signed>> = <<34:18/native-signed>>,
+ check(fun() -> <<X:18/native-signed>> = <<34:18/native-signed>>,
X end,
"begin <<X:18/native-signed>> = <<34:18/native-signed>>,
X end.",
34),
- ?line check(fun() -> <<X:18/big-unsigned>> = <<34:18/big-unsigned>>,
+ check(fun() -> <<X:18/big-unsigned>> = <<34:18/big-unsigned>>,
X end,
"begin <<X:18/big-unsigned>> = <<34:18/big-unsigned>>,
X end.",
34),
- ?line check(fun() ->
+ check(fun() ->
<<X:18/little-unsigned>> = <<34:18/little-unsigned>>,
X end,
"begin <<X:18/little-unsigned>> = <<34:18/little-unsigned>>,
X end.",
34),
- ?line check(fun() ->
+ check(fun() ->
<<X:18/native-unsigned>> = <<34:18/native-unsigned>>,
X end,
"begin <<X:18/native-unsigned>> = <<34:18/native-unsigned>>,
X end.",
34),
- ?line check(fun() -> <<X:32/float-big>> = <<2.0:32/float-big>>, X end,
+ check(fun() -> <<X:32/float-big>> = <<2.0:32/float-big>>, X end,
"begin <<X:32/float-big>> = <<2.0:32/float-big>>,
X end.",
2.0),
- ?line check(fun() -> <<X:32/float-little>> = <<2.0:32/float-little>>,
+ check(fun() -> <<X:32/float-little>> = <<2.0:32/float-little>>,
X end,
"begin <<X:32/float-little>> = <<2.0:32/float-little>>,
X end.",
2.0),
- ?line check(fun() -> <<X:32/float-native>> = <<2.0:32/float-native>>,
+ check(fun() -> <<X:32/float-native>> = <<2.0:32/float-native>>,
X end,
"begin <<X:32/float-native>> = <<2.0:32/float-native>>,
X end.",
2.0),
- ?line check(
+ check(
fun() ->
[X || <<"hej",X:8>> <= <<"hej",8,"san",9,"hej",17,"hej">>]
end,
"[X || <<\"hej\",X:8>> <=
<<\"hej\",8,\"san\",9,\"hej\",17,\"hej\">>].",
[8,17]),
- ?line check(
+ check(
fun() ->
L = 8, << <<B:32>> || <<L:L,B:L>> <= <<16:8, 7:16>> >>
end,
@@ -734,41 +734,41 @@ otp_6543(Config) when is_list(Config) ->
<<0,0,0,7>>),
%% Test the Value part of a binary segment.
%% "Old" bugs have been fixed (partial_eval is called on Value).
- ?line check(fun() -> [ 3 || <<17/float>> <= <<17.0/float>>] end,
+ check(fun() -> [ 3 || <<17/float>> <= <<17.0/float>>] end,
"[ 3 || <<17/float>> <= <<17.0/float>>].",
[3]),
- ?line check(fun() -> [ 3 || <<17/float>> <- [<<17.0/float>>]] end,
+ check(fun() -> [ 3 || <<17/float>> <- [<<17.0/float>>]] end,
"[ 3 || <<17/float>> <- [<<17.0/float>>]].",
[3]),
- ?line check(fun() -> [ X || <<17/float,X:3>> <= <<17.0/float,2:3>>] end,
+ check(fun() -> [ X || <<17/float,X:3>> <= <<17.0/float,2:3>>] end,
"[ X || <<17/float,X:3>> <= <<17.0/float,2:3>>].",
[2]),
- ?line check(fun() ->
+ check(fun() ->
[ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>]
end,
"[ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>].",
[foo]),
- ?line check(fun() ->
+ check(fun() ->
[ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]]
end,
"[ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]].",
[foo]),
- ?line error_check("[ foo || <<(1 bsl 1024)/float>> <-
+ error_check("[ foo || <<(1 bsl 1024)/float>> <-
[<<(1 bsl 1024)/float>>]].",
badarg),
- ?line check(fun() ->
+ check(fun() ->
[ foo || <<(1 bsl 1024)/float>> <- [<<(1 bsl 1023)/float>>]]
end,
"[ foo || <<(1 bsl 1024)/float>> <-
[<<(1 bsl 1023)/float>>]].",
[]),
- ?line check(fun() ->
+ check(fun() ->
[ foo || <<(1 bsl 1024)/float>> <= <<(1 bsl 1023)/float>>]
end,
"[ foo || <<(1 bsl 1024)/float>> <=
<<(1 bsl 1023)/float>>].",
[]),
- ?line check(fun() ->
+ check(fun() ->
L = 8,
[{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
end,
@@ -776,7 +776,7 @@ otp_6543(Config) when is_list(Config) ->
[{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
end.",
[{32,7.0}]),
- ?line check(fun() ->
+ check(fun() ->
L = 8,
[{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
end,
@@ -784,27 +784,27 @@ otp_6543(Config) when is_list(Config) ->
[{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
end.",
[{32,7.0}]),
- ?line check(fun() ->
+ check(fun() ->
[foo || <<"s">> <= <<"st">>]
end,
"[foo || <<\"s\">> <= <<\"st\">>].",
[foo]),
- ?line check(fun() -> <<_:32>> = <<17:32>> end,
+ check(fun() -> <<_:32>> = <<17:32>> end,
"<<_:32>> = <<17:32>>.",
<<17:32>>),
- ?line check(fun() -> [foo || <<_:32>> <= <<17:32,20:32>>] end,
+ check(fun() -> [foo || <<_:32>> <= <<17:32,20:32>>] end,
"[foo || <<_:32>> <= <<17:32,20:32>>].",
[foo,foo]),
- ?line check(fun() -> << <<X:32>> || X <- [1,2,3], X > 1 >> end,
+ check(fun() -> << <<X:32>> || X <- [1,2,3], X > 1 >> end,
"<< <<X:32>> || X <- [1,2,3], X > 1 >>.",
<<0,0,0,2,0,0,0,3>>),
- ?line error_check("[X || <<X>> <= [a,b]].",{bad_generator,[a,b]}),
+ error_check("[X || <<X>> <= [a,b]].",{bad_generator,[a,b]}),
ok.
%% OTP-6787. bitlevel binaries.
otp_6787(Config) when is_list(Config) ->
- ?line check(
+ check(
fun() -> <<16:(1024*1024)>> = <<16:(1024*1024)>> end,
"<<16:(1024*1024)>> = <<16:(1024*1024)>>.",
<<16:1048576>>),
@@ -812,7 +812,7 @@ otp_6787(Config) when is_list(Config) ->
%% OTP-6977. ++ bug.
otp_6977(Config) when is_list(Config) ->
- ?line check(
+ check(
fun() -> (fun([$X] ++ _) -> ok end)("X") end,
"(fun([$X] ++ _) -> ok end)(\"X\").",
ok),
@@ -822,70 +822,70 @@ otp_6977(Config) when is_list(Config) ->
otp_7550(Config) when is_list(Config) ->
%% UTF-8.
- ?line check(
+ check(
fun() -> <<65>> = <<65/utf8>> end,
"<<65>> = <<65/utf8>>.",
<<65>>),
- ?line check(
+ check(
fun() -> <<350/utf8>> = <<197,158>> end,
"<<350/utf8>> = <<197,158>>.",
<<197,158>>),
- ?line check(
+ check(
fun() -> <<$b,$j,$\303,$\266,$r,$n>> = <<"bj\366rn"/utf8>> end,
"<<$b,$j,$\303,$\266,$r,$n>> = <<\"bj\366rn\"/utf8>>.",
<<$b,$j,$\303,$\266,$r,$n>>),
%% UTF-16.
- ?line check(
+ check(
fun() -> <<0,65>> = <<65/utf16>> end,
"<<0,65>> = <<65/utf16>>.",
<<0,65>>),
- ?line check(
+ check(
fun() -> <<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>> end,
"<<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>>.",
<<16#D8,16#08,16#DF,16#45>>),
- ?line check(
+ check(
fun() -> <<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>> end,
"<<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>>.",
<<16#08,16#D8,16#45,16#DF>>),
- ?line check(
+ check(
fun() -> <<350/utf16>> = <<1,94>> end,
"<<350/utf16>> = <<1,94>>.",
<<1,94>>),
- ?line check(
+ check(
fun() -> <<350/little-utf16>> = <<94,1>> end,
"<<350/little-utf16>> = <<94,1>>.",
<<94,1>>),
- ?line check(
+ check(
fun() -> <<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>> end,
"<<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>>.",
<<16#D8,16#08,16#DF,16#45>>),
- ?line check(
+ check(
fun() -> <<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>> end,
"<<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>>.",
<<16#08,16#D8,16#45,16#DF>>),
%% UTF-32.
- ?line check(
+ check(
fun() -> <<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>> end,
"<<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>>.",
<<16#0,16#01,16#23,16#45>>),
- ?line check(
+ check(
fun() -> <<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>> end,
"<<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>>.",
<<16#0,16#01,16#23,16#45>>),
- ?line check(
+ check(
fun() -> <<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>> end,
"<<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>>.",
<<16#45,16#23,16#01,16#00>>),
- ?line check(
+ check(
fun() -> <<16#12345/little-utf32>> end,
"<<16#12345/little-utf32>>.",
<<16#45,16#23,16#01,16#00>>),
%% Mixed.
- ?line check(
+ check(
fun() -> <<16#41,16#12345/utf32,16#0391:16,16#2E:8>> end,
"<<16#41,16#12345/utf32,16#0391:16,16#2E:8>>.",
<<16#41,16#00,16#01,16#23,16#45,16#03,16#91,16#2E>>),
@@ -894,7 +894,7 @@ otp_7550(Config) when is_list(Config) ->
%% OTP-8133. Bit comprehension bug.
otp_8133(Config) when is_list(Config) ->
- ?line check(
+ check(
fun() ->
E = fun(N) ->
if
@@ -917,7 +917,7 @@ otp_8133(Config) when is_list(Config) ->
end
end.",
ok),
- ?line check(
+ check(
fun() ->
E = fun(N) ->
if
@@ -994,35 +994,35 @@ funs(Config) when is_list(Config) ->
do_funs(lfh(), none),
do_funs(lfh(), efh()),
- ?line error_check("nix:foo().", {access_not_allowed,nix}, lfh(), efh()),
- ?line error_check("bar().", undef, none, none),
+ error_check("nix:foo().", {access_not_allowed,nix}, lfh(), efh()),
+ error_check("bar().", undef, none, none),
- ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
+ check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
F1(F1, 1000) end,
"begin F1 = fun(F,N) -> count_down(F, N) end,"
"F1(F1,1000) end.",
0, ['F1'], lfh(), none),
- ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
+ check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
F1(F1, 1000) end,
"begin F1 = fun(F,N) -> count_down(F, N) end,"
"F1(F1,1000) end.",
0, ['F1'], lfh_value(), none),
- ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
+ check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
F1(F1, 1000) end,
"begin F1 = fun(F,N) -> count_down(F, N) end,"
"F1(F1,1000) end.",
0, ['F1'], lfh_value_extra(), none),
- ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
+ check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
F1(F1, 1000) end,
"begin F1 = fun(F,N) -> count_down(F, N) end,"
"F1(F1,1000) end.",
0, ['F1'], {?MODULE,local_func_value}, none),
%% This is not documented, and only for backward compatibility (good!).
B0 = erl_eval:new_bindings(),
- ?line check(fun() -> is_function(?MODULE:count_down_fun()) end,
+ check(fun() -> is_function(?MODULE:count_down_fun()) end,
"begin is_function(count_down_fun()) end.",
true, [], {?MODULE,local_func,[B0]},none),
@@ -1030,19 +1030,19 @@ funs(Config) when is_list(Config) ->
({M,F}, As) -> apply(M, F, As)
end,
EFH = {value, EF},
- ?line error_check("apply(timer, sleep, [1]).", got_it, none, EFH),
- ?line error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
+ error_check("apply(timer, sleep, [1]).", got_it, none, EFH),
+ error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
got_it, none, EFH),
- ?line error_check("fun c/1.", undef),
- ?line error_check("fun a:b/0().", undef),
+ error_check("fun c/1.", undef),
+ error_check("fun a:b/0().", undef),
MaxArgs = 20,
- ?line [true] =
+ [true] =
lists:usort([run_many_args(SAs) || SAs <- many_args(MaxArgs)]),
- ?line {'EXIT',{{argument_limit,_},_}} =
+ {'EXIT',{{argument_limit,_},_}} =
(catch run_many_args(many_args1(MaxArgs+1))),
- ?line check(fun() -> M = lists, F = fun M:reverse/1,
+ check(fun() -> M = lists, F = fun M:reverse/1,
[1,2] = F([2,1]), ok end,
"begin M = lists, F = fun M:reverse/1,"
" [1,2] = F([2,1]), ok end.",
@@ -1076,17 +1076,17 @@ do_funs(LFH, EFH) ->
%% manually with 1000 replaced by 1000000.
M = atom_to_list(?MODULE),
- ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
+ check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
F1(F1, 1000) end,
concat(["begin F1 = fun(F,N) -> ", M,
":count_down(F, N) end, F1(F1,1000) end."]),
0, ['F1'], LFH, EFH),
- ?line check(fun() -> F1 = fun(F,N) -> apply(?MODULE,count_down,[F,N])
+ check(fun() -> F1 = fun(F,N) -> apply(?MODULE,count_down,[F,N])
end, F1(F1, 1000) end,
concat(["begin F1 = fun(F,N) -> apply(", M,
",count_down,[F, N]) end, F1(F1,1000) end."]),
0, ['F1'], LFH, EFH),
- ?line check(fun() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);
+ check(fun() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);
(_F,0) -> ok end,
F(F, 1000)
end,
@@ -1094,7 +1094,7 @@ do_funs(LFH, EFH) ->
"(_F,0) -> ok end,"
"F(F, 1000) end.",
ok, ['F'], LFH, EFH),
- ?line check(fun() -> F = fun(F,N) when N > 0 ->
+ check(fun() -> F = fun(F,N) when N > 0 ->
apply(erlang,apply,[F,[F,N-1]]);
(_F,0) -> ok end,
F(F, 1000)
@@ -1104,7 +1104,7 @@ do_funs(LFH, EFH) ->
"(_F,0) -> ok end,"
"F(F, 1000) end.",
ok, ['F'], LFH, EFH),
- ?line check(fun() -> F = count_down_fun(),
+ check(fun() -> F = count_down_fun(),
SF = fun(SF, F1, N) -> F(SF, F1, N) end,
SF(SF, F, 1000) end,
concat(["begin F = ", M, ":count_down_fun(),"
@@ -1113,7 +1113,7 @@ do_funs(LFH, EFH) ->
ok, ['F','SF'], LFH, EFH),
- ?line check(fun() -> F = fun(X) -> A = 1+X, {X,A} end,
+ check(fun() -> F = fun(X) -> A = 1+X, {X,A} end,
true = {2,3} == F(2) end,
"begin F = fun(X) -> A = 1+X, {X,A} end,
true = {2,3} == F(2) end.", true, ['F'], LFH, EFH),
@@ -1122,13 +1122,13 @@ do_funs(LFH, EFH) ->
"begin F = fun(X) -> erlang:'+'(X,2) end,"
" true = 3 == F(1) end.", true, ['F'],
LFH, EFH),
- ?line check(fun() -> F = fun(X) -> byte_size(X) end,
+ check(fun() -> F = fun(X) -> byte_size(X) end,
?MODULE:do_apply(F,<<"hej">>) end,
concat(["begin F = fun(X) -> size(X) end,",
M,":do_apply(F,<<\"hej\">>) end."]),
3, ['F'], LFH, EFH),
- ?line check(fun() -> F1 = fun(X, Z) -> {X,Z} end,
+ check(fun() -> F1 = fun(X, Z) -> {X,Z} end,
Z = 5,
F2 = fun(X, Y) -> F1(Z,{X,Y}) end,
F3 = fun(X, Y) -> {a,F1(Z,{X,Y})} end,
@@ -1145,26 +1145,26 @@ do_funs(LFH, EFH) ->
{5,{5,y}} = F2(Z,y),
true = {5,{x,5}} == F2(x,Z) end.",
true, ['F1','Z','F2','F3'], LFH, EFH),
- ?line check(fun() -> F = fun(X) -> byte_size(X) end,
+ check(fun() -> F = fun(X) -> byte_size(X) end,
F2 = fun(Y) -> F(Y) end,
?MODULE:do_apply(F2,<<"hej">>) end,
concat(["begin F = fun(X) -> size(X) end,",
"F2 = fun(Y) -> F(Y) end,",
M,":do_apply(F2,<<\"hej\">>) end."]),
3, ['F','F2'], LFH, EFH),
- ?line check(fun() -> Z = 5, F = fun(X) -> {Z,X} end,
+ check(fun() -> Z = 5, F = fun(X) -> {Z,X} end,
F2 = fun(Z) -> F(Z) end, F2(3) end,
"begin Z = 5, F = fun(X) -> {Z,X} end,
F2 = fun(Z) -> F(Z) end, F2(3) end.",
{5,3},['F','F2','Z'], LFH, EFH),
- ?line check(fun() -> F = fun(Z) -> Z end,
+ check(fun() -> F = fun(Z) -> Z end,
F2 = fun(X) -> F(X), Z = {X,X}, Z end,
{1,1} = F2(1), Z = 7, Z end,
"begin F = fun(Z) -> Z end,
F2 = fun(X) -> F(X), Z = {X,X}, Z end,
{1,1} = F2(1), Z = 7, Z end.", 7, ['F','F2','Z'],
LFH, EFH),
- ?line check(fun() -> F = fun(F, N) -> [?MODULE:count_down(F,N) || X <-[1]]
+ check(fun() -> F = fun(F, N) -> [?MODULE:count_down(F,N) || X <-[1]]
end, F(F,2) end,
concat(["begin F = fun(F, N) -> [", M,
":count_down(F,N) || X <-[1]] end, F(F,2) end."]),
@@ -1226,39 +1226,39 @@ external_func({M,F}, As) ->
%% Test try-of-catch-after-end statement.
try_catch(Config) when is_list(Config) ->
%% Match in of with catch
- ?line check(fun() -> try 1 of 1 -> 2 catch _:_ -> 3 end end,
+ check(fun() -> try 1 of 1 -> 2 catch _:_ -> 3 end end,
"try 1 of 1 -> 2 catch _:_ -> 3 end.", 2),
- ?line check(fun() -> try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
+ check(fun() -> try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
"try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 2),
- ?line check(fun() -> try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
+ check(fun() -> try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
"try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 4),
%% Just after
- ?line check(fun () -> X = try 1 after put(try_catch, 2) end,
+ check(fun () -> X = try 1 after put(try_catch, 2) end,
{X,get(try_catch)} end,
"begin X = try 1 after put(try_catch, 2) end, "
"{X,get(try_catch)} end.", {1,2}),
%% Match in of with after
- ?line check(fun() -> X = try 1 of 1 -> 2 after put(try_catch, 3) end,
+ check(fun() -> X = try 1 of 1 -> 2 after put(try_catch, 3) end,
{X,get(try_catch)} end,
"begin X = try 1 of 1 -> 2 after put(try_catch, 3) end, "
"{X,get(try_catch)} end.", {2,3}),
- ?line check(fun() -> X = try 1 of 1 -> 2; 3 -> 4
+ check(fun() -> X = try 1 of 1 -> 2; 3 -> 4
after put(try_catch, 5) end,
{X,get(try_catch)} end,
"begin X = try 1 of 1 -> 2; 3 -> 4 "
" after put(try_catch, 5) end, "
" {X,get(try_catch)} end.", {2,5}),
- ?line check(fun() -> X = try 3 of 1 -> 2; 3 -> 4
+ check(fun() -> X = try 3 of 1 -> 2; 3 -> 4
after put(try_catch, 5) end,
{X,get(try_catch)} end,
"begin X = try 3 of 1 -> 2; 3 -> 4 "
" after put(try_catch, 5) end, "
" {X,get(try_catch)} end.", {4,5}),
%% Nomatch in of
- ?line error_check("try 1 of 2 -> 3 catch _:_ -> 4 end.",
+ error_check("try 1 of 2 -> 3 catch _:_ -> 4 end.",
{try_clause,1}),
%% Nomatch in of with after
- ?line check(fun () -> {'EXIT',{{try_clause,1},_}} =
+ check(fun () -> {'EXIT',{{try_clause,1},_}} =
begin catch try 1 of 2 -> 3
after put(try_catch, 4) end end,
get(try_catch) end,
@@ -1267,14 +1267,14 @@ try_catch(Config) when is_list(Config) ->
" after put(try_catch, 4) end end, "
" get(try_catch) end. ", 4),
%% Exception in try
- ?line check(fun () -> try 1=2 catch error:{badmatch,2} -> 3 end end,
+ check(fun () -> try 1=2 catch error:{badmatch,2} -> 3 end end,
"try 1=2 catch error:{badmatch,2} -> 3 end.", 3),
- ?line check(fun () -> try 1=2 of 3 -> 4
+ check(fun () -> try 1=2 of 3 -> 4
catch error:{badmatch,2} -> 5 end end,
"try 1=2 of 3 -> 4 "
"catch error:{badmatch,2} -> 5 end.", 5),
%% Exception in try with after
- ?line check(fun () -> X = try 1=2
+ check(fun () -> X = try 1=2
catch error:{badmatch,2} -> 3
after put(try_catch, 4) end,
{X,get(try_catch)} end,
@@ -1282,7 +1282,7 @@ try_catch(Config) when is_list(Config) ->
" catch error:{badmatch,2} -> 3 "
" after put(try_catch, 4) end, "
" {X,get(try_catch)} end. ", {3,4}),
- ?line check(fun () -> X = try 1=2 of 3 -> 4
+ check(fun () -> X = try 1=2 of 3 -> 4
catch error:{badmatch,2} -> 5
after put(try_catch, 6) end,
{X,get(try_catch)} end,
@@ -1291,12 +1291,12 @@ try_catch(Config) when is_list(Config) ->
" after put(try_catch, 6) end, "
" {X,get(try_catch)} end. ", {5,6}),
%% Uncaught exception
- ?line error_check("try 1=2 catch error:undefined -> 3 end. ",
+ error_check("try 1=2 catch error:undefined -> 3 end. ",
{badmatch,2}),
- ?line error_check("try 1=2 of 3 -> 4 catch error:undefined -> 5 end. ",
+ error_check("try 1=2 of 3 -> 4 catch error:undefined -> 5 end. ",
{badmatch,2}),
%% Uncaught exception with after
- ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
+ check(fun () -> {'EXIT',{{badmatch,2},_}} =
begin catch try 1=2
after put(try_catch, 3) end end,
get(try_catch) end,
@@ -1304,7 +1304,7 @@ try_catch(Config) when is_list(Config) ->
" begin catch try 1=2 "
" after put(try_catch, 3) end end, "
" get(try_catch) end. ", 3),
- ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
+ check(fun () -> {'EXIT',{{badmatch,2},_}} =
begin catch try 1=2 of 3 -> 4
after put(try_catch, 5) end end,
get(try_catch) end,
@@ -1312,7 +1312,7 @@ try_catch(Config) when is_list(Config) ->
" begin catch try 1=2 of 3 -> 4"
" after put(try_catch, 5) end end, "
" get(try_catch) end. ", 5),
- ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
+ check(fun () -> {'EXIT',{{badmatch,2},_}} =
begin catch try 1=2 catch error:undefined -> 3
after put(try_catch, 4) end end,
get(try_catch) end,
@@ -1320,7 +1320,7 @@ try_catch(Config) when is_list(Config) ->
" begin catch try 1=2 catch error:undefined -> 3 "
" after put(try_catch, 4) end end, "
" get(try_catch) end. ", 4),
- ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
+ check(fun () -> {'EXIT',{{badmatch,2},_}} =
begin catch try 1=2 of 3 -> 4
catch error:undefined -> 5
after put(try_catch, 6) end end,
@@ -1335,21 +1335,21 @@ try_catch(Config) when is_list(Config) ->
%% OTP-7933.
eval_expr_5(Config) when is_list(Config) ->
- ?line {ok,Tokens ,_} =
+ {ok,Tokens ,_} =
erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
- ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
- ?line {value, no, []} = erl_eval:expr(Expr, [], none, none, none),
- ?line no = erl_eval:expr(Expr, [], none, none, value),
+ {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
+ {value, no, []} = erl_eval:expr(Expr, [], none, none, none),
+ no = erl_eval:expr(Expr, [], none, none, value),
try
erl_eval:expr(Expr, [], none, none, 4711),
- ?line function_clause = should_never_reach_here
+ function_clause = should_never_reach_here
catch
error:function_clause ->
ok
end.
zero_width(Config) when is_list(Config) ->
- ?line check(fun() ->
+ check(fun() ->
{'EXIT',{badarg,_}} = (catch <<not_a_number:0>>),
ok
end, "begin {'EXIT',{badarg,_}} = (catch <<not_a_number:0>>), "
diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl
index 601f5ca0b1..d88fa1e152 100644
--- a/lib/stdlib/test/erl_expand_records_SUITE.erl
+++ b/lib/stdlib/test/erl_expand_records_SUITE.erl
@@ -75,20 +75,20 @@ end_per_group(_GroupName, Config) ->
%% Import module and functions.
attributes(Config) when is_list(Config) ->
Ts = [
- <<"-import(lists, [append/2, reverse/1]).
+ <<"-import(lists, [append/2, reverse/1]).
-record(r, {a,b}).
- t() ->
- [2,1] = reverse(append([1],[2])),
- 3 = length([1,2,3]),
- 3 = record_info(size, r),
- [a, b] = record_info(fields, r),
- [_|_] = erl_expand_records_SUITE:all(),
- ok.
- ">>
+t() ->
+ [2,1] = reverse(append([1],[2])),
+ 3 = length([1,2,3]),
+ 3 = record_info(size, r),
+ [a, b] = record_info(fields, r),
+ [_|_] = erl_expand_records_SUITE:all(),
+ ok.
+">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Some expressions.
@@ -151,8 +151,8 @@ expr(Config) when is_list(Config) ->
%% The code above should run equally well with and without
%% strict record tests.
- ?line run(Config, Ts, [no_strict_record_tests]),
- ?line run(Config, Ts, [strict_record_tests]),
+ run(Config, Ts, [no_strict_record_tests]),
+ run(Config, Ts, [strict_record_tests]),
ok.
@@ -192,13 +192,13 @@ guard(Config) when is_list(Config) ->
12.
">>,
- ?line ok = file:write_file(File, Test),
- ?line {ok, guard, Ws} = compile:file(File, [return,{outdir,?privdir}]),
- ?line Warnings = [L || {_File,WL} <- Ws, {L,_M,nomatch_guard} <- WL],
- ?line [7,9,11,13,15,17,19,21,23,25,27] = Warnings,
+ ok = file:write_file(File, Test),
+ {ok, guard, Ws} = compile:file(File, [return,{outdir,?privdir}]),
+ Warnings = [L || {_File,WL} <- Ws, {L,_M,nomatch_guard} <- WL],
+ [7,9,11,13,15,17,19,21,23,25,27] = Warnings,
- ?line ok = file:delete(File),
- ?line ok = file:delete(Beam),
+ ok = file:delete(File),
+ ok = file:delete(Beam),
ok.
%% Wildcard initialisation.
@@ -216,7 +216,7 @@ init(Config) when is_list(Config) ->
end.
">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Some patterns.
@@ -303,7 +303,7 @@ pattern(Config) when is_list(Config) ->
16.
">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
strict(Config) when is_list(Config) ->
@@ -328,7 +328,7 @@ strict(Config) when is_list(Config) ->
error(wrong_element).
">>
],
- ?line run(Config, Ts1, [strict_record_tests]),
+ run(Config, Ts1, [strict_record_tests]),
Ts2 = [
<<"-record(r1, {a,b}).
@@ -344,7 +344,7 @@ strict(Config) when is_list(Config) ->
error(wrong_element).
">>
],
- ?line run(Config, Ts2, [no_strict_record_tests]),
+ run(Config, Ts2, [no_strict_record_tests]),
ok.
%% Record updates.
@@ -382,7 +382,7 @@ update(Config) when is_list(Config) ->
erlang:error(wrong_setelement_called).
">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
maps(Config) when is_list(Config) ->
@@ -544,7 +544,7 @@ otp_5915(Config) when is_list(Config) ->
ok.
">>
],
- ?line run(Config, Ts, [strict_record_tests]),
+ run(Config, Ts, [strict_record_tests]),
ok.
%% Test optimization of record accesses and is_record/3 tests in guards.
@@ -631,7 +631,7 @@ otp_7931(Config) when is_list(Config) ->
ok.
">>
],
- ?line run(Config, Ts, [strict_record_tests]),
+ run(Config, Ts, [strict_record_tests]),
ok.
%% OTP-5990. {erlang,is_record}.
@@ -665,7 +665,7 @@ otp_5990(Config) when is_list(Config) ->
ok.
">>
],
- ?line run(Config, Ts, [strict_record_tests]),
+ run(Config, Ts, [strict_record_tests]),
ok.
@@ -697,7 +697,7 @@ otp_7078(Config) when is_list(Config) ->
">>
],
- ?line run(Config, Ts, [strict_record_tests]),
+ run(Config, Ts, [strict_record_tests]),
ok.
-record(otp_7101, {a,b,c=[],d=[],e=[]}).
@@ -710,23 +710,23 @@ otp_7101(Config) when is_list(Config) ->
%% The tracer will forward all trace messages to us.
Self = self(),
Tracer = spawn_link(fun() -> otp_7101_tracer(Self, 0) end),
- ?line 1 = erlang:trace_pattern({erlang,setelement,3}, true),
- ?line erlang:trace(self(), true, [{tracer,Tracer},call]),
+ 1 = erlang:trace_pattern({erlang,setelement,3}, true),
+ erlang:trace(self(), true, [{tracer,Tracer},call]),
%% Update the record.
- ?line #otp_7101{a=2,b=1,c=[],d=[],e=[]} = otp_7101_update1(Rec),
- ?line #otp_7101{a=1,b=2,c=[],d=[],e=[]} = otp_7101_update2(Rec),
- ?line #otp_7101{a=2,b=1,c=[],d=[],e=[]} = otp_7101_update3(Rec),
- ?line #otp_7101{a=1,b=2,c=[],d=[],e=[]} = otp_7101_update4(Rec),
+ #otp_7101{a=2,b=1,c=[],d=[],e=[]} = otp_7101_update1(Rec),
+ #otp_7101{a=1,b=2,c=[],d=[],e=[]} = otp_7101_update2(Rec),
+ #otp_7101{a=2,b=1,c=[],d=[],e=[]} = otp_7101_update3(Rec),
+ #otp_7101{a=1,b=2,c=[],d=[],e=[]} = otp_7101_update4(Rec),
%% Verify that setelement/3 was called the same number of times as
%% the number of record updates.
- ?line Ref = erlang:trace_delivered(Self),
+ Ref = erlang:trace_delivered(Self),
receive
{trace_delivered, Self, Ref} ->
Tracer ! done
end,
- ?line 1 = erlang:trace_pattern({erlang,setelement,3}, false),
+ 1 = erlang:trace_pattern({erlang,setelement,3}, false),
receive
4 ->
ok;
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 749d52c41c..5fd4574aa8 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -121,42 +121,42 @@ unused_vars_warn_basic(Config) when is_list(Config) ->
<<"f(F) -> % F unused.
ok.
- f(F, F) ->
- ok.
+f(F, F) ->
+ ok.
- g(_X) ->
- y.
+g(_X) ->
+ y.
- h(P) ->
- P.
+h(P) ->
+ P.
- x(N) ->
- case a:b() of
- [N|Y] -> % Y unused.
- ok
- end.
+x(N) ->
+ case a:b() of
+ [N|Y] -> % Y unused.
+ ok
+ end.
- y(N, L) ->
- lists:map(fun(T) -> T*N end, L).
+y(N, L) ->
+ lists:map(fun(T) -> T*N end, L).
- z(N, L) -> % N unused
- lists:map(fun(N, T) -> T*N end, L). % N shadowed.
+z(N, L) -> % N unused
+ lists:map(fun(N, T) -> T*N end, L). % N shadowed.
- c(A) ->
- case A of
- 1 -> B = []; % B unused.
- 2 -> B = []; % B unused.
- 3 -> B = f, B
- end.
- ">>,
+c(A) ->
+ case A of
+ 1 -> B = []; % B unused.
+ 2 -> B = []; % B unused.
+ 3 -> B = f, B
+ end.
+">>,
[warn_unused_vars],
- {warnings,[{1,erl_lint,{unused_var,'F'}},
- {15,erl_lint,{unused_var,'Y'}},
- {22,erl_lint,{unused_var,'N'}},
- {23,erl_lint,{shadowed_var,'N','fun'}},
- {28,erl_lint,{unused_var,'B'}},
- {29,erl_lint,{unused_var,'B'}}]}},
+{warnings,[{1,erl_lint,{unused_var,'F'}},
+ {15,erl_lint,{unused_var,'Y'}},
+ {22,erl_lint,{unused_var,'N'}},
+ {23,erl_lint,{shadowed_var,'N','fun'}},
+ {28,erl_lint,{unused_var,'B'}},
+ {29,erl_lint,{unused_var,'B'}}]}},
{basic2,
<<"-record(r, {x,y}).
f({X,Y}) -> {Z=X,Z=Y};
@@ -166,7 +166,7 @@ unused_vars_warn_basic(Config) when is_list(Config) ->
g({M, F, Arg}) -> (Z=M):F(Z=Arg).
h(X, Y) -> (Z=X) + (Z=Y).">>,
[warn_unused_vars], []}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Warnings for unused variables in list comprehensions.
@@ -509,7 +509,7 @@ unused_vars_warn_lc(Config) when is_list(Config) ->
[{14,erl_lint,{unused_var,'Q'}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
@@ -565,7 +565,7 @@ unused_vars_warn_rec(Config) when is_list(Config) ->
{error,[{2,erl_lint,{redefine_field,r,a}},
{2,erl_lint,{redefine_field,r,a}}],
[{2,erl_lint,{unused_var,'X'}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Warnings for unused variables in funs.
@@ -690,7 +690,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
{33,erl_lint,{unused_var,'U'}},
{33,erl_lint,{shadowed_var,'U','fun'}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Bit syntax, binsize variable used in the same matching.
@@ -712,7 +712,7 @@ unused_vars_OTP_4858(Config) when is_list(Config) ->
{8,erl_lint,{unused_var,'B'}},
{8,erl_lint,{unused_var,'Rest'}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
unused_unsafe_vars_warn(Config) when is_list(Config) ->
@@ -847,7 +847,7 @@ export_vars_warn(Config) when is_list(Config) ->
[],
{warnings,[{7,erl_lint,{exported_var,'Z',{'if',2}}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Shadowed variables are tested in other places, but here we test
@@ -876,7 +876,7 @@ shadow_vars(Config) when is_list(Config) ->
">>,
[],
[]}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Test that the 'warn_unused_import' option works.
@@ -888,7 +888,7 @@ unused_import(Config) when is_list(Config) ->
">>,
[warn_unused_import],
{warnings,[{1,erl_lint,{unused_import,{{foldl,3},lists}}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Test warnings for unused functions.
@@ -934,7 +934,7 @@ unused_function(Config) when is_list(Config) ->
{[]}, %Tuple indicates no 'export_all'.
[]}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-4671. Errors for unsafe variables.
@@ -1035,7 +1035,7 @@ unsafe_vars(Config) when is_list(Config) ->
{24,erl_lint,{unsafe_var,'D',{'case',2}}}],
[]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-4831, seq8202. No warn_unused_vars and unsafe variables.
@@ -1067,7 +1067,7 @@ unsafe_vars2(Config) when is_list(Config) ->
[],
{errors,[{9,erl_lint,{unsafe_var,'State1',{'if',4}}}],[]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Errors for unsafe variables in try/catch constructs.
@@ -1255,7 +1255,7 @@ unsafe_vars_try(Config) when is_list(Config) ->
">>,
[],
{errors,[{13,erl_lint,{unsafe_var,'Acc',{'try',6}}}],[]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Unsized binary fields are forbidden in patterns of bit string generators.
@@ -1506,7 +1506,7 @@ guard(Config) when is_list(Config) ->
">>,
[nowarn_obsolete_guard],
[]}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
Ts1 = [{guard5,
<<"-record(apa, {}).
t3(A) when record(A, {apa}) ->
@@ -1577,7 +1577,7 @@ guard(Config) when is_list(Config) ->
{2,erl_lint,illegal_guard_expr}],
[]}}
],
- ?line [] = run(Config, Ts1),
+ [] = run(Config, Ts1),
ok.
%% OTP-4886. Calling is_record with given record name.
@@ -1599,7 +1599,7 @@ otp_4886(Config) when is_list(Config) ->
{4,erl_lint,{undefined_record,foo}},
{5,erl_lint,{undefined_record,foo}}],
[]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-4988. Error when in-lining non-existent functions.
@@ -1624,7 +1624,7 @@ otp_4988(Config) when is_list(Config) ->
{1,erl_lint,{bad_inline,{f,a}}},
{3,erl_lint,{bad_inline,{g,12}}}],
[]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5091. Patterns and the bit syntax: invalid warnings.
@@ -1840,7 +1840,7 @@ otp_5091(Config) when is_list(Config) ->
<<"-record(r, {f1,f2}).
t(#r{f1 = A, f2 = A}) -> a.">>, [], []}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5276. Check the 'deprecated' attributed.
@@ -1870,7 +1870,7 @@ otp_5276(Config) when is_list(Config) ->
{9,erl_lint,{invalid_deprecated,{{badly,formed},1}}},
{11,erl_lint,{bad_deprecated,{atom_to_list,1}}}],
[{13,erl_lint,{unused_function,{frutt,0}}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5917. Check the 'deprecated' attributed.
@@ -1885,7 +1885,7 @@ otp_5917(Config) when is_list(Config) ->
">>,
{[]},
[]}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-6585. Check the deprecated guards list/1, pid/1, ....
@@ -1906,7 +1906,7 @@ otp_6585(Config) when is_list(Config) ->
{warnings,[{5,erl_lint,{obsolete_guard,{list,1}}},
{6,erl_lint,{obsolete_guard,{record,2}}},
{7,erl_lint,{obsolete_guard,{pid,1}}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5338. Bad warning in record initialization.
@@ -1921,7 +1921,7 @@ otp_5338(Config) when is_list(Config) ->
[],
{error,[{1,erl_lint,{unbound_var,'X'}}],
[{3,erl_lint,{unused_var,'X'}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5362. deprecated_function,
@@ -2125,7 +2125,7 @@ otp_5362(Config) when is_list(Config) ->
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5371. Aliases for bit syntax expressions are no longer allowed.
@@ -2182,7 +2182,7 @@ otp_5371(Config) when is_list(Config) ->
{6,v3_core,nomatch},
{8,v3_core,nomatch}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP_7227. Some aliases for bit syntax expressions were still allowed.
@@ -2252,7 +2252,7 @@ otp_7227(Config) when is_list(Config) ->
[],
{errors,[{2,erl_lint,illegal_bin_pattern}],[]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5494. Warnings for functions exported more than once.
@@ -2264,7 +2264,7 @@ otp_5494(Config) when is_list(Config) ->
">>,
[],
{warnings,[{2,erl_lint,{duplicated_export,{t,0}}}]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5644. M:F/A in record initialization.
@@ -2283,7 +2283,7 @@ otp_5644(Config) when is_list(Config) ->
">>,
[],
[]}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-5878. Record declaration: forward references, introduced variables.
@@ -2402,7 +2402,7 @@ otp_5878(Config) when is_list(Config) ->
[{1,erl_lint,{unused_record,r}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
Abstr = <<"-module(lint_test, [A, B]).
">>,
@@ -2419,7 +2419,7 @@ otp_5878(Config) when is_list(Config) ->
X <- Z ++ [A,Y]])}).
t() -> {#r1{},#r2{},#r3{}}.
">>,
- ?line {error,[{8,qlc,{used_generator_variable,'A'}},
+ {error,[{8,qlc,{used_generator_variable,'A'}},
{8,qlc,{used_generator_variable,'Y'}},
{8,qlc,{used_generator_variable,'Z'}}],
[{6,erl_lint,{unused_var,'V'}}]} =
@@ -2460,7 +2460,7 @@ otp_5878(Config) when is_list(Config) ->
bar.
">>,
- ?line {errors,[{6,erl_lint,{unbound_var,'A'}},
+ {errors,[{6,erl_lint,{unbound_var,'A'}},
{13,erl_lint,illegal_guard_expr},
{15,erl_lint,{undefined_field,r3,q}},
{17,erl_lint,{undefined_field,r,q}},
@@ -2479,14 +2479,14 @@ otp_5878(Config) when is_list(Config) ->
foo
end.
">>,
- ?line {errors,[{4,erl_lint,{undefined_function,{x,0}}},
+ {errors,[{4,erl_lint,{undefined_function,{x,0}}},
{5,erl_lint,illegal_guard_expr},
{7,erl_lint,illegal_guard_expr}],
[]} =
run_test2(Config, Ill2, [warn_unused_record]),
Ill3 = <<"t() -> ok.">>,
- ?line {errors,[{1,erl_lint,undefined_module}],[]} =
+ {errors,[{1,erl_lint,undefined_module}],[]} =
run_test2(Config, Ill3, [warn_unused_record]),
Usage1 = <<"-module(lint_test).
@@ -2499,7 +2499,7 @@ otp_5878(Config) when is_list(Config) ->
t() ->
{#u2{}}.
">>,
- ?line {warnings,[{5,erl_lint,{unused_record,u3}},
+ {warnings,[{5,erl_lint,{unused_record,u3}},
{6,erl_lint,{unused_record,u4}}]} =
run_test2(Config, Usage1, [warn_unused_record]),
@@ -2514,7 +2514,7 @@ otp_5878(Config) when is_list(Config) ->
t() ->
{#u2{}}.
">>,
- ?line [] = run_test2(Config, Usage2, [warn_unused_record]),
+ [] = run_test2(Config, Usage2, [warn_unused_record]),
%% This a completely different story...
%% The linter checks if qlc.hrl hasn't been included
@@ -2528,7 +2528,7 @@ otp_5878(Config) when is_list(Config) ->
H3 = q([X || X <- [1,2]], []),
{H1,H2,H3}.
">>,
- ?line {warnings,[{6,erl_lint,{missing_qlc_hrl,1}},
+ {warnings,[{6,erl_lint,{missing_qlc_hrl,1}},
{7,erl_lint,{missing_qlc_hrl,2}},
{8,erl_lint,{missing_qlc_hrl,2}}]} =
run_test2(Config, QLC2, [warn_unused_record]),
@@ -2544,7 +2544,7 @@ otp_5878(Config) when is_list(Config) ->
foo(#request{}) -> ok.
">>,
- ?line [] = run_test2(Config, UsedByType, [warn_unused_record]),
+ [] = run_test2(Config, UsedByType, [warn_unused_record]),
%% Abstract code generated by OTP 18. Note that the type info for
%% record fields has been put in a separate form.
@@ -2593,7 +2593,7 @@ otp_6885(Config) when is_list(Config) ->
ok.
">>,
- ?line {errors,[{3,erl_lint,unsized_binary_not_at_end},
+ {errors,[{3,erl_lint,unsized_binary_not_at_end},
{4,erl_lint,unsized_binary_not_at_end},
{5,erl_lint,unsized_binary_not_at_end},
{10,erl_lint,typed_literal_string},
@@ -2716,8 +2716,8 @@ export_all(Config) when is_list(Config) ->
id(I) -> I.
">>,
- ?line [] = run_test2(Config, Ts, []),
- ?line {warnings,[{2,erl_lint,export_all}]} =
+ [] = run_test2(Config, Ts, []),
+ {warnings,[{2,erl_lint,export_all}]} =
run_test2(Config, Ts, [warn_export_all]),
ok.
@@ -2988,7 +2988,7 @@ bif_clash(Config) when is_list(Config) ->
[]}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Basic tests with one behaviour.
@@ -3025,7 +3025,7 @@ behaviour_basic(Config) when is_list(Config) ->
[],
{warnings,[{1,erl_lint,{undefined_behaviour_func,{start,2},application}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Basic tests with multiple behaviours.
@@ -3126,7 +3126,7 @@ behaviour_multiple(Config) when is_list(Config) ->
erl_lint,
{conflicting_behaviours,{init,1},supervisor,1,gen_server}}]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% OTP-11861. behaviour_info() and -callback.
@@ -3310,7 +3310,7 @@ otp_11861(Conf) when is_list(Conf) ->
[],
[]}
],
- ?line [] = run(Conf, Ts),
+ [] = run(Conf, Ts),
true = code:set_path(CodePath),
ok.
@@ -3351,7 +3351,7 @@ otp_7550(Config) when is_list(Config) ->
{20,erl_lint,utf_bittype_size_or_unit}
],
[]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
@@ -3363,7 +3363,7 @@ otp_8051(Config) when is_list(Config) ->
">>,
[],
{errors,[{1,erl_lint,{undefined_type,{bar,0}}}],[]}}],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Check that format warnings are generated.
@@ -3376,14 +3376,14 @@ format_warn(Config) when is_list(Config) ->
ok.
format_level(Level, Count, Config) ->
- ?line W = get_compilation_result(Config, "format",
+ W = get_compilation_result(Config, "format",
[{warn_format, Level}]),
%% Pick out the 'format' warnings.
- ?line FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true;
+ FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true;
(_) -> false
end,
W),
- ?line case length(FW) of
+ case length(FW) of
Count ->
ok;
Other ->
@@ -3423,7 +3423,7 @@ on_load_successful(Config) when is_list(Config) ->
{[]}, %Tuple indicates no 'export_all'.
[]}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
on_load_failing(Config) when is_list(Config) ->
@@ -3471,7 +3471,7 @@ on_load_failing(Config) when is_list(Config) ->
{errors,
[{1,erl_lint,{undefined_on_load,{non_existing,0}}}],[]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
%% Test that too many arguments is not accepted.
@@ -3483,7 +3483,7 @@ too_many_arguments(Config) when is_list(Config) ->
[{1,erl_lint,{too_many_arguments,256}}],[]}}
],
- ?line [] = run(Config, Ts),
+ [] = run(Config, Ts),
ok.
@@ -3836,8 +3836,8 @@ run(Config, Tests) ->
%% Compiles a test file and returns the list of warnings/errors.
get_compilation_result(Conf, Filename, Warnings) ->
- ?line DataDir = ?datadir,
- ?line File = filename:join(DataDir, Filename),
+ DataDir = ?datadir,
+ File = filename:join(DataDir, Filename),
{ok,Bin} = file:read_file(File++".erl"),
FileS = binary_to_list(Bin),
{match,[{Start,Length}|_]} = re:run(FileS, "-module.*\\n"),
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index f59cd710d9..66ef34f48e 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -148,7 +148,7 @@ func(Config) when is_list(Config) ->
true
end)().">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
call(Config) when is_list(Config) ->
@@ -159,7 +159,7 @@ call(Config) when is_list(Config) ->
sfds,sdfsdf,sfds).
">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
recs(Config) when is_list(Config) ->
@@ -318,13 +318,13 @@ recs(Config) when is_list(Config) ->
R = #r2{},
R#r2{c = R, d = #r1{}}.">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
- ?line ok = pp_expr(<<"case #r{a={1,2},b=#r{}} of
+ ok = pp_expr(<<"case #r{a={1,2},b=#r{}} of
X=Y=#r{a=foo,b=bar} ->
{(foooo:baaaar(X))#r{a = rep},Y,#r.b}
end">>),
- ?line ok = pp_expr(<<"R#r{a = {kljasdklf,sdkfjsdl,sdafjkllsdf,sdfkjsd,
+ ok = pp_expr(<<"R#r{a = {kljasdklf,sdkfjsdl,sdafjkllsdf,sdfkjsd,
sdafjsd,sdf,sdafsd,sdfdsf,sdfdsf,dsfds}}">>),
ok.
@@ -369,8 +369,8 @@ try_catch(Config) when is_list(Config) ->
<<"t() -> catch begin begin foo, bar, foo:bar(kljsldkfjdls,kljsdl),
(catch bar:foo(foo)) end end.">>}
],
- ?line compile(Config, Ts),
- ?line ok = pp_expr(<<"try
+ compile(Config, Ts),
+ ok = pp_expr(<<"try
erl_internal:bif(M,F,length(Args))
of
true ->
@@ -388,7 +388,7 @@ if_then(Config) when is_list(Config) ->
{if_3,
<<"t() -> if 1 == 2 -> a; 1 > 2 -> b; 1 < 2 -> c end.">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
receive_after(Config) when is_list(Config) ->
@@ -411,7 +411,7 @@ receive_after(Config) when is_list(Config) ->
{3,4}
end.">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
bits(Config) when is_list(Config) ->
@@ -434,17 +434,17 @@ bits(Config) when is_list(Config) ->
{bit_9,
<<"">>}
],
- ?line compile(Config, Ts),
- ?line ok = pp_expr(<<"<<(list_to_binary([1,2]))/binary>>">>),
- ?line ok = pp_expr(
+ compile(Config, Ts),
+ ok = pp_expr(<<"<<(list_to_binary([1,2]))/binary>>">>),
+ ok = pp_expr(
<<"<<(list_to_binary([1,2])):all/binary-unit:8-unsigned-big>>">>),
- ?line ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>),
- ?line ok = pp_expr(<<"<<(foo:bar())/binary>>">>),
- ?line ok = pp_expr(<<"<<(a)/binary>>">>),
- ?line ok = pp_expr(<<"<<a/binary>>">>),
- ?line ok = pp_expr(<<"<<{a,b}/binary>>">>),
- ?line ok = pp_expr(<<"<<{foo:bar(),b}/binary>>">>),
- ?line ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>),
+ ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>),
+ ok = pp_expr(<<"<<(foo:bar())/binary>>">>),
+ ok = pp_expr(<<"<<(a)/binary>>">>),
+ ok = pp_expr(<<"<<a/binary>>">>),
+ ok = pp_expr(<<"<<{a,b}/binary>>">>),
+ ok = pp_expr(<<"<<{foo:bar(),b}/binary>>">>),
+ ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>),
ok.
head_tail(Config) when is_list(Config) ->
@@ -461,7 +461,7 @@ head_tail(Config) when is_list(Config) ->
[foo:bar(lkjljlskdfj, klsdajflds, sdafkljsdlfkjdas, kjlsdadjl),
bar:foo(kljlkjsdf, lkjsdlfj, [kljsfj, sdfdsfsad])].">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
cond1(Config) when is_list(Config) ->
@@ -470,7 +470,7 @@ cond1(Config) when is_list(Config) ->
{clause,4,[],[[{atom,4,true}]],
[{tuple,5,[{atom,5,x},{atom,5,y}]}]}]},
CChars = flat_expr1(C),
- ?line "cond\n"
+ "cond\n"
" {foo,bar} ->\n"
" [a,b];\n"
" true ->\n"
@@ -482,7 +482,7 @@ block(Config) when is_list(Config) ->
Ts = [{block_1,
<<"t() -> begin a,{c,d} end.">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
case1(Config) when is_list(Config) ->
@@ -494,8 +494,8 @@ case1(Config) when is_list(Config) ->
foo
end.">>}
],
- ?line compile(Config, Ts),
- ?line ok = pp_expr(<<"case
+ compile(Config, Ts),
+ ok = pp_expr(<<"case
erl_internal:bif(M,F,length(Args))
of
true ->
@@ -513,13 +513,13 @@ ops(Config) when is_list(Config) ->
{ops_3,
<<"t() -> - (- (- (- (- 3)))).">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
messages(Config) when is_list(Config) ->
- ?line true = "{error,{some,\"error\"}}\n" =:=
+ true = "{error,{some,\"error\"}}\n" =:=
lists:flatten(erl_pp:form({error,{some,"error"}})),
- ?line true = "{warning,{some,\"warning\"}}\n" =:=
+ true = "{warning,{some,\"warning\"}}\n" =:=
lists:flatten(erl_pp:form({warning,{some,"warning"}})),
"\n" = flat_form({eof,0}),
ok.
@@ -538,7 +538,7 @@ import_export(Config) when is_list(Config) ->
<<"-include_lib(\"stdlib/include/qlc.hrl\").
t() -> qlc:q([X || X <- []]).">>}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
ok.
misc_attrs(Config) when is_list(Config) ->
@@ -578,29 +578,29 @@ do_hook(HookFun) ->
Call = {call,A0,{atom,A0,foo},[Lc]},
Expr2 = {call,A0,{atom,A0,fff},[Call,Call,Call]},
EChars2 = erl_pp:exprs([Expr2]),
- ?line true = EChars =:= lists:flatten(EChars2),
+ true = EChars =:= lists:flatten(EChars2),
EsChars = erl_pp:exprs([Expr], H),
- ?line true = EChars =:= lists:flatten(EsChars),
+ true = EChars =:= lists:flatten(EsChars),
A1 = erl_anno:new(1),
F = {function,A1,ffff,0,[{clause,A1,[],[],[Expr]}]},
FuncChars = lists:flatten(erl_pp:function(F, H)),
F2 = {function,A1,ffff,0,[{clause,A1,[],[],[Expr2]}]},
FuncChars2 = erl_pp:function(F2),
- ?line true = FuncChars =:= lists:flatten(FuncChars2),
+ true = FuncChars =:= lists:flatten(FuncChars2),
FFormChars = erl_pp:form(F, H),
- ?line true = FuncChars =:= lists:flatten(FFormChars),
+ true = FuncChars =:= lists:flatten(FFormChars),
A = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr}]}},
AChars = lists:flatten(erl_pp:attribute(A, H)),
A2 = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr2}]}},
AChars2 = erl_pp:attribute(A2),
- ?line true = AChars =:= lists:flatten(AChars2),
+ true = AChars =:= lists:flatten(AChars2),
AFormChars = erl_pp:form(A, H),
- ?line true = AChars =:= lists:flatten(AFormChars),
+ true = AChars =:= lists:flatten(AFormChars),
- ?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})),
+ "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})),
%% A list (as before R6), not a list of lists.
G = [{op,A1,'>',{atom,A1,a},{foo,{atom,A1,b}}}], % not a proper guard
@@ -608,26 +608,26 @@ do_hook(HookFun) ->
G2 = [{op,A1,'>',{atom,A1,a},
{call,A0,{atom,A0,foo},[{atom,A1,b}]}}], % not a proper guard
GChars2 = erl_pp:guard(G2),
- ?line true = GChars =:= lists:flatten(GChars2),
+ true = GChars =:= lists:flatten(GChars2),
EH = HookFun({?MODULE, ehook, [foo,bar]}),
XEChars = erl_pp:expr(Expr, -1, EH),
- ?line true = remove_indentation(EChars) =:= lists:flatten(XEChars),
+ true = remove_indentation(EChars) =:= lists:flatten(XEChars),
XEChars2 = erl_pp:expr(Expr, EH),
- ?line true = EChars =:= lists:flatten(XEChars2),
+ true = EChars =:= lists:flatten(XEChars2),
%% Note: no leading spaces before "begin".
Block = {block,A0,[{match,A0,{var,A0,'A'},{integer,A0,3}},
{atom,A0,true}]},
- ?line "begin\n A =" ++ _ =
+ "begin\n A =" ++ _ =
lists:flatten(erl_pp:expr(Block, 17, none)),
%% Special...
- ?line true =
+ true =
"{some,value}" =:= lists:flatten(erl_pp:expr({value,A0,{some,value}})),
%% Silly...
- ?line true =
+ true =
"if true -> 0 end" =:=
flat_expr({'if',0,[{clause,0,[],[],[{atom,0,0}]}]}),
@@ -636,7 +636,7 @@ do_hook(HookFun) ->
NewIf = {'if',A0,[{clause,A0,[],[[{atom,A0,true}]],[{atom,A0,b}]}]},
OldIfChars = lists:flatten(erl_pp:expr(OldIf)),
NewIfChars = lists:flatten(erl_pp:expr(NewIf)),
- ?line true = OldIfChars =:= NewIfChars,
+ true = OldIfChars =:= NewIfChars,
ok.
@@ -653,15 +653,15 @@ hook({foo,E}, I, P, H) ->
erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H).
neg_indent(Config) when is_list(Config) ->
- ?line ok = pp_expr(<<"begin a end">>),
- ?line ok = pp_expr(<<"begin a,b end">>),
- ?line ok = pp_expr(<<"try a,b,c
+ ok = pp_expr(<<"begin a end">>),
+ ok = pp_expr(<<"begin a,b end">>),
+ ok = pp_expr(<<"try a,b,c
catch exit:_ -> d;
throw:_ -> t;
error:{foo,bar} -> foo,
bar
end">>),
- ?line ok = pp_expr(
+ ok = pp_expr(
<<"fun() ->
F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
or (B#r2.b) or (A#r1.b) ->
@@ -675,36 +675,36 @@ neg_indent(Config) when is_list(Config) ->
ok
end()">>),
- ?line ok = pp_expr(<<"[X || X <- a, true]">>),
- ?line ok = pp_expr(<<"{[a,b,c],[d,e|f]}">>),
- ?line ok = pp_expr(<<"f(a,b,c)">>),
- ?line ok = pp_expr(<<"fun() when a,b;c,d -> a end">>),
- ?line ok = pp_expr(<<"fun A() when a,b;c,d -> a end">>),
- ?line ok = pp_expr(<<"<<34:32,17:32>>">>),
- ?line ok = pp_expr(<<"if a,b,c -> d; e,f,g -> h,i end">>),
- ?line ok = pp_expr(<<"if a -> d; c -> d end">>),
- ?line ok = pp_expr(<<"receive after 1 -> 2 end">>),
- ?line ok = pp_expr(<<"begin a,b,c end">>),
-
- ?line "\"\"" = flat_expr({string,0,""}),
- ?line ok = pp_expr(<<"\"abc\"">>),
- ?line ok = pp_expr(<<"\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n"
- "klafd\n\n\n\n\nkljsdf\n\n\n\n\nsdf\n\n\n\n\n\"">>),
- ?line ok = pp_expr(<<"fkjlskljklkkljlkjlkjkljlkjsljklf"
- "lsdjlfdsjlfjsdlfjdslfjdlsjfsdjfklsdkfjsdf("
- "\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n"
- "kljsafd\n\n\n\n\nkljsdf\n\n\n\n\nkjsdf"
- "\n\n\n\n\n\")">>),
+ ok = pp_expr(<<"[X || X <- a, true]">>),
+ ok = pp_expr(<<"{[a,b,c],[d,e|f]}">>),
+ ok = pp_expr(<<"f(a,b,c)">>),
+ ok = pp_expr(<<"fun() when a,b;c,d -> a end">>),
+ ok = pp_expr(<<"fun A() when a,b;c,d -> a end">>),
+ ok = pp_expr(<<"<<34:32,17:32>>">>),
+ ok = pp_expr(<<"if a,b,c -> d; e,f,g -> h,i end">>),
+ ok = pp_expr(<<"if a -> d; c -> d end">>),
+ ok = pp_expr(<<"receive after 1 -> 2 end">>),
+ ok = pp_expr(<<"begin a,b,c end">>),
+
+ "\"\"" = flat_expr({string,0,""}),
+ ok = pp_expr(<<"\"abc\"">>),
+ ok = pp_expr(<<"\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n"
+ "klafd\n\n\n\n\nkljsdf\n\n\n\n\nsdf\n\n\n\n\n\"">>),
+ ok = pp_expr(<<"fkjlskljklkkljlkjlkjkljlkjsljklf"
+ "lsdjlfdsjlfjsdlfjdslfjdlsjfsdjfklsdkfjsdf("
+ "\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n"
+ "kljsafd\n\n\n\n\nkljsdf\n\n\n\n\nkjsdf"
+ "\n\n\n\n\n\")">>),
%% fun-info is skipped when everything is to fit on one single line
Fun1 = {'fun',1,{function,t,0},{0,45353021,'-t/0-fun-0-'}},
- ?line "fun t/0" = flat_expr(Fun1),
+ "fun t/0" = flat_expr(Fun1),
Fun2 = {'fun',2,{clauses,[{clause,2,[],[],[{atom,3,true}]}]},
{0,108059557,'-t/0-fun-0-'}},
- ?line "fun() -> true end" = flat_expr(Fun2),
+ "fun() -> true end" = flat_expr(Fun2),
Fun3 = {named_fun,3,'True',[{clause,3,[],[],[{atom,3,true}]}],
{0,424242424,'-t/0-True-0-'}},
- ?line "fun True() -> true end" = flat_expr(Fun3),
+ "fun True() -> true end" = flat_expr(Fun3),
ok.
@@ -728,27 +728,27 @@ otp_6911(Config) when is_list(Config) ->
[{clause,7,[{atom,7,true}],[],[{integer,7,12}]},
{clause,8,[{atom,8,false}],[],[{integer,8,14}]}]}]}]},
Chars = flat_form(F),
- ?line "thomas(X) ->\n"
+ "thomas(X) ->\n"
" case X of\n"
" true ->\n"
" 12;\n"
" false ->\n"
" 14\n"
" end.\n" = Chars,
- ?line ok = pp_expr(<<"case X of true -> 12; false -> 14 end">>),
- ?line ok = pp_expr(<<"receive after 1 -> ok end">>),
+ ok = pp_expr(<<"case X of true -> 12; false -> 14 end">>),
+ ok = pp_expr(<<"receive after 1 -> ok end">>),
ok.
%% OTP_6914. Binary comprehensions.
otp_6914(Config) when is_list(Config) ->
- ?line ok = pp_expr(<<"<< <<B:1>> || B <- [0,1,1] >>">>),
- ?line ok = pp_expr(<<"[ B || <<B:1>> <= <<\"hi\">>]">>),
- ?line ok = pp_expr(<<"<< <<1:1>> || true >>">>),
+ ok = pp_expr(<<"<< <<B:1>> || B <- [0,1,1] >>">>),
+ ok = pp_expr(<<"[ B || <<B:1>> <= <<\"hi\">>]">>),
+ ok = pp_expr(<<"<< <<1:1>> || true >>">>),
ok.
%% OTP_8150. Types.
otp_8150(Config) when is_list(Config) ->
- ?line _ = [{N,ok} = {N,pp_forms(B)} ||
+ _ = [{N,ok} = {N,pp_forms(B)} ||
{N,B} <- type_examples()
],
ok.
@@ -768,7 +768,7 @@ otp_8238(Config) when is_list(Config) ->
"t2() ->\n"
" #r{}.\n">>
],
- ?line compile(Config, [{otp_8238,iolist_to_binary(Ex)}]),
+ compile(Config, [{otp_8238,iolist_to_binary(Ex)}]),
ok.
type_examples() ->
@@ -823,13 +823,13 @@ type_examples() ->
%% Erlang/OTP 19.0, but as long as the parser recognizes the
%% is_subtype(V, T) syntax, we need a few examples of the syntax.
{ex31,<<"-spec t1(FooBar :: t99()) -> t99();"
- "(t2()) -> t2();"
- "('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);"
- "(t23()) -> t23() when is_subtype(t23(), atom()),"
- " is_subtype(t23(), t14());"
- "(t24()) -> t24() when is_subtype(t24(), atom()),"
- " is_subtype(t24(), t14()),"
- " is_subtype(t24(), '\\'t::4'()).">>},
+ "(t2()) -> t2();"
+ "('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);"
+ "(t23()) -> t23() when is_subtype(t23(), atom()),"
+ " is_subtype(t23(), t14());"
+ "(t24()) -> t24() when is_subtype(t24(), atom()),"
+ " is_subtype(t24(), t14()),"
+ " is_subtype(t24(), '\\'t::4'()).">>},
{ex32,<<"-spec mod:t2() -> any(). ">>},
{ex33,<<"-opaque attributes_data() :: "
"[{'column', column()} | {'line', info_line()} |"
@@ -853,7 +853,7 @@ type_examples() ->
otp_8473(Config) when is_list(Config) ->
Ex = [{ex1,<<"-type 'fun'(A) :: A.\n"
"-type funkar() :: 'fun'(fun((integer()) -> atom())).\n">>}],
- ?line _ = [{N,ok} = {N,pp_forms(B)} ||
+ _ = [{N,ok} = {N,pp_forms(B)} ||
{N,B} <- Ex],
ok.
@@ -866,13 +866,13 @@ otp_8522(Config) when is_list(Config) ->
" f3 :: (undefined),\n"
" f4 :: x | y | undefined | z,\n"
" f5 :: a}).\n">>,
- ?line ok = file:write_file(FileName, C),
- ?line {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]),
+ ok = file:write_file(FileName, C),
+ {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]),
BF = filename("otp_8522", Config),
- ?line {ok, A} = beam_lib:chunks(BF, [abstract_code]),
+ {ok, A} = beam_lib:chunks(BF, [abstract_code]),
%% OTP-12719: Since 'undefined' is no longer added by the Erlang
%% Parser, the number of 'undefined' is 4. It used to be 5.
- ?line 4 = count_atom(A, undefined),
+ 4 = count_atom(A, undefined),
ok.
count_atom(A, A) ->
@@ -923,8 +923,8 @@ otp_8567(Config) when is_list(Config) ->
"-record r, {a}.\n"
"-record s, {a :: integer()}.\n"
"-type t() :: {#r{},#s{}}.\n">>,
- ?line ok = file:write_file(FileName, C),
- ?line {error,[{_,[{3,erl_parse,["syntax error before: ","')'"]}]}],_} =
+ ok = file:write_file(FileName, C),
+ {error,[{_,[{3,erl_parse,["syntax error before: ","')'"]}]}],_} =
compile:file(FileName, [return]),
F = <<"-module(otp_8567).\n"
@@ -945,7 +945,7 @@ otp_8567(Config) when is_list(Config) ->
"-spec(otp_8567:t4 (ot()) -> ot1()).\n"
"t4(A) ->\n"
" A.\n">>,
- ?line ok = pp_forms(F),
+ ok = pp_forms(F),
ok.
@@ -966,15 +966,15 @@ otp_8664(Config) when is_list(Config) ->
"-type t() :: t1() | t2() | t3() | b1() | u().\n"
"-spec t() -> t().\n"
"t() -> 3.\n">>,
- ?line ok = file:write_file(FileName, C1),
- ?line {ok, _, []} = compile:file(FileName, [return]),
+ ok = file:write_file(FileName, C1),
+ {ok, _, []} = compile:file(FileName, [return]),
C2 = <<"-module(otp_8664).\n"
"-export([t/0]).\n"
"-spec t() -> 9 and 4.\n"
"t() -> 0.\n">>,
- ?line ok = file:write_file(FileName, C2),
- ?line {error,[{_,[{3,erl_lint,{type_syntax,integer}}]}],_} =
+ ok = file:write_file(FileName, C2),
+ {error,[{_,[{3,erl_lint,{type_syntax,integer}}]}],_} =
compile:file(FileName, [return]),
ok.
@@ -986,13 +986,13 @@ otp_9147(Config) when is_list(Config) ->
"-export_type([undef/0]).\n"
"-record(undef, {f1 :: F1 :: a | b}).\n"
"-type undef() :: #undef{}.\n">>,
- ?line ok = file:write_file(FileName, C1),
- ?line {ok, _, []} =
+ ok = file:write_file(FileName, C1),
+ {ok, _, []} =
compile:file(FileName, [return,'P',{outdir,?privdir}]),
PFileName = filename('otp_9147.P', Config),
- ?line {ok, Bin} = file:read_file(PFileName),
+ {ok, Bin} = file:read_file(PFileName),
%% The parentheses around "F1 :: a | b" are new (bugfix).
- ?line true =
+ true =
lists:member("-record(undef,{f1 :: F1 :: a | b}).",
string:tokens(binary_to_list(Bin), "\n")),
ok.
@@ -1290,5 +1290,5 @@ fail() ->
%% +fnu means a peer node has to be started; slave will not do
start_node(Name, Xargs) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
+ PA = filename:dirname(code:which(?MODULE)),
test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]).
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index ad3faec11c..9432edc00f 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -79,12 +79,12 @@ end_per_group(_GroupName, Config) ->
%% (OTP-2347)
error_1(Config) when is_list(Config) ->
- ?line {error, _, _} = erl_scan:string("'a"),
+ {error, _, _} = erl_scan:string("'a"),
ok.
%% Checks that format_error works on the error cases.
error_2(Config) when is_list(Config) ->
- ?line lists:foreach(fun check/1, error_cases()),
+ lists:foreach(fun check/1, error_cases()),
ok.
error_cases() ->
@@ -97,7 +97,7 @@ error_cases() ->
"2.3e",
"2.3e-",
"91#9"
-].
+ ].
assert_type(N, integer) when is_integer(N) ->
ok;
@@ -120,64 +120,64 @@ check_error({error, Info, EndLine}, Module0) ->
%% Tests the support for ISO-8859-1 i.e Latin-1.
iso88591(Config) when is_list(Config) ->
- ?line ok =
- case catch begin
- %% Some atom and variable names
- V1s = [$Á,$á,$é,$ë],
- V2s = [$N,$ä,$r],
- A1s = [$h,$ä,$r],
- A2s = [$ö,$r,$e],
- %% Test parsing atom and variable characters.
- {ok,Ts1,_} = erl_scan_string(V1s ++ " " ++ V2s ++
- "\327" ++
- A1s ++ " " ++ A2s),
- V1s = atom_to_list(element(3, nth(1, Ts1))),
- V2s = atom_to_list(element(3, nth(2, Ts1))),
- A1s = atom_to_list(element(3, nth(4, Ts1))),
- A2s = atom_to_list(element(3, nth(5, Ts1))),
- %% Test printing atoms
- A1s = flatten(print(element(3, nth(4, Ts1)))),
- A2s = flatten(print(element(3, nth(5, Ts1)))),
- %% Test parsing and printing strings.
- S1 = V1s ++ "\327" ++ A1s ++ "\250" ++ A2s,
- S1s = "\"" ++ S1 ++ "\"",
- {ok,Ts2,_} = erl_scan_string(S1s),
- S1 = element(3, nth(1, Ts2)),
- S1s = flatten(print(element(3, nth(1, Ts2)))),
- ok %It all worked
- end of
- {'EXIT',R} -> %Something went wrong!
- {error,R};
- ok -> ok %Aok
- end.
+ ok =
+ case catch begin
+ %% Some atom and variable names
+ V1s = [$Á,$á,$é,$ë],
+ V2s = [$N,$ä,$r],
+ A1s = [$h,$ä,$r],
+ A2s = [$ö,$r,$e],
+ %% Test parsing atom and variable characters.
+ {ok,Ts1,_} = erl_scan_string(V1s ++ " " ++ V2s ++
+ "\327" ++
+ A1s ++ " " ++ A2s),
+ V1s = atom_to_list(element(3, nth(1, Ts1))),
+ V2s = atom_to_list(element(3, nth(2, Ts1))),
+ A1s = atom_to_list(element(3, nth(4, Ts1))),
+ A2s = atom_to_list(element(3, nth(5, Ts1))),
+ %% Test printing atoms
+ A1s = flatten(print(element(3, nth(4, Ts1)))),
+ A2s = flatten(print(element(3, nth(5, Ts1)))),
+ %% Test parsing and printing strings.
+ S1 = V1s ++ "\327" ++ A1s ++ "\250" ++ A2s,
+ S1s = "\"" ++ S1 ++ "\"",
+ {ok,Ts2,_} = erl_scan_string(S1s),
+ S1 = element(3, nth(1, Ts2)),
+ S1s = flatten(print(element(3, nth(1, Ts2)))),
+ ok %It all worked
+ end of
+ {'EXIT',R} -> %Something went wrong!
+ {error,R};
+ ok -> ok %Aok
+ end.
%% OTP-7810. White spaces, comments, and more...
otp_7810(Config) when is_list(Config) ->
- ?line ok = reserved_words(),
- ?line ok = atoms(),
- ?line ok = punctuations(),
- ?line ok = comments(),
- ?line ok = errors(),
- ?line ok = integers(),
- ?line ok = base_integers(),
- ?line ok = floats(),
- ?line ok = dots(),
- ?line ok = chars(),
- ?line ok = variables(),
- ?line ok = eof(),
- ?line ok = illegal(),
- ?line ok = crashes(),
-
- ?line ok = options(),
- ?line ok = token_info(),
- ?line ok = column_errors(),
- ?line ok = white_spaces(),
-
- ?line ok = unicode(),
-
- ?line ok = more_chars(),
- ?line ok = more_options(),
- ?line ok = anno_info(),
+ ok = reserved_words(),
+ ok = atoms(),
+ ok = punctuations(),
+ ok = comments(),
+ ok = errors(),
+ ok = integers(),
+ ok = base_integers(),
+ ok = floats(),
+ ok = dots(),
+ ok = chars(),
+ ok = variables(),
+ ok = eof(),
+ ok = illegal(),
+ ok = crashes(),
+
+ ok = options(),
+ ok = token_info(),
+ ok = column_errors(),
+ ok = white_spaces(),
+
+ ok = unicode(),
+
+ ok = more_chars(),
+ ok = more_options(),
+ ok = anno_info(),
ok.
@@ -188,10 +188,10 @@ reserved_words() ->
'rem', 'band', 'and', 'bor', 'bxor', 'bsl', 'bsr',
'or', 'xor'],
[begin
- ?line {RW, true} = {RW, erl_scan:reserved_word(RW)},
+ {RW, true} = {RW, erl_scan:reserved_word(RW)},
S = atom_to_list(RW),
Ts = [{RW,{1,1}}],
- ?line test_string(S, Ts)
+ test_string(S, Ts)
end || RW <- L],
ok.
@@ -200,14 +200,14 @@ atoms() ->
test_string("a
b", [{atom,{1,1},a},{atom,{2,18},b}]),
test_string("'a b'", [{atom,{1,1},'a b'}]),
- test_string("a", [{atom,{1,1},a}]),
- test_string("a@2", [{atom,{1,1},a@2}]),
- test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]),
- test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]),
- ?line {ok,[{atom,_,'$a'}],{1,6}} =
- erl_scan_string("'$\\a'", {1,1}),
- ?line test("'$\\a'"),
- ok.
+ test_string("a", [{atom,{1,1},a}]),
+ test_string("a@2", [{atom,{1,1},a@2}]),
+ test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]),
+ test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]),
+ {ok,[{atom,_,'$a'}],{1,6}} =
+ erl_scan_string("'$\\a'", {1,1}),
+ test("'$\\a'"),
+ ok.
punctuations() ->
L = ["<<", "<-", "<=", "<", ">>", ">=", ">", "->", "--",
@@ -217,7 +217,7 @@ punctuations() ->
[begin
W = list_to_atom(S),
Ts = [{W,{1,1}}],
- ?line test_string(S, Ts)
+ test_string(S, Ts)
end || S <- L],
Three = ["/=:=", "<=:=", "==:=", ">=:="], % three tokens...
No = Three ++ L,
@@ -233,18 +233,18 @@ punctuations() ->
W1 = list_to_atom(S1),
W2 = list_to_atom(S2),
Ts = [{W1,{1,1}},{W2,{1,-L2+1}}],
- ?line test_string(S, Ts)
+ test_string(S, Ts)
end || {S,[{L2,S1,S2}|_]} <- SL],
PTs1 = [{'!',{1,1}},{'(',{1,2}},{')',{1,3}},{',',{1,4}},{';',{1,5}},
{'=',{1,6}},{'[',{1,7}},{']',{1,8}},{'{',{1,9}},{'|',{1,10}},
{'}',{1,11}}],
- ?line test_string("!(),;=[]{|}", PTs1),
+ test_string("!(),;=[]{|}", PTs1),
PTs2 = [{'#',{1,1}},{'&',{1,2}},{'*',{1,3}},{'+',{1,4}},{'/',{1,5}},
{':',{1,6}},{'<',{1,7}},{'>',{1,8}},{'?',{1,9}},{'@',{1,10}},
{'\\',{1,11}},{'^',{1,12}},{'`',{1,13}},{'~',{1,14}}],
- ?line test_string("#&*+/:<>?@\\^`~", PTs2),
+ test_string("#&*+/:<>?@\\^`~", PTs2),
test_string(".. ", [{'..',{1,1}}]),
test_string("1 .. 2",
@@ -253,9 +253,9 @@ punctuations() ->
ok.
comments() ->
- ?line test("a %%\n b"),
- ?line {ok,[],1} = erl_scan_string("%"),
- ?line test("a %%\n b"),
+ test("a %%\n b"),
+ {ok,[],1} = erl_scan_string("%"),
+ test("a %%\n b"),
{ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} =
erl_scan_string("a %%\n b", {1,1}),
{ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} =
@@ -275,30 +275,30 @@ comments() ->
ok.
errors() ->
- ?line {error,{1,erl_scan,{string,$',"qa"}},1} = erl_scan:string("'qa"), %'
+ {error,{1,erl_scan,{string,$',"qa"}},1} = erl_scan:string("'qa"), %'
{error,{{1,1},erl_scan,{string,$',"qa"}},{1,4}} = %'
erl_scan:string("'qa", {1,1}, []), %'
- ?line {error,{1,erl_scan,{string,$","str"}},1} = %"
+ {error,{1,erl_scan,{string,$","str"}},1} = %"
erl_scan:string("\"str"), %"
{error,{{1,1},erl_scan,{string,$","str"}},{1,5}} = %"
erl_scan:string("\"str", {1,1}, []), %"
- ?line {error,{1,erl_scan,char},1} = erl_scan:string("$"),
+ {error,{1,erl_scan,char},1} = erl_scan:string("$"),
{error,{{1,1},erl_scan,char},{1,2}} = erl_scan:string("$", {1,1}, []),
test_string([34,65,200,34], [{string,{1,1},"AÈ"}]),
test_string("\\", [{'\\',{1,1}}]),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch {foo, erl_scan:string('$\\a', {1,1})}), % type error
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch {foo, erl_scan:tokens([], '$\\a', {1,1})}), % type error
- ?line "{a,tuple}" = erl_scan:format_error({a,tuple}),
+ "{a,tuple}" = erl_scan:format_error({a,tuple}),
ok.
integers() ->
[begin
I = list_to_integer(S),
Ts = [{integer,{1,1},I}],
- ?line test_string(S, Ts)
+ test_string(S, Ts)
end || S <- [[N] || N <- lists:seq($0, $9)] ++ ["2323","000"] ],
ok.
@@ -307,11 +307,11 @@ base_integers() ->
B = list_to_integer(BS),
I = erlang:list_to_integer(S, B),
Ts = [{integer,{1,1},I}],
- ?line test_string(BS++"#"++S, Ts)
+ test_string(BS++"#"++S, Ts)
end || {BS,S} <- [{"2","11"}, {"5","23234"}, {"12","05a"},
{"16","abcdef"}, {"16","ABCDEF"}] ],
- ?line {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"),
+ {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"),
{error,{{1,1},erl_scan,{base,1}},{1,2}} =
erl_scan:string("1#000", {1,1}, []),
@@ -319,11 +319,11 @@ base_integers() ->
[begin
Str = BS ++ "#" ++ S,
- ?line {error,{1,erl_scan,{illegal,integer}},1} =
+ {error,{1,erl_scan,{illegal,integer}},1} =
erl_scan:string(Str)
end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],
- ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
+ {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
{ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} =
erl_scan_string("16#ef@", {1,1}, []),
{ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} =
@@ -335,12 +335,12 @@ floats() ->
[begin
F = list_to_float(FS),
Ts = [{float,{1,1},F}],
- ?line test_string(FS, Ts)
+ test_string(FS, Ts)
end || FS <- ["1.0","001.17","3.31200","1.0e0","1.0E17",
"34.21E-18", "17.0E+14"]],
test_string("1.e2", [{integer,{1,1},1},{'.',{1,2}},{atom,{1,3},e2}]),
- ?line {error,{1,erl_scan,{illegal,float}},1} =
+ {error,{1,erl_scan,{illegal,float}},1} =
erl_scan:string("1.0e400"),
{error,{{1,1},erl_scan,{illegal,float}},{1,8}} =
erl_scan:string("1.0e400", {1,1}, []),
@@ -361,11 +361,11 @@ dots() ->
{".% öh",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,6}}},
{".%\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}},
{".$", {error,{1,erl_scan,char},1},
- {error,{{1,2},erl_scan,char},{1,3}}},
+ {error,{{1,2},erl_scan,char},{1,3}}},
{".$\\", {error,{1,erl_scan,char},1},
{error,{{1,2},erl_scan,char},{1,4}}},
{".a", {ok,[{'.',1},{atom,1,a}],1},
- {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}}
+ {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}}
],
[begin
R = erl_scan_string(S),
@@ -411,27 +411,27 @@ chars() ->
[begin
L = lists:flatten(io_lib:format("$\\~.8b", [C])),
Ts = [{char,{1,1},C}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255)],
%% Leading zeroes...
[begin
L = lists:flatten(io_lib:format("$\\~3.8.0b", [C])),
Ts = [{char,{1,1},C}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255)],
%% $\^\n now increments the line...
[begin
L = "$\\^" ++ [C],
Ts = [{char,{1,1},C band 2#11111}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255)],
[begin
L = "$\\" ++ [C],
Ts = [{char,{1,1},V}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v},
{$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s},
{$d,$\d}]],
@@ -444,13 +444,13 @@ chars() ->
[begin
L = "$\\" ++ [C],
Ts = [{char,{1,1},C}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255) -- No],
[begin
L = "'$\\" ++ [C] ++ "'",
Ts = [{atom,{1,1},list_to_atom("$"++[C])}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255) -- No],
test_string("\"\\013a\\\n\"", [{string,{1,1},"\va\n"}]),
@@ -462,17 +462,17 @@ chars() ->
[begin
L = "$" ++ [C],
Ts = [{char,{1,1},C}],
- ?line test_string(L, Ts)
+ test_string(L, Ts)
end || C <- lists:seq(0, 255) -- (No ++ [$\\])],
test_string("$\n", [{char,{1,1},$\n}]),
- ?line {error,{{1,1},erl_scan,char},{1,4}} =
+ {error,{{1,1},erl_scan,char},{1,4}} =
erl_scan:string("$\\^",{1,1}),
test_string("$\\\n", [{char,{1,1},$\n}]),
%% Robert's scanner returns line 1:
test_string("$\\\n", [{char,{1,1},$\n}]),
test_string("$\n\n", [{char,{1,1},$\n}]),
- ?line test("$\n\n"),
+ test("$\n\n"),
ok.
@@ -485,30 +485,30 @@ variables() ->
ok.
eof() ->
- ?line {done,{eof,1},eof} = erl_scan:tokens([], eof, 1),
+ {done,{eof,1},eof} = erl_scan:tokens([], eof, 1),
{more, C1} = erl_scan:tokens([]," \n", 1),
- ?line {done,{eof,2},eof} = erl_scan:tokens(C1, eof, 1),
+ {done,{eof,2},eof} = erl_scan:tokens(C1, eof, 1),
{more, C2} = erl_scan:tokens([], "abra", 1),
%% An error before R13A.
- %% ?line {done,Err={error,{1,erl_scan,scan},1},eof} =
- ?line {done,{ok,[{atom,1,abra}],1},eof} =
+ %% {done,Err={error,{1,erl_scan,scan},1},eof} =
+ {done,{ok,[{atom,1,abra}],1},eof} =
erl_scan_tokens(C2, eof, 1),
%% With column.
- ?line {more, C3} = erl_scan:tokens([]," \n",{1,1}),
- ?line {done,{eof,{2,1}},eof} = erl_scan:tokens(C3, eof, 1),
+ {more, C3} = erl_scan:tokens([]," \n",{1,1}),
+ {done,{eof,{2,1}},eof} = erl_scan:tokens(C3, eof, 1),
{more, C4} = erl_scan:tokens([], "abra", {1,1}),
%% An error before R13A.
- %% ?line {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} =
- ?line {done,{ok,[{atom,_,abra}],{1,5}},eof} =
+ %% {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} =
+ {done,{ok,[{atom,_,abra}],{1,5}},eof} =
erl_scan_tokens(C4, eof, 1),
%% Robert's scanner returns "" as LeftoverChars;
%% the R12B scanner returns eof as LeftoverChars: (eof is correct)
- ?line {more, C5} = erl_scan:tokens([], "a", 1),
+ {more, C5} = erl_scan:tokens([], "a", 1),
%% An error before R13A.
- %% ?line {done,{error,{1,erl_scan,scan},1},eof} =
- ?line {done,{ok,[{atom,1,a}],1},eof} =
+ %% {done,{error,{1,erl_scan,scan},1},eof} =
+ {done,{ok,[{atom,1,a}],1},eof} =
erl_scan_tokens(C5,eof,1),
%% With column.
@@ -519,9 +519,9 @@ eof() ->
erl_scan_tokens(C6,eof,1),
%% A dot followed by eof is special:
- ?line {more, C} = erl_scan:tokens([], "a.", 1),
- ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1),
- ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."),
+ {more, C} = erl_scan:tokens([], "a.", 1),
+ {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1),
+ {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."),
%% With column.
{more, CCol} = erl_scan:tokens([], "a.", {1,1}),
@@ -534,100 +534,100 @@ eof() ->
illegal() ->
Atom = lists:duplicate(1000, $a),
- ?line {error,{1,erl_scan,{illegal,atom}},1} = erl_scan:string(Atom),
- ?line {done,{error,{1,erl_scan,{illegal,atom}},1},". "} =
+ {error,{1,erl_scan,{illegal,atom}},1} = erl_scan:string(Atom),
+ {done,{error,{1,erl_scan,{illegal,atom}},1},". "} =
erl_scan:tokens([], Atom++". ", 1),
QAtom = "'" ++ Atom ++ "'",
- ?line {error,{1,erl_scan,{illegal,atom}},1} = erl_scan:string(QAtom),
- ?line {done,{error,{1,erl_scan,{illegal,atom}},1},". "} =
+ {error,{1,erl_scan,{illegal,atom}},1} = erl_scan:string(QAtom),
+ {done,{error,{1,erl_scan,{illegal,atom}},1},". "} =
erl_scan:tokens([], QAtom++". ", 1),
Var = lists:duplicate(1000, $A),
- ?line {error,{1,erl_scan,{illegal,var}},1} = erl_scan:string(Var),
- ?line {done,{error,{1,erl_scan,{illegal,var}},1},". "} =
+ {error,{1,erl_scan,{illegal,var}},1} = erl_scan:string(Var),
+ {done,{error,{1,erl_scan,{illegal,var}},1},". "} =
erl_scan:tokens([], Var++". ", 1),
Float = "1" ++ lists:duplicate(400, $0) ++ ".0",
- ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(Float),
- ?line {done,{error,{1,erl_scan,{illegal,float}},1},". "} =
+ {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(Float),
+ {done,{error,{1,erl_scan,{illegal,float}},1},". "} =
erl_scan:tokens([], Float++". ", 1),
String = "\"43\\x{aaaaaa}34\"",
- ?line {error,{1,erl_scan,{illegal,character}},1} = erl_scan:string(String),
- ?line {done,{error,{1,erl_scan,{illegal,character}},1},"34\". "} =
+ {error,{1,erl_scan,{illegal,character}},1} = erl_scan:string(String),
+ {done,{error,{1,erl_scan,{illegal,character}},1},"34\". "} =
%% Would be nice if `34\"' were skipped...
%% Maybe, but then the LeftOverChars would not be the characters
%% immediately following the end location of the error.
erl_scan:tokens([], String++". ", 1),
- ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,1001}} =
+ {error,{{1,1},erl_scan,{illegal,atom}},{1,1001}} =
erl_scan:string(Atom, {1,1}),
- ?line {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1005}},". "} =
+ {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1005}},". "} =
erl_scan:tokens([], "foo "++Atom++". ", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,1003}} =
+ {error,{{1,1},erl_scan,{illegal,atom}},{1,1003}} =
erl_scan:string(QAtom, {1,1}),
- ?line {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1007}},". "} =
+ {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1007}},". "} =
erl_scan:tokens([], "foo "++QAtom++". ", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,var}},{1,1001}} =
+ {error,{{1,1},erl_scan,{illegal,var}},{1,1001}} =
erl_scan:string(Var, {1,1}),
- ?line {done,{error,{{1,5},erl_scan,{illegal,var}},{1,1005}},". "} =
+ {done,{error,{{1,5},erl_scan,{illegal,var}},{1,1005}},". "} =
erl_scan:tokens([], "foo "++Var++". ", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,float}},{1,404}} =
+ {error,{{1,1},erl_scan,{illegal,float}},{1,404}} =
erl_scan:string(Float, {1,1}),
- ?line {done,{error,{{1,5},erl_scan,{illegal,float}},{1,408}},". "} =
+ {done,{error,{{1,5},erl_scan,{illegal,float}},{1,408}},". "} =
erl_scan:tokens([], "foo "++Float++". ", {1,1}),
- ?line {error,{{1,4},erl_scan,{illegal,character}},{1,14}} =
+ {error,{{1,4},erl_scan,{illegal,character}},{1,14}} =
erl_scan:string(String, {1,1}),
- ?line {done,{error,{{1,4},erl_scan,{illegal,character}},{1,14}},"34\". "} =
+ {done,{error,{{1,4},erl_scan,{illegal,character}},{1,14}},"34\". "} =
erl_scan:tokens([], String++". ", {1,1}),
ok.
crashes() ->
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([-1])}), % type error
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$"++[-1])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$\\"++[-1])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$\\^"++[-1])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([$",-1,$"],{1,1})}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[-1,$"])}), %$"
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([$",-1,$"])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[-1])}),
- ?line {'EXIT',_} =
+ {'EXIT',_} = (catch {foo, erl_scan:string([-1])}), % type error
+ {'EXIT',_} = (catch {foo, erl_scan:string("$"++[-1])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("$\\"++[-1])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("$\\^"++[-1])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string([$",-1,$"],{1,1})}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[-1,$"])}), %$"
+ {'EXIT',_} = (catch {foo, erl_scan:string([$",-1,$"])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[-1])}),
+ {'EXIT',_} =
(catch {foo, erl_scan:string("% foo"++[-1],{1,1})}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([a])}), % type error
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$"++[a])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$\\"++[a])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("$\\^"++[a])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([$",a,$"],{1,1})}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[a,$"])}), %$"
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([$",a,$"])}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[a])}),
- ?line {'EXIT',_} =
+ {'EXIT',_} = (catch {foo, erl_scan:string([a])}), % type error
+ {'EXIT',_} = (catch {foo, erl_scan:string("$"++[a])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("$\\"++[a])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("$\\^"++[a])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string([$",a,$"],{1,1})}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[a,$"])}), %$"
+ {'EXIT',_} = (catch {foo, erl_scan:string([$",a,$"])}),
+ {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[a])}),
+ {'EXIT',_} =
(catch {foo, erl_scan:string("% foo"++[a],{1,1})}),
- ?line {'EXIT',_} = (catch {foo, erl_scan:string([3.0])}), % type error
+ {'EXIT',_} = (catch {foo, erl_scan:string([3.0])}), % type error
ok.
options() ->
%% line and column are not options, but tested here
- ?line {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} =
+ {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} =
erl_scan_string("foo % bar", 1, return),
- ?line {ok,[{atom,1,foo},{white_space,1," "}],1} =
+ {ok,[{atom,1,foo},{white_space,1," "}],1} =
erl_scan_string("foo % bar", 1, return_white_spaces),
- ?line {ok,[{atom,1,foo},{comment,1,"% bar"}],1} =
+ {ok,[{atom,1,foo},{comment,1,"% bar"}],1} =
erl_scan_string("foo % bar", 1, return_comments),
- ?line {ok,[{atom,17,foo}],17} =
+ {ok,[{atom,17,foo}],17} =
erl_scan_string("foo % bar", 17),
- ?line {'EXIT',{function_clause,_}} =
+ {'EXIT',{function_clause,_}} =
(catch {foo,
erl_scan:string("foo % bar", {a,1}, [])}), % type error
- ?line {ok,[{atom,_,foo}],{17,18}} =
+ {ok,[{atom,_,foo}],{17,18}} =
erl_scan_string("foo % bar", {17,9}, []),
- ?line {'EXIT',{function_clause,_}} =
+ {'EXIT',{function_clause,_}} =
(catch {foo,
erl_scan:string("foo % bar", {1,0}, [])}), % type error
- ?line {ok,[{foo,1}],1} =
+ {ok,[{foo,1}],1} =
erl_scan_string("foo % bar",1, [{reserved_word_fun,
fun(W) -> W =:= foo end}]),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch {foo,
erl_scan:string("foo % bar",1, % type error
[{reserved_word_fun,
@@ -702,40 +702,40 @@ anno_info() ->
ok.
column_errors() ->
- ?line {error,{{1,1},erl_scan,{string,$',""}},{1,3}} = % $'
+ {error,{{1,1},erl_scan,{string,$',""}},{1,3}} = % $'
erl_scan:string("'\\",{1,1}),
- ?line {error,{{1,1},erl_scan,{string,$",""}},{1,3}} = % $"
+ {error,{{1,1},erl_scan,{string,$",""}},{1,3}} = % $"
erl_scan:string("\"\\",{1,1}),
- ?line {error,{{1,1},erl_scan,{string,$',""}},{1,2}} = % $'
+ {error,{{1,1},erl_scan,{string,$',""}},{1,2}} = % $'
erl_scan:string("'",{1,1}),
- ?line {error,{{1,1},erl_scan,{string,$",""}},{1,2}} = % $"
+ {error,{{1,1},erl_scan,{string,$",""}},{1,2}} = % $"
erl_scan:string("\"",{1,1}),
- ?line {error,{{1,1},erl_scan,char},{1,2}} =
+ {error,{{1,1},erl_scan,char},{1,2}} =
erl_scan:string("$",{1,1}),
- ?line {error,{{1,2},erl_scan,{string,$',"1234567890123456"}},{1,20}} = %'
+ {error,{{1,2},erl_scan,{string,$',"1234567890123456"}},{1,20}} = %'
erl_scan:string(" '12345678901234567", {1,1}),
- ?line {error,{{1,2},erl_scan,{string,$',"123456789012345 "}}, {1,20}} = %'
+ {error,{{1,2},erl_scan,{string,$',"123456789012345 "}}, {1,20}} = %'
erl_scan:string(" '123456789012345\\s", {1,1}),
- ?line {error,{{1,2},erl_scan,{string,$","1234567890123456"}},{1,20}} = %"
+ {error,{{1,2},erl_scan,{string,$","1234567890123456"}},{1,20}} = %"
erl_scan:string(" \"12345678901234567", {1,1}),
- ?line {error,{{1,2},erl_scan,{string,$","123456789012345 "}}, {1,20}} = %"
+ {error,{{1,2},erl_scan,{string,$","123456789012345 "}}, {1,20}} = %"
erl_scan:string(" \"123456789012345\\s", {1,1}),
- ?line {error,{{1,2},erl_scan,{string,$',"1234567890123456"}},{2,1}} = %'
+ {error,{{1,2},erl_scan,{string,$',"1234567890123456"}},{2,1}} = %'
erl_scan:string(" '12345678901234567\n", {1,1}),
ok.
white_spaces() ->
- ?line {ok,[{white_space,_,"\r"},
+ {ok,[{white_space,_,"\r"},
{white_space,_," "},
{atom,_,a},
{white_space,_,"\n"}],
_} = erl_scan_string("\r a\n", {1,1}, return),
- ?line test("\r a\n"),
+ test("\r a\n"),
L = "{\"a\nb\", \"a\\nb\",\nabc\r,def}.\n\n",
- ?line {ok,[{'{',_},
+ {ok,[{'{',_},
{string,_,"a\nb"},
{',',_},
{white_space,_," "},
@@ -750,33 +750,33 @@ white_spaces() ->
{dot,_},
{white_space,_,"\n"}],
_} = erl_scan_string(L, {1,1}, return),
- ?line test(L),
- ?line test("\"\n\"\n"),
- ?line test("\n\r\n"),
- ?line test("\n\r"),
- ?line test("\r\n"),
- ?line test("\n\f"),
- ?line [test(lists:duplicate(N, $\t)) || N <- lists:seq(1, 20)],
- ?line [test([$\n|lists:duplicate(N, $\t)]) || N <- lists:seq(1, 20)],
- ?line [test(lists:duplicate(N, $\s)) || N <- lists:seq(1, 20)],
- ?line [test([$\n|lists:duplicate(N, $\s)]) || N <- lists:seq(1, 20)],
- ?line test("\v\f\n\v "),
- ?line test("\n\e\n\b\f\n\da\n"),
+ test(L),
+ test("\"\n\"\n"),
+ test("\n\r\n"),
+ test("\n\r"),
+ test("\r\n"),
+ test("\n\f"),
+ [test(lists:duplicate(N, $\t)) || N <- lists:seq(1, 20)],
+ [test([$\n|lists:duplicate(N, $\t)]) || N <- lists:seq(1, 20)],
+ [test(lists:duplicate(N, $\s)) || N <- lists:seq(1, 20)],
+ [test([$\n|lists:duplicate(N, $\s)]) || N <- lists:seq(1, 20)],
+ test("\v\f\n\v "),
+ test("\n\e\n\b\f\n\da\n"),
ok.
unicode() ->
- ?line {ok,[{char,1,83},{integer,1,45}],1} =
+ {ok,[{char,1,83},{integer,1,45}],1} =
erl_scan_string("$\\12345"), % not unicode
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string([1089]),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
erl_scan:string([1089], {1,1}),
{error,{1,erl_scan,{illegal,atom}},1} =
erl_scan:string("'a"++[1089]++"b'", 1),
{error,{{1,1},erl_scan,{illegal,atom}},{1,6}} =
erl_scan:string("'a"++[1089]++"b'", {1,1}),
- ?line test("\"a"++[1089]++"b\""),
+ test("\"a"++[1089]++"b\""),
{ok,[{char,1,1}],1} =
erl_scan_string([$$,$\\,$^,1089], 1),
@@ -784,7 +784,7 @@ unicode() ->
erl_scan:string("\"qa\x{aaa}", 1),
"unterminated string starting with \"qa"++[2730]++"\"" =
erl_scan:format_error(Error),
- ?line {error,{{1,1},erl_scan,_},{1,11}} =
+ {error,{{1,1},erl_scan,_},{1,11}} =
erl_scan:string("\"qa\\x{aaa}",{1,1}),
{error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
erl_scan:string("'qa\\x{aaa}'",{1,1}),
@@ -818,17 +818,17 @@ unicode() ->
{ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan_string(U4, 1),
%% Keep these tests:
- ?line test(Qs),
- ?line test(U1),
- ?line test(U2),
- ?line test(U3),
- ?line test(U4),
+ test(Qs),
+ test(U1),
+ test(U2),
+ test(U3),
+ test(U4),
Str1 = "\"ab" ++ [1089] ++ "cd\"",
{ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan_string(Str1, 1),
{ok,[{string,{1,1},[$a,$b,1089,$c,$d]}],{1,8}} =
erl_scan_string(Str1, {1,1}),
- ?line test(Str1),
+ test(Str1),
Comment = "%% "++[1089],
{ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
erl_scan_string(Comment, 1, [return]),
@@ -841,63 +841,63 @@ more_chars() ->
%% $\x{...}, $\xHH
%% All kinds of tests...
- ?line {ok,[{char,_,123}],{1,4}} =
+ {ok,[{char,_,123}],{1,4}} =
erl_scan_string("$\\{",{1,1}),
- ?line {more, C1} = erl_scan:tokens([], "$\\{", {1,1}),
- ?line {done,{ok,[{char,_,123}],{1,4}},eof} =
+ {more, C1} = erl_scan:tokens([], "$\\{", {1,1}),
+ {done,{ok,[{char,_,123}],{1,4}},eof} =
erl_scan_tokens(C1, eof, 1),
- ?line {ok,[{char,1,123},{atom,1,a},{'}',1}],1} =
+ {ok,[{char,1,123},{atom,1,a},{'}',1}],1} =
erl_scan_string("$\\{a}"),
- ?line {error,{{1,1},erl_scan,char},{1,4}} =
+ {error,{{1,1},erl_scan,char},{1,4}} =
erl_scan:string("$\\x", {1,1}),
- ?line {error,{{1,1},erl_scan,char},{1,5}} =
+ {error,{{1,1},erl_scan,char},{1,5}} =
erl_scan:string("$\\x{",{1,1}),
- ?line {more, C3} = erl_scan:tokens([], "$\\x", {1,1}),
- ?line {done,{error,{{1,1},erl_scan,char},{1,4}},eof} =
+ {more, C3} = erl_scan:tokens([], "$\\x", {1,1}),
+ {done,{error,{{1,1},erl_scan,char},{1,4}},eof} =
erl_scan:tokens(C3, eof, 1),
- ?line {error,{{1,1},erl_scan,char},{1,5}} =
+ {error,{{1,1},erl_scan,char},{1,5}} =
erl_scan:string("$\\x{",{1,1}),
- ?line {more, C2} = erl_scan:tokens([], "$\\x{", {1,1}),
- ?line {done,{error,{{1,1},erl_scan,char},{1,5}},eof} =
+ {more, C2} = erl_scan:tokens([], "$\\x{", {1,1}),
+ {done,{error,{{1,1},erl_scan,char},{1,5}},eof} =
erl_scan:tokens(C2, eof, 1),
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("$\\x{g}"),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
erl_scan:string("$\\x{g}", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,6}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,6}} =
erl_scan:string("$\\x{}",{1,1}),
- ?line test("\"\\{0}\""),
- ?line test("\"\\x{0}\""),
- ?line test("\'\\{0}\'"),
- ?line test("\'\\x{0}\'"),
+ test("\"\\{0}\""),
+ test("\"\\x{0}\""),
+ test("\'\\{0}\'"),
+ test("\'\\x{0}\'"),
- ?line {error,{{2,3},erl_scan,{illegal,character}},{2,6}} =
+ {error,{{2,3},erl_scan,{illegal,character}},{2,6}} =
erl_scan:string("\"ab \n $\\x{g}\"",{1,1}),
- ?line {error,{{2,3},erl_scan,{illegal,character}},{2,6}} =
+ {error,{{2,3},erl_scan,{illegal,character}},{2,6}} =
erl_scan:string("\'ab \n $\\x{g}\'",{1,1}),
- ?line test("$\\{34}"),
- ?line test("$\\x{34}"),
- ?line test("$\\{377}"),
- ?line test("$\\x{FF}"),
- ?line test("$\\{400}"),
- ?line test("$\\x{100}"),
- ?line test("$\\x{10FFFF}"),
- ?line test("$\\x{10ffff}"),
- ?line test("\"$\n \\{1}\""),
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ test("$\\{34}"),
+ test("$\\x{34}"),
+ test("$\\{377}"),
+ test("$\\x{FF}"),
+ test("$\\{400}"),
+ test("$\\x{100}"),
+ test("$\\x{10FFFF}"),
+ test("$\\x{10ffff}"),
+ test("\"$\n \\{1}\""),
+ {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("$\\x{110000}"),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,12}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,12}} =
erl_scan:string("$\\x{110000}", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string("$\\xfg", {1,1}),
- ?line test("$\\xffg"),
+ test("$\\xffg"),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string("$\\xg", {1,1}),
ok.
diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl
index 9a5b7620ea..6c618b9814 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -19,7 +19,7 @@
-module(escript_SUITE).
-export([
- all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ 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,
@@ -80,32 +80,32 @@ end_per_testcase(_Case, _Config) ->
basic(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "factorial 5",
- <<"factorial 5 = 120\nExitCode:0">>),
- ?line run(Dir, "factorial_compile 10",
- <<"factorial 10 = 3628800\nExitCode:0">>),
- ?line run(Dir, "factorial_compile_main 7",
- <<"factorial 7 = 5040\nExitCode:0">>),
- ?line run(Dir, "factorial_warning 20",
- [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\n"
- "factorial 20 = 2432902008176640000\nExitCode:0">>]),
- ?line run_with_opts(Dir, "-s", "factorial_warning",
- [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
- ?line run_with_opts(Dir, "-s -i", "factorial_warning",
- [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
- ?line run_with_opts(Dir, "-c -s", "factorial_warning",
- [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
- ?line run(Dir, "filesize "++filename:join(?config(data_dir, Config),"filesize"),
- [data_dir,<<"filesize:11: Warning: function id/1 is unused\n324\nExitCode:0">>]),
- ?line run(Dir, "test_script_name",
- [data_dir,<<"test_script_name\nExitCode:0">>]),
- ?line run(Dir, "tail_rec 1000",
- [<<"ok\nExitCode:0">>]),
+ run(Dir, "factorial 5",
+ <<"factorial 5 = 120\nExitCode:0">>),
+ run(Dir, "factorial_compile 10",
+ <<"factorial 10 = 3628800\nExitCode:0">>),
+ run(Dir, "factorial_compile_main 7",
+ <<"factorial 7 = 5040\nExitCode:0">>),
+ run(Dir, "factorial_warning 20",
+ [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\n"
+ "factorial 20 = 2432902008176640000\nExitCode:0">>]),
+ run_with_opts(Dir, "-s", "factorial_warning",
+ [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
+ run_with_opts(Dir, "-s -i", "factorial_warning",
+ [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
+ run_with_opts(Dir, "-c -s", "factorial_warning",
+ [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
+ run(Dir, "filesize "++filename:join(?config(data_dir, Config),"filesize"),
+ [data_dir,<<"filesize:11: Warning: function id/1 is unused\n324\nExitCode:0">>]),
+ run(Dir, "test_script_name",
+ [data_dir,<<"test_script_name\nExitCode:0">>]),
+ run(Dir, "tail_rec 1000",
+ [<<"ok\nExitCode:0">>]),
%% We expect the trap_exit flag for the process to be false,
%% since that is the default state for newly spawned processes.
- ?line run(Dir, "trap_exit",
- <<"false\nExitCode:0">>),
+ run(Dir, "trap_exit",
+ <<"false\nExitCode:0">>),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -113,18 +113,18 @@ basic(Config) when is_list(Config) ->
errors(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "compile_error",
- [data_dir,<<"compile_error:5: syntax error before: '*'\n">>,
- data_dir,<<"compile_error:8: syntax error before: blarf\n">>,
- <<"escript: There were compilation errors.\nExitCode:127">>]),
- ?line run(Dir, "lint_error",
- [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
- data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
- <<"escript: There were compilation errors.\nExitCode:127">>]),
- ?line run_with_opts(Dir, "-s", "lint_error",
- [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
- data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
- <<"escript: There were compilation errors.\nExitCode:127">>]),
+ run(Dir, "compile_error",
+ [data_dir,<<"compile_error:5: syntax error before: '*'\n">>,
+ data_dir,<<"compile_error:8: syntax error before: blarf\n">>,
+ <<"escript: There were compilation errors.\nExitCode:127">>]),
+ run(Dir, "lint_error",
+ [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
+ data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
+ <<"escript: There were compilation errors.\nExitCode:127">>]),
+ run_with_opts(Dir, "-s", "lint_error",
+ [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
+ data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
+ <<"escript: There were compilation errors.\nExitCode:127">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -132,9 +132,9 @@ errors(Config) when is_list(Config) ->
strange_name(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "strange.name -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "ExitCode:0">>]),
+ run(Dir, "strange.name -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "ExitCode:0">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -142,13 +142,13 @@ strange_name(Config) when is_list(Config) ->
emulator_flags(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "emulator_flags -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[{nostick,[]}]\n"
- "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ run(Dir, "emulator_flags -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[{nostick,[]}]\n"
+ "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -157,13 +157,13 @@ emulator_flags_no_shebang(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
%% Need run_with_opts, to always use "escript" explicitly
- ?line run_with_opts(Dir, "", "emulator_flags_no_shebang -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[{nostick,[]}]\n"
- "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ run_with_opts(Dir, "", "emulator_flags_no_shebang -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[{nostick,[]}]\n"
+ "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -175,8 +175,8 @@ module_script(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
OrigFile = filename:join([Data,"emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
- ?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+ [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
+ {ok, OrigFI} = file:read_file_info(OrigFile),
%% Write source file
Priv = ?config(priv_dir, Config),
@@ -187,85 +187,85 @@ module_script(Config) when is_list(Config) ->
"-export([main/1]).\n\n",
string:join(Source, "\n"),
"\n"],
- ?line ok = file:write_file(ErlFile, ErlCode),
+ ok = file:write_file(ErlFile, ErlCode),
- %%%%%%%
+%%%%%%%
%% Create and run scripts without emulator flags
%% With shebang
NoArgsBase = Base ++ "_no_args_with_shebang",
NoArgsFile = filename:join([Priv, NoArgsBase]),
- ?line ok = file:write_file(NoArgsFile,
- [Shebang, "\n",
- ErlCode]),
- ?line ok = file:write_file_info(NoArgsFile, OrigFI),
-
- ?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
-
- ?line run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(NoArgsFile,
+ [Shebang, "\n",
+ ErlCode]),
+ ok = file:write_file_info(NoArgsFile, OrigFI),
+
+ run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
+
+ run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
%% Without shebang
NoArgsBase2 = Base ++ "_no_args_without_shebang",
NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
- ?line ok = file:write_file(NoArgsFile2,
- ["Something else than shebang!!!", "\n",
- ErlCode]),
- ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
-
- ?line run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(NoArgsFile2,
+ ["Something else than shebang!!!", "\n",
+ ErlCode]),
+ ok = file:write_file_info(NoArgsFile2, OrigFI),
+
+ run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
%% Plain module without header
NoArgsBase3 = Base ++ "_no_args_without_header",
NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
- ?line ok = file:write_file(NoArgsFile3, [ErlCode]),
- ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
-
- ?line run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
-
- %%%%%%%
+ ok = file:write_file(NoArgsFile3, [ErlCode]),
+ ok = file:write_file_info(NoArgsFile3, OrigFI),
+
+ run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
+
+%%%%%%%
%% Create and run scripts with emulator flags
%% With shebang
ArgsBase = Base ++ "_args_with_shebang",
ArgsFile = filename:join([Priv, ArgsBase]),
- ?line ok = file:write_file(ArgsFile,
- [Shebang, "\n",
- Mode, "\n",
- Flags, "\n",
- ErlCode]),
- ?line ok = file:write_file_info(ArgsFile, OrigFI),
-
- ?line run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[{nostick,[]}]\n"
- "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(ArgsFile,
+ [Shebang, "\n",
+ Mode, "\n",
+ Flags, "\n",
+ ErlCode]),
+ ok = file:write_file_info(ArgsFile, OrigFI),
+
+ run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[{nostick,[]}]\n"
+ "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
ok.
@@ -277,100 +277,100 @@ beam_script(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
OrigFile = filename:join([Data,"emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
- ?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+ [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
+ {ok, OrigFI} = file:read_file_info(OrigFile),
%% Write source file
Priv = ?config(priv_dir, Config),
Dir = filename:absname(Priv), % Get rid of trailing slash.
Base = "beam_script",
ErlFile = filename:join([Priv, Base ++ ".erl"]),
- ?line ok = file:write_file(ErlFile,
- ["\n-module(", Base, ").\n",
- "-export([main/1]).\n\n",
- string:join(Source, "\n"),
- "\n"]),
+ ok = file:write_file(ErlFile,
+ ["\n-module(", Base, ").\n",
+ "-export([main/1]).\n\n",
+ string:join(Source, "\n"),
+ "\n"]),
%% Compile the code
- ?line {ok, _Mod, BeamCode} = compile:file(ErlFile, [binary]),
+ {ok, _Mod, BeamCode} = compile:file(ErlFile, [binary]),
- %%%%%%%
+%%%%%%%
%% Create and run scripts without emulator flags
%% With shebang
NoArgsBase = Base ++ "_no_args_with_shebang",
NoArgsFile = filename:join([Priv, NoArgsBase]),
- ?line ok = file:write_file(NoArgsFile,
- [Shebang, "\n",
- BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile, OrigFI),
-
- ?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
-
- ?line run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(NoArgsFile,
+ [Shebang, "\n",
+ BeamCode]),
+ ok = file:write_file_info(NoArgsFile, OrigFI),
+
+ run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
+
+ run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
%% Without shebang
NoArgsBase2 = Base ++ "_no_args_without_shebang",
NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
- ?line ok = file:write_file(NoArgsFile2,
- ["Something else than shebang!!!", "\n",
- BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
-
- ?line run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(NoArgsFile2,
+ ["Something else than shebang!!!", "\n",
+ BeamCode]),
+ ok = file:write_file_info(NoArgsFile2, OrigFI),
+
+ run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
%% Plain beam file without header
NoArgsBase3 = Base ++ "_no_args_without_header",
NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
- ?line ok = file:write_file(NoArgsFile3, [BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
-
- ?line run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[]\n"
- "mnesia:[]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
-
- %%%%%%%
+ ok = file:write_file(NoArgsFile3, [BeamCode]),
+ ok = file:write_file_info(NoArgsFile3, OrigFI),
+
+ run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[]\n"
+ "mnesia:[]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
+
+%%%%%%%
%% Create and run scripts with emulator flags
%% With shebang
ArgsBase = Base ++ "_args",
ArgsFile = filename:join([Priv, ArgsBase]),
- ?line ok = file:write_file(ArgsFile,
- [Shebang, "\n",
- Mode, "\n",
- Flags, "\n",
- BeamCode]),
- ?line ok = file:write_file_info(ArgsFile, OrigFI),
-
- ?line run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "nostick:[{nostick,[]}]\n"
- "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
- "ERL_FLAGS=false\n"
- "unknown:[]\n"
- "ExitCode:0">>]),
+ ok = file:write_file(ArgsFile,
+ [Shebang, "\n",
+ Mode, "\n",
+ Flags, "\n",
+ BeamCode]),
+ ok = file:write_file_info(ArgsFile, OrigFI),
+
+ run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "nostick:[{nostick,[]}]\n"
+ "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -383,104 +383,104 @@ archive_script(Config) when is_list(Config) ->
DataDir = ?config(data_dir, Config),
PrivDir = ?config(priv_dir, Config),
Archive = filename:join([PrivDir, "archive_script.zip"]),
- ?line {ok, _} = zip:create(Archive, ["archive_script"],
- [{compress, []}, {cwd, DataDir}]),
- ?line {ok, _} = zip:extract(Archive, [{cwd, PrivDir}]),
+ {ok, _} = zip:create(Archive, ["archive_script"],
+ [{compress, []}, {cwd, DataDir}]),
+ {ok, _} = zip:extract(Archive, [{cwd, PrivDir}]),
TopDir = filename:join([PrivDir, "archive_script"]),
%% Compile the code
- ?line ok = compile_app(TopDir, "archive_script_dict"),
- ?line ok = compile_app(TopDir, "archive_script_dummy"),
- ?line {ok, MainFiles} = file:list_dir(TopDir),
- ?line ok = compile_files(MainFiles, TopDir, TopDir),
+ ok = compile_app(TopDir, "archive_script_dict"),
+ ok = compile_app(TopDir, "archive_script_dummy"),
+ {ok, MainFiles} = file:list_dir(TopDir),
+ ok = compile_files(MainFiles, TopDir, TopDir),
%% Create the archive
{ok, TopFiles} = file:list_dir(TopDir),
- ?line {ok, {_, ArchiveBin}} = zip:create(Archive, TopFiles,
- [memory, {compress, []}, {cwd, TopDir}]),
+ {ok, {_, ArchiveBin}} = zip:create(Archive, TopFiles,
+ [memory, {compress, []}, {cwd, TopDir}]),
%% Read the source script
OrigFile = filename:join([DataDir, "emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
- ?line [Shebang, Mode, _Flags | _Source] =
+ [Shebang, Mode, _Flags | _Source] =
string:tokens(binary_to_list(OrigBin), "\n"),
Flags = "%%! -archive_script_dict foo bar"
" -archive_script_dict foo"
" -archive_script_dummy bar",
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+ {ok, OrigFI} = file:read_file_info(OrigFile),
- %%%%%%%
+%%%%%%%
%% Create and run scripts without emulator flags
MainBase = "archive_script_main",
MainScript = filename:join([PrivDir, MainBase]),
%% With shebang
- ?line ok = file:write_file(MainScript,
- [Shebang, "\n",
- Flags, "\n",
- ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
-
- ?line run(PrivDir, MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
- "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
- "priv:{ok,<<\"Some private data...\\n\">>}\n"
- "ExitCode:0">>]),
-
- ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
- "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
- "priv:{ok,<<\"Some private data...\\n\">>}\n"
- "ExitCode:0">>]),
-
- ?line ok = file:rename(MainScript, MainScript ++ "_with_shebang"),
+ ok = file:write_file(MainScript,
+ [Shebang, "\n",
+ Flags, "\n",
+ ArchiveBin]),
+ ok = file:write_file_info(MainScript, OrigFI),
+
+ run(PrivDir, MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
+ "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
+ "priv:{ok,<<\"Some private data...\\n\">>}\n"
+ "ExitCode:0">>]),
+
+ run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
+ "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
+ "priv:{ok,<<\"Some private data...\\n\">>}\n"
+ "ExitCode:0">>]),
+
+ ok = file:rename(MainScript, MainScript ++ "_with_shebang"),
%% Without shebang (no flags)
- ?line ok = file:write_file(MainScript,
- ["Something else than shebang!!!", "\n",
- ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
-
- ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "dict:[]\n"
- "dummy:[]\n"
- "priv:{ok,<<\"Some private data...\\n\">>}\n"
- "ExitCode:0">>]),
- ?line ok = file:rename(MainScript, MainScript ++ "_without_shebang"),
+ ok = file:write_file(MainScript,
+ ["Something else than shebang!!!", "\n",
+ ArchiveBin]),
+ ok = file:write_file_info(MainScript, OrigFI),
+
+ run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "dict:[]\n"
+ "dummy:[]\n"
+ "priv:{ok,<<\"Some private data...\\n\">>}\n"
+ "ExitCode:0">>]),
+ ok = file:rename(MainScript, MainScript ++ "_without_shebang"),
%% Plain archive without header (no flags)
- ?line ok = file:write_file(MainScript, [ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
+ ok = file:write_file(MainScript, [ArchiveBin]),
+ ok = file:write_file_info(MainScript, OrigFI),
- ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "dict:[]\n"
- "dummy:[]\n"
- "priv:{ok,<<\"Some private data...\\n\">>}\n"
- "ExitCode:0">>]),
- ?line ok = file:rename(MainScript, MainScript ++ "_without_header"),
+ run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "dict:[]\n"
+ "dummy:[]\n"
+ "priv:{ok,<<\"Some private data...\\n\">>}\n"
+ "ExitCode:0">>]),
+ ok = file:rename(MainScript, MainScript ++ "_without_header"),
- %%%%%%%
+%%%%%%%
%% Create and run scripts with emulator flags
AltBase = "archive_script_alternate_main",
AltScript = filename:join([PrivDir, AltBase]),
- ?line ok = file:write_file(AltScript,
- [Shebang, "\n",
- Mode, "\n",
- Flags, " -escript main archive_script_main2\n",
- ArchiveBin]),
- ?line ok = file:write_file_info(AltScript, OrigFI),
-
- ?line run(PrivDir, AltBase ++ " -arg1 arg2 arg3",
- [<<"main2:[\"-arg1\",\"arg2\",\"arg3\"]\n"
- "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
- "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
- "priv:{ok,<<\"Some private data...\\n\">>}\n"
- "ExitCode:0">>]),
+ ok = file:write_file(AltScript,
+ [Shebang, "\n",
+ Mode, "\n",
+ Flags, " -escript main archive_script_main2\n",
+ ArchiveBin]),
+ ok = file:write_file_info(AltScript, OrigFI),
+
+ run(PrivDir, AltBase ++ " -arg1 arg2 arg3",
+ [<<"main2:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
+ "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
+ "priv:{ok,<<\"Some private data...\\n\">>}\n"
+ "ExitCode:0">>]),
ok.
@@ -515,13 +515,13 @@ archive_script_file_access(Config) when is_list(Config) ->
MainBeam = MainMod ++ ".beam",
Archive = filename:join([PrivDir, "archive_script_file_access.zip"]),
- ?line {ok, _} = zip:create(Archive, ["archive_script_file_access"],
- [{compress, []}, {cwd, DataDir}]),
- ?line {ok, _} = zip:extract(Archive, [{cwd, PrivDir}]),
+ {ok, _} = zip:create(Archive, ["archive_script_file_access"],
+ [{compress, []}, {cwd, DataDir}]),
+ {ok, _} = zip:extract(Archive, [{cwd, PrivDir}]),
TopDir = filename:join([PrivDir, "archive_script_file_access"]),
%% Compile the code
- ?line ok = compile_files([MainSrc], TopDir, TopDir),
+ ok = compile_files([MainSrc], TopDir, TopDir),
%% First, create a file structure which will be included in the archive:
%%
@@ -629,7 +629,7 @@ compile_app(TopDir, AppName) ->
AppDir = filename:join([TopDir, AppName]),
SrcDir = filename:join([AppDir, "src"]),
OutDir = filename:join([AppDir, "ebin"]),
- ?line {ok, Files} = file:list_dir(SrcDir),
+ {ok, Files} = file:list_dir(SrcDir),
compile_files(Files, SrcDir, OutDir).
compile_files([File | Files], SrcDir, OutDir) ->
@@ -653,8 +653,8 @@ compile_files([], _, _) ->
epp(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "factorial_epp 5",
- <<"factorial 5 = 120\nExitCode:0">>),
+ run(Dir, "factorial_epp 5",
+ <<"factorial 5 = 120\nExitCode:0">>),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -694,9 +694,9 @@ create_and_extract(Config) when is_list(Config) ->
%% Verify the compile_source option
file:delete(NewFile),
- ?line ok = escript:create(NewFile, [{source, Source}]),
- ?line {ok, [_, _, _, {source, Source}]} = escript:extract(NewFile, []),
- ?line {ok, [_, _, _, {source, BeamCode2}]} =
+ ok = escript:create(NewFile, [{source, Source}]),
+ {ok, [_, _, _, {source, Source}]} = escript:extract(NewFile, []),
+ {ok, [_, _, _, {source, BeamCode2}]} =
escript:extract(NewFile, [compile_source]),
verify_sections(NewFile, FileInfo,
[{shebang, default},
@@ -711,12 +711,12 @@ prepare_creation(Base, Config) ->
PrivDir = ?config(priv_dir, Config),
DataDir = ?config(data_dir, Config),
OrigFile = filename:join([DataDir,"emulator_flags"]),
- ?line {ok, FileInfo} = file:read_file_info(OrigFile),
+ {ok, FileInfo} = file:read_file_info(OrigFile),
NewFile = filename:join([PrivDir, Base]),
- ?line {ok, [{shebang, default},
- {comment, _},
- {emu_args, EmuArg},
- {source, Source}]} =
+ {ok, [{shebang, default},
+ {comment, _},
+ {emu_args, EmuArg},
+ {source, Source}]} =
escript:extract(OrigFile, []),
%% Compile the code
@@ -724,14 +724,14 @@ prepare_creation(Base, Config) ->
ErlCode = list_to_binary(["\n-module(", Base, ").\n",
"-export([main/1]).\n\n",
Source, "\n\n"]),
- ?line ok = file:write_file(ErlFile, ErlCode),
+ ok = file:write_file(ErlFile, ErlCode),
%% Compile the code
- ?line {ok, _Mod, BeamCode} =
+ {ok, _Mod, BeamCode} =
compile:file(ErlFile, [binary, debug_info]),
%% Create an archive
- ?line {ok, {_, ArchiveBin}} =
+ {ok, {_, ArchiveBin}} =
zip:create("dummy_archive_name",
[{Base ++ ".erl", ErlCode},
{Base ++ ".beam", BeamCode}],
@@ -748,8 +748,8 @@ verify_sections(File, FileInfo, Sections) ->
%% Create
file:delete(File),
- ?line ok = escript:create(File, Sections),
- ?line ok = file:write_file_info(File, FileInfo),
+ ok = escript:create(File, Sections),
+ ok = file:write_file_info(File, FileInfo),
%% Run
Dir = filename:absname(filename:dirname(File)),
@@ -779,21 +779,21 @@ verify_sections(File, FileInfo, Sections) ->
Expected = <<ExpectedMain/binary, ExpectedOutput/binary>>,
case HasArg(shebang) of
true ->
- ?line run(Dir, InputArgs, [Expected]);
+ run(Dir, InputArgs, [Expected]);
false ->
- ?line run_with_opts(Dir, [], InputArgs, [Expected])
+ run_with_opts(Dir, [], InputArgs, [Expected])
end,
%% Verify
- ?line {ok, Bin} = escript:create(binary, Sections),
- ?line {ok, Read} = file:read_file(File),
- ?line Bin = Read, % Assert
+ {ok, Bin} = escript:create(binary, Sections),
+ {ok, Read} = file:read_file(File),
+ Bin = Read, % Assert
Normalized = normalize_sections(Sections),
- ?line {ok, Extracted} = escript:extract(File, []),
+ {ok, Extracted} = escript:extract(File, []),
io:format("Normalized; ~p\n", [Normalized]),
io:format("Extracted ; ~p\n", [Extracted]),
- ?line Normalized = Extracted, % Assert
+ Normalized = Extracted, % Assert
ok.
normalize_sections(Sections) ->
@@ -805,27 +805,27 @@ normalize_sections(Sections) ->
end
end,
case lists:map(AtomToTuple, [{K, V} || {K, V} <- Sections, V =/= undefined]) of
- [{shebang, Shebang} | Rest] ->
- [{shebang, Shebang} |
- case Rest of
- [{comment, Comment} | Rest2] ->
- [{comment, Comment} |
- case Rest2 of
- [{emu_args, EmuArgs}, Body] ->
- [{emu_args, EmuArgs}, Body];
- [Body] ->
- [{emu_args, undefined}, Body]
- end
- ];
- [{emu_args, EmuArgs}, Body] ->
- [{comment, undefined}, {emu_args, EmuArgs}, Body];
- [Body] ->
- [{comment, undefined}, {emu_args, undefined}, Body]
- end
- ];
- [Body] ->
- [{shebang, undefined}, {comment, undefined}, {emu_args, undefined}, Body]
- end.
+ [{shebang, Shebang} | Rest] ->
+ [{shebang, Shebang} |
+ case Rest of
+ [{comment, Comment} | Rest2] ->
+ [{comment, Comment} |
+ case Rest2 of
+ [{emu_args, EmuArgs}, Body] ->
+ [{emu_args, EmuArgs}, Body];
+ [Body] ->
+ [{emu_args, undefined}, Body]
+ end
+ ];
+ [{emu_args, EmuArgs}, Body] ->
+ [{comment, undefined}, {emu_args, EmuArgs}, Body];
+ [Body] ->
+ [{comment, undefined}, {emu_args, undefined}, Body]
+ end
+ ];
+ [Body] ->
+ [{shebang, undefined}, {comment, undefined}, {emu_args, undefined}, Body]
+ end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -845,36 +845,36 @@ foldl(Config) when is_list(Config) ->
%% Get line numbers and the file attribute right
SourceFile = NewFile ++ ".erl",
<<_:1/binary, ErlCode2/binary>> = ErlCode,
- ?line ok = file:write_file(SourceFile, ErlCode2),
- ?line {ok, _Mod, BeamCode} =
+ ok = file:write_file(SourceFile, ErlCode2),
+ {ok, _Mod, BeamCode} =
compile:file(SourceFile, [binary, debug_info]),
%% Verify source script
- ?line ok = escript:create(SourceFile, [{source, ErlCode}]),
- ?line {ok, [{".", _, BeamCode2}]}
+ ok = escript:create(SourceFile, [{source, ErlCode}]),
+ {ok, [{".", _, BeamCode2}]}
= escript_foldl(Collect, [], SourceFile),
- ?line {ok, Abstr} = beam_lib:chunks(BeamCode, [abstract_code]),
- ?line {ok, Abstr2} = beam_lib:chunks(BeamCode2, [abstract_code]),
+ {ok, Abstr} = beam_lib:chunks(BeamCode, [abstract_code]),
+ {ok, Abstr2} = beam_lib:chunks(BeamCode2, [abstract_code]),
%% io:format("abstr1=~p\n", [Abstr]),
%% io:format("abstr2=~p\n", [Abstr2]),
- ?line Abstr = Abstr2, % Assert
+ Abstr = Abstr2, % Assert
%% Verify beam script
- ?line ok = escript:create(NewFile, [{beam, BeamCode}]),
- ?line {ok, [{".", _, BeamCode}]}
+ ok = escript:create(NewFile, [{beam, BeamCode}]),
+ {ok, [{".", _, BeamCode}]}
= escript_foldl(Collect, [], NewFile),
%% Verify archive scripts
- ?line ok = escript:create(NewFile, [{archive, ArchiveBin}]),
- ?line {ok, [{BeamBase, #file_info{}, _},
- {ErlBase, #file_info{}, _}]}
+ ok = escript:create(NewFile, [{archive, ArchiveBin}]),
+ {ok, [{BeamBase, #file_info{}, _},
+ {ErlBase, #file_info{}, _}]}
= escript_foldl(Collect, [], NewFile),
ArchiveFiles = [{ErlBase, ErlCode}, {BeamBase, BeamCode}],
- ?line ok = escript:create(NewFile, [{archive, ArchiveFiles, []}]),
- ?line {ok, [{BeamBase, _, _},
- {ErlBase, _, _}]}
+ ok = escript:create(NewFile, [{archive, ArchiveFiles, []}]),
+ {ok, [{BeamBase, _, _},
+ {ErlBase, _, _}]}
= escript_foldl(Collect, [], NewFile),
ok.
@@ -929,10 +929,10 @@ unicode(Config) when is_list(Config) ->
overflow(Config) when is_list(Config) ->
Data = ?config(data_dir, Config),
Dir = filename:absname(Data), %Get rid of trailing slash.
- ?line run(Dir, "arg_overflow",
- [<<"ExitCode:0">>]),
- ?line run(Dir, "linebuf_overflow",
- [<<"ExitCode:0">>]),
+ run(Dir, "arg_overflow",
+ [<<"ExitCode:0">>]),
+ run(Dir, "linebuf_overflow",
+ [<<"ExitCode:0">>]),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 286cfb0e31..96b268d3be 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -34,7 +34,7 @@
-export([ match1/1, match2/1, match_object/1, match_object2/1]).
-export([ dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]).
-export([ tab2file/1, tab2file2/1, tabfile_ext1/1,
- tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]).
+ tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]).
-export([ heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]).
-export([ lookup_element_mult/1]).
-export([]).
@@ -107,7 +107,7 @@
-include_lib("common_test/include/ct.hrl").
--define(m(A,B), ?line assert_eq(A,B)).
+-define(m(A,B), assert_eq(A,B)).
init_per_testcase(Case, Config) ->
rand:seed(exsplus),
@@ -119,7 +119,7 @@ init_per_testcase(Case, Config) ->
end_per_testcase(_Func, _Config) ->
wait_for_test_procs(true).
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -155,7 +155,7 @@ all() ->
otp_9423,
ets_all,
take,
-
+
memory_check_summary]. % MUST BE LAST
groups() ->
@@ -196,10 +196,10 @@ end_per_suite(_Config) ->
ok.
init_per_group(_GroupName, Config) ->
- Config.
+ Config.
end_per_group(_GroupName, Config) ->
- Config.
+ Config.
%% Test that we did not have "too many" failed verify_etsmem()'s
%% in the test suite.
@@ -230,34 +230,34 @@ t_bucket_disappears(Config) when is_list(Config) ->
repeat_for_opts(t_bucket_disappears_do).
t_bucket_disappears_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line ets_new(abcd, [named_table, public, {keypos, 2} | Opts]),
- ?line ets:insert(abcd, {abcd,1,2}),
- ?line ets:insert(abcd, {abcd,2,2}),
- ?line ets:insert(abcd, {abcd,3,2}),
- ?line {_, Cont} = ets:select(abcd, [{{'_', '$1', '_'},
- [{'<', '$1', {const, 10}}],
- ['$1']}], 1),
- ?line ets:delete(abcd, 2),
- ?line ets:select(Cont),
- ?line true = ets:delete(abcd),
- ?line verify_etsmem(EtsMem).
-
+ EtsMem = etsmem(),
+ ets_new(abcd, [named_table, public, {keypos, 2} | Opts]),
+ ets:insert(abcd, {abcd,1,2}),
+ ets:insert(abcd, {abcd,2,2}),
+ ets:insert(abcd, {abcd,3,2}),
+ {_, Cont} = ets:select(abcd, [{{'_', '$1', '_'},
+ [{'<', '$1', {const, 10}}],
+ ['$1']}], 1),
+ ets:delete(abcd, 2),
+ ets:select(Cont),
+ true = ets:delete(abcd),
+ verify_etsmem(EtsMem).
+
%% Check ets:match_spec_run/2.
t_match_spec_run(Config) when is_list(Config) ->
init_externals(),
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
t_match_spec_run_test([{1},{2},{3}],
[{{'$1'},[{'>','$1',1}],['$1']}],
[2,3]),
- ?line Huge = [{X} || X <- lists:seq(1,2500)],
- ?line L = lists:seq(2476,2500),
+ Huge = [{X} || X <- lists:seq(1,2500)],
+ L = lists:seq(2476,2500),
t_match_spec_run_test(Huge, [{{'$1'},[{'>','$1',2475}],['$1']}], L),
- ?line L2 = [{X*16#FFFFFFF} || X <- L],
+ L2 = [{X*16#FFFFFFF} || X <- L],
t_match_spec_run_test(Huge,
[{{'$1'}, [{'>','$1',2475}], [{{{'*','$1',16#FFFFFFF}}}]}],
L2),
@@ -334,7 +334,7 @@ t_match_spec_run(Config) when is_list(Config) ->
end,
test_terms(Fun, skip_refc_check),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
t_match_spec_run_test(List, MS, Result) ->
@@ -420,172 +420,172 @@ t_repair_continuation(Config) when is_list(Config) ->
t_repair_continuation_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line MS = [{'_',[],[true]}],
- ?line MS2 = [{{{'$1','_'},'_'},[],['$1']}],
+ EtsMem = etsmem(),
+ MS = [{'_',[],[true]}],
+ MS2 = [{{{'$1','_'},'_'},[],['$1']}],
(fun() ->
- ?line T = ets_new(x,[ordered_set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(5,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[ordered_set|Opts]),
+ F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(5,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets_new(x,[ordered_set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,1001),
- ?line C = '$end_of_table',
- ?line C3 = ets:repair_continuation(C,MS),
- ?line '$end_of_table' = ets:select(C3),
- ?line '$end_of_table' = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[ordered_set|Opts]),
+ F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,1001),
+ C = '$end_of_table',
+ C3 = ets:repair_continuation(C,MS),
+ '$end_of_table' = ets:select(C3),
+ '$end_of_table' = ets:select(C),
+ true = ets:delete(T)
end)(),
-
+
(fun() ->
- ?line T = ets_new(x,[ordered_set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{integer_to_list(N),N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(5,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[ordered_set|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{integer_to_list(N),N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(5,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets_new(x,[ordered_set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{{integer_to_list(N),N},N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS2,5),
- ?line C2 = erlang:setelement(5,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS2),
- ?line {[_,_,_,_,_],_} = ets:select(C3),
- ?line {[_,_,_,_,_],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[ordered_set|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{{integer_to_list(N),N},N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS2,5),
+ C2 = erlang:setelement(5,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS2),
+ {[_,_,_,_,_],_} = ets:select(C3),
+ {[_,_,_,_,_],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
-
+
(fun() ->
- ?line T = ets_new(x,[set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{N,N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(4,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[set|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{N,N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(4,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets_new(x,[set|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{integer_to_list(N),N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(4,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[set|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{integer_to_list(N),N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(4,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets_new(x,[bag|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{integer_to_list(N),N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(4,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[bag|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{integer_to_list(N),N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(4,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets_new(x,[duplicate_bag|Opts]),
- ?line F = fun(0,_)->ok;(N,F) ->
- ets:insert(T,{integer_to_list(N),N}),
- F(N-1,F)
- end,
- ?line F(1000,F),
- ?line {_,C} = ets:select(T,MS,5),
- ?line C2 = erlang:setelement(4,C,<<>>),
- ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
- ?line C3 = ets:repair_continuation(C2,MS),
- ?line {[true,true,true,true,true],_} = ets:select(C3),
- ?line {[true,true,true,true,true],_} = ets:select(C),
- ?line true = ets:delete(T)
+ T = ets_new(x,[duplicate_bag|Opts]),
+ F = fun(0,_)->ok;(N,F) ->
+ ets:insert(T,{integer_to_list(N),N}),
+ F(N-1,F)
+ end,
+ F(1000,F),
+ {_,C} = ets:select(T,MS,5),
+ C2 = erlang:setelement(4,C,<<>>),
+ {'EXIT',{badarg,_}} = (catch ets:select(C2)),
+ C3 = ets:repair_continuation(C2,MS),
+ {[true,true,true,true,true],_} = ets:select(C3),
+ {[true,true,true,true,true],_} = ets:select(C),
+ true = ets:delete(T)
end)(),
- ?line false = ets:is_compiled_ms(<<>>),
- ?line true = ets:is_compiled_ms(ets:match_spec_compile(MS)),
- ?line verify_etsmem(EtsMem).
+ false = ets:is_compiled_ms(<<>>),
+ true = ets:is_compiled_ms(ets:match_spec_compile(MS)),
+ verify_etsmem(EtsMem).
%% Test correct default vaules of a new ets table.
default(Config) when is_list(Config) ->
%% Default should be set,protected
- ?line EtsMem = etsmem(),
- ?line Def = ets_new(def,[]),
- ?line set = ets:info(Def,type),
- ?line protected = ets:info(Def,protection),
+ EtsMem = etsmem(),
+ Def = ets_new(def,[]),
+ set = ets:info(Def,type),
+ protected = ets:info(Def,protection),
Compressed = erlang:system_info(ets_always_compress),
- ?line Compressed = ets:info(Def,compressed),
+ Compressed = ets:info(Def,compressed),
Self = self(),
- ?line Self = ets:info(Def,owner),
- ?line none = ets:info(Def, heir),
- ?line false = ets:info(Def,named_table),
- ?line ets:delete(Def),
- ?line verify_etsmem(EtsMem).
+ Self = ets:info(Def,owner),
+ none = ets:info(Def, heir),
+ false = ets:info(Def,named_table),
+ ets:delete(Def),
+ verify_etsmem(EtsMem).
%% Test that select fails even if nothing can match.
select_fail(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(select_fail_do, [all_types,write_concurrency]),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
select_fail_do(Opts) ->
- ?line T = ets_new(x,Opts),
- ?line ets:insert(T,{a,a}),
- ?line case (catch
- ets:select(T,[{{a,'_'},[],[{snuffla}]}])) of
- {'EXIT',{badarg,_}} ->
- ok;
- Else0 ->
- exit({type,ets:info(T,type),
- expected,'EXIT',got,Else0})
- end,
- ?line case (catch
- ets:select(T,[{{b,'_'},[],[{snuffla}]}])) of
- {'EXIT',{badarg,_}} ->
- ok;
- Else1 ->
- exit({type,ets:info(T,type),
- expected,'EXIT',got,Else1})
- end,
- ?line ets:delete(T).
-
+ T = ets_new(x,Opts),
+ ets:insert(T,{a,a}),
+ case (catch
+ ets:select(T,[{{a,'_'},[],[{snuffla}]}])) of
+ {'EXIT',{badarg,_}} ->
+ ok;
+ Else0 ->
+ exit({type,ets:info(T,type),
+ expected,'EXIT',got,Else0})
+ end,
+ case (catch
+ ets:select(T,[{{b,'_'},[],[{snuffla}]}])) of
+ {'EXIT',{badarg,_}} ->
+ ok;
+ Else1 ->
+ exit({type,ets:info(T,type),
+ expected,'EXIT',got,Else1})
+ end,
+ ets:delete(T).
+
-define(S(T),ets:info(T,memory)).
-define(TAB_STRUCT_SZ, erts_debug:get_internal_state('DbTable_words')).
@@ -597,103 +597,103 @@ select_fail_do(Opts) ->
%% Whitebox test of ets:info(X, memory).
memory(Config) when is_list(Config) ->
- ?line ok = chk_normal_tab_struct_size(),
+ ok = chk_normal_tab_struct_size(),
repeat_for_opts(memory_do,[compressed]),
- ?line catch erts_debug:set_internal_state(available_internal_state, false).
+ catch erts_debug:set_internal_state(available_internal_state, false).
memory_do(Opts) ->
- ?line L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts),
+ L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts),
XR1 = case mem_mode(T1) of
- {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078};
- {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278};
- {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286}
+ {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078};
+ {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278};
+ {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286}
end,
- ?line XRes1 = adjust_xmem(L, XR1),
- ?line Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
- ?line lists:foreach(fun(T) ->
- Before = ets:info(T,size),
- Key = 2, %894, %%ets:first(T),
- Objs = ets:lookup(T,Key),
- ?line ets:delete(T,Key),
- io:format("deleted key ~p from ~p changed size ~p to ~p: ~p\n",
- [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
+ XRes1 = adjust_xmem(L, XR1),
+ Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
+ lists:foreach(fun(T) ->
+ Before = ets:info(T,size),
+ Key = 2, %894, %%ets:first(T),
+ Objs = ets:lookup(T,Key),
+ ets:delete(T,Key),
+ io:format("deleted key ~p from ~p changed size ~p to ~p: ~p\n",
+ [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
end,
L),
XR2 = case mem_mode(T1) of
- {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060};
- {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260};
- {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268}
+ {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060};
+ {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260};
+ {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268}
end,
- ?line XRes2 = adjust_xmem(L, XR2),
- ?line Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
- ?line lists:foreach(fun(T) ->
- Before = ets:info(T,size),
- Key = 4, %802, %ets:first(T),
- Objs = ets:lookup(T,Key),
- ?line ets:match_delete(T,{Key,'_'}),
- io:format("match_deleted key ~p from ~p changed size ~p to ~p: ~p\n",
- [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
- end,
- L),
+ XRes2 = adjust_xmem(L, XR2),
+ Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
+ lists:foreach(fun(T) ->
+ Before = ets:info(T,size),
+ Key = 4, %802, %ets:first(T),
+ Objs = ets:lookup(T,Key),
+ ets:match_delete(T,{Key,'_'}),
+ io:format("match_deleted key ~p from ~p changed size ~p to ~p: ~p\n",
+ [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
+ end,
+ L),
XR3 = case mem_mode(T1) of
- {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042};
- {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242};
- {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250}
+ {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042};
+ {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242};
+ {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250}
end,
- ?line XRes3 = adjust_xmem(L, XR3),
- ?line Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
- ?line lists:foreach(fun(T) ->
- ?line ets:delete_all_objects(T)
+ XRes3 = adjust_xmem(L, XR3),
+ Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
+ lists:foreach(fun(T) ->
+ ets:delete_all_objects(T)
end,
L),
- ?line XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
- ?line Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
+ XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
+ Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
- ?line ets:delete(T)
+ ets:delete(T)
end,
L),
- ?line L2 = [T11,T12,T13,T14] = fill_sets_int(1000),
- ?line lists:foreach(fun(T) ->
- ?line ets:select_delete(T,[{'_',[],[true]}])
+ L2 = [T11,T12,T13,T14] = fill_sets_int(1000),
+ lists:foreach(fun(T) ->
+ ets:select_delete(T,[{'_',[],[true]}])
end,
L2),
- ?line XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
- ?line Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
- ?line io:format("XRes1 = ~p~n"
- " Res1 = ~p~n~n"
- "XRes2 = ~p~n"
- " Res2 = ~p~n~n"
- "XRes3 = ~p~n"
- " Res3 = ~p~n~n"
- "XRes4 = ~p~n"
- " Res4 = ~p~n~n"
- "XRes5 = ~p~n"
- " Res5 = ~p~n~n",
- [XRes1, Res1,
- XRes2, Res2,
- XRes3, Res3,
- XRes4, Res4,
- XRes5, Res5]),
- ?line XRes1 = Res1,
- ?line XRes2 = Res2,
- ?line XRes3 = Res3,
- ?line XRes4 = Res4,
- ?line XRes5 = Res5,
- ?line ok.
+ XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
+ Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
+ io:format("XRes1 = ~p~n"
+ " Res1 = ~p~n~n"
+ "XRes2 = ~p~n"
+ " Res2 = ~p~n~n"
+ "XRes3 = ~p~n"
+ " Res3 = ~p~n~n"
+ "XRes4 = ~p~n"
+ " Res4 = ~p~n~n"
+ "XRes5 = ~p~n"
+ " Res5 = ~p~n~n",
+ [XRes1, Res1,
+ XRes2, Res2,
+ XRes3, Res3,
+ XRes4, Res4,
+ XRes5, Res5]),
+ XRes1 = Res1,
+ XRes2 = Res2,
+ XRes3 = Res3,
+ XRes4 = Res4,
+ XRes5 = Res5,
+ ok.
mem_mode(T) ->
{case ets:info(T,compressed) of
- true -> compressed;
- false -> normal
+ true -> compressed;
+ false -> normal
end,
erlang:system_info(wordsize)}.
chk_normal_tab_struct_size() ->
- ?line System = {os:type(),
- os:version(),
- erlang:system_info(wordsize),
- erlang:system_info(smp_support),
- erlang:system_info(heap_type)},
+ System = {os:type(),
+ os:version(),
+ erlang:system_info(wordsize),
+ erlang:system_info(smp_support),
+ erlang:system_info(heap_type)},
io:format("System = ~p~n", [System]),
io:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]),
ok.
@@ -707,67 +707,67 @@ adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) ->
%% Misc. whitebox tests
t_whitebox(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(whitebox_1),
repeat_for_opts(whitebox_1),
repeat_for_opts(whitebox_1),
repeat_for_opts(whitebox_2),
repeat_for_opts(whitebox_2),
repeat_for_opts(whitebox_2),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
whitebox_1(Opts) ->
- ?line T=ets_new(x,[bag | Opts]),
- ?line ets:insert(T,[{du,glade},{ta,en}]),
- ?line ets:insert(T,[{hej,hopp2},{du,glade2},{ta,en2}]),
- ?line {_,C}=ets:match(T,{ta,'$1'},1),
- ?line ets:select(C),
- ?line ets:match(C),
- ?line ets:delete(T),
+ T=ets_new(x,[bag | Opts]),
+ ets:insert(T,[{du,glade},{ta,en}]),
+ ets:insert(T,[{hej,hopp2},{du,glade2},{ta,en2}]),
+ {_,C}=ets:match(T,{ta,'$1'},1),
+ ets:select(C),
+ ets:match(C),
+ ets:delete(T),
ok.
whitebox_2(Opts) ->
- ?line T=ets_new(x,[ordered_set, {keypos,2} | Opts]),
- ?line T2=ets_new(x,[set, {keypos,2}| Opts]),
- ?line 0 = ets:select_delete(T,[{{hej},[],[true]}]),
- ?line 0 = ets:select_delete(T,[{{hej,hopp},[],[true]}]),
- ?line 0 = ets:select_delete(T2,[{{hej},[],[true]}]),
- ?line 0 = ets:select_delete(T2,[{{hej,hopp},[],[true]}]),
- ?line ets:delete(T),
- ?line ets:delete(T2),
+ T=ets_new(x,[ordered_set, {keypos,2} | Opts]),
+ T2=ets_new(x,[set, {keypos,2}| Opts]),
+ 0 = ets:select_delete(T,[{{hej},[],[true]}]),
+ 0 = ets:select_delete(T,[{{hej,hopp},[],[true]}]),
+ 0 = ets:select_delete(T2,[{{hej},[],[true]}]),
+ 0 = ets:select_delete(T2,[{{hej,hopp},[],[true]}]),
+ ets:delete(T),
+ ets:delete(T2),
ok.
-
-
+
+
%% Test ets:to/from_dets.
t_ets_dets(Config) when is_list(Config) ->
repeat_for_opts(fun(Opts) -> t_ets_dets(Config,Opts) end).
t_ets_dets(Config, Opts) ->
- ?line Fname = gen_dets_filename(Config,1),
- ?line (catch file:delete(Fname)),
- ?line {ok,DTab} = dets:open_file(testdets_1,
+ Fname = gen_dets_filename(Config,1),
+ (catch file:delete(Fname)),
+ {ok,DTab} = dets:open_file(testdets_1,
[{file, Fname}]),
- ?line ETab = ets_new(x,Opts),
- ?line filltabint(ETab,3000),
- ?line DTab = ets:to_dets(ETab,DTab),
- ?line ets:delete_all_objects(ETab),
- ?line 0 = ets:info(ETab,size),
- ?line true = ets:from_dets(ETab,DTab),
- ?line 3000 = ets:info(ETab,size),
- ?line ets:delete(ETab),
- ?line check_badarg(catch ets:to_dets(ETab,DTab),
- ets, to_dets, [ETab,DTab]),
- ?line check_badarg(catch ets:from_dets(ETab,DTab),
- ets, from_dets, [ETab,DTab]),
- ?line ETab2 = ets_new(x,Opts),
- ?line filltabint(ETab2,3000),
- ?line dets:close(DTab),
- ?line check_badarg(catch ets:to_dets(ETab2,DTab),
- ets, to_dets, [ETab2,DTab]),
- ?line check_badarg(catch ets:from_dets(ETab2,DTab),
- ets, from_dets, [ETab2,DTab]),
- ?line ets:delete(ETab2),
- ?line (catch file:delete(Fname)),
+ ETab = ets_new(x,Opts),
+ filltabint(ETab,3000),
+ DTab = ets:to_dets(ETab,DTab),
+ ets:delete_all_objects(ETab),
+ 0 = ets:info(ETab,size),
+ true = ets:from_dets(ETab,DTab),
+ 3000 = ets:info(ETab,size),
+ ets:delete(ETab),
+ check_badarg(catch ets:to_dets(ETab,DTab),
+ ets, to_dets, [ETab,DTab]),
+ check_badarg(catch ets:from_dets(ETab,DTab),
+ ets, from_dets, [ETab,DTab]),
+ ETab2 = ets_new(x,Opts),
+ filltabint(ETab2,3000),
+ dets:close(DTab),
+ check_badarg(catch ets:to_dets(ETab2,DTab),
+ ets, to_dets, [ETab2,DTab]),
+ check_badarg(catch ets:from_dets(ETab2,DTab),
+ ets, from_dets, [ETab2,DTab]),
+ ets:delete(ETab2),
+ (catch file:delete(Fname)),
ok.
check_badarg({'EXIT', {badarg, [{M,F,Args,_} | _]}}, M, F, Args) ->
@@ -777,9 +777,9 @@ check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) ->
%% Test ets:delete_all_objects/1.
t_delete_all_objects(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(t_delete_all_objects_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
get_kept_objects(T) ->
case ets:info(T,stats) of
@@ -790,77 +790,77 @@ get_kept_objects(T) ->
end.
t_delete_all_objects_do(Opts) ->
- ?line T=ets_new(x,Opts),
- ?line filltabint(T,4000),
- ?line O=ets:first(T),
- ?line ets:next(T,O),
- ?line ets:safe_fixtable(T,true),
- ?line true = ets:delete_all_objects(T),
- ?line '$end_of_table' = ets:next(T,O),
- ?line 0 = ets:info(T,size),
- ?line 4000 = get_kept_objects(T),
- ?line ets:safe_fixtable(T,false),
- ?line 0 = ets:info(T,size),
- ?line 0 = get_kept_objects(T),
- ?line filltabint(T,4000),
- ?line 4000 = ets:info(T,size),
- ?line true = ets:delete_all_objects(T),
- ?line 0 = ets:info(T,size),
- ?line ets:delete(T).
+ T=ets_new(x,Opts),
+ filltabint(T,4000),
+ O=ets:first(T),
+ ets:next(T,O),
+ ets:safe_fixtable(T,true),
+ true = ets:delete_all_objects(T),
+ '$end_of_table' = ets:next(T,O),
+ 0 = ets:info(T,size),
+ 4000 = get_kept_objects(T),
+ ets:safe_fixtable(T,false),
+ 0 = ets:info(T,size),
+ 0 = get_kept_objects(T),
+ filltabint(T,4000),
+ 4000 = ets:info(T,size),
+ true = ets:delete_all_objects(T),
+ 0 = ets:info(T,size),
+ ets:delete(T).
%% Test ets:delete_object/2.
t_delete_object(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(t_delete_object_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
t_delete_object_do(Opts) ->
- ?line T = ets_new(x,Opts),
- ?line filltabint(T,4000),
- ?line del_one_by_one_set(T,1,4001),
- ?line filltabint(T,4000),
- ?line del_one_by_one_set(T,4000,0),
- ?line filltabint(T,4000),
- ?line First = ets:first(T),
- ?line Next = ets:next(T,First),
- ?line ets:safe_fixtable(T,true),
- ?line ets:delete_object(T,{First, integer_to_list(First)}),
- ?line Next = ets:next(T,First),
- ?line 3999 = ets:info(T,size),
- ?line 1 = get_kept_objects(T),
- ?line ets:safe_fixtable(T,false),
- ?line 3999 = ets:info(T,size),
- ?line 0 = get_kept_objects(T),
- ?line ets:delete(T),
- ?line T1 = ets_new(x,[ordered_set | Opts]),
- ?line filltabint(T1,4000),
- ?line del_one_by_one_set(T1,1,4001),
- ?line filltabint(T1,4000),
- ?line del_one_by_one_set(T1,4000,0),
- ?line ets:delete(T1),
- ?line T2 = ets_new(x,[bag | Opts]),
- ?line filltabint2(T2,4000),
- ?line del_one_by_one_bag(T2,1,4001),
- ?line filltabint2(T2,4000),
- ?line del_one_by_one_bag(T2,4000,0),
- ?line ets:delete(T2),
- ?line T3 = ets_new(x,[duplicate_bag | Opts]),
- ?line filltabint3(T3,4000),
- ?line del_one_by_one_dbag_1(T3,1,4001),
- ?line filltabint3(T3,4000),
- ?line del_one_by_one_dbag_1(T3,4000,0),
- ?line filltabint(T3,4000),
- ?line filltabint3(T3,4000),
- ?line del_one_by_one_dbag_2(T3,1,4001),
- ?line filltabint(T3,4000),
- ?line filltabint3(T3,4000),
- ?line del_one_by_one_dbag_2(T3,4000,0),
-
- ?line filltabint2(T3,4000),
- ?line filltabint(T3,4000),
- ?line del_one_by_one_dbag_3(T3,4000,0),
- ?line ets:delete(T3),
+ T = ets_new(x,Opts),
+ filltabint(T,4000),
+ del_one_by_one_set(T,1,4001),
+ filltabint(T,4000),
+ del_one_by_one_set(T,4000,0),
+ filltabint(T,4000),
+ First = ets:first(T),
+ Next = ets:next(T,First),
+ ets:safe_fixtable(T,true),
+ ets:delete_object(T,{First, integer_to_list(First)}),
+ Next = ets:next(T,First),
+ 3999 = ets:info(T,size),
+ 1 = get_kept_objects(T),
+ ets:safe_fixtable(T,false),
+ 3999 = ets:info(T,size),
+ 0 = get_kept_objects(T),
+ ets:delete(T),
+ T1 = ets_new(x,[ordered_set | Opts]),
+ filltabint(T1,4000),
+ del_one_by_one_set(T1,1,4001),
+ filltabint(T1,4000),
+ del_one_by_one_set(T1,4000,0),
+ ets:delete(T1),
+ T2 = ets_new(x,[bag | Opts]),
+ filltabint2(T2,4000),
+ del_one_by_one_bag(T2,1,4001),
+ filltabint2(T2,4000),
+ del_one_by_one_bag(T2,4000,0),
+ ets:delete(T2),
+ T3 = ets_new(x,[duplicate_bag | Opts]),
+ filltabint3(T3,4000),
+ del_one_by_one_dbag_1(T3,1,4001),
+ filltabint3(T3,4000),
+ del_one_by_one_dbag_1(T3,4000,0),
+ filltabint(T3,4000),
+ filltabint3(T3,4000),
+ del_one_by_one_dbag_2(T3,1,4001),
+ filltabint(T3,4000),
+ filltabint3(T3,4000),
+ del_one_by_one_dbag_2(T3,4000,0),
+
+ filltabint2(T3,4000),
+ filltabint(T3,4000),
+ del_one_by_one_dbag_3(T3,4000,0),
+ ets:delete(T3),
ok.
make_init_fun(N) when N > 4000->
@@ -884,16 +884,16 @@ make_init_fun(N) ->
%% Test ets:init_table/2.
t_init_table(Config) when is_list(Config)->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(t_init_table_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
t_init_table_do(Opts) ->
- ?line T = ets_new(x,[duplicate_bag | Opts]),
- ?line filltabint(T,4000),
- ?line ets:init_table(T, make_init_fun(1)),
- ?line del_one_by_one_dbag_1(T,4000,0),
- ?line ets:delete(T),
+ T = ets_new(x,[duplicate_bag | Opts]),
+ filltabint(T,4000),
+ ets:init_table(T, make_init_fun(1)),
+ del_one_by_one_dbag_1(T,4000,0),
+ ets:delete(T),
ok.
do_fill_dbag_using_lists(T,0) ->
@@ -906,118 +906,118 @@ do_fill_dbag_using_lists(T,N) ->
%% Test the insert_new function.
t_insert_new(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line L = fill_sets_int(1000) ++ fill_sets_int(1000,[{write_concurrency,true}]),
+ EtsMem = etsmem(),
+ L = fill_sets_int(1000) ++ fill_sets_int(1000,[{write_concurrency,true}]),
lists:foreach(fun(Tab) ->
- ?line false = ets:insert_new(Tab,{2,"2"}),
- ?line true = ets:insert_new(Tab,{2002,"2002"}),
- ?line false = ets:insert_new(Tab,{2002,"2002"}),
- ?line true = ets:insert(Tab,{2002,"2002"}),
- ?line false = ets:insert_new(Tab,[{2002,"2002"}]),
- ?line false = ets:insert_new(Tab,[{2002,"2002"},
+ false = ets:insert_new(Tab,{2,"2"}),
+ true = ets:insert_new(Tab,{2002,"2002"}),
+ false = ets:insert_new(Tab,{2002,"2002"}),
+ true = ets:insert(Tab,{2002,"2002"}),
+ false = ets:insert_new(Tab,[{2002,"2002"}]),
+ false = ets:insert_new(Tab,[{2002,"2002"},
{2003,"2003"}]),
- ?line false = ets:insert_new(Tab,[{2001,"2001"},
+ false = ets:insert_new(Tab,[{2001,"2001"},
{2002,"2002"},
{2003,"2003"}]),
- ?line false = ets:insert_new(Tab,[{2001,"2001"},
+ false = ets:insert_new(Tab,[{2001,"2001"},
{2002,"2002"}]),
- ?line true = ets:insert_new(Tab,[{2001,"2001"},
+ true = ets:insert_new(Tab,[{2001,"2001"},
{2003,"2003"}]),
- ?line false = ets:insert_new(Tab,{2001,"2001"}),
- ?line false = ets:insert_new(Tab,{2002,"2002"}),
- ?line false = ets:insert_new(Tab,{2003,"2003"}),
- ?line true = ets:insert_new(Tab,{2004,"2004"}),
- ?line true = ets:insert_new(Tab,{2000,"2000"}),
- ?line true = ets:insert_new(Tab,[{2005,"2005"},
- {2006,"2006"},
- {2007,"2007"}]),
- ?line Num =
+ false = ets:insert_new(Tab,{2001,"2001"}),
+ false = ets:insert_new(Tab,{2002,"2002"}),
+ false = ets:insert_new(Tab,{2003,"2003"}),
+ true = ets:insert_new(Tab,{2004,"2004"}),
+ true = ets:insert_new(Tab,{2000,"2000"}),
+ true = ets:insert_new(Tab,[{2005,"2005"},
+ {2006,"2006"},
+ {2007,"2007"}]),
+ Num =
case ets:info(Tab,type) of
bag ->
- ?line true =
+ true =
ets:insert(Tab,{2004,"2004-2"}),
- ?line false =
+ false =
ets:insert_new(Tab,{2004,"2004-3"}),
1009;
duplicate_bag ->
- ?line true =
+ true =
ets:insert(Tab,{2004,"2004"}),
- ?line false =
+ false =
ets:insert_new(Tab,{2004,"2004"}),
1010;
_ ->
1008
end,
- ?line Num = ets:info(Tab,size),
- ?line List = ets:tab2list(Tab),
- ?line ets:delete_all_objects(Tab),
- ?line true = ets:insert_new(Tab,List),
- ?line false = ets:insert_new(Tab,List),
- ?line ets:delete(Tab)
+ Num = ets:info(Tab,size),
+ List = ets:tab2list(Tab),
+ ets:delete_all_objects(Tab),
+ true = ets:insert_new(Tab,List),
+ false = ets:insert_new(Tab,List),
+ ets:delete(Tab)
end,
L),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% Test ets:insert/2 with list of objects.
t_insert_list(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(t_insert_list_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
t_insert_list_do(Opts) ->
- ?line T = ets_new(x,[duplicate_bag | Opts]),
- ?line do_fill_dbag_using_lists(T,4000),
- ?line del_one_by_one_dbag_2(T,4000,0),
- ?line ets:delete(T).
+ T = ets_new(x,[duplicate_bag | Opts]),
+ do_fill_dbag_using_lists(T,4000),
+ del_one_by_one_dbag_2(T,4000,0),
+ ets:delete(T).
%% Test interface of ets:test_ms/2.
t_test_ms(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line {ok,[a,b]} = ets:test_ms({a,b},
- [{{'$1','$2'},[{'<','$1','$2'}],['$$']}]),
- ?line {ok,false} = ets:test_ms({a,b},
- [{{'$1','$2'},[{'>','$1','$2'}],['$$']}]),
+ EtsMem = etsmem(),
+ {ok,[a,b]} = ets:test_ms({a,b},
+ [{{'$1','$2'},[{'<','$1','$2'}],['$$']}]),
+ {ok,false} = ets:test_ms({a,b},
+ [{{'$1','$2'},[{'>','$1','$2'}],['$$']}]),
Tpl = {a,gb_sets:new()},
- ?line {ok,Tpl} = ets:test_ms(Tpl, [{{'_','_'}, [], ['$_']}]), % OTP-10190
- ?line {error,[{error,String}]} = ets:test_ms({a,b},
- [{{'$1','$2'},
- [{'flurp','$1','$2'}],
- ['$$']}]),
- ?line true = (if is_list(String) -> true; true -> false end),
- ?line verify_etsmem(EtsMem).
+ {ok,Tpl} = ets:test_ms(Tpl, [{{'_','_'}, [], ['$_']}]), % OTP-10190
+ {error,[{error,String}]} = ets:test_ms({a,b},
+ [{{'$1','$2'},
+ [{'flurp','$1','$2'}],
+ ['$$']}]),
+ true = (if is_list(String) -> true; true -> false end),
+ verify_etsmem(EtsMem).
%% Test the select reverse BIFs.
t_select_reverse(Config) when is_list(Config) ->
- ?line Table = ets_new(xxx, [ordered_set]),
- ?line filltabint(Table,1000),
- ?line A = lists:reverse(ets:select(Table,[{{'$1', '_'},
+ Table = ets_new(xxx, [ordered_set]),
+ filltabint(Table,1000),
+ A = lists:reverse(ets:select(Table,[{{'$1', '_'},
[{'>',
{'rem',
'$1', 5},
2}],
['$_']}])),
- ?line A = ets:select_reverse(Table,[{{'$1', '_'},
+ A = ets:select_reverse(Table,[{{'$1', '_'},
[{'>',
{'rem',
'$1', 5},
2}],
['$_']}]),
- ?line A = reverse_chunked(Table,[{{'$1', '_'},
- [{'>',
- {'rem',
- '$1', 5},
- 2}],
- ['$_']}],3),
+ A = reverse_chunked(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}],3),
%% A set/bag/duplicate_bag should get the same result regardless
%% of select or select_reverse
- ?line Table2 = ets_new(xxx, [set]),
- ?line filltabint(Table2,1000),
- ?line Table3 = ets_new(xxx, [bag]),
- ?line filltabint(Table3,1000),
- ?line Table4 = ets_new(xxx, [duplicate_bag]),
- ?line filltabint(Table4,1000),
- ?line lists:map(fun(Tab) ->
+ Table2 = ets_new(xxx, [set]),
+ filltabint(Table2,1000),
+ Table3 = ets_new(xxx, [bag]),
+ filltabint(Table3,1000),
+ Table4 = ets_new(xxx, [duplicate_bag]),
+ filltabint(Table4,1000),
+ lists:map(fun(Tab) ->
B = ets:select(Tab,[{{'$1', '_'},
[{'>',
{'rem',
@@ -1047,47 +1047,47 @@ do_reverse_chunked({L,C},Acc) ->
%% Test the ets:select_delete/2 and ets:select_count/2 BIFs.
t_select_delete(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Tables = fill_sets_int(10000) ++ fill_sets_int(10000,[{write_concurrency,true}]),
+ EtsMem = etsmem(),
+ Tables = fill_sets_int(10000) ++ fill_sets_int(10000,[{write_concurrency,true}]),
lists:foreach
(fun(Table) ->
- ?line 4000 = ets:select_count(Table,[{{'$1', '_'},
- [{'>',
- {'rem',
- '$1', 5},
- 2}],
- [true]}]),
- ?line 4000 = ets:select_delete(Table,[{{'$1', '_'},
- [{'>',
- {'rem',
- '$1', 5},
- 2}],
- [true]}]),
- ?line check(Table,
- fun({N,_}) when (N rem 5) =< 2 ->
- true;
- (_) ->
- false
- end,
- 6000)
+ 4000 = ets:select_count(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ [true]}]),
+ 4000 = ets:select_delete(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ [true]}]),
+ check(Table,
+ fun({N,_}) when (N rem 5) =< 2 ->
+ true;
+ (_) ->
+ false
+ end,
+ 6000)
end,
Tables),
lists:foreach
(fun(Table) ->
- ?line ets:select_delete(Table,[{'_',[],[true]}]),
- ?line xfilltabint(Table,4000),
- ?line successive_delete(Table,1,4001,bound),
- ?line 0 = ets:info(Table,size),
- ?line xfilltabint(Table,4000),
- ?line successive_delete(Table,4000,0, bound),
- ?line 0 = ets:info(Table,size),
- ?line xfilltabint(Table,4000),
- ?line successive_delete(Table,1,4001,unbound),
- ?line 0 = ets:info(Table,size),
- ?line xfilltabint(Table,4000),
- ?line successive_delete(Table,4000,0, unbound),
- ?line 0 = ets:info(Table,size)
+ ets:select_delete(Table,[{'_',[],[true]}]),
+ xfilltabint(Table,4000),
+ successive_delete(Table,1,4001,bound),
+ 0 = ets:info(Table,size),
+ xfilltabint(Table,4000),
+ successive_delete(Table,4000,0, bound),
+ 0 = ets:info(Table,size),
+ xfilltabint(Table,4000),
+ successive_delete(Table,1,4001,unbound),
+ 0 = ets:info(Table,size),
+ xfilltabint(Table,4000),
+ successive_delete(Table,4000,0, unbound),
+ 0 = ets:info(Table,size)
end,
Tables),
@@ -1099,83 +1099,83 @@ t_select_delete(Config) when is_list(Config) ->
_ ->
1
end,
- ?line xfilltabstr(Table, 4000),
- ?line 1000 = ets:select_count(Table,
- [{{[$3 | '$1'], '_'},
- [{'==',
- {'length', '$1'},
- 3}],[true]}]) div F,
- ?line 1000 = ets:select_delete(Table,
- [{{[$3 | '$1'], '_'},
- [{'==',
- {'length', '$1'},
- 3}],[true]}]) div F,
- ?line check(Table, fun({[3,_,_,_],_}) -> false;
- (_) -> true
- end, 3000*F),
- ?line 8 = ets:select_count(Table,
- [{{"7",'_'},[],[false]},
- {{['_'], '_'},
- [],[true]}]) div F,
- ?line 8 = ets:select_delete(Table,
- [{{"7",'_'},[],[false]},
- {{['_'], '_'},
- [],[true]}]) div F,
- ?line check(Table, fun({"7",_}) -> true;
- ({[_],_}) -> false;
- (_) -> true
- end, 2992*F),
- ?line xfilltabstr(Table, 4000),
+ xfilltabstr(Table, 4000),
+ 1000 = ets:select_count(Table,
+ [{{[$3 | '$1'], '_'},
+ [{'==',
+ {'length', '$1'},
+ 3}],[true]}]) div F,
+ 1000 = ets:select_delete(Table,
+ [{{[$3 | '$1'], '_'},
+ [{'==',
+ {'length', '$1'},
+ 3}],[true]}]) div F,
+ check(Table, fun({[3,_,_,_],_}) -> false;
+ (_) -> true
+ end, 3000*F),
+ 8 = ets:select_count(Table,
+ [{{"7",'_'},[],[false]},
+ {{['_'], '_'},
+ [],[true]}]) div F,
+ 8 = ets:select_delete(Table,
+ [{{"7",'_'},[],[false]},
+ {{['_'], '_'},
+ [],[true]}]) div F,
+ check(Table, fun({"7",_}) -> true;
+ ({[_],_}) -> false;
+ (_) -> true
+ end, 2992*F),
+ xfilltabstr(Table, 4000),
%% This happens to be interesting for other select types too
- ?line 200 = length(ets:select(Table,
- [{{[$3,'_','_'],'_'},
- [],[true]},
- {{[$1,'_','_'],'_'},
- [],[true]}])) div F,
- ?line 200 = ets:select_count(Table,
- [{{[$3,'_','_'],'_'},
- [],[true]},
- {{[$1,'_','_'],'_'},
- [],[true]}]) div F,
- ?line 200 = length(element(1,ets:select(Table,
- [{{[$3,'_','_'],'_'},
- [],[true]},
- {{[$1,'_','_'],'_'},
- [],[true]}],
- 1000))) div F,
- ?line 200 = length(
- ets:select_reverse(Table,
- [{{[$3,'_','_'],'_'},
- [],[true]},
- {{[$1,'_','_'],'_'},
- [],[true]}])) div F,
- ?line 200 = length(
- element(1,
- ets:select_reverse
- (Table,
+ 200 = length(ets:select(Table,
+ [{{[$3,'_','_'],'_'},
+ [],[true]},
+ {{[$1,'_','_'],'_'},
+ [],[true]}])) div F,
+ 200 = ets:select_count(Table,
[{{[$3,'_','_'],'_'},
[],[true]},
{{[$1,'_','_'],'_'},
- [],[true]}],
- 1000))) div F,
- ?line 200 = ets:select_delete(Table,
- [{{[$3,'_','_'],'_'},
- [],[true]},
- {{[$1,'_','_'],'_'},
- [],[true]}]) div F,
- ?line 0 = ets:select_count(Table,
+ [],[true]}]) div F,
+ 200 = length(element(1,ets:select(Table,
+ [{{[$3,'_','_'],'_'},
+ [],[true]},
+ {{[$1,'_','_'],'_'},
+ [],[true]}],
+ 1000))) div F,
+ 200 = length(
+ ets:select_reverse(Table,
[{{[$3,'_','_'],'_'},
[],[true]},
{{[$1,'_','_'],'_'},
- [],[true]}]) div F,
- ?line check(Table, fun({[$3,_,_],_}) -> false;
- ({[$1,_,_],_}) -> false;
- (_) -> true
- end, 3800*F)
+ [],[true]}])) div F,
+ 200 = length(
+ element(1,
+ ets:select_reverse
+ (Table,
+ [{{[$3,'_','_'],'_'},
+ [],[true]},
+ {{[$1,'_','_'],'_'},
+ [],[true]}],
+ 1000))) div F,
+ 200 = ets:select_delete(Table,
+ [{{[$3,'_','_'],'_'},
+ [],[true]},
+ {{[$1,'_','_'],'_'},
+ [],[true]}]) div F,
+ 0 = ets:select_count(Table,
+ [{{[$3,'_','_'],'_'},
+ [],[true]},
+ {{[$1,'_','_'],'_'},
+ [],[true]}]) div F,
+ check(Table, fun({[$3,_,_],_}) -> false;
+ ({[$1,_,_],_}) -> false;
+ (_) -> true
+ end, 3800*F)
end,
Tables),
lists:foreach(fun(Tab) -> ets:delete(Tab) end,Tables),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% Test that partly bound keys gives faster matches.
partly_bound(Config) when is_list(Config) ->
@@ -1183,44 +1183,44 @@ partly_bound(Config) when is_list(Config) ->
{win32,_} ->
{skip,"Inaccurate measurements on Windows"};
_ ->
- ?line EtsMem = etsmem(),
- ?line dont_make_worse(),
- ?line make_better(),
- ?line verify_etsmem(EtsMem)
+ EtsMem = etsmem(),
+ dont_make_worse(),
+ make_better(),
+ verify_etsmem(EtsMem)
end.
dont_make_worse() ->
seventyfive_percent_success({?MODULE,dont_make_worse_sub,[]},0,0,10).
dont_make_worse_sub() ->
- ?line T = build_table([a,b],[a,b],15000),
- ?line T1 = time_match_object(T,{'_',a,a,1500}, [{{a,a,1500},a,a,1500}]),
- ?line T2 = time_match_object(T,{{a,a,'_'},a,a,1500},
- [{{a,a,1500},a,a,1500}]),
- ?line ets:delete(T),
- ?line true = (T1 > T2),
+ T = build_table([a,b],[a,b],15000),
+ T1 = time_match_object(T,{'_',a,a,1500}, [{{a,a,1500},a,a,1500}]),
+ T2 = time_match_object(T,{{a,a,'_'},a,a,1500},
+ [{{a,a,1500},a,a,1500}]),
+ ets:delete(T),
+ true = (T1 > T2),
ok.
-
+
make_better() ->
fifty_percent_success({?MODULE,make_better_sub2,[]},0,0,10),
fifty_percent_success({?MODULE,make_better_sub1,[]},0,0,10).
make_better_sub1() ->
- ?line T = build_table2([a,b],[a,b],15000),
- ?line T1 = time_match_object(T,{'_',1500,a,a}, [{{1500,a,a},1500,a,a}]),
- ?line T2 = time_match_object(T,{{1500,a,'_'},1500,a,a},
- [{{1500,a,a},1500,a,a}]),
- ?line ets:delete(T),
- ?line io:format("~p>~p~n",[(T1 / 100),T2]),
- ?line true = ((T1 / 100) > T2), % More marginal than needed.
+ T = build_table2([a,b],[a,b],15000),
+ T1 = time_match_object(T,{'_',1500,a,a}, [{{1500,a,a},1500,a,a}]),
+ T2 = time_match_object(T,{{1500,a,'_'},1500,a,a},
+ [{{1500,a,a},1500,a,a}]),
+ ets:delete(T),
+ io:format("~p>~p~n",[(T1 / 100),T2]),
+ true = ((T1 / 100) > T2), % More marginal than needed.
ok.
make_better_sub2() ->
- ?line T = build_table2([a,b],[a,b],15000),
- ?line T1 = time_match(T,{'$1',1500,a,a}),
- ?line T2 = time_match(T,{{1500,a,'$1'},1500,a,a}),
- ?line ets:delete(T),
- ?line io:format("~p>~p~n",[(T1 / 100),T2]),
- ?line true = ((T1 / 100) > T2), % More marginal than needed.
+ T = build_table2([a,b],[a,b],15000),
+ T1 = time_match(T,{'$1',1500,a,a}),
+ T2 = time_match(T,{{1500,a,'$1'},1500,a,a}),
+ ets:delete(T),
+ io:format("~p>~p~n",[(T1 / 100),T2]),
+ true = ((T1 / 100) > T2), % More marginal than needed.
ok.
@@ -1239,12 +1239,12 @@ match_heavy(Config) when is_list(Config) ->
%%% Extra safety for the very low probability that this is not
%%% caught by the random test (Statistically impossible???)
drop_match() ->
- ?line EtsMem = etsmem(),
- ?line T = build_table([a,b],[a],1500),
- ?line [{{a,a,1},a,a,1},{{b,a,1},b,a,1}] =
+ EtsMem = etsmem(),
+ T = build_table([a,b],[a],1500),
+ [{{a,a,1},a,a,1},{{b,a,1},b,a,1}] =
ets:match_object(T, {'_','_','_',1}),
- ?line true = ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ true = ets:delete(T),
+ verify_etsmem(EtsMem).
@@ -1281,11 +1281,11 @@ match_object_chunked_collect({Results, Continuation}) ->
Results ++ match_object_chunked_collect(ets:match_object(Continuation)).
-
+
random_test() ->
- ?line ReadDir = get(where_to_read),
- ?line WriteDir = get(where_to_write),
- ?line (catch file:make_dir(WriteDir)),
+ ReadDir = get(where_to_read),
+ WriteDir = get(where_to_write),
+ (catch file:make_dir(WriteDir)),
case file:consult(filename:join([ReadDir,"preset_random_seed.txt"])) of
{ok,[X]} ->
rand:seed(X);
@@ -1294,152 +1294,152 @@ random_test() ->
end,
Seed = rand:export_seed(),
{ok,F} = file:open(filename:join([WriteDir,"last_random_seed.txt"]),
- [write]),
+ [write]),
io:format(F,"~p. ~n",[Seed]),
file:close(F),
io:format("Random seed ~p written to ~s, copy to ~s to rerun with "
"same seed.",[Seed,
filename:join([WriteDir, "last_random_seed.txt"]),
filename:join([ReadDir,
- "preset_random_seed.txt"])]),
+ "preset_random_seed.txt"])]),
do_random_test().
do_random_test() ->
- ?line EtsMem = etsmem(),
- ?line OrdSet = ets_new(xxx,[ordered_set]),
- ?line Set = ets_new(xxx,[]),
- ?line do_n_times(fun() ->
- ?line Key = create_random_string(25),
- ?line Value = create_random_tuple(25),
- ?line ets:insert(OrdSet,{Key,Value}),
- ?line ets:insert(Set,{Key,Value})
+ EtsMem = etsmem(),
+ OrdSet = ets_new(xxx,[ordered_set]),
+ Set = ets_new(xxx,[]),
+ do_n_times(fun() ->
+ Key = create_random_string(25),
+ Value = create_random_tuple(25),
+ ets:insert(OrdSet,{Key,Value}),
+ ets:insert(Set,{Key,Value})
end, 5000),
- ?line io:format("~nData inserted~n"),
- ?line do_n_times(fun() ->
+ io:format("~nData inserted~n"),
+ do_n_times(fun() ->
I = rand:uniform(25),
- ?line Key = create_random_string(I) ++ '_',
- ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
+ Key = create_random_string(I) ++ '_',
+ L1 = ets_match_object(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end,
2000),
- ?line io:format("~nData matched~n"),
- ?line ets:match_delete(OrdSet,'_'),
- ?line ets:match_delete(Set,'_'),
- ?line do_n_times(fun() ->
- ?line Value = create_random_string(25),
- ?line Key = create_random_tuple(25),
- ?line ets:insert(OrdSet,{Key,Value}),
- ?line ets:insert(Set,{Key,Value})
+ io:format("~nData matched~n"),
+ ets:match_delete(OrdSet,'_'),
+ ets:match_delete(Set,'_'),
+ do_n_times(fun() ->
+ Value = create_random_string(25),
+ Key = create_random_tuple(25),
+ ets:insert(OrdSet,{Key,Value}),
+ ets:insert(Set,{Key,Value})
end, 2000),
- ?line io:format("~nData inserted~n"),
+ io:format("~nData inserted~n"),
(fun() ->
- ?line Key = list_to_tuple(lists:duplicate(25,'_')),
- ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
- ?line 2000 = length(L1),
+ Key = list_to_tuple(lists:duplicate(25,'_')),
+ L1 = ets_match_object(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
+ 2000 = length(L1),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end)(),
(fun() ->
- ?line Key = {'$1','$2','$3','$4',
- '$5','$6','$7','$8',
- '$9','$10','$11','$12',
- '$13','$14','$15','$16',
- '$17','$18','$19','$20',
- '$21','$22','$23','$24',
- '$25'},
- ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
- ?line 2000 = length(L1),
+ Key = {'$1','$2','$3','$4',
+ '$5','$6','$7','$8',
+ '$9','$10','$11','$12',
+ '$13','$14','$15','$16',
+ '$17','$18','$19','$20',
+ '$21','$22','$23','$24',
+ '$25'},
+ L1 = ets_match_object(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
+ 2000 = length(L1),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end)(),
(fun() ->
- ?line Key = {'$1','$2','$3','$4',
- '$5','$6','$7','$8',
- '$9','$10','$11','$12',
- '$13','$14','$15','$16',
- '$17','$18','$19','$20',
- '$21','$22','$23','$24',
- '$25'},
- ?line L1 = ets_match(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match(Set,{Key,'_'})),
- ?line 2000 = length(L1),
+ Key = {'$1','$2','$3','$4',
+ '$5','$6','$7','$8',
+ '$9','$10','$11','$12',
+ '$13','$14','$15','$16',
+ '$17','$18','$19','$20',
+ '$21','$22','$23','$24',
+ '$25'},
+ L1 = ets_match(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match(Set,{Key,'_'})),
+ 2000 = length(L1),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end)(),
- ?line ets:match_delete(OrdSet,'_'),
- ?line ets:match_delete(Set,'_'),
- ?line do_n_times(fun() ->
- ?line Value = create_random_string(25),
- ?line Key = create_random_tuple(25),
- ?line ets:insert(OrdSet,{Key,Value}),
- ?line ets:insert(Set,{Key,Value})
+ ets:match_delete(OrdSet,'_'),
+ ets:match_delete(Set,'_'),
+ do_n_times(fun() ->
+ Value = create_random_string(25),
+ Key = create_random_tuple(25),
+ ets:insert(OrdSet,{Key,Value}),
+ ets:insert(Set,{Key,Value})
end, 2000),
- ?line io:format("~nData inserted~n"),
+ io:format("~nData inserted~n"),
do_n_times(fun() ->
- ?line Key = create_partly_bound_tuple(25),
- ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
+ Key = create_partly_bound_tuple(25),
+ L1 = ets_match_object(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end,
2000),
- ?line do_n_times(fun() ->
- ?line Key = create_partly_bound_tuple2(25),
- ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
+ do_n_times(fun() ->
+ Key = create_partly_bound_tuple2(25),
+ L1 = ets_match_object(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
end,
2000),
do_n_times(fun() ->
- ?line Key = create_partly_bound_tuple2(25),
- ?line L1 = ets_match(OrdSet,{Key,'_'}),
- ?line L2 = lists:sort(ets_match(Set,{Key,'_'})),
+ Key = create_partly_bound_tuple2(25),
+ L1 = ets_match(OrdSet,{Key,'_'}),
+ L2 = lists:sort(ets_match(Set,{Key,'_'})),
case L1 == L2 of
false ->
io:format("~p != ~p~n",
[L1,L2]),
- ?line exit({not_eq, L1, L2});
+ exit({not_eq, L1, L2});
true ->
ok
end
@@ -1450,15 +1450,15 @@ do_random_test() ->
ets:match_delete(Set,'_'),
do_n_times(fun() ->
do_n_times(fun() ->
- ?line Value =
+ Value =
create_random_string(25),
- ?line Key = create_random_tuple(25),
- ?line ets:insert(OrdSet,{Key,Value}),
- ?line ets:insert(Set,{Key,Value})
+ Key = create_random_tuple(25),
+ ets:insert(OrdSet,{Key,Value}),
+ ets:insert(Set,{Key,Value})
end, 500),
io:format("~nData inserted~n"),
do_n_times(fun() ->
- ?line Key =
+ Key =
create_partly_bound_tuple(25),
ets:match_delete(OrdSet,{Key,'_'}),
ets:match_delete(Set,{Key,'_'}),
@@ -1483,13 +1483,13 @@ do_random_test() ->
10),
ets:delete(OrdSet),
ets:delete(Set),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% Ttest various variants of update_element.
update_element(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(update_element_opts),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
update_element_opts(Opts) ->
TupleCases = [{{key,val}, 1 ,2},
@@ -1499,12 +1499,12 @@ update_element_opts(Opts) ->
{{val,key,val,val}, 2, [3,4,1]},
{{val,val,key,val}, 3, [1,4,1,2]}, % update pos1 twice
{{val,val,val,key}, 4, [2,1,2,3]}],% update pos2 twice
-
+
lists:foreach(fun({Tuple,KeyPos,UpdPos}) -> update_element_opts(Tuple,KeyPos,UpdPos,Opts) end,
TupleCases),
-
+
update_element_neg(Opts).
-
+
update_element_opts(Tuple,KeyPos,UpdPos,Opts) ->
@@ -1523,7 +1523,7 @@ update_element(T,Tuple,KeyPos,UpdPos) ->
update_element_do(T,TupleWithKey,Key,UpdPos)
end,
KeyList).
-
+
update_element_do(Tab,Tuple,Key,UpdPos) ->
%% Strategy: Step around in Values array and call ets:update_element for the values.
@@ -1541,14 +1541,14 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
(fun(X) -> X*Big32 end),
make_ref(), make_ref(), self(), ok, update_element, 28, 29 },
Length = size(Values),
-
+
PosValArgF = fun(ToIx, ResList, [Pos | PosTail], Rand, MeF) ->
NextIx = (ToIx+Rand) rem Length,
MeF(NextIx, [{Pos,element(ToIx+1,Values)} | ResList], PosTail, Rand, MeF);
(_ToIx, ResList, [], _Rand, _MeF) ->
ResList;
-
+
(ToIx, [], Pos, _Rand, _MeF) ->
{Pos, element(ToIx+1,Values)} % single {pos,value} arg
end,
@@ -1557,10 +1557,10 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
PosValArg = PosValArgF(ToIx,[],UpdPos,Rand,PosValArgF),
%%io:format("update_element(~p)~n",[PosValArg]),
ArgHash = erlang:phash2({Tab,Key,PosValArg}),
- ?line true = ets:update_element(Tab, Key, PosValArg),
- ?line ArgHash = erlang:phash2({Tab,Key,PosValArg}),
+ true = ets:update_element(Tab, Key, PosValArg),
+ ArgHash = erlang:phash2({Tab,Key,PosValArg}),
NewTuple = update_tuple(PosValArg,Tuple),
- ?line [NewTuple] = ets:lookup(Tab,Key)
+ [NewTuple] = ets:lookup(Tab,Key)
end,
LoopF = fun(_FromIx, Incr, _Times, Checksum, _MeF) when Incr >= Length ->
@@ -1580,11 +1580,11 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
end,
FirstTuple = Tuple,
- ?line true = ets:insert(Tab,FirstTuple),
- ?line [FirstTuple] = ets:lookup(Tab,Key),
-
+ true = ets:insert(Tab,FirstTuple),
+ [FirstTuple] = ets:lookup(Tab,Key),
+
Checksum = LoopF(0, 1, Length, 0, LoopF),
- ?line Checksum = (Length-1)*Length*(Length+1) div 2, % if Length is a prime
+ Checksum = (Length-1)*Length*(Length+1) div 2, % if Length is a prime
ok.
update_tuple({Pos,Val}, Tpl) ->
@@ -1602,14 +1602,14 @@ update_element_neg(Opts) ->
update_element_neg_do(Set),
update_element_neg_do(OrdSet),
ets:delete(Set),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_element(Set,key,{2,1})),
+ {'EXIT',{badarg,_}} = (catch ets:update_element(Set,key,{2,1})),
ets:delete(OrdSet),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_element(OrdSet,key,{2,1})),
+ {'EXIT',{badarg,_}} = (catch ets:update_element(OrdSet,key,{2,1})),
- ?line Bag = ets_new(bag,[bag | Opts]),
- ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1})),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1})),
+ Bag = ets_new(bag,[bag | Opts]),
+ DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
+ {'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1})),
+ {'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1})),
true = ets:delete(Bag),
true = ets:delete(DBag),
ok.
@@ -1617,13 +1617,13 @@ update_element_neg(Opts) ->
update_element_neg_do(T) ->
Object = {key, 0, "Hej"},
- ?line true = ets:insert(T,Object),
+ true = ets:insert(T,Object),
UpdateF = fun(Arg3) ->
ArgHash = erlang:phash2({T,key,Arg3}),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_element(T,key,Arg3)),
- ?line ArgHash = erlang:phash2({T,key,Arg3}),
- ?line [Object] = ets:lookup(T,key)
+ {'EXIT',{badarg,_}} = (catch ets:update_element(T,key,Arg3)),
+ ArgHash = erlang:phash2({T,key,Arg3}),
+ [Object] = ets:lookup(T,key)
end,
%% List of invalid {Pos,Value} tuples
@@ -1639,19 +1639,19 @@ update_element_neg_do(T) ->
UpdateF([{2,1} | {3,1}]),
lists:foreach(fun(InvTpl) -> UpdateF([{2,1} | InvTpl]) end, InvList),
- ?line true = ets:update_element(T,key,[]),
- ?line false = ets:update_element(T,false,[]),
- ?line false = ets:update_element(T,false,{2,1}),
- ?line ets:delete(T,key),
- ?line false = ets:update_element(T,key,{2,1}),
+ true = ets:update_element(T,key,[]),
+ false = ets:update_element(T,false,[]),
+ false = ets:update_element(T,false,{2,1}),
+ ets:delete(T,key),
+ false = ets:update_element(T,key,{2,1}),
ok.
%% test various variants of update_counter.
update_counter(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(update_counter_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
update_counter_do(Opts) ->
Set = ets_new(set,Opts),
@@ -1671,26 +1671,26 @@ update_counter_do(Opts) ->
update_counter_neg(Opts).
update_counter_for(T) ->
- ?line ets:insert(T,{a,1,1}),
- ?line 101 = ets:update_counter(T,a,100),
- ?line [{a,101,1}] = ets:lookup(T,a),
- ?line 101 = ets:update_counter(T,a,{3,100}),
- ?line [{a,101,101}] = ets:lookup(T,a),
+ ets:insert(T,{a,1,1}),
+ 101 = ets:update_counter(T,a,100),
+ [{a,101,1}] = ets:lookup(T,a),
+ 101 = ets:update_counter(T,a,{3,100}),
+ [{a,101,101}] = ets:lookup(T,a),
LooperF = fun(Obj, 0, _, _) ->
Obj;
-
+
(Obj, Times, Arg3, Myself) ->
- ?line {NewObj, Ret} = uc_mimic(Obj,Arg3),
+ {NewObj, Ret} = uc_mimic(Obj,Arg3),
ArgHash = erlang:phash2({T,a,Arg3}),
%%io:format("update_counter(~p, ~p, ~p) expecting ~p\n",[T,a,Arg3,Ret]),
[DefaultObj] = ets:lookup(T, a),
- ?line Ret = ets:update_counter(T,a,Arg3),
+ Ret = ets:update_counter(T,a,Arg3),
Ret = ets:update_counter(T, b, Arg3, DefaultObj), % Use other key
- ?line ArgHash = erlang:phash2({T,a,Arg3}),
+ ArgHash = erlang:phash2({T,a,Arg3}),
%%io:format("NewObj=~p~n ",[NewObj]),
- ?line [NewObj] = ets:lookup(T,a),
+ [NewObj] = ets:lookup(T,a),
true = ets:lookup(T, b) =:= [setelement(1, NewObj, b)],
ets:delete(T, b),
Myself(NewObj,Times-1,Arg3,Myself)
@@ -1708,78 +1708,78 @@ update_counter_for(T) ->
Steps = 100,
Obj0 = {a,0,0,0,0},
- ?line ets:insert(T,Obj0),
- ?line Obj1 = LoopF(Obj0, Steps, {2,(SmallMax32 div Steps)*2}),
- ?line Obj2 = LoopF(Obj1, Steps, {3,(SmallMax64 div Steps)*2}),
- ?line Obj3 = LoopF(Obj2, Steps, {4,(Big1Max32 div Steps)*2}),
- ?line Obj4 = LoopF(Obj3, Steps, {5,(Big1Max64 div Steps)*2}),
-
- ?line Obj5 = LoopF(Obj4, Steps, {2,-(SmallMax32 div Steps)*4}),
- ?line Obj6 = LoopF(Obj5, Steps, {3,-(SmallMax64 div Steps)*4}),
- ?line Obj7 = LoopF(Obj6, Steps, {4,-(Big1Max32 div Steps)*4}),
- ?line Obj8 = LoopF(Obj7, Steps, {5,-(Big1Max64 div Steps)*4}),
-
- ?line Obj9 = LoopF(Obj8, Steps, {2,(SmallMax32 div Steps)*2}),
- ?line ObjA = LoopF(Obj9, Steps, {3,(SmallMax64 div Steps)*2}),
- ?line ObjB = LoopF(ObjA, Steps, {4,(Big1Max32 div Steps)*2}),
- ?line Obj0 = LoopF(ObjB, Steps, {5,(Big1Max64 div Steps)*2}),
+ ets:insert(T,Obj0),
+ Obj1 = LoopF(Obj0, Steps, {2,(SmallMax32 div Steps)*2}),
+ Obj2 = LoopF(Obj1, Steps, {3,(SmallMax64 div Steps)*2}),
+ Obj3 = LoopF(Obj2, Steps, {4,(Big1Max32 div Steps)*2}),
+ Obj4 = LoopF(Obj3, Steps, {5,(Big1Max64 div Steps)*2}),
+
+ Obj5 = LoopF(Obj4, Steps, {2,-(SmallMax32 div Steps)*4}),
+ Obj6 = LoopF(Obj5, Steps, {3,-(SmallMax64 div Steps)*4}),
+ Obj7 = LoopF(Obj6, Steps, {4,-(Big1Max32 div Steps)*4}),
+ Obj8 = LoopF(Obj7, Steps, {5,-(Big1Max64 div Steps)*4}),
+
+ Obj9 = LoopF(Obj8, Steps, {2,(SmallMax32 div Steps)*2}),
+ ObjA = LoopF(Obj9, Steps, {3,(SmallMax64 div Steps)*2}),
+ ObjB = LoopF(ObjA, Steps, {4,(Big1Max32 div Steps)*2}),
+ Obj0 = LoopF(ObjB, Steps, {5,(Big1Max64 div Steps)*2}),
%% back at zero, same trip again with lists
- ?line Obj4 = LoopF(Obj0,Steps,[{2, (SmallMax32 div Steps)*2},
- {3, (SmallMax64 div Steps)*2},
- {4, (Big1Max32 div Steps)*2},
- {5, (Big1Max64 div Steps)*2}]),
+ Obj4 = LoopF(Obj0,Steps,[{2, (SmallMax32 div Steps)*2},
+ {3, (SmallMax64 div Steps)*2},
+ {4, (Big1Max32 div Steps)*2},
+ {5, (Big1Max64 div Steps)*2}]),
- ?line Obj8 = LoopF(Obj4,Steps,[{4, -(Big1Max32 div Steps)*4},
- {2, -(SmallMax32 div Steps)*4},
- {5, -(Big1Max64 div Steps)*4},
- {3, -(SmallMax64 div Steps)*4}]),
+ Obj8 = LoopF(Obj4,Steps,[{4, -(Big1Max32 div Steps)*4},
+ {2, -(SmallMax32 div Steps)*4},
+ {5, -(Big1Max64 div Steps)*4},
+ {3, -(SmallMax64 div Steps)*4}]),
- ?line Obj0 = LoopF(Obj8,Steps,[{5, (Big1Max64 div Steps)*2},
- {2, (SmallMax32 div Steps)*2},
- {4, (Big1Max32 div Steps)*2},
- {3, (SmallMax64 div Steps)*2}]),
+ Obj0 = LoopF(Obj8,Steps,[{5, (Big1Max64 div Steps)*2},
+ {2, (SmallMax32 div Steps)*2},
+ {4, (Big1Max32 div Steps)*2},
+ {3, (SmallMax64 div Steps)*2}]),
%% make them shift size at the same time
- ?line ObjC = LoopF(Obj0,Steps,[{5, (Big1Max64 div Steps)*2},
- {3, (Big1Max64 div Steps)*2 + 1},
- {2, -(Big1Max64 div Steps)*2},
- {4, -(Big1Max64 div Steps)*2 + 1}]),
+ ObjC = LoopF(Obj0,Steps,[{5, (Big1Max64 div Steps)*2},
+ {3, (Big1Max64 div Steps)*2 + 1},
+ {2, -(Big1Max64 div Steps)*2},
+ {4, -(Big1Max64 div Steps)*2 + 1}]),
%% update twice in same list
- ?line ObjD = LoopF(ObjC,Steps,[{5, -(Big1Max64 div Steps) + 1},
- {3, -(Big1Max64 div Steps)*2 - 1},
- {5, -(Big1Max64 div Steps) - 1},
- {4, (Big1Max64 div Steps)*2 - 1}]),
+ ObjD = LoopF(ObjC,Steps,[{5, -(Big1Max64 div Steps) + 1},
+ {3, -(Big1Max64 div Steps)*2 - 1},
+ {5, -(Big1Max64 div Steps) - 1},
+ {4, (Big1Max64 div Steps)*2 - 1}]),
- ?line Obj0 = LoopF(ObjD,Steps,[{2, (Big1Max64 div Steps) - 1},
- {4, Big1Max64*2},
- {2, (Big1Max64 div Steps) + 1},
- {4, -Big1Max64*2}]),
+ Obj0 = LoopF(ObjD,Steps,[{2, (Big1Max64 div Steps) - 1},
+ {4, Big1Max64*2},
+ {2, (Big1Max64 div Steps) + 1},
+ {4, -Big1Max64*2}]),
%% warping with list
- ?line ObjE = LoopF(Obj0,1000,
- [{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2},
- {5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2},
- {4,-Big1Max32*4 div 11,-Big1Max32*2,Big1Max32*2},
- {2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}]),
+ ObjE = LoopF(Obj0,1000,
+ [{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2},
+ {5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2},
+ {4,-Big1Max32*4 div 11,-Big1Max32*2,Big1Max32*2},
+ {2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}]),
%% warping without list
- ?line ObjF = LoopF(ObjE,1000,{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2}),
- ?line ObjG = LoopF(ObjF,1000,{5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2}),
- ?line ObjH = LoopF(ObjG,1000,{4,-Big1Max32*4 div 11,-Big1Max32*2,Big1Max32*2}),
- ?line ObjI = LoopF(ObjH,1000,{2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}),
+ ObjF = LoopF(ObjE,1000,{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2}),
+ ObjG = LoopF(ObjF,1000,{5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2}),
+ ObjH = LoopF(ObjG,1000,{4,-Big1Max32*4 div 11,-Big1Max32*2,Big1Max32*2}),
+ ObjI = LoopF(ObjH,1000,{2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}),
%% mixing it up
- ?line LoopF(ObjI,1000,
- [{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2},
- {5,-SmallMax64*4 div 3},
- {3,-SmallMax32*4 div 11},
- {5,0},
- {4,1},
- {5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2},
- {2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}]),
+ LoopF(ObjI,1000,
+ [{3,SmallMax32*4 div 5,SmallMax32*2,-SmallMax32*2},
+ {5,-SmallMax64*4 div 3},
+ {3,-SmallMax32*4 div 11},
+ {5,0},
+ {4,1},
+ {5,-SmallMax64*4 div 7,-SmallMax64*2,SmallMax64*2},
+ {2,Big1Max64*4 div 13,Big1Max64*2,-Big1Max64*2}]),
ok.
%% uc_mimic works kind of like the real ets:update_counter
@@ -1787,19 +1787,19 @@ update_counter_for(T) ->
%% Pits = {Pos,Incr} | {Pos,Incr,Thres,Warp}
%% Returns {Updated tuple in ets, Return value from update_counter}
uc_mimic(Obj, Pits) when is_tuple(Pits) ->
- ?line Pos = element(1,Pits),
- ?line NewObj = setelement(Pos, Obj, uc_adder(element(Pos,Obj),Pits)),
- ?line {NewObj, element(Pos,NewObj)};
+ Pos = element(1,Pits),
+ NewObj = setelement(Pos, Obj, uc_adder(element(Pos,Obj),Pits)),
+ {NewObj, element(Pos,NewObj)};
uc_mimic(Obj, PitsList) when is_list(PitsList) ->
- ?line {NewObj,ValList} = uc_mimic(Obj,PitsList,[]),
- ?line {NewObj,lists:reverse(ValList)}.
+ {NewObj,ValList} = uc_mimic(Obj,PitsList,[]),
+ {NewObj,lists:reverse(ValList)}.
uc_mimic(Obj, [], Acc) ->
- ?line {Obj,Acc};
+ {Obj,Acc};
uc_mimic(Obj, [Pits|Tail], Acc) ->
- ?line {NewObj,NewVal} = uc_mimic(Obj,Pits),
- ?line uc_mimic(NewObj,Tail,[NewVal|Acc]).
+ {NewObj,NewVal} = uc_mimic(Obj,Pits),
+ uc_mimic(NewObj,Tail,[NewVal|Acc]).
uc_adder(Init, {_Pos, Add}) ->
Init + Add;
@@ -1812,34 +1812,34 @@ uc_adder(Init, {_Pos, Add, Thres, Warp}) ->
Z ->
Z
end.
-
+
update_counter_neg(Opts) ->
Set = ets_new(set,Opts),
OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
update_counter_neg_for(Set),
update_counter_neg_for(OrdSet),
ets:delete(Set),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(Set,key,1)),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(Set,key,1)),
ets:delete(OrdSet),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(OrdSet,key,1)),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(OrdSet,key,1)),
- ?line Bag = ets_new(bag,[bag | Opts]),
- ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(Bag,key,1)),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(DBag,key,1)),
+ Bag = ets_new(bag,[bag | Opts]),
+ DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(Bag,key,1)),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(DBag,key,1)),
true = ets:delete(Bag),
true = ets:delete(DBag),
ok.
update_counter_neg_for(T) ->
Object = {key,0,false,1},
- ?line true = ets:insert(T,Object),
+ true = ets:insert(T,Object),
UpdateF = fun(Arg3) ->
ArgHash = erlang:phash2({T,key,Arg3}),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(T,key,Arg3)),
- ?line ArgHash = erlang:phash2({T,key,Arg3}),
- ?line [Object] = ets:lookup(T,key)
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(T,key,Arg3)),
+ ArgHash = erlang:phash2({T,key,Arg3}),
+ [Object] = ets:lookup(T,key)
end,
%% List of invalid arg3-tuples
@@ -1857,12 +1857,12 @@ update_counter_neg_for(T) ->
UpdateF([{2,1} | {4,1}]),
lists:foreach(fun(Inv) -> UpdateF([{2,1} | Inv]) end, InvList),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(T,false,1)),
- ?line ets:delete(T,key),
- ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(T,key,1)),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(T,false,1)),
+ ets:delete(T,key),
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(T,key,1)),
ok.
-
+
evil_update_counter(Config) when is_list(Config) ->
%% The code server uses ets table. Pre-load modules that might not be
%% already loaded.
@@ -1874,11 +1874,11 @@ evil_update_counter(Config) when is_list(Config) ->
repeat_for_opts(evil_update_counter_do).
evil_update_counter_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line process_flag(trap_exit, true),
- ?line Pids = [my_spawn_link(fun() -> evil_counter(I,Opts) end) || I <- lists:seq(1, 40)],
- ?line wait_for_all(gb_sets:from_list(Pids)),
- ?line verify_etsmem(EtsMem),
+ EtsMem = etsmem(),
+ process_flag(trap_exit, true),
+ Pids = [my_spawn_link(fun() -> evil_counter(I,Opts) end) || I <- lists:seq(1, 40)],
+ wait_for_all(gb_sets:from_list(Pids)),
+ verify_etsmem(EtsMem),
ok.
wait_for_all(Pids0) ->
@@ -1888,7 +1888,7 @@ wait_for_all(Pids0) ->
false ->
receive
{'EXIT',Pid,normal} ->
- ?line Pids = gb_sets:delete(Pid, Pids0),
+ Pids = gb_sets:delete(Pid, Pids0),
wait_for_all(Pids);
Other ->
io:format("unexpected: ~p\n", [Other]),
@@ -1899,10 +1899,10 @@ wait_for_all(Pids0) ->
evil_counter(I,Opts) ->
T = ets_new(a, Opts),
Start0 = case I rem 3 of
- 0 -> 16#12345678;
- 1 -> 16#12345678FFFFFFFF;
- 2 -> 16#7777777777FFFFFFFF863648726743
- end,
+ 0 -> 16#12345678;
+ 1 -> 16#12345678FFFFFFFF;
+ 2 -> 16#7777777777FFFFFFFF863648726743
+ end,
Start = Start0 + rand:uniform(100000),
ets:insert(T, {dracula,Start}),
Iter = 40000,
@@ -1918,7 +1918,7 @@ evil_counter_1(Iter, T) ->
evil_counter_1(Iter-1, T).
update_counter_with_default(Config) when is_list(Config) ->
- repeat_for_opts(update_counter_with_default_do).
+ repeat_for_opts(update_counter_with_default_do).
update_counter_with_default_do(Opts) ->
T1 = ets_new(a, [set | Opts]),
@@ -1960,12 +1960,12 @@ fixtable_next(Config) when is_list(Config) ->
repeat_for_opts(fixtable_next_do, [write_concurrency,all_types]).
fixtable_next_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line do_fixtable_next(ets_new(set,[public | Opts])),
- ?line verify_etsmem(EtsMem).
-
+ EtsMem = etsmem(),
+ do_fixtable_next(ets_new(set,[public | Opts])),
+ verify_etsmem(EtsMem).
+
do_fixtable_next(Tab) ->
- ?line F = fun(X,T,FF) -> case X of
+ F = fun(X,T,FF) -> case X of
0 -> true;
_ ->
ets:insert(T, {X,
@@ -1974,17 +1974,17 @@ do_fixtable_next(Tab) ->
FF(X-1,T,FF)
end
end,
- ?line F(100,Tab,F),
- ?line ets:safe_fixtable(Tab,true),
- ?line First = ets:first(Tab),
- ?line ets:delete(Tab, First),
- ?line ets:next(Tab, First),
- ?line ets:match_delete(Tab,{'_','_','_'}),
- ?line '$end_of_table' = ets:next(Tab, First),
- ?line true = ets:info(Tab, fixed),
- ?line ets:safe_fixtable(Tab, false),
- ?line false = ets:info(Tab, fixed),
- ?line ets:delete(Tab).
+ F(100,Tab,F),
+ ets:safe_fixtable(Tab,true),
+ First = ets:first(Tab),
+ ets:delete(Tab, First),
+ ets:next(Tab, First),
+ ets:match_delete(Tab,{'_','_','_'}),
+ '$end_of_table' = ets:next(Tab, First),
+ true = ets:info(Tab, fixed),
+ ets:safe_fixtable(Tab, false),
+ false = ets:info(Tab, fixed),
+ ets:delete(Tab).
%% Check inserts of deleted keys in fixed bags.
fixtable_insert(Config) when is_list(Config) ->
@@ -1993,43 +1993,43 @@ fixtable_insert(Config) when is_list(Config) ->
lists:foreach(fun(Opts) -> fixtable_insert_do(Opts) end,
Combos),
ok.
-
+
fixtable_insert_do(Opts) ->
io:format("Opts = ~p\n",[Opts]),
Ets = make_table(ets, Opts, [{a,1}, {a,2}, {b,1}, {b,2}]),
ets:safe_fixtable(Ets,true),
ets:match_delete(Ets,{b,1}),
First = ets:first(Ets),
- ?line Next = case First of
- a -> b;
- b -> a
- end,
- ?line Next = ets:next(Ets,First),
+ Next = case First of
+ a -> b;
+ b -> a
+ end,
+ Next = ets:next(Ets,First),
ets:delete(Ets,Next),
- ?line '$end_of_table' = ets:next(Ets,First),
+ '$end_of_table' = ets:next(Ets,First),
ets:insert(Ets, {Next,1}),
- ?line false = ets:insert_new(Ets, {Next,1}),
- ?line Next = ets:next(Ets,First),
- ?line '$end_of_table' = ets:next(Ets,Next),
+ false = ets:insert_new(Ets, {Next,1}),
+ Next = ets:next(Ets,First),
+ '$end_of_table' = ets:next(Ets,Next),
ets:delete(Ets,Next),
'$end_of_table' = ets:next(Ets,First),
ets:insert(Ets, {Next,2}),
- ?line false = ets:insert_new(Ets, {Next,1}),
+ false = ets:insert_new(Ets, {Next,1}),
Next = ets:next(Ets,First),
'$end_of_table' = ets:next(Ets,Next),
ets:delete(Ets,First),
- ?line Next = ets:first(Ets),
- ?line '$end_of_table' = ets:next(Ets,Next),
+ Next = ets:first(Ets),
+ '$end_of_table' = ets:next(Ets,Next),
ets:delete(Ets,Next),
- ?line '$end_of_table' = ets:next(Ets,First),
- ?line true = ets:insert_new(Ets,{Next,1}),
- ?line false = ets:insert_new(Ets,{Next,2}),
- ?line Next = ets:next(Ets,First),
+ '$end_of_table' = ets:next(Ets,First),
+ true = ets:insert_new(Ets,{Next,1}),
+ false = ets:insert_new(Ets,{Next,2}),
+ Next = ets:next(Ets,First),
ets:delete_object(Ets,{Next,1}),
- ?line '$end_of_table' = ets:next(Ets,First),
- ?line true = ets:insert_new(Ets,{Next,2}),
- ?line false = ets:insert_new(Ets,{Next,1}),
- ?line Next = ets:next(Ets,First),
+ '$end_of_table' = ets:next(Ets,First),
+ true = ets:insert_new(Ets,{Next,2}),
+ false = ets:insert_new(Ets,{Next,1}),
+ Next = ets:next(Ets,First),
ets:delete(Ets,First),
ets:safe_fixtable(Ets,false),
{'EXIT',{badarg,_}} = (catch ets:next(Ets,First)),
@@ -2037,7 +2037,7 @@ fixtable_insert_do(Opts) ->
%% Test the 'write_concurrency' option.
write_concurrency(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
Yes1 = ets_new(foo,[public,{write_concurrency,true}]),
Yes2 = ets_new(foo,[protected,{write_concurrency,true}]),
No1 = ets_new(foo,[private,{write_concurrency,true}]),
@@ -2057,49 +2057,49 @@ write_concurrency(Config) when is_list(Config) ->
No7 = ets_new(foo,[public,{write_concurrency,false}]),
No8 = ets_new(foo,[protected,{write_concurrency,false}]),
- ?line YesMem = ets:info(Yes1,memory),
- ?line NoHashMem = ets:info(No1,memory),
- ?line NoTreeMem = ets:info(No4,memory),
+ YesMem = ets:info(Yes1,memory),
+ NoHashMem = ets:info(No1,memory),
+ NoTreeMem = ets:info(No4,memory),
io:format("YesMem=~p NoHashMem=~p NoTreeMem=~p\n",[YesMem,NoHashMem,NoTreeMem]),
- ?line YesMem = ets:info(Yes2,memory),
- ?line YesMem = ets:info(Yes3,memory),
- ?line YesMem = ets:info(Yes4,memory),
- ?line YesMem = ets:info(Yes5,memory),
- ?line YesMem = ets:info(Yes6,memory),
- ?line NoHashMem = ets:info(No2,memory),
- ?line NoHashMem = ets:info(No3,memory),
- ?line NoTreeMem = ets:info(No5,memory),
- ?line NoTreeMem = ets:info(No6,memory),
- ?line NoHashMem = ets:info(No7,memory),
- ?line NoHashMem = ets:info(No8,memory),
-
+ YesMem = ets:info(Yes2,memory),
+ YesMem = ets:info(Yes3,memory),
+ YesMem = ets:info(Yes4,memory),
+ YesMem = ets:info(Yes5,memory),
+ YesMem = ets:info(Yes6,memory),
+ NoHashMem = ets:info(No2,memory),
+ NoHashMem = ets:info(No3,memory),
+ NoTreeMem = ets:info(No5,memory),
+ NoTreeMem = ets:info(No6,memory),
+ NoHashMem = ets:info(No7,memory),
+ NoHashMem = ets:info(No8,memory),
+
case erlang:system_info(smp_support) of
true ->
- ?line true = YesMem > NoHashMem,
- ?line true = YesMem > NoTreeMem;
+ true = YesMem > NoHashMem,
+ true = YesMem > NoTreeMem;
false ->
- ?line true = YesMem =:= NoHashMem
+ true = YesMem =:= NoHashMem
end,
- ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,true,foo}])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,write_concurrency])),
+ {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])),
+ {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])),
+ {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,true,foo}])),
+ {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,write_concurrency])),
lists:foreach(fun(T) -> ets:delete(T) end,
[Yes1,Yes2,Yes3,Yes4,Yes5,Yes6,
No1,No2,No3,No4,No5,No6,No7,No8]),
- ?line verify_etsmem(EtsMem),
+ verify_etsmem(EtsMem),
ok.
-
-
+
+
%% The 'heir' option.
heir(Config) when is_list(Config) ->
repeat_for_opts(heir_do).
heir_do(Opts) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
Master = self(),
%% Different types of heir data and link/monitor relations
@@ -2108,33 +2108,33 @@ heir_do(Opts) ->
lists:seq(1,10), {17,TestFun,self()},
"The busy heir"],
Mode<-[none,link,monitor]],
- ?line lists:foreach(fun({Data,Mode})-> heir_1(Data,Mode,Opts) end,
- Combos),
-
+ lists:foreach(fun({Data,Mode})-> heir_1(Data,Mode,Opts) end,
+ Combos),
+
%% No heir
{Founder1,MrefF1} = my_spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
Founder1 ! {go, none},
- ?line {"No heir",Founder1} = receive_any(),
- ?line {'DOWN', MrefF1, process, Founder1, normal} = receive_any(),
- ?line undefined = ets:info(foo),
+ {"No heir",Founder1} = receive_any(),
+ {'DOWN', MrefF1, process, Founder1, normal} = receive_any(),
+ undefined = ets:info(foo),
%% An already dead heir
{Heir2,MrefH2} = my_spawn_monitor(fun()->die end),
- ?line {'DOWN', MrefH2, process, Heir2, normal} = receive_any(),
+ {'DOWN', MrefH2, process, Heir2, normal} = receive_any(),
{Founder2,MrefF2} = my_spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
Founder2 ! {go, Heir2},
- ?line {"No heir",Founder2} = receive_any(),
- ?line {'DOWN', MrefF2, process, Founder2, normal} = receive_any(),
- ?line undefined = ets:info(foo),
+ {"No heir",Founder2} = receive_any(),
+ {'DOWN', MrefF2, process, Founder2, normal} = receive_any(),
+ undefined = ets:info(foo),
%% When heir dies before founder
{Founder3,MrefF3} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
{Heir3,MrefH3} = my_spawn_monitor(fun()->heir_heir(Founder3)end),
Founder3 ! {go, Heir3},
- ?line {'DOWN', MrefH3, process, Heir3, normal} = receive_any(),
+ {'DOWN', MrefH3, process, Heir3, normal} = receive_any(),
Founder3 ! die_please,
- ?line {'DOWN', MrefF3, process, Founder3, normal} = receive_any(),
- ?line undefined = ets:info(foo),
+ {'DOWN', MrefF3, process, Founder3, normal} = receive_any(),
+ undefined = ets:info(foo),
%% When heir dies and pid reused before founder dies
repeat_while(fun() ->
@@ -2142,177 +2142,177 @@ heir_do(Opts) ->
{Founder4,MrefF4} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
{Heir4,MrefH4} = my_spawn_monitor(fun()->heir_heir(Founder4)end),
Founder4 ! {go, Heir4},
- ?line {'DOWN', MrefH4, process, Heir4, normal} = receive_any(),
+ {'DOWN', MrefH4, process, Heir4, normal} = receive_any(),
erts_debug:set_internal_state(next_pid, NextPidIx),
DoppelGanger = spawn_monitor_with_pid(Heir4,
- fun()-> ?line die_please = receive_any() end),
+ fun()-> die_please = receive_any() end),
Founder4 ! die_please,
- ?line {'DOWN', MrefF4, process, Founder4, normal} = receive_any(),
+ {'DOWN', MrefF4, process, Founder4, normal} = receive_any(),
case DoppelGanger of
{Heir4,MrefH4_B} ->
Heir4 ! die_please,
- ?line {'DOWN', MrefH4_B, process, Heir4, normal} = receive_any(),
- ?line undefined = ets:info(foo),
+ {'DOWN', MrefH4_B, process, Heir4, normal} = receive_any(),
+ undefined = ets:info(foo),
false;
failed ->
io:format("Failed to spawn process with pid ~p\n", [Heir4]),
true % try again
end
end),
-
- ?line verify_etsmem(EtsMem).
+
+ verify_etsmem(EtsMem).
heir_founder(Master, HeirData, Opts) ->
- ?line {go,Heir} = receive_any(),
+ {go,Heir} = receive_any(),
HeirTpl = case Heir of
none -> {heir,none};
_ -> {heir, Heir, HeirData}
end,
- ?line T = ets_new(foo,[named_table, private, HeirTpl | Opts]),
- ?line true = ets:insert(T,{key,1}),
- ?line [{key,1}] = ets:lookup(T,key),
+ T = ets_new(foo,[named_table, private, HeirTpl | Opts]),
+ true = ets:insert(T,{key,1}),
+ [{key,1}] = ets:lookup(T,key),
Self = self(),
- ?line Self = ets:info(T,owner),
- ?line case ets:info(T,heir) of
- none ->
- ?line true = (Heir =:= none) orelse (not is_process_alive(Heir)),
- Master ! {"No heir",self()};
-
- Heir ->
- ?line true = is_process_alive(Heir),
- Heir ! {table,T,HeirData},
- die_please = receive_any()
- end.
+ Self = ets:info(T,owner),
+ case ets:info(T,heir) of
+ none ->
+ true = (Heir =:= none) orelse (not is_process_alive(Heir)),
+ Master ! {"No heir",self()};
+
+ Heir ->
+ true = is_process_alive(Heir),
+ Heir ! {table,T,HeirData},
+ die_please = receive_any()
+ end.
heir_heir(Founder) ->
heir_heir(Founder, none).
heir_heir(Founder, Mode) ->
- ?line {table,T,HeirData} = receive_any(),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
- ?line case HeirData of
- "The dying heir" -> exit(normal);
- _ -> ok
- end,
+ {table,T,HeirData} = receive_any(),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
+ case HeirData of
+ "The dying heir" -> exit(normal);
+ _ -> ok
+ end,
- ?line Mref = case Mode of
- link -> process_flag(trap_exit, true),
- link(Founder);
- monitor -> erlang:monitor(process,Founder);
- none -> ok
- end,
- ?line Founder ! die_please,
- ?line Msg = case HeirData of
- "The busy heir" -> receive_any_spinning();
- _ -> receive_any()
- end,
- ?line {'ETS-TRANSFER', T, Founder, HeirData} = Msg,
- ?line foo = T,
- ?line Self = self(),
- ?line Self = ets:info(T,owner),
- ?line Self = ets:info(T,heir),
- ?line [{key,1}] = ets:lookup(T,key),
- ?line true = ets:insert(T,{key,2}),
- ?line [{key,2}] = ets:lookup(T,key),
- ?line case Mode of % Verify that EXIT or DOWN comes after ETS-TRANSFER
- link ->
- {'EXIT',Founder,normal} = receive_any(),
- process_flag(trap_exit, false);
- monitor ->
- {'DOWN', Mref, process, Founder, normal} = receive_any();
- none -> ok
- end.
+ Mref = case Mode of
+ link -> process_flag(trap_exit, true),
+ link(Founder);
+ monitor -> erlang:monitor(process,Founder);
+ none -> ok
+ end,
+ Founder ! die_please,
+ Msg = case HeirData of
+ "The busy heir" -> receive_any_spinning();
+ _ -> receive_any()
+ end,
+ {'ETS-TRANSFER', T, Founder, HeirData} = Msg,
+ foo = T,
+ Self = self(),
+ Self = ets:info(T,owner),
+ Self = ets:info(T,heir),
+ [{key,1}] = ets:lookup(T,key),
+ true = ets:insert(T,{key,2}),
+ [{key,2}] = ets:lookup(T,key),
+ case Mode of % Verify that EXIT or DOWN comes after ETS-TRANSFER
+ link ->
+ {'EXIT',Founder,normal} = receive_any(),
+ process_flag(trap_exit, false);
+ monitor ->
+ {'DOWN', Mref, process, Founder, normal} = receive_any();
+ none -> ok
+ end.
heir_1(HeirData,Mode,Opts) ->
io:format("test with heir_data = ~p\n", [HeirData]),
Master = self(),
- ?line Founder = my_spawn_link(fun() -> heir_founder(Master,HeirData,Opts) end),
+ Founder = my_spawn_link(fun() -> heir_founder(Master,HeirData,Opts) end),
io:format("founder spawned = ~p\n", [Founder]),
- ?line {Heir,Mref} = my_spawn_monitor(fun() -> heir_heir(Founder,Mode) end),
+ {Heir,Mref} = my_spawn_monitor(fun() -> heir_heir(Founder,Mode) end),
io:format("heir spawned = ~p\n", [{Heir,Mref}]),
- ?line Founder ! {go, Heir},
- ?line {'DOWN', Mref, process, Heir, normal} = receive_any().
+ Founder ! {go, Heir},
+ {'DOWN', Mref, process, Heir, normal} = receive_any().
%% Test ets:give_way/3.
give_away(Config) when is_list(Config) ->
repeat_for_opts(give_away_do).
give_away_do(Opts) ->
- ?line T = ets_new(foo,[named_table, private | Opts]),
- ?line true = ets:insert(T,{key,1}),
- ?line [{key,1}] = ets:lookup(T,key),
+ T = ets_new(foo,[named_table, private | Opts]),
+ true = ets:insert(T,{key,1}),
+ [{key,1}] = ets:lookup(T,key),
Parent = self(),
%% Give and then give back
- ?line {Receiver,Mref} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
- ?line give_me = receive_any(),
- ?line true = ets:give_away(T,Receiver,here_you_are),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
- ?line Receiver ! give_back,
- ?line {'ETS-TRANSFER',T,Receiver,"Tillbakakaka"} = receive_any(),
- ?line [{key,2}] = ets:lookup(T,key),
- ?line {'DOWN', Mref, process, Receiver, normal} = receive_any(),
+ {Receiver,Mref} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
+ give_me = receive_any(),
+ true = ets:give_away(T,Receiver,here_you_are),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
+ Receiver ! give_back,
+ {'ETS-TRANSFER',T,Receiver,"Tillbakakaka"} = receive_any(),
+ [{key,2}] = ets:lookup(T,key),
+ {'DOWN', Mref, process, Receiver, normal} = receive_any(),
%% Give and then let receiver keep it
- ?line true = ets:insert(T,{key,1}),
- ?line {Receiver3,Mref3} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
- ?line give_me = receive_any(),
- ?line true = ets:give_away(T,Receiver3,here_you_are),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
- ?line Receiver3 ! die_please,
- ?line {'DOWN', Mref3, process, Receiver3, normal} = receive_any(),
- ?line undefined = ets:info(T),
+ true = ets:insert(T,{key,1}),
+ {Receiver3,Mref3} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
+ give_me = receive_any(),
+ true = ets:give_away(T,Receiver3,here_you_are),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
+ Receiver3 ! die_please,
+ {'DOWN', Mref3, process, Receiver3, normal} = receive_any(),
+ undefined = ets:info(T),
%% Give and then kill receiver to get back
- ?line T2 = ets_new(foo,[private | Opts]),
- ?line true = ets:insert(T2,{key,1}),
- ?line ets:setopts(T2,{heir,self(),"Som en gummiboll..."}),
- ?line {Receiver2,Mref2} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
- ?line give_me = receive_any(),
- ?line true = ets:give_away(T2,Receiver2,here_you_are),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T2,key)),
- ?line Receiver2 ! die_please,
- ?line {'ETS-TRANSFER',T2,Receiver2,"Som en gummiboll..."} = receive_any(),
- ?line [{key,2}] = ets:lookup(T2,key),
- ?line {'DOWN', Mref2, process, Receiver2, normal} = receive_any(),
+ T2 = ets_new(foo,[private | Opts]),
+ true = ets:insert(T2,{key,1}),
+ ets:setopts(T2,{heir,self(),"Som en gummiboll..."}),
+ {Receiver2,Mref2} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
+ give_me = receive_any(),
+ true = ets:give_away(T2,Receiver2,here_you_are),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T2,key)),
+ Receiver2 ! die_please,
+ {'ETS-TRANSFER',T2,Receiver2,"Som en gummiboll..."} = receive_any(),
+ [{key,2}] = ets:lookup(T2,key),
+ {'DOWN', Mref2, process, Receiver2, normal} = receive_any(),
%% Some negative testing
- ?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,Receiver,"To a dead one")),
- ?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,self(),"To myself")),
- ?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,"not a pid","To wrong type")),
+ {'EXIT',{badarg,_}} = (catch ets:give_away(T2,Receiver,"To a dead one")),
+ {'EXIT',{badarg,_}} = (catch ets:give_away(T2,self(),"To myself")),
+ {'EXIT',{badarg,_}} = (catch ets:give_away(T2,"not a pid","To wrong type")),
- ?line true = ets:delete(T2),
- ?line {ReceiverNeg,MrefNeg} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
- ?line give_me = receive_any(),
- ?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,ReceiverNeg,"A deleted table")),
+ true = ets:delete(T2),
+ {ReceiverNeg,MrefNeg} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
+ give_me = receive_any(),
+ {'EXIT',{badarg,_}} = (catch ets:give_away(T2,ReceiverNeg,"A deleted table")),
- ?line T3 = ets_new(foo,[public | Opts]),
+ T3 = ets_new(foo,[public | Opts]),
my_spawn_link(fun()-> {'EXIT',{badarg,_}} = (catch ets:give_away(T3,ReceiverNeg,"From non owner")),
- Parent ! done
- end),
- ?line done = receive_any(),
- ?line ReceiverNeg ! no_soup_for_you,
- ?line {'DOWN', MrefNeg, process, ReceiverNeg, normal} = receive_any(),
+ Parent ! done
+ end),
+ done = receive_any(),
+ ReceiverNeg ! no_soup_for_you,
+ {'DOWN', MrefNeg, process, ReceiverNeg, normal} = receive_any(),
ok.
give_away_receiver(T, Giver) ->
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
- ?line Giver ! give_me,
- ?line case receive_any() of
- {'ETS-TRANSFER',T,Giver,here_you_are} ->
- ?line [{key,1}] = ets:lookup(T,key),
- ?line true = ets:insert(T,{key,2}),
- ?line case receive_any() of
- give_back ->
- ?line true = ets:give_away(T,Giver,"Tillbakakaka"),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key));
- die_please ->
- ok
- end;
- no_soup_for_you ->
- ok
- end.
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
+ Giver ! give_me,
+ case receive_any() of
+ {'ETS-TRANSFER',T,Giver,here_you_are} ->
+ [{key,1}] = ets:lookup(T,key),
+ true = ets:insert(T,{key,2}),
+ case receive_any() of
+ give_back ->
+ true = ets:give_away(T,Giver,"Tillbakakaka"),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(T,key));
+ die_please ->
+ ok
+ end;
+ no_soup_for_you ->
+ ok
+ end.
%% Test ets:setopts/2.
@@ -2321,37 +2321,37 @@ setopts(Config) when is_list(Config) ->
setopts_do(Opts) ->
Self = self(),
- ?line T = ets_new(foo,[named_table, private | Opts]),
- ?line none = ets:info(T,heir),
+ T = ets_new(foo,[named_table, private | Opts]),
+ none = ets:info(T,heir),
Heir = my_spawn_link(fun()->heir_heir(Self) end),
- ?line ets:setopts(T,{heir,Heir,"Data"}),
- ?line Heir = ets:info(T,heir),
- ?line ets:setopts(T,{heir,self(),"Data"}),
- ?line Self = ets:info(T,heir),
- ?line ets:setopts(T,[{heir,Heir,"Data"}]),
- ?line Heir = ets:info(T,heir),
- ?line ets:setopts(T,[{heir,none}]),
- ?line none = ets:info(T,heir),
-
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,[{heir,self(),"Data"},false])),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,self()})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,heir)),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false,"Data"})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{false,self(),"Data"})),
-
- ?line ets:setopts(T,{protection,protected}),
- ?line ets:setopts(T,{protection,public}),
- ?line ets:setopts(T,{protection,private}),
- ?line ets:setopts(T,[{protection,protected}]),
- ?line ets:setopts(T,[{protection,public}]),
- ?line ets:setopts(T,[{protection,private}]),
-
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,false})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,private,false})),
- ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,protection)),
- ?line ets:delete(T),
+ ets:setopts(T,{heir,Heir,"Data"}),
+ Heir = ets:info(T,heir),
+ ets:setopts(T,{heir,self(),"Data"}),
+ Self = ets:info(T,heir),
+ ets:setopts(T,[{heir,Heir,"Data"}]),
+ Heir = ets:info(T,heir),
+ ets:setopts(T,[{heir,none}]),
+ none = ets:info(T,heir),
+
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,[{heir,self(),"Data"},false])),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,self()})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,heir)),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false,"Data"})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{false,self(),"Data"})),
+
+ ets:setopts(T,{protection,protected}),
+ ets:setopts(T,{protection,public}),
+ ets:setopts(T,{protection,private}),
+ ets:setopts(T,[{protection,protected}]),
+ ets:setopts(T,[{protection,public}]),
+ ets:setopts(T,[{protection,private}]),
+
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,false})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,private,false})),
+ {'EXIT',{badarg,_}} = (catch ets:setopts(T,protection)),
+ ets:delete(T),
unlink(Heir),
exit(Heir, bang),
ok.
@@ -2361,16 +2361,16 @@ bad_table(Config) when is_list(Config) ->
%% Open and close disk_log to stabilize etsmem.
Name = make_ref(),
- ?line File = filename:join([?config(priv_dir, Config),"bad_table.dummy"]),
- ?line {ok, Name} = disk_log:open([{name, Name}, {file, File}]),
- ?line disk_log:close(Name),
+ File = filename:join([?config(priv_dir, Config),"bad_table.dummy"]),
+ {ok, Name} = disk_log:open([{name, Name}, {file, File}]),
+ disk_log:close(Name),
file:delete(File),
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(fun(Opts) -> bad_table_do(Opts,File) end,
[write_concurrency, all_types]),
- ?line verify_etsmem(EtsMem),
+ verify_etsmem(EtsMem),
ok.
bad_table_do(Opts, DummyFile) ->
@@ -2454,12 +2454,12 @@ bad_table_op({Opts,Priv,Prot}, Op) ->
end.
bad_table_call(T,{F,Args,_}) ->
- ?line {'EXIT',{badarg,_}} = (catch apply(ets, F, [T|Args]));
+ {'EXIT',{badarg,_}} = (catch apply(ets, F, [T|Args]));
bad_table_call(T,{F,Args,_,tabarg_last}) ->
- ?line {'EXIT',{badarg,_}} = (catch apply(ets, F, Args++[T]));
+ {'EXIT',{badarg,_}} = (catch apply(ets, F, Args++[T]));
bad_table_call(T,{F,Args,_,{return,Return}}) ->
try
- ?line Return = apply(ets, F, [T|Args])
+ Return = apply(ets, F, [T|Args])
catch
error:badarg -> ok
end.
@@ -2470,7 +2470,7 @@ rename(Config) when is_list(Config) ->
repeat_for_opts(rename_do, [write_concurrency, all_types]).
rename_do(Opts) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
ets_new(foobazz,[named_table, public | Opts]),
ets:insert(foobazz,{foo,bazz}),
ungermanbazz = ets:rename(foobazz,ungermanbazz),
@@ -2478,38 +2478,38 @@ rename_do(Opts) ->
[{foo,bazz}] = ets:lookup(ungermanbazz,foo),
{'EXIT',{badarg,_}} = (catch ets:rename(ungermanbazz,"no atom")),
ets:delete(ungermanbazz),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% Check rename of unnamed ets table.
rename_unnamed(Config) when is_list(Config) ->
repeat_for_opts(rename_unnamed_do,[write_concurrency,all_types]).
rename_unnamed_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(bonkz,[public | Opts]),
- ?line {'EXIT',{badarg, _}} = (catch ets:insert(bonkz,{foo,bazz})),
- ?line bonkz = ets:info(Tab, name),
- ?line Tab = ets:rename(Tab, tjabonkz),
- ?line {'EXIT',{badarg, _}} = (catch ets:insert(tjabonkz,{foo,bazz})),
- ?line tjabonkz = ets:info(Tab, name),
- ?line ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(bonkz,[public | Opts]),
+ {'EXIT',{badarg, _}} = (catch ets:insert(bonkz,{foo,bazz})),
+ bonkz = ets:info(Tab, name),
+ Tab = ets:rename(Tab, tjabonkz),
+ {'EXIT',{badarg, _}} = (catch ets:insert(tjabonkz,{foo,bazz})),
+ tjabonkz = ets:info(Tab, name),
+ ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Rename a table with many fixations, and at the same time delete it.
evil_rename(Config) when is_list(Config) ->
- ?line evil_rename_1(old_hash, new_hash, [public,named_table]),
- ?line EtsMem = etsmem(),
- ?line evil_rename_1(old_tree, new_tree, [public,ordered_set,named_table]),
- ?line verify_etsmem(EtsMem).
+ evil_rename_1(old_hash, new_hash, [public,named_table]),
+ EtsMem = etsmem(),
+ evil_rename_1(old_tree, new_tree, [public,ordered_set,named_table]),
+ verify_etsmem(EtsMem).
evil_rename_1(Old, New, Flags) ->
- ?line process_flag(trap_exit, true),
- ?line Old = ets_new(Old, Flags),
- ?line Fixer = fun() -> ets:safe_fixtable(Old, true) end,
- ?line crazy_fixtable(15000, Fixer),
- ?line erlang:yield(),
- ?line New = ets:rename(Old, New),
- ?line erlang:yield(),
+ process_flag(trap_exit, true),
+ Old = ets_new(Old, Flags),
+ Fixer = fun() -> ets:safe_fixtable(Old, true) end,
+ crazy_fixtable(15000, Fixer),
+ erlang:yield(),
+ New = ets:rename(Old, New),
+ erlang:yield(),
ets:delete(New),
ok.
@@ -2558,10 +2558,10 @@ interface_equality(Config) when is_list(Config) ->
repeat_for_opts(interface_equality_do).
interface_equality_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Set = ets_new(set,[set | Opts]),
- ?line OrderedSet = ets_new(ordered_set,[ordered_set | Opts]),
- ?line F = fun(X,T,FF) -> case X of
+ EtsMem = etsmem(),
+ Set = ets_new(set,[set | Opts]),
+ OrderedSet = ets_new(ordered_set,[ordered_set | Opts]),
+ F = fun(X,T,FF) -> case X of
0 -> true;
_ ->
ets:insert(T, {X,
@@ -2570,38 +2570,38 @@ interface_equality_do(Opts) ->
FF(X-1,T,FF)
end
end,
- ?line F(100,Set,F),
- ?line F(100,OrderedSet,F),
- ?line equal_results(ets, insert, Set, OrderedSet, [{a,"a"}]),
- ?line equal_results(ets, insert, Set, OrderedSet, [{1,1,"1"}]),
- ?line equal_results(ets, lookup, Set, OrderedSet, [10]),
- ?line equal_results(ets, lookup, Set, OrderedSet, [1000]),
- ?line equal_results(ets, delete, Set, OrderedSet, [10]),
- ?line equal_results(ets, delete, Set, OrderedSet, [nott]),
- ?line equal_results(ets, lookup, Set, OrderedSet, [1000]),
- ?line equal_results(ets, insert, Set, OrderedSet, [10]),
- ?line equal_results(ets, next, Set, OrderedSet, ['$end_of_table']),
- ?line equal_results(ets, prev, Set, OrderedSet, ['$end_of_table']),
- ?line equal_results(ets, match, Set, OrderedSet, [{'_','_','_'}]),
- ?line equal_results(ets, match, Set, OrderedSet, [{'_','_','_','_'}]),
- ?line equal_results(ets, match, Set, OrderedSet, [{$3,$2,2}]),
- ?line equal_results(ets, match, Set, OrderedSet, ['_']),
- ?line equal_results(ets, match, Set, OrderedSet, ['$1']),
- ?line equal_results(ets, match, Set, OrderedSet, [{'_','$50',3}]),
- ?line equal_results(ets, match, Set, OrderedSet, [['_','$50',3]]),
- ?line equal_results(ets, match_delete, Set, OrderedSet, [{'_','_',4}]),
- ?line equal_results(ets, match_delete, Set, OrderedSet, [{'_','_',4}]),
- ?line equal_results(ets, match_object, Set, OrderedSet, [{'_','_',4}]),
- ?line equal_results(ets, match_object, Set, OrderedSet, [{'_','_',5}]),
- ?line equal_results(ets, match_object, Set, OrderedSet, [{'_','_',4}]),
- ?line equal_results(ets, match_object, Set, OrderedSet, ['_']),
- ?line equal_results(ets, match_object, Set, OrderedSet, ['$5011']),
- ?line equal_results(ets, match_delete, Set, OrderedSet, ['$20']),
- ?line equal_results(ets, lookup_element, Set, OrderedSet, [13,2]),
- ?line equal_results(ets, lookup_element, Set, OrderedSet, [13,4]),
- ?line equal_results(ets, lookup_element, Set, OrderedSet, [14,2]),
- ?line equal_results(ets, delete, Set, OrderedSet, []),
- ?line verify_etsmem(EtsMem).
+ F(100,Set,F),
+ F(100,OrderedSet,F),
+ equal_results(ets, insert, Set, OrderedSet, [{a,"a"}]),
+ equal_results(ets, insert, Set, OrderedSet, [{1,1,"1"}]),
+ equal_results(ets, lookup, Set, OrderedSet, [10]),
+ equal_results(ets, lookup, Set, OrderedSet, [1000]),
+ equal_results(ets, delete, Set, OrderedSet, [10]),
+ equal_results(ets, delete, Set, OrderedSet, [nott]),
+ equal_results(ets, lookup, Set, OrderedSet, [1000]),
+ equal_results(ets, insert, Set, OrderedSet, [10]),
+ equal_results(ets, next, Set, OrderedSet, ['$end_of_table']),
+ equal_results(ets, prev, Set, OrderedSet, ['$end_of_table']),
+ equal_results(ets, match, Set, OrderedSet, [{'_','_','_'}]),
+ equal_results(ets, match, Set, OrderedSet, [{'_','_','_','_'}]),
+ equal_results(ets, match, Set, OrderedSet, [{$3,$2,2}]),
+ equal_results(ets, match, Set, OrderedSet, ['_']),
+ equal_results(ets, match, Set, OrderedSet, ['$1']),
+ equal_results(ets, match, Set, OrderedSet, [{'_','$50',3}]),
+ equal_results(ets, match, Set, OrderedSet, [['_','$50',3]]),
+ equal_results(ets, match_delete, Set, OrderedSet, [{'_','_',4}]),
+ equal_results(ets, match_delete, Set, OrderedSet, [{'_','_',4}]),
+ equal_results(ets, match_object, Set, OrderedSet, [{'_','_',4}]),
+ equal_results(ets, match_object, Set, OrderedSet, [{'_','_',5}]),
+ equal_results(ets, match_object, Set, OrderedSet, [{'_','_',4}]),
+ equal_results(ets, match_object, Set, OrderedSet, ['_']),
+ equal_results(ets, match_object, Set, OrderedSet, ['$5011']),
+ equal_results(ets, match_delete, Set, OrderedSet, ['$20']),
+ equal_results(ets, lookup_element, Set, OrderedSet, [13,2]),
+ equal_results(ets, lookup_element, Set, OrderedSet, [13,4]),
+ equal_results(ets, lookup_element, Set, OrderedSet, [14,2]),
+ equal_results(ets, delete, Set, OrderedSet, []),
+ verify_etsmem(EtsMem).
equal_results(M, F, FirstArg1, FirstArg2 ,ACommon) ->
Res = maybe_sort((catch apply(M,F, [FirstArg1 | ACommon]))),
@@ -2622,22 +2622,22 @@ ordered_match(Config) when is_list(Config)->
repeat_for_opts(ordered_match_do).
ordered_match_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line F = fun(X,T,FF) -> case X of
- 0 -> true;
- _ ->
- ets:insert(T, {X,
- integer_to_list(X),
- X rem 10,
- X rem 100,
- X rem 1000}),
- FF(X-1,T,FF)
- end
+ EtsMem = etsmem(),
+ F = fun(X,T,FF) -> case X of
+ 0 -> true;
+ _ ->
+ ets:insert(T, {X,
+ integer_to_list(X),
+ X rem 10,
+ X rem 100,
+ X rem 1000}),
+ FF(X-1,T,FF)
+ end
end,
- ?line T1 = ets_new(xxx,[ordered_set| Opts]),
- ?line F(3000,T1,F),
- ?line [[3,3],[3,3],[3,3]] = ets:match(T1, {'_','_','$1','$2',3}),
- ?line F2 = fun(X,Rem,Res,FF) -> case X of
+ T1 = ets_new(xxx,[ordered_set| Opts]),
+ F(3000,T1,F),
+ [[3,3],[3,3],[3,3]] = ets:match(T1, {'_','_','$1','$2',3}),
+ F2 = fun(X,Rem,Res,FF) -> case X of
0 -> [];
_ ->
case X rem Rem of
@@ -2653,140 +2653,140 @@ ordered_match_do(Opts) ->
end
end
end,
- ?line OL1 = F2(3000,100,2,F2),
- ?line OL1 = ets:match_object(T1, {'_','_','_',2,'_'}),
- ?line true = ets:match_delete(T1,{'_','_','_',2,'_'}),
- ?line [] = ets:match_object(T1, {'_','_','_',2,'_'}),
- ?line OL2 = F2(3000,100,3,F2),
- ?line OL2 = ets:match_object(T1, {'_','_','_',3,'_'}),
- ?line ets:delete(T1),
- ?line verify_etsmem(EtsMem).
-
+ OL1 = F2(3000,100,2,F2),
+ OL1 = ets:match_object(T1, {'_','_','_',2,'_'}),
+ true = ets:match_delete(T1,{'_','_','_',2,'_'}),
+ [] = ets:match_object(T1, {'_','_','_',2,'_'}),
+ OL2 = F2(3000,100,3,F2),
+ OL2 = ets:match_object(T1, {'_','_','_',3,'_'}),
+ ets:delete(T1),
+ verify_etsmem(EtsMem).
+
%% Test basic functionality in ordered_set's.
ordered(Config) when is_list(Config) ->
repeat_for_opts(ordered_do).
ordered_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line T = ets_new(oset, [ordered_set | Opts]),
- ?line InsList = [
- 25,26,27,28,
- 5,6,7,8,
- 21,22,23,24,
- 9,10,11,12,
- 1,2,3,4,
- 17,18,19,20,
- 13,14,15,16,
- 1 bsl 33
- ],
- ?line lists:foreach(fun(X) ->
+ EtsMem = etsmem(),
+ T = ets_new(oset, [ordered_set | Opts]),
+ InsList = [
+ 25,26,27,28,
+ 5,6,7,8,
+ 21,22,23,24,
+ 9,10,11,12,
+ 1,2,3,4,
+ 17,18,19,20,
+ 13,14,15,16,
+ 1 bsl 33
+ ],
+ lists:foreach(fun(X) ->
ets:insert(T,{X,integer_to_list(X)})
end,
InsList),
- ?line IL2 = lists:map(fun(X) -> {X,integer_to_list(X)} end, InsList),
- ?line L1 = pick_all_forward(T),
- ?line L2 = pick_all_backwards(T),
- ?line S1 = lists:sort(IL2),
- ?line S2 = lists:reverse(lists:sort(IL2)),
- ?line S1 = L1,
- ?line S2 = L2,
- ?line [{1,"1"}] = ets:slot(T,0),
- ?line [{28,"28"}] = ets:slot(T,27),
- ?line [{1 bsl 33,_}] = ets:slot(T,28),
- ?line 27 = ets:prev(T,28),
- ?line [{7,"7"}] = ets:slot(T,6),
- ?line '$end_of_table' = ets:next(T,1 bsl 33),
- ?line [{12,"12"}] = ets:slot(T,11),
- ?line '$end_of_table' = ets:slot(T,29),
- ?line [{1,"1"}] = ets:slot(T,0),
- ?line 28 = ets:prev(T,1 bsl 33),
- ?line 1 = ets:next(T,0),
- ?line pick_all_forward(T),
- ?line [{7,"7"}] = ets:slot(T,6),
- ?line L2 = pick_all_backwards(T),
- ?line [{7,"7"}] = ets:slot(T,6),
- ?line ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ IL2 = lists:map(fun(X) -> {X,integer_to_list(X)} end, InsList),
+ L1 = pick_all_forward(T),
+ L2 = pick_all_backwards(T),
+ S1 = lists:sort(IL2),
+ S2 = lists:reverse(lists:sort(IL2)),
+ S1 = L1,
+ S2 = L2,
+ [{1,"1"}] = ets:slot(T,0),
+ [{28,"28"}] = ets:slot(T,27),
+ [{1 bsl 33,_}] = ets:slot(T,28),
+ 27 = ets:prev(T,28),
+ [{7,"7"}] = ets:slot(T,6),
+ '$end_of_table' = ets:next(T,1 bsl 33),
+ [{12,"12"}] = ets:slot(T,11),
+ '$end_of_table' = ets:slot(T,29),
+ [{1,"1"}] = ets:slot(T,0),
+ 28 = ets:prev(T,1 bsl 33),
+ 1 = ets:next(T,0),
+ pick_all_forward(T),
+ [{7,"7"}] = ets:slot(T,6),
+ L2 = pick_all_backwards(T),
+ [{7,"7"}] = ets:slot(T,6),
+ ets:delete(T),
+ verify_etsmem(EtsMem).
pick_all(_T,'$end_of_table',_How) ->
[];
pick_all(T,Last,How) ->
- ?line This = case How of
+ This = case How of
next ->
- ?line ets:next(T,Last);
+ ets:next(T,Last);
prev ->
- ?line ets:prev(T,Last)
+ ets:prev(T,Last)
end,
- ?line [LastObj] = ets:lookup(T,Last),
- ?line [LastObj | pick_all(T,This,How)].
+ [LastObj] = ets:lookup(T,Last),
+ [LastObj | pick_all(T,This,How)].
pick_all_forward(T) ->
- ?line pick_all(T,ets:first(T),next).
+ pick_all(T,ets:first(T),next).
pick_all_backwards(T) ->
- ?line pick_all(T,ets:last(T),prev).
-
-
+ pick_all(T,ets:last(T),prev).
+
+
%% Small test case for both set and bag type ets tables.
setbag(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Set = ets_new(set,[set]),
- ?line Bag = ets_new(bag,[bag]),
- ?line Key = {foo,bar},
-
+ EtsMem = etsmem(),
+ Set = ets_new(set,[set]),
+ Bag = ets_new(bag,[bag]),
+ Key = {foo,bar},
+
%% insert some value
- ?line ets:insert(Set,{Key,val1}),
- ?line ets:insert(Bag,{Key,val1}),
-
+ ets:insert(Set,{Key,val1}),
+ ets:insert(Bag,{Key,val1}),
+
%% insert new value for same key again
- ?line ets:insert(Set,{Key,val2}),
- ?line ets:insert(Bag,{Key,val2}),
-
+ ets:insert(Set,{Key,val2}),
+ ets:insert(Bag,{Key,val2}),
+
%% check
- ?line [{Key,val2}] = ets:lookup(Set,Key),
- ?line [{Key,val1},{Key,val2}] = ets:lookup(Bag,Key),
+ [{Key,val2}] = ets:lookup(Set,Key),
+ [{Key,val1},{Key,val2}] = ets:lookup(Bag,Key),
true = ets:delete(Set),
true = ets:delete(Bag),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% Test case to check proper return values for illegal ets_new() calls.
badnew(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(12,[])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(name,bag)),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ {'EXIT',{badarg,_}} = (catch ets_new(12,[])),
+ {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])),
+ {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])),
+ {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})),
+ {'EXIT',{badarg,_}} = (catch ets_new(name,bag)),
+ verify_etsmem(EtsMem).
%% OTP-2314. Test case to check that a non-proper list does not
%% crash the emulator.
verybadnew(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])),
+ verify_etsmem(EtsMem).
%% Small check to see if named tables work.
named(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Tab = make_table(foo,
- [named_table],
- [{key,val}]),
- ?line [{key,val}] = ets:lookup(foo,key),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = make_table(foo,
+ [named_table],
+ [{key,val}]),
+ [{key,val}] = ets:lookup(foo,key),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Test case to check if specified keypos works.
keypos2(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Tab = make_table(foo,
- [set,{keypos,2}],
- [{val,key}, {val2,key}]),
- ?line [{val2,key}] = ets:lookup(Tab,key),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = make_table(foo,
+ [set,{keypos,2}],
+ [{val,key}, {val2,key}]),
+ [{val2,key}] = ets:lookup(Tab,key),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Privacy check. Check that a named(public/private/protected) table
%% cannot be read by the wrong process(es).
@@ -2794,12 +2794,12 @@ privacy(Config) when is_list(Config) ->
repeat_for_opts(privacy_do).
privacy_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line process_flag(trap_exit,true),
- ?line Owner = my_spawn_link(?MODULE,privacy_owner,[self(),Opts]),
+ EtsMem = etsmem(),
+ process_flag(trap_exit,true),
+ Owner = my_spawn_link(?MODULE,privacy_owner,[self(),Opts]),
receive
{'EXIT',Owner,Reason} ->
- ?line exit({privacy_test,Reason});
+ exit({privacy_test,Reason});
ok ->
ok
end,
@@ -2820,21 +2820,21 @@ privacy_do(Opts) ->
Owner ! die,
receive {'EXIT',Owner,_} -> ok end,
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
privacy_check(Pub,Prot,Priv) ->
%% check read rights
- ?line [] = ets:lookup(Pub, foo),
- ?line [] = ets:lookup(Prot,foo),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(Priv,foo)),
+ [] = ets:lookup(Pub, foo),
+ [] = ets:lookup(Prot,foo),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(Priv,foo)),
%% check write rights
- ?line true = ets:insert(Pub, {1,foo}),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(Prot,{2,foo})),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(Priv,{3,foo})),
+ true = ets:insert(Pub, {1,foo}),
+ {'EXIT',{badarg,_}} = (catch ets:insert(Prot,{2,foo})),
+ {'EXIT',{badarg,_}} = (catch ets:insert(Priv,{3,foo})),
%% check that it really wasn't written, either
- ?line [] = ets:lookup(Prot,foo).
+ [] = ets:lookup(Prot,foo).
privacy_owner(Boss, Opts) ->
ets_new(pub, [public,named_table | Opts]),
@@ -2847,7 +2847,7 @@ privacy_owner_loop(Boss) ->
receive
{shift,N,Pub_Prot_Priv} ->
{Pub,Prot,Priv} = rotate_tuple(Pub_Prot_Priv, N),
-
+
ets:setopts(Pub,{protection,public}),
ets:setopts(Prot,{protection,protected}),
ets:setopts(Priv,{protection,private}),
@@ -2872,32 +2872,32 @@ empty(Config) when is_list(Config) ->
repeat_for_opts(empty_do).
empty_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line [] = ets:lookup(Tab,key),
- ?line true = ets:insert(Tab,{key2,val}),
- ?line [] = ets:lookup(Tab,key),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ [] = ets:lookup(Tab,key),
+ true = ets:insert(Tab,{key2,val}),
+ [] = ets:lookup(Tab,key),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Check proper return values for illegal insert operations.
badinsert(Config) when is_list(Config) ->
repeat_for_opts(badinsert_do).
badinsert_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(foo,{key,val})),
-
- ?line Tab = ets_new(foo,Opts),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,{})),
+ EtsMem = etsmem(),
+ {'EXIT',{badarg,_}} = (catch ets:insert(foo,{key,val})),
- ?line Tab3 = ets_new(foo,[{keypos,3}| Opts]),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab3,{a,b})),
+ Tab = ets_new(foo,Opts),
+ {'EXIT',{badarg,_}} = (catch ets:insert(Tab,{})),
- ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,[key,val2])),
- ?line true = ets:delete(Tab),
- ?line true = ets:delete(Tab3),
- ?line verify_etsmem(EtsMem).
+ Tab3 = ets_new(foo,[{keypos,3}| Opts]),
+ {'EXIT',{badarg,_}} = (catch ets:insert(Tab3,{a,b})),
+
+ {'EXIT',{badarg,_}} = (catch ets:insert(Tab,[key,val2])),
+ true = ets:delete(Tab),
+ true = ets:delete(Tab3),
+ verify_etsmem(EtsMem).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -2905,11 +2905,11 @@ badinsert_do(Opts) ->
%% Test lookup timing.
time_lookup(Config) when is_list(Config) ->
%% just for timing, really
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
Values = repeat_for_opts(time_lookup_do),
- ?line verify_etsmem(EtsMem),
- ?line {comment,lists:flatten(io_lib:format(
- "~p ets lookups/s",[Values]))}.
+ verify_etsmem(EtsMem),
+ {comment,lists:flatten(io_lib:format(
+ "~p ets lookups/s",[Values]))}.
time_lookup_do(Opts) ->
Tab = ets_new(foo,Opts),
@@ -2930,18 +2930,18 @@ time_lookup_many(N, Tab) ->
%% Check proper return values from bad lookups in existing/non existing
%% ets tables.
badlookup(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(foo,key)),
- ?line Tab = ets_new(foo,[]),
- ?line ets:delete(Tab),
- ?line {'EXIT',{badarg,_}} = (catch ets:lookup(Tab,key)),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(foo,key)),
+ Tab = ets_new(foo,[]),
+ ets:delete(Tab),
+ {'EXIT',{badarg,_}} = (catch ets:lookup(Tab,key)),
+ verify_etsmem(EtsMem).
%% Test that lookup returns objects in order of insertion for bag and dbag.
lookup_order(Config) when is_list(Config) ->
EtsMem = etsmem(),
repeat_for_opts(lookup_order_do, [write_concurrency,[bag,duplicate_bag]]),
- ?line verify_etsmem(EtsMem),
+ verify_etsmem(EtsMem),
ok.
lookup_order_do(Opts) ->
@@ -2978,7 +2978,7 @@ lookup_order_2(Opts, Fixed) ->
true = ets:delete(T)
end,
Combos).
-
+
check_insert({T,List0,Key},Val) ->
%%io:format("insert ~p into ~p\n",[Val,List0]),
@@ -2993,7 +2993,7 @@ check_insert({T,List0,Key},Val) ->
check_insert_new({T,List0,Key},Val) ->
%%io:format("insert_new ~p into ~p\n",[Val,List0]),
Ret = ets:insert_new(T,{Key,Val}),
- ?line Ret = (List0 =:= []),
+ Ret = (List0 =:= []),
List1 = case Ret of
true -> [{Key,Val}];
false -> List0
@@ -3014,17 +3014,17 @@ check_check(S={T,List,Key}) ->
ETS -> io:format("check failed:\nETS: ~p\nCHK: ~p\n", [ETS,List]),
ct:fail("Invalid return value from ets:lookup")
end,
- ?line Items = ets:info(T,size),
- ?line Items = length(List),
+ Items = ets:info(T,size),
+ Items = length(List),
S.
-
+
fill_tab(Tab,Val) ->
- ?line ets:insert(Tab,{key,Val}),
- ?line ets:insert(Tab,{{a,144},Val}),
- ?line ets:insert(Tab,{{a,key2},Val}),
- ?line ets:insert(Tab,{14,Val}),
+ ets:insert(Tab,{key,Val}),
+ ets:insert(Tab,{{a,144},Val}),
+ ets:insert(Tab,{{a,key2},Val}),
+ ets:insert(Tab,{14,Val}),
ok.
@@ -3036,15 +3036,15 @@ lookup_element_mult(Config) when is_list(Config) ->
repeat_for_opts(lookup_element_mult_do).
lookup_element_mult_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line T = ets_new(service, [bag, {keypos, 2} | Opts]),
- ?line D = lists:reverse(lem_data()),
- ?line lists:foreach(fun(X) -> ets:insert(T, X) end, D),
- ?line ok = lem_crash_3(T),
- ?line ets:insert(T, {0, "heap_key"}),
- ?line ets:lookup_element(T, "heap_key", 2),
- ?line true = ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ T = ets_new(service, [bag, {keypos, 2} | Opts]),
+ D = lists:reverse(lem_data()),
+ lists:foreach(fun(X) -> ets:insert(T, X) end, D),
+ ok = lem_crash_3(T),
+ ets:insert(T, {0, "heap_key"}),
+ ets:lookup_element(T, "heap_key", 2),
+ true = ets:delete(T),
+ verify_etsmem(EtsMem).
lem_data() ->
[
@@ -3076,17 +3076,17 @@ delete_elem(Config) when is_list(Config) ->
repeat_for_opts(delete_elem_do, [write_concurrency, all_types]).
delete_elem_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line fill_tab(Tab,foo),
- ?line ets:insert(Tab,{{b,key},foo}),
- ?line ets:insert(Tab,{{c,key},foo}),
- ?line true = ets:delete(Tab,{b,key}),
- ?line [] = ets:lookup(Tab,{b,key}),
- ?line [{{c,key},foo}] = ets:lookup(Tab,{c,key}),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
-
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ fill_tab(Tab,foo),
+ ets:insert(Tab,{{b,key},foo}),
+ ets:insert(Tab,{{c,key},foo}),
+ true = ets:delete(Tab,{b,key}),
+ [] = ets:lookup(Tab,{b,key}),
+ [{{c,key},foo}] = ets:lookup(Tab,{c,key}),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
+
%% Check that ets:delete() works and releases the name of the
%% deleted table.
delete_tab(Config) when is_list(Config) ->
@@ -3094,41 +3094,41 @@ delete_tab(Config) when is_list(Config) ->
delete_tab_do(Opts) ->
Name = foo,
- ?line EtsMem = etsmem(),
- ?line Name = ets_new(Name, [named_table | Opts]),
- ?line true = ets:delete(foo),
+ EtsMem = etsmem(),
+ Name = ets_new(Name, [named_table | Opts]),
+ true = ets:delete(foo),
%% The name should be available again.
- ?line Name = ets_new(Name, [named_table | Opts]),
- ?line true = ets:delete(Name),
- ?line verify_etsmem(EtsMem).
+ Name = ets_new(Name, [named_table | Opts]),
+ true = ets:delete(Name),
+ verify_etsmem(EtsMem).
%% Check that ets:delete/1 works and that other processes can run.
delete_large_tab(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
- ?line EtsMem = etsmem(),
+ Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
+ EtsMem = etsmem(),
repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
delete_large_tab_do(Opts,Data) ->
- ?line delete_large_tab_1(foo_hash, Opts, Data, false),
- ?line delete_large_tab_1(foo_tree, [ordered_set | Opts], Data, false),
- ?line delete_large_tab_1(foo_hash, Opts, Data, true).
+ delete_large_tab_1(foo_hash, Opts, Data, false),
+ delete_large_tab_1(foo_tree, [ordered_set | Opts], Data, false),
+ delete_large_tab_1(foo_hash, Opts, Data, true).
delete_large_tab_1(Name, Flags, Data, Fix) ->
- ?line Tab = ets_new(Name, Flags),
- ?line ets:insert(Tab, Data),
+ Tab = ets_new(Name, Flags),
+ ets:insert(Tab, Data),
case Fix of
false -> ok;
true ->
- ?line true = ets:safe_fixtable(Tab, true),
- ?line lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
+ true = ets:safe_fixtable(Tab, true),
+ lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
end,
{priority, Prio} = process_info(self(), priority),
- ?line Deleter = self(),
- ?line [SchedTracer]
+ Deleter = self(),
+ [SchedTracer]
= start_loopers(1,
Prio,
fun (SC) ->
@@ -3148,59 +3148,59 @@ delete_large_tab_1(Name, Flags, Data, Fix) ->
end,
0),
SchedTracerMon = monitor(process, SchedTracer),
- ?line Loopers = start_loopers(erlang:system_info(schedulers),
- Prio,
- fun (_) -> erlang:yield() end,
- ok),
- ?line erlang:yield(),
- ?line 1 = erlang:trace(self(),true,[running,procs,{tracer,SchedTracer}]),
- ?line true = ets:delete(Tab),
+ Loopers = start_loopers(erlang:system_info(schedulers),
+ Prio,
+ fun (_) -> erlang:yield() end,
+ ok),
+ erlang:yield(),
+ 1 = erlang:trace(self(),true,[running,procs,{tracer,SchedTracer}]),
+ true = ets:delete(Tab),
%% The register stuff is just a trace marker
- ?line true = register(delete_large_tab_done_marker, self()),
- ?line true = unregister(delete_large_tab_done_marker),
- ?line undefined = ets:info(Tab),
- ?line ok = stop_loopers(Loopers),
- ?line receive
- {schedule_count, N} ->
- ?line io:format("~s: context switches: ~p", [Name,N]),
- if
- N >= 5 -> ?line ok;
- true -> ct:fail(failed)
- end
- end,
+ true = register(delete_large_tab_done_marker, self()),
+ true = unregister(delete_large_tab_done_marker),
+ undefined = ets:info(Tab),
+ ok = stop_loopers(Loopers),
+ receive
+ {schedule_count, N} ->
+ io:format("~s: context switches: ~p", [Name,N]),
+ if
+ N >= 5 -> ok;
+ true -> ct:fail(failed)
+ end
+ end,
receive {'DOWN',SchedTracerMon,process,SchedTracer,_} -> ok end,
ok.
%% Delete a large name table and try to create a new table with
%% the same name in another process.
delete_large_named_table(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
- ?line EtsMem = etsmem(),
+ Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
+ EtsMem = etsmem(),
repeat_for_opts(fun(Opts) -> delete_large_named_table_do(Opts,Data) end),
- ?line verify_etsmem(EtsMem),
+ verify_etsmem(EtsMem),
ok.
delete_large_named_table_do(Opts,Data) ->
- ?line delete_large_named_table_1(foo_hash, [named_table | Opts], Data, false),
- ?line delete_large_named_table_1(foo_tree, [ordered_set,named_table | Opts], Data, false),
- ?line delete_large_named_table_1(foo_hash, [named_table | Opts], Data, true).
+ delete_large_named_table_1(foo_hash, [named_table | Opts], Data, false),
+ delete_large_named_table_1(foo_tree, [ordered_set,named_table | Opts], Data, false),
+ delete_large_named_table_1(foo_hash, [named_table | Opts], Data, true).
delete_large_named_table_1(Name, Flags, Data, Fix) ->
- ?line Tab = ets_new(Name, Flags),
- ?line ets:insert(Tab, Data),
+ Tab = ets_new(Name, Flags),
+ ets:insert(Tab, Data),
case Fix of
false -> ok;
true ->
- ?line true = ets:safe_fixtable(Tab, true),
- ?line lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
+ true = ets:safe_fixtable(Tab, true),
+ lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
end,
Parent = self(),
{Pid, MRef} = my_spawn_opt(fun() ->
- receive
- ets_new ->
- ets_new(Name, [named_table])
- end
+ receive
+ ets_new ->
+ ets_new(Name, [named_table])
+ end
end,
[link, monitor]),
true = ets:delete(Tab),
@@ -3210,126 +3210,126 @@ delete_large_named_table_1(Name, Flags, Data, Fix) ->
%% Delete a large table, and kill the process during the delete.
evil_delete(Config) when is_list(Config) ->
- ?line Data = [{I,I*I} || I <- lists:seq(1, 100000)],
+ Data = [{I,I*I} || I <- lists:seq(1, 100000)],
repeat_for_opts(fun(Opts) -> evil_delete_do(Opts,Data) end).
evil_delete_do(Opts,Data) ->
- ?line EtsMem = etsmem(),
- ?line evil_delete_owner(foo_hash, Opts, Data, false),
- ?line verify_etsmem(EtsMem),
- ?line evil_delete_owner(foo_hash, Opts, Data, true),
- ?line verify_etsmem(EtsMem),
- ?line evil_delete_owner(foo_tree, [ordered_set | Opts], Data, false),
- ?line verify_etsmem(EtsMem),
- ?line TabA = evil_delete_not_owner(foo_hash, Opts, Data, false),
- ?line verify_etsmem(EtsMem),
- ?line TabB = evil_delete_not_owner(foo_hash, Opts, Data, true),
- ?line verify_etsmem(EtsMem),
- ?line TabC = evil_delete_not_owner(foo_tree, [ordered_set | Opts], Data, false),
- ?line verify_etsmem(EtsMem),
- ?line lists:foreach(fun(T) -> undefined = ets:info(T) end,
- [TabA,TabB,TabC]).
+ EtsMem = etsmem(),
+ evil_delete_owner(foo_hash, Opts, Data, false),
+ verify_etsmem(EtsMem),
+ evil_delete_owner(foo_hash, Opts, Data, true),
+ verify_etsmem(EtsMem),
+ evil_delete_owner(foo_tree, [ordered_set | Opts], Data, false),
+ verify_etsmem(EtsMem),
+ TabA = evil_delete_not_owner(foo_hash, Opts, Data, false),
+ verify_etsmem(EtsMem),
+ TabB = evil_delete_not_owner(foo_hash, Opts, Data, true),
+ verify_etsmem(EtsMem),
+ TabC = evil_delete_not_owner(foo_tree, [ordered_set | Opts], Data, false),
+ verify_etsmem(EtsMem),
+ lists:foreach(fun(T) -> undefined = ets:info(T) end,
+ [TabA,TabB,TabC]).
evil_delete_not_owner(Name, Flags, Data, Fix) ->
io:format("Not owner: ~p, fix = ~p", [Name,Fix]),
- ?line Tab = ets_new(Name, [public|Flags]),
- ?line ets:insert(Tab, Data),
+ Tab = ets_new(Name, [public|Flags]),
+ ets:insert(Tab, Data),
case Fix of
false -> ok;
true ->
- ?line true = ets:safe_fixtable(Tab, true),
- ?line lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
+ true = ets:safe_fixtable(Tab, true),
+ lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
end,
- ?line Pid = my_spawn(fun() ->
- P = my_spawn_link(
- fun() ->
- receive kill -> ok end,
- erlang:yield(),
- exit(kill_linked_processes_now)
- end),
- erlang:yield(),
- P ! kill,
- true = ets:delete(Tab)
- end),
- ?line Ref = erlang:monitor(process, Pid),
- ?line receive {'DOWN',Ref,_,_,_} -> ok end,
+ Pid = my_spawn(fun() ->
+ P = my_spawn_link(
+ fun() ->
+ receive kill -> ok end,
+ erlang:yield(),
+ exit(kill_linked_processes_now)
+ end),
+ erlang:yield(),
+ P ! kill,
+ true = ets:delete(Tab)
+ end),
+ Ref = erlang:monitor(process, Pid),
+ receive {'DOWN',Ref,_,_,_} -> ok end,
Tab.
evil_delete_owner(Name, Flags, Data, Fix) ->
- ?line Fun = fun() ->
- ?line Tab = ets_new(Name, [public|Flags]),
- ?line ets:insert(Tab, Data),
- case Fix of
- false -> ok;
- true ->
- ?line true = ets:safe_fixtable(Tab, true),
- ?line lists:foreach(fun({K,_}) ->
- ets:delete(Tab, K)
- end, Data)
- end,
- erlang:yield(),
- my_spawn_link(fun() ->
- erlang:yield(),
- exit(kill_linked_processes_now)
- end),
- true = ets:delete(Tab)
- end,
- ?line Pid = my_spawn(Fun),
- ?line Ref = erlang:monitor(process, Pid),
- ?line receive {'DOWN',Ref,_,_,_} -> ok end.
+ Fun = fun() ->
+ Tab = ets_new(Name, [public|Flags]),
+ ets:insert(Tab, Data),
+ case Fix of
+ false -> ok;
+ true ->
+ true = ets:safe_fixtable(Tab, true),
+ lists:foreach(fun({K,_}) ->
+ ets:delete(Tab, K)
+ end, Data)
+ end,
+ erlang:yield(),
+ my_spawn_link(fun() ->
+ erlang:yield(),
+ exit(kill_linked_processes_now)
+ end),
+ true = ets:delete(Tab)
+ end,
+ Pid = my_spawn(Fun),
+ Ref = erlang:monitor(process, Pid),
+ receive {'DOWN',Ref,_,_,_} -> ok end.
exit_large_table_owner(Config) when is_list(Config) ->
- %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
- (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
- {true, I+1}
- end, 1)
- end,
- ?line EtsMem = etsmem(),
+ %%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
+ {true, I+1}
+ end, 1)
+ end,
+ EtsMem = etsmem(),
repeat_for_opts({exit_large_table_owner_do,{FEData,Config}}),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
exit_large_table_owner_do(Opts,{FEData,Config}) ->
- ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1),
- ?line verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1).
+ verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1),
+ verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1).
exit_many_large_table_owner(Config) when is_list(Config) ->
- %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
- (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
- {true, I+1}
- end, 1)
- end,
- ?line EtsMem = etsmem(),
+ %%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
+ {true, I+1}
+ end, 1)
+ end,
+ EtsMem = etsmem(),
repeat_for_opts(fun(Opts) -> exit_many_large_table_owner_do(Opts,FEData,Config) end),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
exit_many_large_table_owner_do(Opts,FEData,Config) ->
- ?line verify_rescheduling_exit(Config, FEData, Opts, true, 1, 4),
- ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 1, 4).
+ verify_rescheduling_exit(Config, FEData, Opts, true, 1, 4),
+ verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 1, 4).
exit_many_tables_owner(Config) when is_list(Config) ->
NoData = fun(_Do) -> ok end,
- ?line EtsMem = etsmem(),
- ?line verify_rescheduling_exit(Config, NoData, [named_table], false, 1000, 1),
- ?line verify_rescheduling_exit(Config, NoData, [named_table,{write_concurrency,true}], false, 1000, 1),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ verify_rescheduling_exit(Config, NoData, [named_table], false, 1000, 1),
+ verify_rescheduling_exit(Config, NoData, [named_table,{write_concurrency,true}], false, 1000, 1),
+ verify_etsmem(EtsMem).
exit_many_many_tables_owner(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 50)],
- ?line FEData = fun(Do) -> lists:foreach(Do, Data) end,
+ Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 50)],
+ FEData = fun(Do) -> lists:foreach(Do, Data) end,
repeat_for_opts(fun(Opts) -> exit_many_many_tables_owner_do(Opts,FEData,Config) end).
exit_many_many_tables_owner_do(Opts,FEData,Config) ->
- ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 200, 5),
- ?line verify_rescheduling_exit(Config, FEData, Opts, false, 200, 5),
- ?line wait_for_test_procs(),
- ?line EtsMem = etsmem(),
- ?line verify_rescheduling_exit(Config, FEData, Opts, true, 200, 5),
- ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 200, 5),
- ?line verify_etsmem(EtsMem).
-
+ verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 200, 5),
+ verify_rescheduling_exit(Config, FEData, Opts, false, 200, 5),
+ wait_for_test_procs(),
+ EtsMem = etsmem(),
+ verify_rescheduling_exit(Config, FEData, Opts, true, 200, 5),
+ verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 200, 5),
+ verify_etsmem(EtsMem).
+
count_exit_sched(TP) ->
receive
@@ -3371,11 +3371,11 @@ vre_fix_tables(Tab) ->
ok.
verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
- ?line NoFix = 5,
- ?line TestCase = atom_to_list(?config(test_case, Config)),
- ?line Parent = self(),
- ?line KillMe = make_ref(),
- ?line PFun =
+ NoFix = 5,
+ TestCase = atom_to_list(?config(test_case, Config)),
+ Parent = self(),
+ KillMe = make_ref(),
+ PFun =
fun () ->
repeat(
fun () ->
@@ -3393,7 +3393,7 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
lists:seq(1,NoFix)),
KeyPos = ets:info(Tab,keypos),
ForEachData(fun(Data) ->
- ets:delete(Tab, element(KeyPos,Data))
+ ets:delete(Tab, element(KeyPos,Data))
end)
end
end,
@@ -3401,38 +3401,38 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
Parent ! {KillMe, self()},
receive after infinity -> ok end
end,
- ?line TPs = lists:map(fun (_) ->
- ?line TP = my_spawn_link(PFun),
- ?line 1 = erlang:trace(TP, true, [exiting]),
- TP
- end,
- lists:seq(1, NOProcs)),
- ?line lists:foreach(fun (TP) ->
- receive {KillMe, TP} -> ok end
- end,
- TPs),
- ?line LPs = start_loopers(erlang:system_info(schedulers),
- normal,
- fun (_) ->
- erlang:yield()
- end,
- ok),
- ?line lists:foreach(fun (TP) ->
- ?line unlink(TP),
- ?line exit(TP, bang)
- end,
- TPs),
- ?line lists:foreach(fun (TP) ->
- ?line XScheds = count_exit_sched(TP),
- io:format("~p XScheds=~p~n",
- [TP, XScheds]),
- ?line true = XScheds >= 5
+ TPs = lists:map(fun (_) ->
+ TP = my_spawn_link(PFun),
+ 1 = erlang:trace(TP, true, [exiting]),
+ TP
+ end,
+ lists:seq(1, NOProcs)),
+ lists:foreach(fun (TP) ->
+ receive {KillMe, TP} -> ok end
+ end,
+ TPs),
+ LPs = start_loopers(erlang:system_info(schedulers),
+ normal,
+ fun (_) ->
+ erlang:yield()
end,
- TPs),
- ?line stop_loopers(LPs),
- ?line ok.
+ ok),
+ lists:foreach(fun (TP) ->
+ unlink(TP),
+ exit(TP, bang)
+ end,
+ TPs),
+ lists:foreach(fun (TP) ->
+ XScheds = count_exit_sched(TP),
+ io:format("~p XScheds=~p~n",
+ [TP, XScheds]),
+ true = XScheds >= 5
+ end,
+ TPs),
+ stop_loopers(LPs),
+ ok.
+
-
%% Make sure that slots for ets tables are cleared properly.
table_leak(Config) when is_list(Config) ->
@@ -3440,43 +3440,43 @@ table_leak(Config) when is_list(Config) ->
table_leak_1(_,0) -> ok;
table_leak_1(Opts,N) ->
- ?line T = ets_new(fooflarf, Opts),
- ?line true = ets:delete(T),
+ T = ets_new(fooflarf, Opts),
+ true = ets:delete(T),
table_leak_1(Opts,N-1).
%% Check proper return values for illegal delete operations.
baddelete(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets:delete(foo)),
- ?line Tab = ets_new(foo,[]),
- ?line true = ets:delete(Tab),
- ?line {'EXIT',{badarg,_}} = (catch ets:delete(Tab)),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ {'EXIT',{badarg,_}} = (catch ets:delete(foo)),
+ Tab = ets_new(foo,[]),
+ true = ets:delete(Tab),
+ {'EXIT',{badarg,_}} = (catch ets:delete(Tab)),
+ verify_etsmem(EtsMem).
%% Check that match_delete works. Also tests tab2list function.
match_delete(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(match_delete_do,[write_concurrency,all_types]),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
match_delete_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(kad,Opts),
- ?line fill_tab(Tab,foo),
- ?line ets:insert(Tab,{{c,key},bar}),
- ?line _ = ets:match_delete(Tab,{'_',foo}),
- ?line [{{c,key},bar}] = ets:tab2list(Tab),
- ?line _ = ets:match_delete(Tab,'_'),
- ?line [] = ets:tab2list(Tab),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(kad,Opts),
+ fill_tab(Tab,foo),
+ ets:insert(Tab,{{c,key},bar}),
+ _ = ets:match_delete(Tab,{'_',foo}),
+ [{{c,key},bar}] = ets:tab2list(Tab),
+ _ = ets:match_delete(Tab,'_'),
+ [] = ets:tab2list(Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% OTP-3005: check match_delete with constant argument.
match_delete3(Config) when is_list(Config) ->
repeat_for_opts(match_delete3_do).
match_delete3_do(Opts) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
T = make_table(test,
[duplicate_bag | Opts],
[{aa,17},
@@ -3491,7 +3491,7 @@ match_delete3_do(Opts) ->
ets:match_delete(T, {cA,1000}),
[] = ets:match_object(T, {'_', 1000}),
ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -3501,19 +3501,19 @@ firstnext(Config) when is_list(Config) ->
repeat_for_opts(firstnext_do).
firstnext_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line [] = firstnext_collect(Tab,ets:first(Tab),[]),
- ?line fill_tab(Tab,foo),
- ?line Len = length(ets:tab2list(Tab)),
- ?line Len = length(firstnext_collect(Tab,ets:first(Tab),[])),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ [] = firstnext_collect(Tab,ets:first(Tab),[]),
+ fill_tab(Tab,foo),
+ Len = length(ets:tab2list(Tab)),
+ Len = length(firstnext_collect(Tab,ets:first(Tab),[])),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
firstnext_collect(_Tab,'$end_of_table',List) ->
- ?line List;
+ List;
firstnext_collect(Tab,Key,List) ->
- ?line firstnext_collect(Tab,ets:next(Tab,Key),[Key|List]).
+ firstnext_collect(Tab,ets:next(Tab,Key),[Key|List]).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -3524,7 +3524,7 @@ firstnext_concurrent(Config) when is_list(Config) ->
ets_init(?MODULE, 20),
[dynamic_go() || _ <- lists:seq(1, 2)],
receive
- after 5000 -> ok
+ after 5000 -> ok
end.
ets_init(Tab, N) ->
@@ -3559,22 +3559,22 @@ slot(Config) when is_list(Config) ->
repeat_for_opts(slot_do).
slot_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line fill_tab(Tab,foo),
- ?line Elts = ets:info(Tab,size),
- ?line Elts = slot_loop(Tab,0,0),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ fill_tab(Tab,foo),
+ Elts = ets:info(Tab,size),
+ Elts = slot_loop(Tab,0,0),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
slot_loop(Tab,SlotNo,EltsSoFar) ->
- ?line case ets:slot(Tab,SlotNo) of
- '$end_of_table' ->
- ?line {'EXIT',{badarg,_}} =
- (catch ets:slot(Tab,SlotNo+1)),
- ?line EltsSoFar;
- Elts ->
- ?line slot_loop(Tab,SlotNo+1,EltsSoFar+length(Elts))
+ case ets:slot(Tab,SlotNo) of
+ '$end_of_table' ->
+ {'EXIT',{badarg,_}} =
+ (catch ets:slot(Tab,SlotNo+1)),
+ EltsSoFar;
+ Elts ->
+ slot_loop(Tab,SlotNo+1,EltsSoFar+length(Elts))
end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -3584,63 +3584,63 @@ match1(Config) when is_list(Config) ->
repeat_for_opts(match1_do).
match1_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line fill_tab(Tab,foo),
- ?line [] = ets:match(Tab,{}),
- ?line ets:insert(Tab,{{one,4},4}),
- ?line ets:insert(Tab,{{one,5},5}),
- ?line ets:insert(Tab,{{two,4},4}),
- ?line ets:insert(Tab,{{two,5},6}),
- ?line case ets:match(Tab,{{one,'_'},'$0'}) of
- [[4],[5]] -> ok;
- [[5],[4]] -> ok
- end,
- ?line case ets:match(Tab,{{two,'$1'},'$0'}) of
- [[4,4],[6,5]] -> ok;
- [[6,5],[4,4]] -> ok
- end,
- ?line case ets:match(Tab,{{two,'$9'},'$4'}) of
- [[4,4],[6,5]] -> ok;
- [[6,5],[4,4]] -> ok
- end,
- ?line case ets:match(Tab,{{two,'$9'},'$22'}) of
- [[4,4],[5,6]] -> ok;
- [[5,6],[4,4]] -> ok
- end,
- ?line [[4]] = ets:match(Tab,{{two,'$0'},'$0'}),
- ?line Len = length(ets:match(Tab,'$0')),
- ?line Len = length(ets:match(Tab,'_')),
- ?line if Len > 4 -> ok end,
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ fill_tab(Tab,foo),
+ [] = ets:match(Tab,{}),
+ ets:insert(Tab,{{one,4},4}),
+ ets:insert(Tab,{{one,5},5}),
+ ets:insert(Tab,{{two,4},4}),
+ ets:insert(Tab,{{two,5},6}),
+ case ets:match(Tab,{{one,'_'},'$0'}) of
+ [[4],[5]] -> ok;
+ [[5],[4]] -> ok
+ end,
+ case ets:match(Tab,{{two,'$1'},'$0'}) of
+ [[4,4],[6,5]] -> ok;
+ [[6,5],[4,4]] -> ok
+ end,
+ case ets:match(Tab,{{two,'$9'},'$4'}) of
+ [[4,4],[6,5]] -> ok;
+ [[6,5],[4,4]] -> ok
+ end,
+ case ets:match(Tab,{{two,'$9'},'$22'}) of
+ [[4,4],[5,6]] -> ok;
+ [[5,6],[4,4]] -> ok
+ end,
+ [[4]] = ets:match(Tab,{{two,'$0'},'$0'}),
+ Len = length(ets:match(Tab,'$0')),
+ Len = length(ets:match(Tab,'_')),
+ if Len > 4 -> ok end,
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Test match with specified keypos bag table.
match2(Config) when is_list(Config) ->
repeat_for_opts(match2_do).
match2_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = make_table(foobar,
- [bag, named_table, {keypos, 2} | Opts],
- [{value1, key1},
- {value2_1, key2},
- {value2_2, key2},
- {value3_1, key3},
- {value3_2, key3},
- {value2_1, key2_wannabe}]),
- ?line case length(ets:match(Tab, '$1')) of
- 6 -> ok;
- _ -> ct:fail("Length of matched list is wrong.")
- end,
- ?line [[value3_1],[value3_2]] = ets:match(Tab, {'$1', key3}),
- ?line [[key1]] = ets:match(Tab, {value1, '$1'}),
- ?line [[key2_wannabe],[key2]] = ets:match(Tab, {value2_1, '$2'}),
- ?line [] = ets:match(Tab,{'$1',nosuchkey}),
- ?line [] = ets:match(Tab,{'$1',kgY2}), % same hash as key2
- ?line [] = ets:match(Tab,{nosuchvalue,'$1'}),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = make_table(foobar,
+ [bag, named_table, {keypos, 2} | Opts],
+ [{value1, key1},
+ {value2_1, key2},
+ {value2_2, key2},
+ {value3_1, key3},
+ {value3_2, key3},
+ {value2_1, key2_wannabe}]),
+ case length(ets:match(Tab, '$1')) of
+ 6 -> ok;
+ _ -> ct:fail("Length of matched list is wrong.")
+ end,
+ [[value3_1],[value3_2]] = ets:match(Tab, {'$1', key3}),
+ [[key1]] = ets:match(Tab, {value1, '$1'}),
+ [[key2_wannabe],[key2]] = ets:match(Tab, {value2_1, '$2'}),
+ [] = ets:match(Tab,{'$1',nosuchkey}),
+ [] = ets:match(Tab,{'$1',kgY2}), % same hash as key2
+ [] = ets:match(Tab,{nosuchvalue,'$1'}),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Some ets:match_object tests.
match_object(Config) when is_list(Config) ->
@@ -3747,35 +3747,35 @@ match_object2(Config) when is_list(Config) ->
repeat_for_opts(match_object2_do).
match_object2_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo, [bag, {keypos, 2} | Opts]),
- ?line fill_tab2(Tab, 0, 13005), % match_db_object does 1000
- % elements per pass, might
- % change in the future.
- ?line case catch ets:match_object(Tab, {hej, '$1'}) of
- {'EXIT', _} ->
- ets:delete(Tab),
- ct:fail("match_object EXIT:ed");
- [] ->
- io:format("Nothing matched.");
- List ->
- io:format("Matched:~p~n",[List])
- end,
+ EtsMem = etsmem(),
+ Tab = ets_new(foo, [bag, {keypos, 2} | Opts]),
+ fill_tab2(Tab, 0, 13005), % match_db_object does 1000
+ % elements per pass, might
+ % change in the future.
+ case catch ets:match_object(Tab, {hej, '$1'}) of
+ {'EXIT', _} ->
+ ets:delete(Tab),
+ ct:fail("match_object EXIT:ed");
+ [] ->
+ io:format("Nothing matched.");
+ List ->
+ io:format("Matched:~p~n",[List])
+ end,
ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% OTP-3319. Test tab2list.
tab2list(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Tab = make_table(foo,
- [ordered_set],
- [{a,b}, {c,b}, {b,b}, {a,c}]),
- ?line [{a,c},{b,b},{c,b}] = ets:tab2list(Tab),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = make_table(foo,
+ [ordered_set],
+ [{a,b}, {c,b}, {b,b}, {a,c}]),
+ [{a,c},{b,b},{c,b}] = ets:tab2list(Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Simple general small test. If this fails, ets is in really bad
%% shape.
@@ -3783,17 +3783,17 @@ misc1(Config) when is_list(Config) ->
repeat_for_opts(misc1_do).
misc1_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo,Opts),
- ?line true = lists:member(Tab,ets:all()),
- ?line ets:delete(Tab),
- ?line false = lists:member(Tab,ets:all()),
- ?line case catch ets:delete(Tab) of
- {'EXIT',_Reason} ->
- ?line verify_etsmem(EtsMem);
- true ->
- ct:fail("Delete of nonexisting table returned `true'.")
- end,
+ EtsMem = etsmem(),
+ Tab = ets_new(foo,Opts),
+ true = lists:member(Tab,ets:all()),
+ ets:delete(Tab),
+ false = lists:member(Tab,ets:all()),
+ case catch ets:delete(Tab) of
+ {'EXIT',_Reason} ->
+ verify_etsmem(EtsMem);
+ true ->
+ ct:fail("Delete of nonexisting table returned `true'.")
+ end,
ok.
%% Check the safe_fixtable function.
@@ -3801,12 +3801,12 @@ safe_fixtable(Config) when is_list(Config) ->
repeat_for_opts(safe_fixtable_do).
safe_fixtable_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foo, Opts),
- ?line fill_tab(Tab, foobar),
- ?line true = ets:safe_fixtable(Tab, true),
- ?line receive after 1 -> ok end,
- ?line true = ets:safe_fixtable(Tab, false),
+ EtsMem = etsmem(),
+ Tab = ets_new(foo, Opts),
+ fill_tab(Tab, foobar),
+ true = ets:safe_fixtable(Tab, true),
+ receive after 1 -> ok end,
+ true = ets:safe_fixtable(Tab, false),
false = ets:info(Tab,safe_fixed_monotonic_time),
false = ets:info(Tab,safe_fixed),
SysBefore = erlang:timestamp(),
@@ -3839,19 +3839,19 @@ safe_fixtable_do(Opts) ->
{FixMonTime,[{Self,1}]} = ets:info(Tab,safe_fixed_monotonic_time),
{FixSysTime,[{Self,1}]} = ets:info(Tab,safe_fixed),
%% badarg's
- ?line {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)),
- ?line true = ets:info(Tab,fixed),
- ?line true = ets:safe_fixtable(Tab, false),
- ?line false = ets:info(Tab,fixed),
- ?line {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)),
- ?line false = ets:info(Tab,fixed),
- ?line ets:delete(Tab),
- ?line case catch ets:safe_fixtable(Tab, true) of
- {'EXIT', _Reason} ->
- ?line verify_etsmem(EtsMem);
- _ ->
- ct:fail("Fixtable on nonexisting table returned `true'")
- end,
+ {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)),
+ true = ets:info(Tab,fixed),
+ true = ets:safe_fixtable(Tab, false),
+ false = ets:info(Tab,fixed),
+ {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)),
+ false = ets:info(Tab,fixed),
+ ets:delete(Tab),
+ case catch ets:safe_fixtable(Tab, true) of
+ {'EXIT', _Reason} ->
+ verify_etsmem(EtsMem);
+ _ ->
+ ct:fail("Fixtable on nonexisting table returned `true'")
+ end,
ok.
%% Tests ets:info result for required tuples.
@@ -3859,66 +3859,66 @@ info(Config) when is_list(Config) ->
repeat_for_opts(info_do).
info_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line MeMyselfI=self(),
- ?line ThisNode=node(),
- ?line Tab = ets_new(foobar, [{keypos, 2} | Opts]),
+ EtsMem = etsmem(),
+ MeMyselfI=self(),
+ ThisNode=node(),
+ Tab = ets_new(foobar, [{keypos, 2} | Opts]),
%% Note: ets:info/1 used to return a tuple, but from R11B onwards it
%% returns a list.
- ?line Res = ets:info(Tab),
- ?line {value, {memory, _Mem}} = lists:keysearch(memory, 1, Res),
- ?line {value, {owner, MeMyselfI}} = lists:keysearch(owner, 1, Res),
- ?line {value, {name, foobar}} = lists:keysearch(name, 1, Res),
- ?line {value, {size, 0}} = lists:keysearch(size, 1, Res),
- ?line {value, {node, ThisNode}} = lists:keysearch(node, 1, Res),
- ?line {value, {named_table, false}} = lists:keysearch(named_table, 1, Res),
- ?line {value, {type, set}} = lists:keysearch(type, 1, Res),
- ?line {value, {keypos, 2}} = lists:keysearch(keypos, 1, Res),
- ?line {value, {protection, protected}} =
+ Res = ets:info(Tab),
+ {value, {memory, _Mem}} = lists:keysearch(memory, 1, Res),
+ {value, {owner, MeMyselfI}} = lists:keysearch(owner, 1, Res),
+ {value, {name, foobar}} = lists:keysearch(name, 1, Res),
+ {value, {size, 0}} = lists:keysearch(size, 1, Res),
+ {value, {node, ThisNode}} = lists:keysearch(node, 1, Res),
+ {value, {named_table, false}} = lists:keysearch(named_table, 1, Res),
+ {value, {type, set}} = lists:keysearch(type, 1, Res),
+ {value, {keypos, 2}} = lists:keysearch(keypos, 1, Res),
+ {value, {protection, protected}} =
lists:keysearch(protection, 1, Res),
- ?line true = ets:delete(Tab),
- ?line undefined = ets:info(non_existing_table_xxyy),
- ?line undefined = ets:info(non_existing_table_xxyy,type),
- ?line undefined = ets:info(non_existing_table_xxyy,node),
- ?line undefined = ets:info(non_existing_table_xxyy,named_table),
- ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed_monotonic_time),
- ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed),
- ?line verify_etsmem(EtsMem).
+ true = ets:delete(Tab),
+ undefined = ets:info(non_existing_table_xxyy),
+ undefined = ets:info(non_existing_table_xxyy,type),
+ undefined = ets:info(non_existing_table_xxyy,node),
+ undefined = ets:info(non_existing_table_xxyy,named_table),
+ undefined = ets:info(non_existing_table_xxyy,safe_fixed_monotonic_time),
+ undefined = ets:info(non_existing_table_xxyy,safe_fixed),
+ verify_etsmem(EtsMem).
%% Test various duplicate_bags stuff.
dups(Config) when is_list(Config) ->
repeat_for_opts(dups_do).
dups_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line T = make_table(funky,
- [duplicate_bag | Opts],
- [{1, 2}, {1, 2}]),
- ?line 2 = length(ets:tab2list(T)),
- ?line ets:delete(T, 1),
- ?line [] = ets:lookup(T, 1),
-
- ?line ets:insert(T, {1, 2, 2}),
- ?line ets:insert(T, {1, 2, 4}),
- ?line ets:insert(T, {1, 2, 2}),
- ?line ets:insert(T, {1, 2, 2}),
- ?line ets:insert(T, {1, 2, 4}),
-
- ?line 5 = length(ets:tab2list(T)),
-
- ?line 5 = length(ets:match(T, {'$1', 2, '$2'})),
- ?line 3 = length(ets:match(T, {'_', '$1', '$1'})),
- ?line ets:match_delete(T, {'_', '$1', '$1'}),
- ?line 0 = length(ets:match(T, {'_', '$1', '$1'})),
- ?line ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ T = make_table(funky,
+ [duplicate_bag | Opts],
+ [{1, 2}, {1, 2}]),
+ 2 = length(ets:tab2list(T)),
+ ets:delete(T, 1),
+ [] = ets:lookup(T, 1),
+
+ ets:insert(T, {1, 2, 2}),
+ ets:insert(T, {1, 2, 4}),
+ ets:insert(T, {1, 2, 2}),
+ ets:insert(T, {1, 2, 2}),
+ ets:insert(T, {1, 2, 4}),
+
+ 5 = length(ets:tab2list(T)),
+
+ 5 = length(ets:match(T, {'$1', 2, '$2'})),
+ 3 = length(ets:match(T, {'_', '$1', '$1'})),
+ ets:match_delete(T, {'_', '$1', '$1'}),
+ 0 = length(ets:match(T, {'_', '$1', '$1'})),
+ ets:delete(T),
+ verify_etsmem(EtsMem).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Test the ets:tab2file function on an empty ets table.
tab2file(Config) when is_list(Config) ->
- ?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
+ FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
tab2file_do(FName, []),
tab2file_do(FName, [{sync,true}]),
tab2file_do(FName, [{sync,false}]),
@@ -3928,60 +3928,60 @@ tab2file(Config) when is_list(Config) ->
tab2file_do(FName, Opts) ->
%% Write an empty ets table to a file, read back and check properties.
- ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, public,
- {keypos, 2},
- compressed,
- {write_concurrency,true},
- {read_concurrency,true}]),
+ Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, public,
+ {keypos, 2},
+ compressed,
+ {write_concurrency,true},
+ {read_concurrency,true}]),
catch file:delete(FName),
Res = ets:tab2file(Tab, FName, Opts),
true = ets:delete(Tab),
ok = Res,
%%
- ?line EtsMem = etsmem(),
- ?line {ok, Tab2} = ets:file2tab(FName),
+ EtsMem = etsmem(),
+ {ok, Tab2} = ets:file2tab(FName),
public = ets:info(Tab2, protection),
- ?line true = ets:info(Tab2, named_table),
- ?line 2 = ets:info(Tab2, keypos),
- ?line set = ets:info(Tab2, type),
+ true = ets:info(Tab2, named_table),
+ 2 = ets:info(Tab2, keypos),
+ set = ets:info(Tab2, type),
true = ets:info(Tab2, compressed),
Smp = erlang:system_info(smp_support),
Smp = ets:info(Tab2, read_concurrency),
Smp = ets:info(Tab2, write_concurrency),
- ?line true = ets:delete(Tab2),
- ?line verify_etsmem(EtsMem).
+ true = ets:delete(Tab2),
+ verify_etsmem(EtsMem).
+
-
%% Check the ets:tab2file function on a filled set/bag type ets table.
tab2file2(Config) when is_list(Config) ->
repeat_for_opts({tab2file2_do,Config}, [[set,bag],compressed]).
tab2file2_do(Opts, Config) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, private,
- {keypos, 2} | Opts]),
- ?line FName = filename:join([?config(priv_dir, Config),"tab2file2_case"]),
- ?line ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!)
- ?line Len = length(ets:tab2list(Tab)),
- ?line Mem = ets:info(Tab, memory),
- ?line Type = ets:info(Tab, type),
+ EtsMem = etsmem(),
+ Tab = ets_new(ets_SUITE_foo_tab, [named_table, private,
+ {keypos, 2} | Opts]),
+ FName = filename:join([?config(priv_dir, Config),"tab2file2_case"]),
+ ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!)
+ Len = length(ets:tab2list(Tab)),
+ Mem = ets:info(Tab, memory),
+ Type = ets:info(Tab, type),
%%io:format("org tab: ~p\n",[ets:info(Tab)]),
- ?line ok = ets:tab2file(Tab, FName),
- ?line true = ets:delete(Tab),
+ ok = ets:tab2file(Tab, FName),
+ true = ets:delete(Tab),
- ?line EtsMem4 = etsmem(),
+ EtsMem4 = etsmem(),
- ?line {ok, Tab2} = ets:file2tab(FName),
+ {ok, Tab2} = ets:file2tab(FName),
%%io:format("loaded tab: ~p\n",[ets:info(Tab2)]),
- ?line private = ets:info(Tab2, protection),
- ?line true = ets:info(Tab2, named_table),
- ?line 2 = ets:info(Tab2, keypos),
- ?line Type = ets:info(Tab2, type),
- ?line Len = length(ets:tab2list(Tab2)),
- ?line Mem = ets:info(Tab2, memory),
- ?line true = ets:delete(Tab2),
+ private = ets:info(Tab2, protection),
+ true = ets:info(Tab2, named_table),
+ 2 = ets:info(Tab2, keypos),
+ Type = ets:info(Tab2, type),
+ Len = length(ets:tab2list(Tab2)),
+ Mem = ets:info(Tab2, memory),
+ true = ets:delete(Tab2),
io:format("Between = ~p\n", [EtsMem4]),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
-define(test_list, [8,5,4,1,58,125,255, 250, 245, 240, 235,
230, Num rem 255, 255, 125, 130, 135, 140, 145,
@@ -3996,21 +3996,21 @@ tab2file2_do(Opts, Config) ->
fill_tab2(_Tab, _Val, 0) ->
ok;
fill_tab2(Tab, Val, Num) ->
- ?line Item =
+ Item =
case Num rem 10 of
0 -> "String";
- 1 -> ?line ?test_atom;
- 2 -> ?line ?test_tuple;
- 3 -> ?line ?test_integer;
- 4 -> ?line ?test_float;
- 5 -> ?line list_to_binary(?test_list); %Heap binary
- 6 -> ?line list_to_binary(?big_test_list); %Refc binary
- 7 -> ?line make_sub_binary(?test_list, Num); %Sub binary
- 8 -> ?line ?test_list;
- 9 -> ?line fun(X) -> {Tab,Val,X*Num} end
+ 1 -> ?test_atom;
+ 2 -> ?test_tuple;
+ 3 -> ?test_integer;
+ 4 -> ?test_float;
+ 5 -> list_to_binary(?test_list); %Heap binary
+ 6 -> list_to_binary(?big_test_list); %Refc binary
+ 7 -> make_sub_binary(?test_list, Num); %Sub binary
+ 8 -> ?test_list;
+ 9 -> fun(X) -> {Tab,Val,X*Num} end
end,
- ?line true=ets:insert(Tab, {Item, Val}),
- ?line fill_tab2(Tab, Val+1, Num-1),
+ true=ets:insert(Tab, {Item, Val}),
+ fill_tab2(Tab, Val+1, Num-1),
ok.
%% Test verification of tables with object count extended_info.
@@ -4018,8 +4018,8 @@ tabfile_ext1(Config) when is_list(Config) ->
repeat_for_opts(fun(Opts) -> tabfile_ext1_do(Opts, Config) end).
tabfile_ext1_do(Opts,Config) ->
- ?line FName = filename:join([?config(priv_dir, Config),"nisse.dat"]),
- ?line FName2 = filename:join([?config(priv_dir, Config),"countflip.dat"]),
+ FName = filename:join([?config(priv_dir, Config),"nisse.dat"]),
+ FName2 = filename:join([?config(priv_dir, Config),"countflip.dat"]),
L = lists:seq(1,10),
T = ets_new(x,Opts),
Name = make_ref(),
@@ -4056,8 +4056,8 @@ tabfile_ext2(Config) when is_list(Config) ->
repeat_for_opts(fun(Opts) -> tabfile_ext2_do(Opts,Config) end).
tabfile_ext2_do(Opts,Config) ->
- ?line FName = filename:join([?config(priv_dir, Config),"olle.dat"]),
- ?line FName2 = filename:join([?config(priv_dir, Config),"bitflip.dat"]),
+ FName = filename:join([?config(priv_dir, Config),"olle.dat"]),
+ FName2 = filename:join([?config(priv_dir, Config),"bitflip.dat"]),
L = lists:seq(1,10),
T = ets_new(x,Opts),
Name = make_ref(),
@@ -4090,8 +4090,8 @@ tabfile_ext2_do(Opts,Config) ->
%% Test verification of (named) tables without extended info.
tabfile_ext3(Config) when is_list(Config) ->
- ?line FName = filename:join([?config(priv_dir, Config),"namn.dat"]),
- ?line FName2 = filename:join([?config(priv_dir, Config),"ncountflip.dat"]),
+ FName = filename:join([?config(priv_dir, Config),"namn.dat"]),
+ FName2 = filename:join([?config(priv_dir, Config),"ncountflip.dat"]),
L = lists:seq(1,10),
Name = make_ref(),
?MODULE = ets_new(?MODULE,[named_table]),
@@ -4121,7 +4121,7 @@ tabfile_ext3(Config) when is_list(Config) ->
%% Tests verification of large table with md5 sum.
tabfile_ext4(Config) when is_list(Config) ->
- ?line FName = filename:join([?config(priv_dir, Config),"bauta.dat"]),
+ FName = filename:join([?config(priv_dir, Config),"bauta.dat"]),
LL = lists:seq(1,10000),
TL = ets_new(x,[]),
Name2 = make_ref(),
@@ -4222,12 +4222,12 @@ heavy_lookup(Config) when is_list(Config) ->
repeat_for_opts(heavy_lookup_do).
heavy_lookup_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
- ?line ok = fill_tab2(Tab, 0, 7000),
+ EtsMem = etsmem(),
+ Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
+ ok = fill_tab2(Tab, 0, 7000),
_ = [do_lookup(Tab, 6999) || _ <- lists:seq(1, 50)],
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
do_lookup(_Tab, 0) -> ok;
do_lookup(Tab, N) ->
@@ -4255,15 +4255,15 @@ heavy_lookup_element_do(Opts) ->
do_lookup_element(_Tab, 0, _) -> ok;
do_lookup_element(Tab, N, M) ->
- ?line case catch ets:lookup_element(Tab, N, M) of
- {'EXIT', {badarg, _}} ->
- case M of
- 1 -> ct:fail("Set #~p reported as empty. Not valid.",
- [N]),
- exit('Invalid lookup_element');
- _ -> ?line do_lookup_element(Tab, N-1, 1)
- end;
- _ -> ?line do_lookup_element(Tab, N, M+1)
+ case catch ets:lookup_element(Tab, N, M) of
+ {'EXIT', {badarg, _}} ->
+ case M of
+ 1 -> ct:fail("Set #~p reported as empty. Not valid.",
+ [N]),
+ exit('Invalid lookup_element');
+ _ -> do_lookup_element(Tab, N-1, 1)
+ end;
+ _ -> do_lookup_element(Tab, N, M+1)
end.
@@ -4271,28 +4271,28 @@ heavy_concurrent(Config) when is_list(Config) ->
repeat_for_opts(do_heavy_concurrent).
do_heavy_concurrent(Opts) ->
- ?line Size = 10000,
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
- ?line ok = fill_tab2(Tab, 0, Size),
- ?line Procs = lists:map(
- fun (N) ->
- my_spawn_link(
- fun () ->
- do_heavy_concurrent_proc(Tab, Size, N)
- end)
- end,
- lists:seq(1, 500)),
- ?line lists:foreach(fun (P) ->
- M = erlang:monitor(process, P),
- receive
- {'DOWN', M, process, P, _} ->
- ok
- end
- end,
- Procs),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ Size = 10000,
+ EtsMem = etsmem(),
+ Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
+ ok = fill_tab2(Tab, 0, Size),
+ Procs = lists:map(
+ fun (N) ->
+ my_spawn_link(
+ fun () ->
+ do_heavy_concurrent_proc(Tab, Size, N)
+ end)
+ end,
+ lists:seq(1, 500)),
+ lists:foreach(fun (P) ->
+ M = erlang:monitor(process, P),
+ receive
+ {'DOWN', M, process, P, _} ->
+ ok
+ end
+ end,
+ Procs),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
do_heavy_concurrent_proc(_Tab, 0, _Offs) ->
done;
@@ -4307,77 +4307,77 @@ do_heavy_concurrent_proc(Tab, N, Offs) ->
fold_empty(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line Tab = make_table(a, [], []),
- ?line [] = ets:foldl(fun(_X) -> exit(hej) end, [], Tab),
- ?line [] = ets:foldr(fun(_X) -> exit(hej) end, [], Tab),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = make_table(a, [], []),
+ [] = ets:foldl(fun(_X) -> exit(hej) end, [], Tab),
+ [] = ets:foldr(fun(_X) -> exit(hej) end, [], Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
foldl(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line L = [{a,1}, {c,3}, {b,2}],
- ?line LS = lists:sort(L),
- ?line Tab = make_table(a, [bag], L),
- ?line LS = lists:sort(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, [bag], L),
+ LS = lists:sort(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
foldr(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line L = [{a,1}, {c,3}, {b,2}],
- ?line LS = lists:sort(L),
- ?line Tab = make_table(a, [bag], L),
- ?line LS = lists:sort(ets:foldr(fun(E,A) -> [E|A] end, [], Tab)),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, [bag], L),
+ LS = lists:sort(ets:foldr(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
foldl_ordered(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line L = [{a,1}, {c,3}, {b,2}],
- ?line LS = lists:sort(L),
- ?line Tab = make_table(a, [ordered_set], L),
- ?line LS = lists:reverse(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, [ordered_set], L),
+ LS = lists:reverse(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
foldr_ordered(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
- ?line L = [{a,1}, {c,3}, {b,2}],
- ?line LS = lists:sort(L),
- ?line Tab = make_table(a, [ordered_set], L),
- ?line LS = ets:foldr(fun(E,A) -> [E|A] end, [], Tab),
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, [ordered_set], L),
+ LS = ets:foldr(fun(E,A) -> [E|A] end, [], Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
%% Test ets:member BIF.
member(Config) when is_list(Config) ->
repeat_for_opts(member_do, [write_concurrency, all_types]).
member_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line T = ets_new(xxx, Opts),
- ?line false = ets:member(T,hej),
- ?line E = fun(0,_F)->ok;
- (N,F) ->
- ?line ets:insert(T,{N,N rem 10}),
- F(N-1,F)
- end,
- ?line E(10000,E),
- ?line false = ets:member(T,hej),
- ?line true = ets:member(T,1),
- ?line false = ets:member(T,20000),
- ?line ets:delete(T,5),
- ?line false = ets:member(T,5),
- ?line ets:safe_fixtable(T,true),
- ?line ets:delete(T,6),
- ?line false = ets:member(T,6),
- ?line ets:safe_fixtable(T,false),
- ?line false = ets:member(T,6),
- ?line ets:delete(T),
- ?line {'EXIT',{badarg,_}} = (catch ets:member(finnsinte, 23)),
- ?line {'EXIT',{badarg,_}} = (catch ets:member(T, 23)),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ T = ets_new(xxx, Opts),
+ false = ets:member(T,hej),
+ E = fun(0,_F)->ok;
+ (N,F) ->
+ ets:insert(T,{N,N rem 10}),
+ F(N-1,F)
+ end,
+ E(10000,E),
+ false = ets:member(T,hej),
+ true = ets:member(T,1),
+ false = ets:member(T,20000),
+ ets:delete(T,5),
+ false = ets:member(T,5),
+ ets:safe_fixtable(T,true),
+ ets:delete(T,6),
+ false = ets:member(T,6),
+ ets:safe_fixtable(T,false),
+ false = ets:member(T,6),
+ ets:delete(T),
+ {'EXIT',{badarg,_}} = (catch ets:member(finnsinte, 23)),
+ {'EXIT',{badarg,_}} = (catch ets:member(T, 23)),
+ verify_etsmem(EtsMem).
build_table(L1,L2,Num) ->
@@ -4464,10 +4464,10 @@ create_random_string(0) ->
create_random_string(OfLength) ->
C = case rand:uniform(2) of
- 1 ->
- (rand:uniform($Z - $A + 1) - 1) + $A;
- _ ->
- (rand:uniform($z - $a + 1) - 1) + $a
+ 1 ->
+ (rand:uniform($Z - $A + 1) - 1) + $A;
+ _ ->
+ (rand:uniform($z - $a + 1) - 1) + $a
end,
[C | create_random_string(OfLength - 1)].
@@ -4480,9 +4480,9 @@ create_random_tuple(OfLength) ->
create_partly_bound_tuple(OfLength) ->
case rand:uniform(2) of
1 ->
- create_partly_bound_tuple1(OfLength);
+ create_partly_bound_tuple1(OfLength);
_ ->
- create_partly_bound_tuple3(OfLength)
+ create_partly_bound_tuple3(OfLength)
end.
create_partly_bound_tuple1(OfLength) ->
@@ -4557,7 +4557,7 @@ xfilltabint(Tab,N) ->
_ ->
filltabint(Tab,N)
end.
-
+
filltabstr(Tab,N) ->
filltabstr(Tab,0,N).
@@ -4751,15 +4751,15 @@ gen_dets_filename(Config,N) ->
"testdets_" ++ integer_to_list(N) ++ ".dets").
otp_6842_select_1000(Config) when is_list(Config) ->
- ?line Tab = ets_new(xxx,[ordered_set]),
- ?line [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)],
- ?line AllTrue = lists:duplicate(10,true),
- ?line AllTrue =
+ Tab = ets_new(xxx,[ordered_set]),
+ [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)],
+ AllTrue = lists:duplicate(10,true),
+ AllTrue =
[ length(
element(1,
ets:select(Tab,[{'_',[],['$_']}],X*1000))) =:=
- X*1000 || X <- lists:seq(1,10) ],
- ?line Sequences = [[1000,1000,1000,1000,1000,1000,1000,1000,1000,1000],
+ X*1000 || X <- lists:seq(1,10) ],
+ Sequences = [[1000,1000,1000,1000,1000,1000,1000,1000,1000,1000],
[2000,2000,2000,2000,2000],
[3000,3000,3000,1000],
[4000,4000,2000],
@@ -4769,9 +4769,9 @@ otp_6842_select_1000(Config) when is_list(Config) ->
[8000,2000],
[9000,1000],
[10000]],
- ?line AllTrue = [ check_seq(Tab, ets:select(Tab,[{'_',[],['$_']}],hd(L)),L) ||
+ AllTrue = [ check_seq(Tab, ets:select(Tab,[{'_',[],['$_']}],hd(L)),L) ||
L <- Sequences ],
- ?line ets:delete(Tab),
+ ets:delete(Tab),
ok.
check_seq(_,'$end_of_table',[]) ->
@@ -4805,7 +4805,7 @@ w(_,0, _) -> ok;
w(T,N, Id) ->
ets:insert(T, {N, Id}),
w(T,N-1,Id).
-
+
verify(T, Ids) ->
List = my_tab_to_list(T),
Errors = lists:filter(fun(Bucket) ->
@@ -4835,30 +4835,30 @@ otp_7665_do(Opts) ->
Max = 10,
lists:foreach(fun(N)-> otp_7665_act(Tab,Min,Max,N) end,
lists:seq(Min,Max)),
- ?line true = ets:delete(Tab).
-
+ true = ets:delete(Tab).
+
otp_7665_act(Tab,Min,Max,DelNr) ->
List1 = [{key,N} || N <- lists:seq(Min,Max)],
- ?line true = ets:insert(Tab, List1),
- ?line true = ets:safe_fixtable(Tab, true),
- ?line true = ets:delete_object(Tab, {key,DelNr}),
+ true = ets:insert(Tab, List1),
+ true = ets:safe_fixtable(Tab, true),
+ true = ets:delete_object(Tab, {key,DelNr}),
List2 = lists:delete({key,DelNr}, List1),
%% Now verify that we find all remaining objects
- ?line List2 = ets:lookup(Tab,key),
- ?line EList2 = lists:map(fun({key,N})-> N end,
- List2),
- ?line EList2 = ets:lookup_element(Tab,key,2),
- ?line true = ets:delete(Tab, key),
- ?line [] = ets:lookup(Tab, key),
- ?line true = ets:safe_fixtable(Tab, false),
+ List2 = ets:lookup(Tab,key),
+ EList2 = lists:map(fun({key,N})-> N end,
+ List2),
+ EList2 = ets:lookup_element(Tab,key,2),
+ true = ets:delete(Tab, key),
+ [] = ets:lookup(Tab, key),
+ true = ets:safe_fixtable(Tab, false),
ok.
%% Whitebox testing of meta name table hashing.
meta_wb(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
repeat_for_opts(meta_wb_do),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
meta_wb_do(Opts) ->
@@ -4871,7 +4871,7 @@ meta_wb_do(Opts) ->
Len = length(Names),
OpFuns = {fun meta_wb_new/4, fun meta_wb_delete/4, fun meta_wb_rename/4},
- ?line true = (Len >= 3),
+ true = (Len >= 3),
io:format("Colliding names = ~p\n",[Names]),
F = fun(0,_,_) -> ok;
@@ -4887,38 +4887,38 @@ meta_wb_do(Opts) ->
%% cleanup
lists:foreach(fun(Name)->catch ets:delete(Name) end,
Names).
-
+
meta_wb_new(Name, _, Tabs, Opts) ->
case (catch ets_new(Name,[named_table|Opts])) of
Name ->
- ?line false = lists:member(Name, Tabs),
+ false = lists:member(Name, Tabs),
[Name | Tabs];
{'EXIT',{badarg,_}} ->
- ?line true = lists:member(Name, Tabs),
+ true = lists:member(Name, Tabs),
Tabs
end.
meta_wb_delete(Name, _, Tabs, _) ->
case (catch ets:delete(Name)) of
true ->
- ?line true = lists:member(Name, Tabs),
+ true = lists:member(Name, Tabs),
lists:delete(Name, Tabs);
{'EXIT',{badarg,_}} ->
- ?line false = lists:member(Name, Tabs),
+ false = lists:member(Name, Tabs),
Tabs
end.
meta_wb_rename(Old, New, Tabs, _) ->
case (catch ets:rename(Old,New)) of
New ->
- ?line true = lists:member(Old, Tabs)
+ true = lists:member(Old, Tabs)
andalso not lists:member(New, Tabs),
[New | lists:delete(Old, Tabs)];
{'EXIT',{badarg,_}} ->
- ?line true = not lists:member(Old, Tabs)
+ true = not lists:member(Old, Tabs)
orelse lists:member(New,Tabs),
Tabs
end.
-
-
+
+
colliding_names(Name) ->
erts_debug:set_internal_state(colliding_names, {Name,5}).
@@ -4926,13 +4926,13 @@ colliding_names(Name) ->
%% OTP_6913: Grow and shrink.
grow_shrink(Config) when is_list(Config) ->
- ?line EtsMem = etsmem(),
+ EtsMem = etsmem(),
Set = ets_new(a, [set]),
grow_shrink_0(0, 3071, 3000, 5000, Set),
ets:delete(Set),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
grow_shrink_0(N, _, _, Max, _) when N >= Max ->
ok;
@@ -4955,7 +4955,7 @@ grow_shrink_3(N, ShrinkTo, _) when N =< ShrinkTo ->
grow_shrink_3(N, ShrinkTo, T) ->
true = ets:delete(T, N),
grow_shrink_3(N-1, ShrinkTo, T).
-
+
%% Grow a table that still contains pseudo-deleted objects.
grow_pseudo_deleted(Config) when is_list(Config) ->
only_if_smp(fun() -> grow_pseudo_deleted_do() end).
@@ -4967,17 +4967,17 @@ grow_pseudo_deleted_do() ->
grow_pseudo_deleted_do(Type) ->
process_flag(scheduler,1),
Self = self(),
- ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
+ T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
Mod = 7, Mult = 10000,
filltabint(T,Mod*Mult),
- ?line true = ets:safe_fixtable(T,true),
- ?line Mult = ets:select_delete(T,
- [{{'$1', '_'},
- [{'=:=', {'rem', '$1', Mod}, 0}],
- [true]}]),
+ true = ets:safe_fixtable(T,true),
+ Mult = ets:select_delete(T,
+ [{{'$1', '_'},
+ [{'=:=', {'rem', '$1', Mod}, 0}],
+ [true]}]),
Left = Mult*(Mod-1),
- ?line Left = ets:info(T,size),
- ?line Mult = get_kept_objects(T),
+ Left = ets:info(T,size),
+ Mult = get_kept_objects(T),
filltabstr(T,Mult),
my_spawn_opt(
fun() ->
@@ -4993,7 +4993,7 @@ grow_pseudo_deleted_do(Type) ->
end),
Self ! done
end, [link, {scheduler,2}]),
- ?line start = receive_any(),
+ start = receive_any(),
io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]),
do_tc(fun() ->
true = ets:safe_fixtable(T, false)
@@ -5002,9 +5002,9 @@ grow_pseudo_deleted_do(Type) ->
io:format("Unfix table done in ~p ms. nitems=~p\n",
[Elapsed,ets:info(T, size)])
end),
- ?line false = ets:info(T,fixed),
- ?line 0 = get_kept_objects(T),
- ?line done = receive_any(),
+ false = ets:info(T,fixed),
+ 0 = get_kept_objects(T),
+ done = receive_any(),
%%verify_table_load(T), % may fail if concurrency is poor (genny)
ets:delete(T),
process_flag(scheduler,0).
@@ -5020,16 +5020,16 @@ shrink_pseudo_deleted_do() ->
shrink_pseudo_deleted_do(Type) ->
process_flag(scheduler,1),
Self = self(),
- ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
+ T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
Half = 10000,
filltabint(T,Half*2),
- ?line true = ets:safe_fixtable(T,true),
- ?line Half = ets:select_delete(T,
- [{{'$1', '_'},
- [{'>', '$1', Half}],
- [true]}]),
- ?line Half = ets:info(T,size),
- ?line Half = get_kept_objects(T),
+ true = ets:safe_fixtable(T,true),
+ Half = ets:select_delete(T,
+ [{{'$1', '_'},
+ [{'>', '$1', Half}],
+ [true]}]),
+ Half = ets:info(T,size),
+ Half = get_kept_objects(T),
my_spawn_opt(
fun()-> true = ets:info(T,fixed),
Self ! start,
@@ -5040,10 +5040,10 @@ shrink_pseudo_deleted_do(Type) ->
fun(Elapsed) ->
io:format("Done with delete in ~p ms.\n",
[Elapsed])
- end),
+ end),
Self ! done
end, [link, {scheduler,2}]),
- ?line start = receive_any(),
+ start = receive_any(),
io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]),
do_tc(fun() ->
true = ets:safe_fixtable(T, false)
@@ -5052,19 +5052,19 @@ shrink_pseudo_deleted_do(Type) ->
io:format("Unfix table done in ~p ms. nitems=~p\n",
[Elapsed,ets:info(T, size)])
end),
- ?line false = ets:info(T,fixed),
- ?line 0 = get_kept_objects(T),
- ?line done = receive_any(),
+ false = ets:info(T,fixed),
+ 0 = get_kept_objects(T),
+ done = receive_any(),
%%verify_table_load(T), % may fail if concurrency is poor (genny)
ets:delete(T),
process_flag(scheduler,0).
-
+
meta_lookup_unnamed_read(Config) when is_list(Config) ->
InitF = fun(_) -> Tab = ets_new(unnamed,[]),
- true = ets:insert(Tab,{key,data}),
- Tab
+ true = ets:insert(Tab,{key,data}),
+ Tab
end,
ExecF = fun(Tab) -> [{key,data}] = ets:lookup(Tab,key),
Tab
@@ -5075,7 +5075,7 @@ meta_lookup_unnamed_read(Config) when is_list(Config) ->
meta_lookup_unnamed_write(Config) when is_list(Config) ->
InitF = fun(_) -> Tab = ets_new(unnamed,[]),
- {Tab,0}
+ {Tab,0}
end,
ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
{Tab,N+1}
@@ -5099,8 +5099,8 @@ meta_lookup_named_read(Config) when is_list(Config) ->
meta_lookup_named_write(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
- Tab = ets_new(Name,[named_table]),
- {Tab,0}
+ Tab = ets_new(Name,[named_table]),
+ {Tab,0}
end,
ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
{Tab,N+1}
@@ -5158,18 +5158,18 @@ smp_fixed_delete_do() ->
end,
FiniF = fun(_) -> ok end,
run_workers_do(InitF,ExecF,FiniF,NumOfObjs),
- ?line 0 = ets:info(T,size),
- ?line true = ets:info(T,fixed),
- ?line Buckets = num_of_buckets(T),
- ?line NumOfObjs = get_kept_objects(T),
+ 0 = ets:info(T,size),
+ true = ets:info(T,fixed),
+ Buckets = num_of_buckets(T),
+ NumOfObjs = get_kept_objects(T),
ets:safe_fixtable(T,false),
%% Will fail as unfix does not shrink the table:
- %%?line Mem = ets:info(T,memory),
+ %%Mem = ets:info(T,memory),
%%verify_table_load(T),
ets:delete(T).
num_of_buckets(T) ->
- ?line element(1,ets:info(T,stats)).
+ element(1,ets:info(T,stats)).
%% Fixate hash table while other process is busy doing unfix.
smp_unfix_fix(Config) when is_list(Config) ->
@@ -5185,15 +5185,15 @@ smp_unfix_fix_do() ->
filltabint(T,NumOfObjs),
ets:safe_fixtable(T,true),
Buckets = num_of_buckets(T),
- ?line Deleted = ets:select_delete(T,[{{'$1', '_'},
- [{'=<','$1', Deleted}],
- [true]}]),
- ?line Buckets = num_of_buckets(T),
+ Deleted = ets:select_delete(T,[{{'$1', '_'},
+ [{'=<','$1', Deleted}],
+ [true]}]),
+ Buckets = num_of_buckets(T),
Left = NumOfObjs - Deleted,
- ?line Left = ets:info(T,size),
- ?line true = ets:info(T,fixed),
- ?line Deleted = get_kept_objects(T),
-
+ Left = ets:info(T,size),
+ true = ets:info(T,fixed),
+ Deleted = get_kept_objects(T),
+
{Child, Mref} =
my_spawn_opt(
fun()->
@@ -5220,9 +5220,9 @@ smp_unfix_fix_do() ->
done = receive_any()
end,
[link, monitor, {scheduler,2}]),
-
- ?line start = receive_any(),
- ?line true = ets:info(T,fixed),
+
+ start = receive_any(),
+ true = ets:info(T,fixed),
io:put_chars("Parent starting to unfix... ~p\n"),
do_tc(fun() ->
ets:safe_fixtable(T, false)
@@ -5233,8 +5233,8 @@ smp_unfix_fix_do() ->
end),
Child ! done,
{'DOWN', Mref, process, Child, normal} = receive_any(),
- ?line false = ets:info(T,fixed),
- ?line 0 = get_kept_objects(T),
+ false = ets:info(T,fixed),
+ 0 = get_kept_objects(T),
%%verify_table_load(T),
ets:delete(T),
process_flag(scheduler,0).
@@ -5270,8 +5270,8 @@ otp_8166_do(WC) ->
{'DOWN', ReaderMref, process, ReaderPid, normal} = receive_any(),
ZombieCrPid ! quit,
{'DOWN', ZombieCrMref, process, ZombieCrPid, normal} = receive_any(),
- ?line false = ets:info(T,fixed),
- ?line 0 = get_kept_objects(T),
+ false = ets:info(T,fixed),
+ 0 = get_kept_objects(T),
%%verify_table_load(T),
ets:delete(T),
process_flag(scheduler,0).
@@ -5312,9 +5312,9 @@ otp_8166_zombie_creator(T,Deleted) ->
{loop,Pid} ->
filltabint(T,Deleted),
ets:safe_fixtable(T,true),
- ?line Deleted = ets:select_delete(T,[{{'$1', '_'},
- [{'=<','$1', Deleted}],
- [true]}]),
+ Deleted = ets:select_delete(T,[{{'$1', '_'},
+ [{'=<','$1', Deleted}],
+ [true]}]),
Pid ! zombies_created,
repeat_while(fun() -> case ets:info(T,safe_fixed_monotonic_time) of
{_,[_P1,_P2]} ->
@@ -5332,41 +5332,41 @@ otp_8166_zombie_creator(T,Deleted) ->
io:format("ignore unfix in outer loop?\n",[]),
otp_8166_zombie_creator(T,Deleted)
end.
-
-
-
+
+
+
verify_table_load(T) ->
- ?line Stats = ets:info(T,stats),
- ?line {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
- ?line ok = if
- AvgLen > 7 ->
- io:format("Table overloaded: Stats=~p\n~p\n",
- [Stats, ets:info(T)]),
- false;
-
- Buckets>256, AvgLen < 6 ->
- io:format("Table underloaded: Stats=~p\n~p\n",
- [Stats, ets:info(T)]),
- false;
-
- StdDev > ExpSD*2 ->
- io:format("Too large standard deviation (poor hashing?),"
- " stats=~p\n~p\n",[Stats, ets:info(T)]),
- false;
-
- true ->
- io:format("Stats = ~p\n",[Stats]),
- ok
- end.
-
-
+ Stats = ets:info(T,stats),
+ {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
+ ok = if
+ AvgLen > 7 ->
+ io:format("Table overloaded: Stats=~p\n~p\n",
+ [Stats, ets:info(T)]),
+ false;
+
+ Buckets>256, AvgLen < 6 ->
+ io:format("Table underloaded: Stats=~p\n~p\n",
+ [Stats, ets:info(T)]),
+ false;
+
+ StdDev > ExpSD*2 ->
+ io:format("Too large standard deviation (poor hashing?),"
+ " stats=~p\n~p\n",[Stats, ets:info(T)]),
+ false;
+
+ true ->
+ io:format("Stats = ~p\n",[Stats]),
+ ok
+ end.
+
+
%% ets:select on a tree with NIL key object.
otp_8732(Config) when is_list(Config) ->
Tab = ets_new(noname,[ordered_set]),
filltabstr(Tab,999),
ets:insert(Tab,{[],"nasty NIL object"}),
- ?line [] = ets:match(Tab,{'_',nomatch}), %% Will hang if bug not fixed
+ [] = ets:match(Tab,{'_',nomatch}), %% Will hang if bug not fixed
ok.
@@ -5391,38 +5391,38 @@ smp_select_delete(Config) when is_list(Config) ->
_ ->
Key = rand:uniform(10000),
Eq = Key rem Mod,
- ?line case ets:insert_new(T,{Key,Key}) of
- true ->
- Diffs1 = setelement(Eq+1, Diffs0,
- element(Eq+1,Diffs0)+1),
- Diffs1;
- false -> Diffs0
- end
+ case ets:insert_new(T,{Key,Key}) of
+ true ->
+ Diffs1 = setelement(Eq+1, Diffs0,
+ element(Eq+1,Diffs0)+1),
+ Diffs1;
+ false -> Diffs0
+ end
end
end,
FiniF = fun(Result) -> Result end,
Results = run_workers_do(InitF,ExecF,FiniF,20000),
- ?line TotCnts = lists:foldl(fun(Diffs, Sum) -> add_lists(Sum,tuple_to_list(Diffs)) end,
- lists:duplicate(Mod, 0), Results),
+ TotCnts = lists:foldl(fun(Diffs, Sum) -> add_lists(Sum,tuple_to_list(Diffs)) end,
+ lists:duplicate(Mod, 0), Results),
io:format("TotCnts = ~p\n",[TotCnts]),
- ?line LeftInTab = lists:foldl(fun(N,Sum) -> Sum+N end,
- 0, TotCnts),
+ LeftInTab = lists:foldl(fun(N,Sum) -> Sum+N end,
+ 0, TotCnts),
io:format("LeftInTab = ~p\n",[LeftInTab]),
- ?line LeftInTab = ets:info(T,size),
+ LeftInTab = ets:info(T,size),
lists:foldl(fun(Cnt,Eq) ->
WasCnt = ets:select_count(T,
[{{'_', '$1'},
[{'=:=', {'rem', '$1', Mod}, Eq}],
[true]}]),
io:format("~p: ~p =?= ~p\n",[Eq,Cnt,WasCnt]),
- ?line Cnt = WasCnt,
+ Cnt = WasCnt,
Eq+1
end,
0, TotCnts),
verify_table_load(T),
- ?line LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
- ?line 0 = ets:info(T,size),
- ?line false = ets:info(T,fixed),
+ LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
+ 0 = ets:info(T,size),
+ false = ets:info(T,fixed),
ets:delete(T).
%% Test different types.
@@ -5432,24 +5432,24 @@ types(Config) when is_list(Config) ->
types_do(Opts) ->
EtsMem = etsmem(),
- ?line T = ets_new(xxx,Opts),
+ T = ets_new(xxx,Opts),
Fun = fun(Term) ->
- ets:insert(T,{Term}),
- ?line [{Term}] = ets:lookup(T,Term),
- ets:insert(T,{Term,xxx}),
- ?line [{Term,xxx}] = ets:lookup(T,Term),
- ets:insert(T,{Term,"xxx"}),
- ?line [{Term,"xxx"}] = ets:lookup(T,Term),
- ets:insert(T,{xxx,Term}),
- ?line [{xxx,Term}] = ets:lookup(T,xxx),
- ets:insert(T,{"xxx",Term}),
- ?line [{"xxx",Term}] = ets:lookup(T,"xxx"),
- ets:delete_all_objects(T),
- ?line 0 = ets:info(T,size)
+ ets:insert(T,{Term}),
+ [{Term}] = ets:lookup(T,Term),
+ ets:insert(T,{Term,xxx}),
+ [{Term,xxx}] = ets:lookup(T,Term),
+ ets:insert(T,{Term,"xxx"}),
+ [{Term,"xxx"}] = ets:lookup(T,Term),
+ ets:insert(T,{xxx,Term}),
+ [{xxx,Term}] = ets:lookup(T,xxx),
+ ets:insert(T,{"xxx",Term}),
+ [{"xxx",Term}] = ets:lookup(T,"xxx"),
+ ets:delete_all_objects(T),
+ 0 = ets:info(T,size)
end,
test_terms(Fun, strict),
ets:delete(T),
- ?line verify_etsmem(EtsMem).
+ verify_etsmem(EtsMem).
%% OTP-9932: Memory overwrite when inserting large integers in compressed bag.
@@ -5466,7 +5466,7 @@ otp_9932(Config) when is_list(Config) ->
end,
lists:foreach(Fun, lists:seq(0, 16)),
ets:delete(T).
-
+
%% vm-deadlock caused by race between ets:delete and others on
%% write_concurrency table.
@@ -5496,10 +5496,10 @@ otp_9423(Config) when is_list(Config) ->
[P ! stop || P <- Pids],
wait_pids(Pids),
ok;
-
+
Skipped -> Skipped
end.
-
+
%% Corrupted binary in compressed table
otp_10182(Config) when is_list(Config) ->
@@ -5527,7 +5527,7 @@ ets_all_run() ->
ets:delete(Table),
false = lists:member(Table, ets:all()),
ets_all_run().
-
+
take(Config) when is_list(Config) ->
%% Simple test for set tables.
@@ -5590,9 +5590,9 @@ run_workers(InitF,ExecF,FiniF,Laps, Exclude) ->
run_workers_do(InitF,ExecF,FiniF,Laps) ->
run_workers_do(InitF,ExecF,FiniF,Laps, 0).
run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
- ?line NumOfProcs = case erlang:system_info(schedulers) of
- N when (N > Exclude) -> N - Exclude
- end,
+ NumOfProcs = case erlang:system_info(schedulers) of
+ N when (N > Exclude) -> N - Exclude
+ end,
io:format("smp starting ~p workers\n",[NumOfProcs]),
Seeds = [{ProcN,rand:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
Parent = self(),
@@ -5602,7 +5602,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
infinite -> Pids;
_ -> wait_pids(Pids)
end.
-
+
worker({ProcN,Seed}, InitF, ExecF, FiniF, Laps, Parent, NumOfProcs) ->
io:format("smp worker ~p, seed=~p~n",[self(),Seed]),
rand:seed(exsplus, {Seed,Seed,Seed}),
@@ -5620,7 +5620,7 @@ worker_loop(infinite, ExecF, State) ->
worker_loop(infinite,ExecF,ExecF(State));
worker_loop(N, ExecF, State) ->
worker_loop(N-1,ExecF,ExecF(State)).
-
+
wait_pids(Pids) ->
wait_pids(Pids,[]).
wait_pids([],Acc) ->
@@ -5628,7 +5628,7 @@ wait_pids([],Acc) ->
wait_pids(Pids, Acc) ->
receive
{Pid,Result} ->
- ?line true = lists:member(Pid,Pids),
+ true = lists:member(Pid,Pids),
Others = lists:delete(Pid,Pids),
io:format("wait_pid got ~p from ~p, still waiting for ~p\n",[Result,Pid,Others]),
wait_pids(Others,[Result | Acc])
@@ -5654,7 +5654,7 @@ wait_for_memory_deallocations() ->
erts_debug:set_internal_state(available_internal_state, true),
wait_for_memory_deallocations()
end.
-
+
etsmem() ->
wait_for_memory_deallocations(),
@@ -5667,35 +5667,35 @@ etsmem() ->
ErlangMemoryEts = try erlang:memory(ets) catch error:notsup -> notsup end,
Mem =
- {ErlangMemoryEts,
- case EtsAllocInfo of
- false -> undefined;
- MemInfo ->
- CS = lists:foldl(
- fun ({instance, _, L}, Acc) ->
- {value,{mbcs,MBCS}} = lists:keysearch(mbcs, 1, L),
- {value,{sbcs,SBCS}} = lists:keysearch(sbcs, 1, L),
- NewAcc = [MBCS, SBCS | Acc],
- case lists:keysearch(mbcs_pool, 1, L) of
- {value,{mbcs_pool, MBCS_POOL}} ->
- [MBCS_POOL|NewAcc];
- _ -> NewAcc
- end
- end,
- [],
- MemInfo),
- lists:foldl(
- fun(L, {Bl0,BlSz0}) ->
- {value,BlTup} = lists:keysearch(blocks, 1, L),
- blocks = element(1, BlTup),
- Bl = element(2, BlTup),
- {value,BlSzTup} = lists:keysearch(blocks_size, 1, L),
- blocks_size = element(1, BlSzTup),
- BlSz = element(2, BlSzTup),
- {Bl0+Bl,BlSz0+BlSz}
- end, {0,0}, CS)
- end},
- {Mem,AllTabs}.
+ {ErlangMemoryEts,
+ case EtsAllocInfo of
+ false -> undefined;
+ MemInfo ->
+ CS = lists:foldl(
+ fun ({instance, _, L}, Acc) ->
+ {value,{mbcs,MBCS}} = lists:keysearch(mbcs, 1, L),
+ {value,{sbcs,SBCS}} = lists:keysearch(sbcs, 1, L),
+ NewAcc = [MBCS, SBCS | Acc],
+ case lists:keysearch(mbcs_pool, 1, L) of
+ {value,{mbcs_pool, MBCS_POOL}} ->
+ [MBCS_POOL|NewAcc];
+ _ -> NewAcc
+ end
+ end,
+ [],
+ MemInfo),
+ lists:foldl(
+ fun(L, {Bl0,BlSz0}) ->
+ {value,BlTup} = lists:keysearch(blocks, 1, L),
+ blocks = element(1, BlTup),
+ Bl = element(2, BlTup),
+ {value,BlSzTup} = lists:keysearch(blocks_size, 1, L),
+ blocks_size = element(1, BlSzTup),
+ BlSz = element(2, BlSzTup),
+ {Bl0+Bl,BlSz0+BlSz}
+ end, {0,0}, CS)
+ end},
+ {Mem,AllTabs}.
verify_etsmem({MemInfo,AllTabs}) ->
wait_for_test_procs(),
@@ -5881,7 +5881,7 @@ receive_any_spinning(Loops,0,Tries) ->
end;
receive_any_spinning(Loops, N, Tries) when N>0 ->
receive_any_spinning(Loops, N-1, Tries).
-
+
spawn_monitor_with_pid(Pid, Fun) when is_pid(Pid) ->
@@ -5916,130 +5916,130 @@ only_if_smp(Schedulers, Func) ->
-define(heap_binary_size, 64).
test_terms(Test_Func, Mode) ->
garbage_collect(),
- ?line Pib0 = process_info(self(),binary),
-
- ?line Test_Func(atom),
- ?line Test_Func(''),
- ?line Test_Func('a'),
- ?line Test_Func('ab'),
- ?line Test_Func('abc'),
- ?line Test_Func('abcd'),
- ?line Test_Func('abcde'),
- ?line Test_Func('abcdef'),
- ?line Test_Func('abcdefg'),
- ?line Test_Func('abcdefgh'),
-
- ?line Test_Func(fun() -> ok end),
+ Pib0 = process_info(self(),binary),
+
+ Test_Func(atom),
+ Test_Func(''),
+ Test_Func('a'),
+ Test_Func('ab'),
+ Test_Func('abc'),
+ Test_Func('abcd'),
+ Test_Func('abcde'),
+ Test_Func('abcdef'),
+ Test_Func('abcdefg'),
+ Test_Func('abcdefgh'),
+
+ Test_Func(fun() -> ok end),
X = id([a,{b,c},c]),
Y = id({x,y,z}),
Z = id(1 bsl 8*257),
- ?line Test_Func(fun() -> X end),
- ?line Test_Func(fun() -> {X,Y} end),
- ?line Test_Func([fun() -> {X,Y,Z} end,
- fun() -> {Z,X,Y} end,
- fun() -> {Y,Z,X} end]),
-
- ?line Test_Func({trace_ts,{even_bigger,{some_data,fun() -> ok end}},{1,2,3}}),
- ?line Test_Func({trace_ts,{even_bigger,{some_data,<<1,2,3,4,5,6,7,8,9,10>>}},
- {1,2,3}}),
-
- ?line Test_Func(1),
- ?line Test_Func(42),
- ?line Test_Func(-23),
- ?line Test_Func(256),
- ?line Test_Func(25555),
- ?line Test_Func(-3333),
-
- ?line Test_Func(1.0),
-
- ?line Test_Func(183749783987483978498378478393874),
- ?line Test_Func(-37894183749783987483978498378478393874),
+ Test_Func(fun() -> X end),
+ Test_Func(fun() -> {X,Y} end),
+ Test_Func([fun() -> {X,Y,Z} end,
+ fun() -> {Z,X,Y} end,
+ fun() -> {Y,Z,X} end]),
+
+ Test_Func({trace_ts,{even_bigger,{some_data,fun() -> ok end}},{1,2,3}}),
+ Test_Func({trace_ts,{even_bigger,{some_data,<<1,2,3,4,5,6,7,8,9,10>>}},
+ {1,2,3}}),
+
+ Test_Func(1),
+ Test_Func(42),
+ Test_Func(-23),
+ Test_Func(256),
+ Test_Func(25555),
+ Test_Func(-3333),
+
+ Test_Func(1.0),
+
+ Test_Func(183749783987483978498378478393874),
+ Test_Func(-37894183749783987483978498378478393874),
Very_Big = very_big_num(),
- ?line Test_Func(Very_Big),
- ?line Test_Func(-Very_Big+1),
+ Test_Func(Very_Big),
+ Test_Func(-Very_Big+1),
- ?line Test_Func([]),
- ?line Test_Func("abcdef"),
- ?line Test_Func([a, b, 1, 2]),
- ?line Test_Func([a|b]),
+ Test_Func([]),
+ Test_Func("abcdef"),
+ Test_Func([a, b, 1, 2]),
+ Test_Func([a|b]),
- ?line Test_Func({}),
- ?line Test_Func({1}),
- ?line Test_Func({a, b}),
- ?line Test_Func({a, b, c}),
- ?line Test_Func(list_to_tuple(lists:seq(0, 255))),
- ?line Test_Func(list_to_tuple(lists:seq(0, 256))),
+ Test_Func({}),
+ Test_Func({1}),
+ Test_Func({a, b}),
+ Test_Func({a, b, c}),
+ Test_Func(list_to_tuple(lists:seq(0, 255))),
+ Test_Func(list_to_tuple(lists:seq(0, 256))),
- ?line Test_Func(make_ref()),
- ?line Test_Func([make_ref(), make_ref()]),
+ Test_Func(make_ref()),
+ Test_Func([make_ref(), make_ref()]),
- ?line Test_Func(make_port()),
+ Test_Func(make_port()),
- ?line Test_Func(make_pid()),
- ?line Test_Func(make_ext_pid()),
- ?line Test_Func(make_ext_port()),
- ?line Test_Func(make_ext_ref()),
+ Test_Func(make_pid()),
+ Test_Func(make_ext_pid()),
+ Test_Func(make_ext_port()),
+ Test_Func(make_ext_ref()),
Bin0 = list_to_binary(lists:seq(0, 14)),
- ?line Test_Func(Bin0),
+ Test_Func(Bin0),
Bin1 = list_to_binary(lists:seq(0, ?heap_binary_size)),
- ?line Test_Func(Bin1),
+ Test_Func(Bin1),
Bin2 = list_to_binary(lists:seq(0, ?heap_binary_size+1)),
- ?line Test_Func(Bin2),
+ Test_Func(Bin2),
Bin3 = list_to_binary(lists:seq(0, 255)),
garbage_collect(),
Pib = process_info(self(),binary),
- ?line Test_Func(Bin3),
+ Test_Func(Bin3),
garbage_collect(),
case Mode of
- strict -> ?line Pib = process_info(self(),binary);
+ strict -> Pib = process_info(self(),binary);
skip_refc_check -> ok
end,
- ?line Test_Func(make_unaligned_sub_binary(Bin0)),
- ?line Test_Func(make_unaligned_sub_binary(Bin1)),
- ?line Test_Func(make_unaligned_sub_binary(Bin2)),
- ?line Test_Func(make_unaligned_sub_binary(Bin3)),
-
- ?line Test_Func(make_sub_binary(lists:seq(42, 43))),
- ?line Test_Func(make_sub_binary([42,43,44])),
- ?line Test_Func(make_sub_binary([42,43,44,45])),
- ?line Test_Func(make_sub_binary([42,43,44,45,46])),
- ?line Test_Func(make_sub_binary([42,43,44,45,46,47])),
- ?line Test_Func(make_sub_binary([42,43,44,45,46,47,48])),
- ?line Test_Func(make_sub_binary(lists:seq(42, 49))),
- ?line Test_Func(make_sub_binary(lists:seq(0, 14))),
- ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size))),
- ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size+1))),
- ?line Test_Func(make_sub_binary(lists:seq(0, 255))),
-
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 43))),
- ?line Test_Func(make_unaligned_sub_binary([42,43,44])),
- ?line Test_Func(make_unaligned_sub_binary([42,43,44,45])),
- ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46])),
- ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47])),
- ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47,48])),
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 49))),
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 14))),
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size))),
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size+1))),
- ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 255))),
+ Test_Func(make_unaligned_sub_binary(Bin0)),
+ Test_Func(make_unaligned_sub_binary(Bin1)),
+ Test_Func(make_unaligned_sub_binary(Bin2)),
+ Test_Func(make_unaligned_sub_binary(Bin3)),
+
+ Test_Func(make_sub_binary(lists:seq(42, 43))),
+ Test_Func(make_sub_binary([42,43,44])),
+ Test_Func(make_sub_binary([42,43,44,45])),
+ Test_Func(make_sub_binary([42,43,44,45,46])),
+ Test_Func(make_sub_binary([42,43,44,45,46,47])),
+ Test_Func(make_sub_binary([42,43,44,45,46,47,48])),
+ Test_Func(make_sub_binary(lists:seq(42, 49))),
+ Test_Func(make_sub_binary(lists:seq(0, 14))),
+ Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size))),
+ Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size+1))),
+ Test_Func(make_sub_binary(lists:seq(0, 255))),
+
+ Test_Func(make_unaligned_sub_binary(lists:seq(42, 43))),
+ Test_Func(make_unaligned_sub_binary([42,43,44])),
+ Test_Func(make_unaligned_sub_binary([42,43,44,45])),
+ Test_Func(make_unaligned_sub_binary([42,43,44,45,46])),
+ Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47])),
+ Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47,48])),
+ Test_Func(make_unaligned_sub_binary(lists:seq(42, 49))),
+ Test_Func(make_unaligned_sub_binary(lists:seq(0, 14))),
+ Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size))),
+ Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size+1))),
+ Test_Func(make_unaligned_sub_binary(lists:seq(0, 255))),
%% Bit level binaries.
- ?line Test_Func(<<1:1>>),
- ?line Test_Func(<<2:2>>),
- ?line Test_Func(<<42:10>>),
- ?line Test_Func(list_to_bitstring([<<5:6>>|lists:seq(0, 255)])),
+ Test_Func(<<1:1>>),
+ Test_Func(<<2:2>>),
+ Test_Func(<<42:10>>),
+ Test_Func(list_to_bitstring([<<5:6>>|lists:seq(0, 255)])),
- ?line Test_Func(F = fun(A) -> 42*A end),
- ?line Test_Func(lists:duplicate(32, F)),
+ Test_Func(F = fun(A) -> 42*A end),
+ Test_Func(lists:duplicate(32, F)),
- ?line Test_Func(FF = fun binary_SUITE:all/1),
- ?line Test_Func(lists:duplicate(32, FF)),
+ Test_Func(FF = fun binary_SUITE:all/1),
+ Test_Func(lists:duplicate(32, FF)),
garbage_collect(),
case Mode of
- strict -> ?line Pib0 = process_info(self(),binary);
+ strict -> Pib0 = process_info(self(),binary);
skip_refc_check -> ok
end,
ok.
@@ -6051,18 +6051,18 @@ very_big_num() ->
very_big_num(33, 1).
very_big_num(Left, Result) when Left > 0 ->
- ?line very_big_num(Left-1, Result*256);
+ very_big_num(Left-1, Result*256);
very_big_num(0, Result) ->
- ?line Result.
+ Result.
make_port() ->
- ?line open_port({spawn, "efile"}, [eof]).
+ open_port({spawn, "efile"}, [eof]).
make_pid() ->
- ?line spawn_link(?MODULE, sleeper, []).
+ spawn_link(?MODULE, sleeper, []).
sleeper() ->
- ?line receive after infinity -> ok end.
+ receive after infinity -> ok end.
make_ext_pid() ->
{Pid, _, _} = get(externals),
@@ -6120,11 +6120,11 @@ mk_pid({NodeName, Creation}, Number, Serial) when is_atom(NodeName) ->
mk_pid({NodeNameExt, Creation}, Number, Serial);
mk_pid({NodeNameExt, Creation}, Number, Serial) ->
case catch binary_to_term(list_to_binary([?VERSION_MAGIC,
- ?PID_EXT,
- NodeNameExt,
- uint32_be(Number),
- uint32_be(Serial),
- uint8(Creation)])) of
+ ?PID_EXT,
+ NodeNameExt,
+ uint32_be(Number),
+ uint32_be(Serial),
+ uint8(Creation)])) of
Pid when is_pid(Pid) ->
Pid;
{'EXIT', {badarg, _}} ->
@@ -6214,7 +6214,7 @@ repeat_for_opts(F, [], Acc) ->
_ -> [RV | RV_Acc]
end
end
- end, [], Acc);
+ end, [], Acc);
repeat_for_opts(F, [OptList | Tail], []) when is_list(OptList) ->
repeat_for_opts(F, Tail, [[Opt] || Opt <- OptList]);
repeat_for_opts(F, [OptList | Tail], AccList) when is_list(OptList) ->
@@ -6226,7 +6226,7 @@ repeat_for_opts_atom2list(all_types) -> [set,ordered_set,bag,duplicate_bag];
repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}];
repeat_for_opts_atom2list(read_concurrency) -> [{read_concurrency,false},{read_concurrency,true}];
repeat_for_opts_atom2list(compressed) -> [compressed,void].
-
+
ets_new(Name, Opts) ->
%%ets:new(Name, [compressed | Opts]).
ets:new(Name, Opts).
diff --git a/lib/stdlib/test/ets_tough_SUITE.erl b/lib/stdlib/test/ets_tough_SUITE.erl
index 90911f86ef..1cdaaed0f0 100644
--- a/lib/stdlib/test/ets_tough_SUITE.erl
+++ b/lib/stdlib/test/ets_tough_SUITE.erl
@@ -61,18 +61,18 @@ end_per_testcase(_Func, _Config) ->
ex1(Config) when is_list(Config) ->
- ?line ets:new(?GLOBAL_PARAMS,[named_table,public]),
- ?line ets:insert(?GLOBAL_PARAMS,{a,set}),
- ?line ets:insert(?GLOBAL_PARAMS,{b,set}),
- ?line ex1_sub(Config),
- ?line ets:insert(?GLOBAL_PARAMS,{a,ordered_set}),
- ?line ets:insert(?GLOBAL_PARAMS,{b,set}),
- ?line ex1_sub(Config),
- ?line ets:insert(?GLOBAL_PARAMS,{a,ordered_set}),
- ?line ets:insert(?GLOBAL_PARAMS,{b,ordered_set}),
- ?line ex1_sub(Config).
-
-
+ ets:new(?GLOBAL_PARAMS,[named_table,public]),
+ ets:insert(?GLOBAL_PARAMS,{a,set}),
+ ets:insert(?GLOBAL_PARAMS,{b,set}),
+ ex1_sub(Config),
+ ets:insert(?GLOBAL_PARAMS,{a,ordered_set}),
+ ets:insert(?GLOBAL_PARAMS,{b,set}),
+ ex1_sub(Config),
+ ets:insert(?GLOBAL_PARAMS,{a,ordered_set}),
+ ets:insert(?GLOBAL_PARAMS,{b,ordered_set}),
+ ex1_sub(Config).
+
+
ex1_sub(Config) ->
@@ -187,9 +187,9 @@ operate(dump,A,_B) ->
NewTicket = ddump_next(A,Units,Ticket),
put(dump_ticket,NewTicket),
_Result = case NewTicket of
- done -> done;
- _ -> dump_more
- end,
+ done -> done;
+ _ -> dump_more
+ end,
?DEBUG(io:format("dump ~w (~w)\n",[Units,_Result]));
_ ->
DumpDir = get(dump_dir),
@@ -210,7 +210,7 @@ operate(dump,A,_B) ->
ok
end
end.
-
+
random_operation() ->
Ops = {get,put,erase,dirty_get,dump},
random_element(Ops).
@@ -245,7 +245,7 @@ show_table(N) ->
_ ->
error
end.
-
+
show_entries(Fd) ->
case phys_read_len(Fd) of
{ok,Len} ->
@@ -369,7 +369,7 @@ derase(ServerPid,Class,Key) ->
dget_class(ServerPid,Class,Condition) ->
gen_server:call(ServerPid,
- {handle_get_class,Class,Condition},infinity).
+ {handle_get_class,Class,Condition},infinity).
%%% derase_class(ServerPid,Class) -> ok
%%%
@@ -827,7 +827,7 @@ table_lookup_batch([],_Class,_Cond) ->
[];
table_lookup_batch([Table|Tables],Class,Cond) ->
table_lookup_batch([],Tables,Table,ets:first(Table),Class,Cond,[]).
-
+
table_lookup_batch(_Passed,[],_,'$end_of_table',_Class,_Cond,Ack) ->
Ack;
table_lookup_batch(Passed,[NewTable|Tables],Table,'$end_of_table',
@@ -837,7 +837,7 @@ table_lookup_batch(Passed,[NewTable|Tables],Table,'$end_of_table',
table_lookup_batch(Passed,Tables,Table,?ERASE_MARK(Key),Class,Cond,Ack) ->
table_lookup_batch(Passed,Tables,Table,?ets_next(Table,?ERASE_MARK(Key)),
Class,Cond,Ack);
-
+
table_lookup_batch(Passed,Tables,Table,Key,Class,Cond,Ack) ->
NewAck =
case table_lookup(Passed,Key) of
@@ -1068,7 +1068,7 @@ phys_load_table(DumpDir,N,Tab) ->
Other ->
{error,{open_error,Other}}
end.
-
+
phys_load_entries(Fd,Tab) ->
case phys_read_len(Fd) of
{ok,Len} ->
diff --git a/lib/stdlib/test/file_sorter_SUITE.erl b/lib/stdlib/test/file_sorter_SUITE.erl
index d9805fb6f5..2e7499c058 100644
--- a/lib/stdlib/test/file_sorter_SUITE.erl
+++ b/lib/stdlib/test/file_sorter_SUITE.erl
@@ -89,47 +89,47 @@ basic(Config) when is_list(Config) ->
Foo = outfile("foo", Config),
P0 = pps(),
- ?line F1s = [F1] = to_files([[]], Fmt, Config),
- ?line ok = file_sorter:sort(F1),
- ?line [] = from_files(F1, Fmt),
- ?line ok = file_sorter:keysort(17, F1),
- ?line [] = from_files(F1, Fmt),
- ?line ok = file_sorter:merge(F1s, Foo),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keymerge(17, F1s, Foo),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files([Foo | F1s]),
-
- ?line [F2] = to_files([[foo,bar]], Fmt, Config),
- ?line ok = file_sorter:sort([F2], F2, Arg),
- ?line [bar,foo] = from_files(F2, Fmt),
- ?line delete_files(F2),
-
- ?line Fs1 = to_files([[foo],[bar]], Fmt, Config),
- ?line ok = file_sorter:sort(Fs1, Foo, Arg),
- ?line [bar,foo] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:merge(Fs1, Foo, Arg),
- ?line [bar,foo] = from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs1]),
-
- ?line Fmt2 = binary_term,
- ?line Arg2 = {format, Fmt2},
- ?line [F3] = to_files([[{foo,1},{bar,2}]], Fmt2, Config),
- ?line ok = file_sorter:keysort([2], [F3], F3, Arg2),
- ?line [{foo,1},{bar,2}] = from_files(F3, Fmt2),
- ?line delete_files(F3),
-
- ?line Fs2 = to_files([[{foo,1}],[{bar,2}]], Fmt2, Config),
- ?line ok = file_sorter:keysort(1, Fs2, Foo, Arg2),
- ?line [{bar,2},{foo,1}] = from_files(Foo, Fmt2),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keymerge(1, Fs2, Foo, Arg2),
- ?line [{bar,2},{foo,1}] = from_files(Foo, Fmt2),
- ?line delete_files([Foo | Fs2]),
-
- ?line true = P0 =:= pps(),
+ F1s = [F1] = to_files([[]], Fmt, Config),
+ ok = file_sorter:sort(F1),
+ [] = from_files(F1, Fmt),
+ ok = file_sorter:keysort(17, F1),
+ [] = from_files(F1, Fmt),
+ ok = file_sorter:merge(F1s, Foo),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:keymerge(17, F1s, Foo),
+ [] = from_files(Foo, Fmt),
+ delete_files([Foo | F1s]),
+
+ [F2] = to_files([[foo,bar]], Fmt, Config),
+ ok = file_sorter:sort([F2], F2, Arg),
+ [bar,foo] = from_files(F2, Fmt),
+ delete_files(F2),
+
+ Fs1 = to_files([[foo],[bar]], Fmt, Config),
+ ok = file_sorter:sort(Fs1, Foo, Arg),
+ [bar,foo] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:merge(Fs1, Foo, Arg),
+ [bar,foo] = from_files(Foo, Fmt),
+ delete_files([Foo | Fs1]),
+
+ Fmt2 = binary_term,
+ Arg2 = {format, Fmt2},
+ [F3] = to_files([[{foo,1},{bar,2}]], Fmt2, Config),
+ ok = file_sorter:keysort([2], [F3], F3, Arg2),
+ [{foo,1},{bar,2}] = from_files(F3, Fmt2),
+ delete_files(F3),
+
+ Fs2 = to_files([[{foo,1}],[{bar,2}]], Fmt2, Config),
+ ok = file_sorter:keysort(1, Fs2, Foo, Arg2),
+ [{bar,2},{foo,1}] = from_files(Foo, Fmt2),
+ delete_files(Foo),
+ ok = file_sorter:keymerge(1, Fs2, Foo, Arg2),
+ [{bar,2},{foo,1}] = from_files(Foo, Fmt2),
+ delete_files([Foo | Fs2]),
+
+ true = P0 =:= pps(),
ok.
@@ -138,264 +138,264 @@ badarg(Config) when is_list(Config) ->
PrivDir = ?privdir(Config),
BadFile = filename:join(PrivDir, "not_a_file"),
ABadFile = filename:absname(BadFile),
- ?line file:delete(BadFile),
- ?line {error,{file_error,ABadFile,enoent}} =
+ file:delete(BadFile),
+ {error,{file_error,ABadFile,enoent}} =
file_sorter:sort(BadFile),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:sort({flipp})),
- ?line {error,{file_error,ABadFile,enoent}} =
+ {error,{file_error,ABadFile,enoent}} =
file_sorter:keysort(1, BadFile),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:keysort(1, {flipp})),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:merge([{flipp}],foo)),
- ?line {error,{file_error,ABadFile,enoent}} =
+ {error,{file_error,ABadFile,enoent}} =
file_sorter:keymerge(1,[BadFile],foo),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:keymerge(1,[{flipp}],foo)),
- ?line {'EXIT', {{badarg, _}, _}} =
+ {'EXIT', {{badarg, _}, _}} =
(catch file_sorter:merge(fun(X) -> X end, foo)),
- ?line {'EXIT', {{badarg, _}, _}} =
+ {'EXIT', {{badarg, _}, _}} =
(catch file_sorter:keymerge(1, fun(X) -> X end, foo)),
- ?line {error,{file_error,ABadFile,enoent}} =
+ {error,{file_error,ABadFile,enoent}} =
file_sorter:check(BadFile),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:check({flipp})),
- ?line {error,{file_error,ABadFile,enoent}} =
+ {error,{file_error,ABadFile,enoent}} =
file_sorter:keycheck(1, BadFile),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:keycheck(1, {flipp})),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:check([{flipp}],foo)),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:keycheck(1,[{flipp}],foo)),
- ?line {'EXIT', {{badarg, _}, _}} =
+ {'EXIT', {{badarg, _}, _}} =
(catch file_sorter:check(fun(X) -> X end, foo)),
- ?line {'EXIT', {{badarg, _}, _}} =
+ {'EXIT', {{badarg, _}, _}} =
(catch file_sorter:keycheck(1, fun(X) -> X end, foo)),
- ?line Fs1 = to_files([[1,2,3]], binary_term, Config),
- ?line {'EXIT', {{badarg, flipp}, _}} =
+ Fs1 = to_files([[1,2,3]], binary_term, Config),
+ {'EXIT', {{badarg, flipp}, _}} =
(catch file_sorter:check(Fs1 ++ flipp, [])),
[F1] = Fs1,
- ?line {error,{file_error,_,_}} =
+ {error,{file_error,_,_}} =
file_sorter:sort(Fs1, foo, [{tmpdir,F1},{size,0}]),
- ?line delete_files(Fs1),
- ?line Fs2 = to_files([[1,2,3]], binary_term, Config),
+ delete_files(Fs1),
+ Fs2 = to_files([[1,2,3]], binary_term, Config),
{error,{file_error,_,enoent}} =
file_sorter:sort(Fs2, foo, [{tmpdir,filename:absname(BadFile)},
{size,0}]),
- ?line delete_files(Fs2),
+ delete_files(Fs2),
- ?line {'EXIT', {{badarg, bad}, _}} =
+ {'EXIT', {{badarg, bad}, _}} =
(catch file_sorter:check([], [{format,term} | bad])),
- ?line {'EXIT', {{badarg, [{flipp}]}, _}} =
+ {'EXIT', {{badarg, [{flipp}]}, _}} =
(catch file_sorter:check([{flipp}])),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch file_sorter:keycheck(1, {flipp})),
- ?line {'EXIT', {{badarg, [{flipp}]}, _}} =
+ {'EXIT', {{badarg, [{flipp}]}, _}} =
(catch file_sorter:keycheck(2, [{flipp}])),
- ?line {error,{file_error,_,eisdir}} = file_sorter:keycheck(1, []),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch file_sorter:keycheck(kp, [])),
- ?line {'EXIT', {{badarg, kp}, _}} =
+ {error,{file_error,_,eisdir}} = file_sorter:keycheck(1, []),
+ {'EXIT', {{badarg, kp}, _}} = (catch file_sorter:keycheck(kp, [])),
+ {'EXIT', {{badarg, kp}, _}} =
(catch file_sorter:keycheck([1, kp], [])),
- ?line {'EXIT', {{badarg, kp}, _}} =
+ {'EXIT', {{badarg, kp}, _}} =
(catch file_sorter:keycheck([1 | kp], [])),
- ?line {'EXIT', {{badarg, []}, _}} = (catch file_sorter:keycheck([], [])),
- ?line {'EXIT', {{badarg, {format, foo}}, _}} =
+ {'EXIT', {{badarg, []}, _}} = (catch file_sorter:keycheck([], [])),
+ {'EXIT', {{badarg, {format, foo}}, _}} =
(catch file_sorter:check([], {format,foo})),
- ?line {'EXIT', {{badarg, not_an_option}, _}} =
+ {'EXIT', {{badarg, not_an_option}, _}} =
(catch file_sorter:keycheck(7, [], [not_an_option])),
- ?line {'EXIT', {{badarg, format}, _}} =
+ {'EXIT', {{badarg, format}, _}} =
(catch file_sorter:keycheck(1, [], [{format, binary}])),
- ?line {'EXIT', {{badarg, order}, _}} =
+ {'EXIT', {{badarg, order}, _}} =
(catch file_sorter:keycheck(1, [], [{order, fun compare/2}])),
- ?line do_badarg(fun(I, O) -> file_sorter:sort(I, O) end,
- fun(Kp, I, O) -> file_sorter:keysort(Kp, I, O) end,
- BadFile),
- ?line do_badarg_opt(fun(I, O, X) -> file_sorter:sort(I, O, X) end,
- fun(Kp, I, O, X) -> file_sorter:keysort(Kp, I, O, X)
- end),
- ?line do_badarg(fun(I, O) -> file_sorter:merge(I, O) end,
- fun(Kp, I, O) -> file_sorter:keymerge(Kp, I, O) end,
- BadFile),
- ?line do_badarg_opt(fun(I, O, X) -> file_sorter:merge(I, O, X) end,
- fun(Kp, I, O, X) -> file_sorter:keymerge(Kp, I, O, X)
- end).
+ do_badarg(fun(I, O) -> file_sorter:sort(I, O) end,
+ fun(Kp, I, O) -> file_sorter:keysort(Kp, I, O) end,
+ BadFile),
+ do_badarg_opt(fun(I, O, X) -> file_sorter:sort(I, O, X) end,
+ fun(Kp, I, O, X) -> file_sorter:keysort(Kp, I, O, X)
+ end),
+ do_badarg(fun(I, O) -> file_sorter:merge(I, O) end,
+ fun(Kp, I, O) -> file_sorter:keymerge(Kp, I, O) end,
+ BadFile),
+ do_badarg_opt(fun(I, O, X) -> file_sorter:merge(I, O, X) end,
+ fun(Kp, I, O, X) -> file_sorter:keymerge(Kp, I, O, X)
+ end).
do_badarg(F, KF, BadFile) ->
[Char | _] = BadFile,
AFlipp = filename:absname(flipp),
- ?line {error,{file_error,AFlipp,enoent}} = F([flipp | flopp], foo),
- ?line {'EXIT', {{badarg, {foo,bar}}, _}} = (catch F([], {foo,bar})),
- ?line {'EXIT', {{badarg, Char}, _}} = (catch F(BadFile, [])),
- ?line {'EXIT', {{badarg, {flipp}}, _}} = (catch F({flipp}, [])),
-
- ?line {'EXIT', {{badarg, Char}, _}} = (catch KF(1, BadFile, [])),
- ?line {'EXIT', {{badarg, {flipp}}, _}} = (catch KF(1, {flipp}, [])),
- ?line {error,{file_error,AFlipp,enoent}} =
+ {error,{file_error,AFlipp,enoent}} = F([flipp | flopp], foo),
+ {'EXIT', {{badarg, {foo,bar}}, _}} = (catch F([], {foo,bar})),
+ {'EXIT', {{badarg, Char}, _}} = (catch F(BadFile, [])),
+ {'EXIT', {{badarg, {flipp}}, _}} = (catch F({flipp}, [])),
+
+ {'EXIT', {{badarg, Char}, _}} = (catch KF(1, BadFile, [])),
+ {'EXIT', {{badarg, {flipp}}, _}} = (catch KF(1, {flipp}, [])),
+ {error,{file_error,AFlipp,enoent}} =
KF(2, [flipp | flopp], foo),
- ?line {'EXIT', {{badarg, {foo,bar}}, _}} = (catch KF(1, [], {foo,bar})),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF(kp, [], foo)),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF([1, kp], [], foo)),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF([1 | kp], [], foo)),
- ?line {'EXIT', {{badarg, []}, _}} = (catch KF([], [], foo)),
+ {'EXIT', {{badarg, {foo,bar}}, _}} = (catch KF(1, [], {foo,bar})),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF(kp, [], foo)),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF([1, kp], [], foo)),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF([1 | kp], [], foo)),
+ {'EXIT', {{badarg, []}, _}} = (catch KF([], [], foo)),
ok.
do_badarg_opt(F, KF) ->
AFlipp = filename:absname(flipp),
- ?line {error,{file_error,AFlipp,enoent}} =
- F([flipp | flopp], foo, []),
- ?line {'EXIT', {{badarg, {flipp}}, _}} = (catch F([{flipp}], foo, [])),
- ?line {'EXIT', {{badarg, {out,put}}, _}} = (catch F([], {out,put}, [])),
- ?line {'EXIT', {{badarg, not_an_option}, _}} =
+ {error,{file_error,AFlipp,enoent}} =
+ F([flipp | flopp], foo, []),
+ {'EXIT', {{badarg, {flipp}}, _}} = (catch F([{flipp}], foo, [])),
+ {'EXIT', {{badarg, {out,put}}, _}} = (catch F([], {out,put}, [])),
+ {'EXIT', {{badarg, not_an_option}, _}} =
(catch F([], foo, [not_an_option])),
- ?line {'EXIT', {{badarg, {format, foo}}, _}} =
- (catch F([], foo, {format,foo})),
- ?line {'EXIT', {{badarg, {size,foo}}, _}} = (catch F([], foo, {size,foo})),
+ {'EXIT', {{badarg, {format, foo}}, _}} =
+ (catch F([], foo, {format,foo})),
+ {'EXIT', {{badarg, {size,foo}}, _}} = (catch F([], foo, {size,foo})),
- ?line {'EXIT', {{badarg, {size, -1}}, _}} = (catch F([], foo, {size,-1})),
- ?line {'EXIT', {{badarg, {no_files, foo}}, _}} =
+ {'EXIT', {{badarg, {size, -1}}, _}} = (catch F([], foo, {size,-1})),
+ {'EXIT', {{badarg, {no_files, foo}}, _}} =
(catch F([], foo, {no_files,foo})),
- ?line {'EXIT', {{badarg, {no_files, 1}}, _}} =
+ {'EXIT', {{badarg, {no_files, 1}}, _}} =
(catch F([], foo, {no_files,1})),
- ?line {'EXIT', {{badarg, 1}, _}} = (catch F([], foo, {tmpdir,1})),
- ?line {'EXIT', {{badarg, {order,1}}, _}} = (catch F([], foo, {order,1})),
- ?line {'EXIT', {{badarg, {compressed, flopp}}, _}} =
- (catch F([], foo, {compressed,flopp})),
- ?line {'EXIT', {{badarg, {unique,flopp}}, _}} =
- (catch F([], foo, {unique,flopp})),
- ?line {'EXIT', {{badarg, {header,foo}}, _}} =
+ {'EXIT', {{badarg, 1}, _}} = (catch F([], foo, {tmpdir,1})),
+ {'EXIT', {{badarg, {order,1}}, _}} = (catch F([], foo, {order,1})),
+ {'EXIT', {{badarg, {compressed, flopp}}, _}} =
+ (catch F([], foo, {compressed,flopp})),
+ {'EXIT', {{badarg, {unique,flopp}}, _}} =
+ (catch F([], foo, {unique,flopp})),
+ {'EXIT', {{badarg, {header,foo}}, _}} =
(catch F([], foo, {header,foo})),
- ?line {'EXIT', {{badarg, {header, 0}}, _}} =
+ {'EXIT', {{badarg, {header, 0}}, _}} =
(catch F([], foo, {header,0})),
- ?line {'EXIT', {{badarg, {header, 1 bsl 35}}, _}} =
+ {'EXIT', {{badarg, {header, 1 bsl 35}}, _}} =
(catch F([], foo, {header,1 bsl 35})),
- ?line {'EXIT', {{badarg, header}, _}} =
+ {'EXIT', {{badarg, header}, _}} =
(catch F([], foo, [{header,1},{format,term}])),
- ?line {'EXIT', {{badarg, not_an_option}, _}} =
+ {'EXIT', {{badarg, not_an_option}, _}} =
(catch KF(7, [], foo, [not_an_option])),
- ?line {'EXIT', {{badarg,format}, _}} =
+ {'EXIT', {{badarg,format}, _}} =
(catch KF(1, [], foo, [{format, binary}])),
- ?line {'EXIT', {{badarg, order}, _}} =
+ {'EXIT', {{badarg, order}, _}} =
(catch KF(1, [], foo, [{order, fun compare/2}])),
- ?line {'EXIT', {{badarg, {flipp}}, _}} =
+ {'EXIT', {{badarg, {flipp}}, _}} =
(catch KF(2, [{flipp}], foo,[])),
- ?line {error,{file_error,AFlipp,enoent}} =
+ {error,{file_error,AFlipp,enoent}} =
KF(2, [flipp | flopp], foo,[]),
- ?line {'EXIT', {{badarg, {out, put}}, _}} =
+ {'EXIT', {{badarg, {out, put}}, _}} =
(catch KF(1, [], {out,put}, [])),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF(kp, [], foo, [])),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF([1, kp], [], foo, [])),
- ?line {'EXIT', {{badarg, kp}, _}} = (catch KF([1 | kp], [], foo, [])),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF(kp, [], foo, [])),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF([1, kp], [], foo, [])),
+ {'EXIT', {{badarg, kp}, _}} = (catch KF([1 | kp], [], foo, [])),
ok.
%% Sort terms on files.
term_sort(Config) when is_list(Config) ->
- ?line sort(term, [{compressed,false}], Config),
- ?line sort(term, [{order, fun compare/2}], Config),
- ?line sort(term, [{order, ascending}, {compressed,true}], Config),
- ?line sort(term, [{order, descending}], Config),
+ sort(term, [{compressed,false}], Config),
+ sort(term, [{order, fun compare/2}], Config),
+ sort(term, [{order, ascending}, {compressed,true}], Config),
+ sort(term, [{order, descending}], Config),
ok.
%% Keysort terms on files.
term_keysort(Config) when is_list(Config) ->
- ?line keysort(term, [{tmpdir, ""}], Config),
- ?line keysort(term, [{order,descending}], Config),
+ keysort(term, [{tmpdir, ""}], Config),
+ keysort(term, [{order,descending}], Config),
ok.
%% Sort binary terms on files.
binary_term_sort(Config) when is_list(Config) ->
PrivDir = ?privdir(Config),
- ?line sort({2, binary_term}, [], Config),
- ?line sort(binary_term, [{tmpdir, list_to_atom(PrivDir)}], Config),
- ?line sort(binary_term, [{tmpdir,PrivDir}], Config),
- ?line sort({3,binary_term}, [{order, fun compare/2}], Config),
- ?line sort(binary_term, [{order, fun compare/2}], Config),
- ?line sort(binary_term, [{order,descending}], Config),
+ sort({2, binary_term}, [], Config),
+ sort(binary_term, [{tmpdir, list_to_atom(PrivDir)}], Config),
+ sort(binary_term, [{tmpdir,PrivDir}], Config),
+ sort({3,binary_term}, [{order, fun compare/2}], Config),
+ sort(binary_term, [{order, fun compare/2}], Config),
+ sort(binary_term, [{order,descending}], Config),
ok.
%% Keysort binary terms on files.
binary_term_keysort(Config) when is_list(Config) ->
- ?line keysort({3, binary_term}, [], Config),
- ?line keysort(binary_term, [], Config),
- ?line keysort(binary_term, [{order,descending}], Config),
+ keysort({3, binary_term}, [], Config),
+ keysort(binary_term, [], Config),
+ keysort(binary_term, [{order,descending}], Config),
ok.
%% Sort binaries on files.
binary_sort(Config) when is_list(Config) ->
PrivDir = ?privdir(Config),
- ?line sort({2, binary}, [], Config),
- ?line sort(binary, [{tmpdir, list_to_atom(PrivDir)}], Config),
- ?line sort(binary, [{tmpdir,PrivDir}], Config),
- ?line sort({3,binary}, [{order, fun compare/2}], Config),
- ?line sort(binary, [{order, fun compare/2}], Config),
- ?line sort(binary, [{order,descending}], Config),
+ sort({2, binary}, [], Config),
+ sort(binary, [{tmpdir, list_to_atom(PrivDir)}], Config),
+ sort(binary, [{tmpdir,PrivDir}], Config),
+ sort({3,binary}, [{order, fun compare/2}], Config),
+ sort(binary, [{order, fun compare/2}], Config),
+ sort(binary, [{order,descending}], Config),
ok.
%% Merge terms on files.
term_merge(Config) when is_list(Config) ->
- ?line merge(term, [{order, fun compare/2}], Config),
- ?line merge(term, [{order, ascending}, {compressed,true}], Config),
- ?line merge(term, [{order, descending}, {compressed,false}], Config),
+ merge(term, [{order, fun compare/2}], Config),
+ merge(term, [{order, ascending}, {compressed,true}], Config),
+ merge(term, [{order, descending}, {compressed,false}], Config),
ok.
%% Keymerge terms on files.
term_keymerge(Config) when is_list(Config) ->
- ?line keymerge(term, [], Config),
- ?line keymerge(term, [{order, descending}], Config),
- ?line funmerge(term, [], Config),
+ keymerge(term, [], Config),
+ keymerge(term, [{order, descending}], Config),
+ funmerge(term, [], Config),
ok.
%% Merge binary terms on files.
binary_term_merge(Config) when is_list(Config) ->
- ?line merge(binary_term, [], Config),
- ?line merge({7, binary_term}, [], Config),
- ?line merge({3, binary_term}, [{order, fun compare/2}], Config),
+ merge(binary_term, [], Config),
+ merge({7, binary_term}, [], Config),
+ merge({3, binary_term}, [{order, fun compare/2}], Config),
ok.
%% Keymerge binary terms on files.
binary_term_keymerge(Config) when is_list(Config) ->
- ?line keymerge({3, binary_term}, [], Config),
- ?line keymerge(binary_term, [], Config),
- ?line funmerge({3, binary_term}, [], Config),
- ?line funmerge(binary_term, [], Config),
+ keymerge({3, binary_term}, [], Config),
+ keymerge(binary_term, [], Config),
+ funmerge({3, binary_term}, [], Config),
+ funmerge(binary_term, [], Config),
ok.
%% Merge binaries on files.
binary_merge(Config) when is_list(Config) ->
- ?line merge(binary, [], Config),
- ?line merge({7, binary}, [], Config),
- ?line merge({3, binary}, [{order, fun compare/2}], Config),
+ merge(binary, [], Config),
+ merge({7, binary}, [], Config),
+ merge({3, binary}, [{order, fun compare/2}], Config),
ok.
%% Check terms on files.
term_check(Config) when is_list(Config) ->
- ?line check(term, Config),
+ check(term, Config),
ok.
%% Check binary terms on files.
binary_term_check(Config) when is_list(Config) ->
- ?line check(binary_term, Config),
+ check(binary_term, Config),
ok.
%% Keycheck terms on files.
term_keycheck(Config) when is_list(Config) ->
- ?line keycheck(term, Config),
+ keycheck(term, Config),
ok.
%% Keycheck binary terms on files.
binary_term_keycheck(Config) when is_list(Config) ->
- ?line keycheck(binary_term, Config),
+ keycheck(binary_term, Config),
ok.
%% Check binary terms on files.
binary_check(Config) when is_list(Config) ->
- ?line check(binary, Config),
+ check(binary, Config),
ok.
%% Funs as input or output.
@@ -407,52 +407,52 @@ inout(Config) when is_list(Config) ->
End = fun(read) -> end_of_input end,
IF1 = fun(read) -> {[1,7,5], End} end,
- ?line ok = file_sorter:sort(IF1, Foo, [{format, term}]),
+ ok = file_sorter:sort(IF1, Foo, [{format, term}]),
%% 'close' is called, but the return value is caught and ignored.
IF2 = fun(read) -> {[1,2,3], fun(close) -> throw(ignored) end} end,
- ?line {error, bad_object} = file_sorter:sort(IF2, Foo, BTF),
+ {error, bad_object} = file_sorter:sort(IF2, Foo, BTF),
IF3 = fun(no_match) -> foo end,
- ?line {'EXIT', {function_clause, _}} =
+ {'EXIT', {function_clause, _}} =
(catch file_sorter:sort(IF3, Foo)),
IF4 = fun(read) -> throw(my_message) end,
- ?line my_message = (catch file_sorter:sort(IF4, Foo)),
+ my_message = (catch file_sorter:sort(IF4, Foo)),
IF5 = fun(read) -> {error, my_error} end,
- ?line {error, my_error} = file_sorter:sort(IF5, Foo),
+ {error, my_error} = file_sorter:sort(IF5, Foo),
%% Output is fun.
- ?line {error, bad_object} =
+ {error, bad_object} =
file_sorter:sort(IF2, fun(close) -> ignored end, BTF),
Args = [{format, term}],
- ?line {error, bad_object} =
- file_sorter:keysort(1, IF2, fun(close) -> ignored end, Args),
+ {error, bad_object} =
+ file_sorter:keysort(1, IF2, fun(close) -> ignored end, Args),
OF1 = fun(close) -> fine; (L) when is_list(L) -> fun(close) -> nice end end,
- ?line nice = file_sorter:sort(IF1, OF1, Args),
+ nice = file_sorter:sort(IF1, OF1, Args),
OF2 = fun(_) -> my_return end,
- ?line my_return = file_sorter:sort(IF1, OF2, Args),
+ my_return = file_sorter:sort(IF1, OF2, Args),
OF3 = fun(_) -> throw(my_message) end,
- ?line my_message = (catch file_sorter:sort(IF1, OF3, Args)),
+ my_message = (catch file_sorter:sort(IF1, OF3, Args)),
OF4 = fun(no_match) -> foo end,
- ?line {'EXIT', {function_clause, _}} =
+ {'EXIT', {function_clause, _}} =
(catch file_sorter:sort(IF1, OF4, Args)),
- ?line P0 = pps(),
- ?line Fs1 = to_files([[3,1,2,5,4], [8,3,10]], term, Config),
- ?line error = file_sorter:sort(Fs1, fun(_) -> error end, Args),
- ?line delete_files(Fs1),
+ P0 = pps(),
+ Fs1 = to_files([[3,1,2,5,4], [8,3,10]], term, Config),
+ error = file_sorter:sort(Fs1, fun(_) -> error end, Args),
+ delete_files(Fs1),
- ?line true = P0 =:= pps(),
+ true = P0 =:= pps(),
%% Passing a value from the input functions to the output functions.
IFV1 = fun(read) -> {end_of_input, 17} end,
OFV1 = fun({value, Value}) -> ofv(Value, []) end,
- ?line {17, []} = file_sorter:sort(IFV1, OFV1, Args),
+ {17, []} = file_sorter:sort(IFV1, OFV1, Args),
%% Output is not a fun. The value returned by input funs is ignored.
%% OTP-5009.
- ?line ok = file_sorter:sort(IFV1, Foo, [{format,term}]),
- ?line [] = from_files(Foo, term),
- ?line delete_files(Foo),
+ ok = file_sorter:sort(IFV1, Foo, [{format,term}]),
+ [] = from_files(Foo, term),
+ delete_files(Foo),
ok.
@@ -472,56 +472,56 @@ many(Config) when is_list(Config) ->
Args = [{format, term}],
L1 = lists:map(fun(I) -> {one, two, three, I} end, lists:seq(1,1000)),
L2 = lists:map(fun(I) -> {four, five, six, I} end, lists:seq(1,1000)),
- ?line Fs2 = to_files([L1, L2], term, Config),
- ?line ok = file_sorter:sort(Fs2, Foo, [{size,1000} | Args]),
- ?line R = lists:sort(L1++L2),
- ?line R = from_files(Foo, term),
- ?line 2000 = length(R),
- ?line ok = file_sorter:sort(Fs2, Foo, [{no_files,4},{size,1000} | Args]),
- ?line R = from_files(Foo, term),
- ?line ok =
+ Fs2 = to_files([L1, L2], term, Config),
+ ok = file_sorter:sort(Fs2, Foo, [{size,1000} | Args]),
+ R = lists:sort(L1++L2),
+ R = from_files(Foo, term),
+ 2000 = length(R),
+ ok = file_sorter:sort(Fs2, Foo, [{no_files,4},{size,1000} | Args]),
+ R = from_files(Foo, term),
+ ok =
file_sorter:sort(Fs2, Foo,
[{no_files,4},{size,1000},{order,descending} | Args]),
- ?line true = lists:reverse(R) =:= from_files(Foo, term),
- ?line ok =
+ true = lists:reverse(R) =:= from_files(Foo, term),
+ ok =
file_sorter:sort(Fs2, Foo,
[{no_files,4},{size,1000},
{order,fun compare/2} | Args]),
- ?line R = from_files(Foo, term),
- ?line ok = file_sorter:keysort(4, Fs2, Foo,
- [{no_files,4},{size,1000} | Args]),
- ?line RK = lists:keysort(4, L1++L2),
- ?line RK = from_files(Foo, term),
- ?line delete_files(Foo),
- ?line ok =
+ R = from_files(Foo, term),
+ ok = file_sorter:keysort(4, Fs2, Foo,
+ [{no_files,4},{size,1000} | Args]),
+ RK = lists:keysort(4, L1++L2),
+ RK = from_files(Foo, term),
+ delete_files(Foo),
+ ok =
file_sorter:keysort(4, Fs2, Foo,
- [{no_files,4},{size,1000},{order,descending} | Args]),
- ?line true = lists:reverse(RK) =:= from_files(Foo, term),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keysort(4, Fs2, Foo,
- [{size,500},{order,descending} | Args]),
- ?line true = lists:reverse(RK) =:= from_files(Foo, term),
- ?line delete_files(Foo),
- ?line error = file_sorter:sort(Fs2, fun(_) -> error end,
- [{tmpdir, PrivDir}, {no_files,3},
- {size,10000} | Args]),
+ [{no_files,4},{size,1000},{order,descending} | Args]),
+ true = lists:reverse(RK) =:= from_files(Foo, term),
+ delete_files(Foo),
+ ok = file_sorter:keysort(4, Fs2, Foo,
+ [{size,500},{order,descending} | Args]),
+ true = lists:reverse(RK) =:= from_files(Foo, term),
+ delete_files(Foo),
+ error = file_sorter:sort(Fs2, fun(_) -> error end,
+ [{tmpdir, PrivDir}, {no_files,3},
+ {size,10000} | Args]),
TmpDir = filename:join(PrivDir, "tmpdir"),
file:del_dir(TmpDir),
- ?line ok = file:make_dir(TmpDir),
- ?line case os:type() of
- {unix, _} ->
- ?line ok = file:change_mode(TmpDir, 8#0000),
- ?line {error, {file_error, _,_}} =
- file_sorter:sort(Fs2, fun(_M) -> foo end,
- [{no_files,3},{size,10000},
- {tmpdir,TmpDir} | Args]);
- _ ->
- true
- end,
- ?line ok = file:del_dir(TmpDir),
+ ok = file:make_dir(TmpDir),
+ case os:type() of
+ {unix, _} ->
+ ok = file:change_mode(TmpDir, 8#0000),
+ {error, {file_error, _,_}} =
+ file_sorter:sort(Fs2, fun(_M) -> foo end,
+ [{no_files,3},{size,10000},
+ {tmpdir,TmpDir} | Args]);
+ _ ->
+ true
+ end,
+ ok = file:del_dir(TmpDir),
delete_files(Fs2),
- ?line true = P0 =:= pps(),
+ true = P0 =:= pps(),
ok.
%% Some other tests.
@@ -531,109 +531,109 @@ misc(Config) when is_list(Config) ->
FFoo = filename:absname(Foo),
P0 = pps(),
- ?line [File] = Fs1 = to_files([[1,3,2]], term, Config),
- ?line ok = file:write_file(Foo,<<>>),
- ?line case os:type() of
- {unix, _} ->
- ok = file:change_mode(Foo, 8#0000),
- {error,{file_error,FFoo,eacces}} =
- file_sorter:sort(Fs1, Foo, {format,term});
- _ ->
- true
- end,
- ?line file:delete(Foo),
- ?line NoBytes = 16, % RAM memory will never get this big, or?
- ?line ALot = (1 bsl (NoBytes*8)) - 1,
- ?line ok = file:write_file(File, <<ALot:NoBytes/unit:8,"foobar">>),
+ [File] = Fs1 = to_files([[1,3,2]], term, Config),
+ ok = file:write_file(Foo,<<>>),
+ case os:type() of
+ {unix, _} ->
+ ok = file:change_mode(Foo, 8#0000),
+ {error,{file_error,FFoo,eacces}} =
+ file_sorter:sort(Fs1, Foo, {format,term});
+ _ ->
+ true
+ end,
+ file:delete(Foo),
+ NoBytes = 16, % RAM memory will never get this big, or?
+ ALot = (1 bsl (NoBytes*8)) - 1,
+ ok = file:write_file(File, <<ALot:NoBytes/unit:8,"foobar">>),
FFile = filename:absname(File),
- ?line {error, {bad_object,FFile}} =
+ {error, {bad_object,FFile}} =
file_sorter:sort(Fs1, Foo, [BTF, {header, 20}]),
- ?line ok = file:write_file(File, <<30:32,"foobar">>),
- ?line {error, {premature_eof, FFile}} = file_sorter:sort(Fs1, Foo, BTF),
- ?line ok = file:write_file(File, <<6:32,"foobar">>),
- ?line {error, {bad_object,FFile}} = file_sorter:sort(Fs1, Foo, BTF),
- ?line case os:type() of
- {unix, _} ->
- ok = file:change_mode(File, 8#0000),
- {error, {file_error,FFile,eacces}} =
- file_sorter:sort(Fs1, Foo),
- {error, {file_error,FFile,eacces}} =
- file_sorter:sort(Fs1, Foo, {format, binary_term});
- _ ->
- true
- end,
- ?line delete_files(Fs1),
- ?line true = P0 =:= pps(),
+ ok = file:write_file(File, <<30:32,"foobar">>),
+ {error, {premature_eof, FFile}} = file_sorter:sort(Fs1, Foo, BTF),
+ ok = file:write_file(File, <<6:32,"foobar">>),
+ {error, {bad_object,FFile}} = file_sorter:sort(Fs1, Foo, BTF),
+ case os:type() of
+ {unix, _} ->
+ ok = file:change_mode(File, 8#0000),
+ {error, {file_error,FFile,eacces}} =
+ file_sorter:sort(Fs1, Foo),
+ {error, {file_error,FFile,eacces}} =
+ file_sorter:sort(Fs1, Foo, {format, binary_term});
+ _ ->
+ true
+ end,
+ delete_files(Fs1),
+ true = P0 =:= pps(),
%% bigger than chunksize
- ?line E1 = <<32000:32, 10:256000>>,
- ?line E2 = <<32000:32, 5:256000>>,
- ?line E3 = <<32000:32, 8:256000>>,
- ?line ok = file:write_file(Foo, [E1, E2, E3]),
- ?line ok = file_sorter:sort([Foo], Foo, [{format,binary},{size,10000}]),
- ?line ok = file_sorter:sort([Foo], Foo, [{format,fun(X) -> X end},
- {size,10000}]),
- ?line Es = list_to_binary([E2,E3,E1]),
- ?line {ok, Es} = file:read_file(Foo),
- ?line delete_files(Foo),
- ?line true = P0 =:= pps(),
+ E1 = <<32000:32, 10:256000>>,
+ E2 = <<32000:32, 5:256000>>,
+ E3 = <<32000:32, 8:256000>>,
+ ok = file:write_file(Foo, [E1, E2, E3]),
+ ok = file_sorter:sort([Foo], Foo, [{format,binary},{size,10000}]),
+ ok = file_sorter:sort([Foo], Foo, [{format,fun(X) -> X end},
+ {size,10000}]),
+ Es = list_to_binary([E2,E3,E1]),
+ {ok, Es} = file:read_file(Foo),
+ delete_files(Foo),
+ true = P0 =:= pps(),
%% keysort more than one element
L = [{c,1,a},{c,2,b},{c,3,c},{b,1,c},{b,2,b},{b,3,a},{a,1,a},{a,2,b},
{a,3,c}],
- ?line Fs2 = to_files([L], binary_term, Config),
- ?line ok = file_sorter:keysort([2,3], Fs2, Foo, {format, binary_term}),
- ?line KS2_1 = from_files(Foo, binary_term),
- ?line KS2_2 = lists:keysort(2,lists:keysort(3, L)),
- ?line KS2_1 = KS2_2,
- ?line ok = file_sorter:keysort([2,3], Fs2, Foo,
- [{format, binary_term},{size,5}]),
- ?line KS2_3 = from_files(Foo, binary_term),
- ?line KS2_3 = KS2_2,
- ?line ok = file_sorter:keysort([2,3,1], Fs2, Foo, {format, binary_term}),
- ?line KS3_1 = from_files(Foo, binary_term),
- ?line KS3_2 = lists:keysort(2, lists:keysort(3,lists:keysort(1, L))),
- ?line KS3_1 = KS3_2,
- ?line ok = file_sorter:keysort([2,3,1], Fs2, Foo,
- [{format, binary_term},{size,5}]),
- ?line KS3_3 = from_files(Foo, binary_term),
- ?line KS3_3 = KS3_2,
- ?line delete_files([Foo | Fs2]),
- ?line true = P0 =:= pps(),
+ Fs2 = to_files([L], binary_term, Config),
+ ok = file_sorter:keysort([2,3], Fs2, Foo, {format, binary_term}),
+ KS2_1 = from_files(Foo, binary_term),
+ KS2_2 = lists:keysort(2,lists:keysort(3, L)),
+ KS2_1 = KS2_2,
+ ok = file_sorter:keysort([2,3], Fs2, Foo,
+ [{format, binary_term},{size,5}]),
+ KS2_3 = from_files(Foo, binary_term),
+ KS2_3 = KS2_2,
+ ok = file_sorter:keysort([2,3,1], Fs2, Foo, {format, binary_term}),
+ KS3_1 = from_files(Foo, binary_term),
+ KS3_2 = lists:keysort(2, lists:keysort(3,lists:keysort(1, L))),
+ KS3_1 = KS3_2,
+ ok = file_sorter:keysort([2,3,1], Fs2, Foo,
+ [{format, binary_term},{size,5}]),
+ KS3_3 = from_files(Foo, binary_term),
+ KS3_3 = KS3_2,
+ delete_files([Foo | Fs2]),
+ true = P0 =:= pps(),
%% bigger than chunksize
%% Assumes that CHUNKSIZE = 16384. Illustrates that the Last argument
%% of merge_files/5 is necessary.
- ?line EP1 = erlang:make_tuple(2728,foo),
- ?line EP2 = lists:duplicate(2729,qqq),
- ?line LL = [EP1, EP2, EP1, EP2, EP1, EP2],
- ?line Fs3 = to_files([LL], binary, Config),
- ?line ok = file_sorter:sort(Fs3, Foo, [{format,binary}, {unique,true}]),
- ?line [EP1,EP2] = from_files(Foo, binary),
- ?line delete_files(Foo),
- ?line ok = file_sorter:sort(Fs3, Foo,
- [{format,binary_term}, {unique,true},
- {size,30000}]),
- ?line [EP1,EP2] = from_files(Foo, binary_term),
- ?line delete_files([Foo | Fs3]),
-
- ?line true = P0 =:= pps(),
-
- ?line BE1 = <<20000:32, 17:160000>>,
- ?line BE2 = <<20000:32, 1717:160000>>,
- ?line ok = file:write_file(Foo, [BE1,BE2,BE1,BE2]),
- ?line ok = file_sorter:sort([Foo], Foo, [{format,binary},
- {size,10000},
- {unique,true}]),
- ?line BEs = list_to_binary([BE1, BE2]),
- ?line {ok, BEs} = file:read_file(Foo),
- ?line delete_files(Foo),
- ?line true = P0 =:= pps(),
-
- ?line Fs4 = to_files([[7,4,1]], binary_term, Config),
- ?line {error, {bad_term, _}} = file_sorter:sort(Fs4, Foo, {format, term}),
- ?line delete_files([Foo | Fs4]),
- ?line true = P0 =:= pps(),
+ EP1 = erlang:make_tuple(2728,foo),
+ EP2 = lists:duplicate(2729,qqq),
+ LL = [EP1, EP2, EP1, EP2, EP1, EP2],
+ Fs3 = to_files([LL], binary, Config),
+ ok = file_sorter:sort(Fs3, Foo, [{format,binary}, {unique,true}]),
+ [EP1,EP2] = from_files(Foo, binary),
+ delete_files(Foo),
+ ok = file_sorter:sort(Fs3, Foo,
+ [{format,binary_term}, {unique,true},
+ {size,30000}]),
+ [EP1,EP2] = from_files(Foo, binary_term),
+ delete_files([Foo | Fs3]),
+
+ true = P0 =:= pps(),
+
+ BE1 = <<20000:32, 17:160000>>,
+ BE2 = <<20000:32, 1717:160000>>,
+ ok = file:write_file(Foo, [BE1,BE2,BE1,BE2]),
+ ok = file_sorter:sort([Foo], Foo, [{format,binary},
+ {size,10000},
+ {unique,true}]),
+ BEs = list_to_binary([BE1, BE2]),
+ {ok, BEs} = file:read_file(Foo),
+ delete_files(Foo),
+ true = P0 =:= pps(),
+
+ Fs4 = to_files([[7,4,1]], binary_term, Config),
+ {error, {bad_term, _}} = file_sorter:sort(Fs4, Foo, {format, term}),
+ delete_files([Foo | Fs4]),
+ true = P0 =:= pps(),
ok.
@@ -647,71 +647,71 @@ sort(Fmt, XArgs, Config) ->
Foo = outfile("foo", Config),
%% Input is a fun. Output is a fun.
- ?line [] = file_sorter:sort(input([], 2, Fmt), output([], Fmt), Args),
- ?line L1 = [3,1,2,5,4],
- ?line S1 = file_sorter:sort(input(L1, 2, Fmt), output([], Fmt), TmpArgs),
- ?line S1 = rev(lists:sort(L1), TmpArgs),
+ [] = file_sorter:sort(input([], 2, Fmt), output([], Fmt), Args),
+ L1 = [3,1,2,5,4],
+ S1 = file_sorter:sort(input(L1, 2, Fmt), output([], Fmt), TmpArgs),
+ S1 = rev(lists:sort(L1), TmpArgs),
%% Input is a file. Output is a fun.
- ?line [] = file_sorter:sort([], output([], Fmt), Args),
- ?line L2 = [3,1,2,5,4],
- ?line Fs1 = to_files([L2], Fmt, Config),
- ?line S2 = file_sorter:sort(Fs1, output([], Fmt), TmpArgs),
- ?line S2 = rev(lists:sort(L2), TmpArgs),
- ?line delete_files(Fs1),
+ [] = file_sorter:sort([], output([], Fmt), Args),
+ L2 = [3,1,2,5,4],
+ Fs1 = to_files([L2], Fmt, Config),
+ S2 = file_sorter:sort(Fs1, output([], Fmt), TmpArgs),
+ S2 = rev(lists:sort(L2), TmpArgs),
+ delete_files(Fs1),
%% Input is a file. Output is a file
- ?line ok = file_sorter:sort([], Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:sort([], Foo, [{unique,true} | Args]),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line L3 = [3,1,2,5,4,6],
- ?line Fs2 = to_files([L3], Fmt, Config),
- ?line ok = file_sorter:sort(Fs2, Foo, Args),
- ?line true = rev(lists:sort(L3), Args) =:= from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs2]),
- ?line L4 = [1,3,4,1,2,5,4,5,6],
- ?line Fs3 = to_files([L4], Fmt, Config),
- ?line ok = file_sorter:sort(Fs3, Foo, Args++[{unique,true},
- {size,100000}]),
- ?line true = rev(lists:usort(L4), Args) =:= from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:sort(Fs3, Foo, Args++[{unique,true}]),
- ?line true = rev(lists:usort(L4), Args) =:= from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs3]),
+ ok = file_sorter:sort([], Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:sort([], Foo, [{unique,true} | Args]),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ L3 = [3,1,2,5,4,6],
+ Fs2 = to_files([L3], Fmt, Config),
+ ok = file_sorter:sort(Fs2, Foo, Args),
+ true = rev(lists:sort(L3), Args) =:= from_files(Foo, Fmt),
+ delete_files([Foo | Fs2]),
+ L4 = [1,3,4,1,2,5,4,5,6],
+ Fs3 = to_files([L4], Fmt, Config),
+ ok = file_sorter:sort(Fs3, Foo, Args++[{unique,true},
+ {size,100000}]),
+ true = rev(lists:usort(L4), Args) =:= from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:sort(Fs3, Foo, Args++[{unique,true}]),
+ true = rev(lists:usort(L4), Args) =:= from_files(Foo, Fmt),
+ delete_files([Foo | Fs3]),
%% Input is a fun. Output is a file.
- ?line ok = file_sorter:sort(input([], 2, Fmt), Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line L5 = [3,1,2,5,4,7],
- ?line ok = file_sorter:sort(input(L5, 2, Fmt), Foo, Args),
- ?line true = rev(lists:sort(L5), Args) =:= from_files(Foo, Fmt),
- ?line delete_files(Foo),
+ ok = file_sorter:sort(input([], 2, Fmt), Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ L5 = [3,1,2,5,4,7],
+ ok = file_sorter:sort(input(L5, 2, Fmt), Foo, Args),
+ true = rev(lists:sort(L5), Args) =:= from_files(Foo, Fmt),
+ delete_files(Foo),
%% Removing duplicate keys.
KFun = key_compare(2),
L6 = [{5,e},{2,b},{3,c},{1,a},{4,d}] ++ [{2,c},{1,b},{4,a}],
KUArgs = lists:keydelete(order, 1, Args) ++
- [{unique, true}, {order, KFun},{size,100000}],
- ?line ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KUArgs),
- ?line true = rev(lists:ukeysort(2, L6), KUArgs) =:= from_files(Foo, Fmt),
+ [{unique, true}, {order, KFun},{size,100000}],
+ ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KUArgs),
+ true = rev(lists:ukeysort(2, L6), KUArgs) =:= from_files(Foo, Fmt),
KArgs = lists:keydelete(unique, 1, KUArgs),
- ?line ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KArgs),
- ?line true = rev(lists:keysort(2, L6), KArgs) =:= from_files(Foo, Fmt),
+ ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KArgs),
+ true = rev(lists:keysort(2, L6), KArgs) =:= from_files(Foo, Fmt),
%% Removing duplicate keys. Again.
KUArgs2 = lists:keydelete(order, 1, Args) ++
- [{unique, true}, {order, KFun},{size,5}],
- ?line ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KUArgs2),
- ?line true = rev(lists:ukeysort(2, L6), KUArgs2) =:= from_files(Foo, Fmt),
+ [{unique, true}, {order, KFun},{size,5}],
+ ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KUArgs2),
+ true = rev(lists:ukeysort(2, L6), KUArgs2) =:= from_files(Foo, Fmt),
KArgs2 = lists:keydelete(unique, 1, KUArgs2),
- ?line ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KArgs2),
- ?line true = rev(lists:keysort(2, L6), KArgs2) =:= from_files(Foo, Fmt),
- ?line delete_files(Foo),
-
+ ok = file_sorter:sort(input(L6, 2, Fmt), Foo, KArgs2),
+ true = rev(lists:keysort(2, L6), KArgs2) =:= from_files(Foo, Fmt),
+ delete_files(Foo),
+
ok.
keysort(Fmt, XArgs, Config) ->
@@ -720,58 +720,58 @@ keysort(Fmt, XArgs, Config) ->
Foo = outfile("foo", Config),
%% Input is files. Output is a file.
- ?line ok = file_sorter:keysort(2, [], Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keysort(2, [], Foo, [{unique,true} | Args]),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line L0 = [{a,2},{a,1},{a,2},{a,2},{a,1},{a,2},{a,2},{a,3}],
- ?line Fs0 = to_files([L0], Fmt, Config),
- ?line S = rev(lists:ukeysort(1, L0), Args),
- ?line ok =
+ ok = file_sorter:keysort(2, [], Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:keysort(2, [], Foo, [{unique,true} | Args]),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ L0 = [{a,2},{a,1},{a,2},{a,2},{a,1},{a,2},{a,2},{a,3}],
+ Fs0 = to_files([L0], Fmt, Config),
+ S = rev(lists:ukeysort(1, L0), Args),
+ ok =
file_sorter:keysort(1, Fs0, Foo, Args ++ [{unique,true},
{size,100000}]),
- ?line S = from_files(Foo, Fmt),
- ?line ok =
+ S = from_files(Foo, Fmt),
+ ok =
file_sorter:keysort(1, Fs0, Foo, Args ++ [{unique,true},
{size,5}]),
- ?line S = from_files(Foo, Fmt),
- ?line ok = file_sorter:keysort(1, Fs0, Foo, Args ++ [{unique,true}]),
- ?line S = from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs0]),
- ?line L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
- ?line L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
- ?line L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
- ?line L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
- ?line All = [L11, L21, L31, L41],
- ?line AllFlat = lists:append(All),
- ?line Sorted = rev(lists:keysort(2, AllFlat), Args),
- ?line Fs1 = to_files(All, Fmt, Config),
- ?line ok = file_sorter:keysort(2, Fs1, Foo, Args),
- ?line Sorted = from_files(Foo, Fmt),
- ?line delete_files(Foo),
+ S = from_files(Foo, Fmt),
+ ok = file_sorter:keysort(1, Fs0, Foo, Args ++ [{unique,true}]),
+ S = from_files(Foo, Fmt),
+ delete_files([Foo | Fs0]),
+ L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
+ L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
+ L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
+ L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
+ All = [L11, L21, L31, L41],
+ AllFlat = lists:append(All),
+ Sorted = rev(lists:keysort(2, AllFlat), Args),
+ Fs1 = to_files(All, Fmt, Config),
+ ok = file_sorter:keysort(2, Fs1, Foo, Args),
+ Sorted = from_files(Foo, Fmt),
+ delete_files(Foo),
%% Input is files. Output is a fun.
- ?line [] = file_sorter:keysort(2, [], output([], Fmt), Args),
- ?line KS1 = file_sorter:keysort(2, Fs1, output([], Fmt), TmpArgs),
- ?line Sorted = KS1,
- ?line delete_files(Fs1),
+ [] = file_sorter:keysort(2, [], output([], Fmt), Args),
+ KS1 = file_sorter:keysort(2, Fs1, output([], Fmt), TmpArgs),
+ Sorted = KS1,
+ delete_files(Fs1),
%% Input is a fun. Output is a file.
- ?line ok = file_sorter:keysort(2, input([], 2, Fmt), Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keysort(2, input(AllFlat, 4, Fmt), Foo, Args),
- ?line Sorted = from_files(Foo, Fmt),
- ?line delete_files(Foo),
+ ok = file_sorter:keysort(2, input([], 2, Fmt), Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:keysort(2, input(AllFlat, 4, Fmt), Foo, Args),
+ Sorted = from_files(Foo, Fmt),
+ delete_files(Foo),
%% Input is a fun. Output is a fun.
- ?line [] = file_sorter:keysort(2, input([], 2, Fmt), output([], Fmt),Args),
- ?line KS2 =
+ [] = file_sorter:keysort(2, input([], 2, Fmt), output([], Fmt),Args),
+ KS2 =
file_sorter:keysort(2, input(AllFlat, 4, Fmt), output([], Fmt),
TmpArgs),
- ?line Sorted = KS2,
+ Sorted = KS2,
ok.
merge(Fmt, XArgs, Config) ->
@@ -779,35 +779,35 @@ merge(Fmt, XArgs, Config) ->
Foo = outfile("foo", Config),
%% Input is a file. Output is a fun.
- ?line [] = file_sorter:merge([], output([], Fmt), Args),
- ?line L2 = [[1,3,5],[2,4,5]],
- ?line Fs1 = to_files(L2, Fmt, Config),
- ?line S2 = file_sorter:sort(Fs1, output([], Fmt), Args),
- ?line S2 = rev(lists:sort(lists:append(L2)), Args),
- ?line delete_files(Fs1),
+ [] = file_sorter:merge([], output([], Fmt), Args),
+ L2 = [[1,3,5],[2,4,5]],
+ Fs1 = to_files(L2, Fmt, Config),
+ S2 = file_sorter:sort(Fs1, output([], Fmt), Args),
+ S2 = rev(lists:sort(lists:append(L2)), Args),
+ delete_files(Fs1),
%% Input is a file. Output is a file
- ?line ok = file_sorter:merge([], Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:merge([], Foo, [{unique,true} | Args]),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line L31 = [1,2,3],
- ?line L32 = [2,3,4],
- ?line L33 = [4,5,6],
- ?line L3r = [L31, L32, L33],
- ?line L3 = [rev(L31,Args), rev(L32,Args), rev(L33,Args)],
- ?line Fs2 = to_files(L3, Fmt, Config),
- ?line ok = file_sorter:merge(Fs2, Foo, Args),
- ?line true = rev(lists:merge(L3r), Args) =:= from_files(Foo, Fmt),
- ?line ok = file_sorter:merge(Fs2, Foo, Args++[{unique,true},
- {size,100000}]),
- ?line true = rev(lists:umerge(L3r), Args) =:= from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:merge(Fs2, Foo, Args++[{unique,true}]),
- ?line true = rev(lists:umerge(L3r), Args) =:= from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs2]),
+ ok = file_sorter:merge([], Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:merge([], Foo, [{unique,true} | Args]),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ L31 = [1,2,3],
+ L32 = [2,3,4],
+ L33 = [4,5,6],
+ L3r = [L31, L32, L33],
+ L3 = [rev(L31,Args), rev(L32,Args), rev(L33,Args)],
+ Fs2 = to_files(L3, Fmt, Config),
+ ok = file_sorter:merge(Fs2, Foo, Args),
+ true = rev(lists:merge(L3r), Args) =:= from_files(Foo, Fmt),
+ ok = file_sorter:merge(Fs2, Foo, Args++[{unique,true},
+ {size,100000}]),
+ true = rev(lists:umerge(L3r), Args) =:= from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:merge(Fs2, Foo, Args++[{unique,true}]),
+ true = rev(lists:umerge(L3r), Args) =:= from_files(Foo, Fmt),
+ delete_files([Foo | Fs2]),
ok.
@@ -816,83 +816,83 @@ keymerge(Fmt, XArgs, Config) ->
Foo = outfile("foo", Config),
%% Input is files. Output is a file.
- ?line ok = file_sorter:keymerge(2, [], Foo, Args),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keymerge(2, [], Foo, [{unique,true} | Args]),
- ?line [] = from_files(Foo, Fmt),
- ?line delete_files(Foo),
- ?line L0 = [rev([{a,1},{a,2}], Args), rev([{a,2},{a,1},{a,3}], Args)],
- ?line Fs0 = to_files(L0, Fmt, Config),
- ?line delete_files(Foo),
- ?line ok = file_sorter:keymerge(1, Fs0, Foo, Args ++ [{unique,false}]),
- ?line S2 = rev([{a,1},{a,2},{a,2},{a,1},{a,3}], Args),
- ?line S2 = from_files(Foo, Fmt),
- ?line delete_files([Foo | Fs0]),
- ?line L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
- ?line L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
- ?line L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
- ?line L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
- ?line All =
+ ok = file_sorter:keymerge(2, [], Foo, Args),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ ok = file_sorter:keymerge(2, [], Foo, [{unique,true} | Args]),
+ [] = from_files(Foo, Fmt),
+ delete_files(Foo),
+ L0 = [rev([{a,1},{a,2}], Args), rev([{a,2},{a,1},{a,3}], Args)],
+ Fs0 = to_files(L0, Fmt, Config),
+ delete_files(Foo),
+ ok = file_sorter:keymerge(1, Fs0, Foo, Args ++ [{unique,false}]),
+ S2 = rev([{a,1},{a,2},{a,2},{a,1},{a,3}], Args),
+ S2 = from_files(Foo, Fmt),
+ delete_files([Foo | Fs0]),
+ L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
+ L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
+ L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
+ L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
+ All =
[rev(L11, Args), rev(L21, Args), rev(L31, Args), rev(L41, Args)],
- ?line Merged1 = lists:keymerge(2, L11, L21),
- ?line Merged2 = lists:keymerge(2, L31, L41),
- ?line Merged = rev(lists:keymerge(2, Merged1, Merged2), Args),
- ?line Fs1 = to_files(All, Fmt, Config),
- ?line ok = file_sorter:keymerge(2, Fs1, Foo, Args),
- ?line Merged = from_files(Foo, Fmt),
+ Merged1 = lists:keymerge(2, L11, L21),
+ Merged2 = lists:keymerge(2, L31, L41),
+ Merged = rev(lists:keymerge(2, Merged1, Merged2), Args),
+ Fs1 = to_files(All, Fmt, Config),
+ ok = file_sorter:keymerge(2, Fs1, Foo, Args),
+ Merged = from_files(Foo, Fmt),
fun() ->
- UArgs = [{unique,true} | Args],
- ?line UMerged1 = lists:ukeymerge(2, L11, L21),
- ?line UMerged2 = lists:ukeymerge(2, L31, L41),
- ?line UMerged = rev(lists:ukeymerge(2, UMerged1, UMerged2), Args),
- ?line ok = file_sorter:keymerge(2, Fs1, Foo, UArgs),
- ?line UMerged = from_files(Foo, Fmt),
- UArgs2 = make_args(Fmt, [{unique,true}, {size,50} | XArgs]),
- ?line ok = file_sorter:keymerge(2, Fs1, Foo, UArgs2),
- ?line UMerged = from_files(Foo, Fmt),
- ?line List = rev([{a,1,x4},{b,2,x4},{c,3,x4}], Args),
- ?line FsL = to_files([List], Fmt, Config),
- ?line ok = file_sorter:keymerge(2, FsL, Foo, UArgs),
- ?line List = from_files(Foo, Fmt),
- ?line List1 = [{a,1,x4},{b,2,x4},{c,3,x4}],
- ?line List2 = [{a,3,x4},{b,4,x4},{c,5,x4}],
- ?line FsLL = to_files([rev(List1, Args), rev(List2, Args)], Fmt, Config),
- ?line ok = file_sorter:keymerge(2, FsLL, Foo, UArgs),
- ?line List1_2 = rev(lists:ukeymerge(2, List1, List2), Args),
- ?line List1_2 = from_files(Foo, Fmt),
- ?line delete_files(Foo)
+ UArgs = [{unique,true} | Args],
+ UMerged1 = lists:ukeymerge(2, L11, L21),
+ UMerged2 = lists:ukeymerge(2, L31, L41),
+ UMerged = rev(lists:ukeymerge(2, UMerged1, UMerged2), Args),
+ ok = file_sorter:keymerge(2, Fs1, Foo, UArgs),
+ UMerged = from_files(Foo, Fmt),
+ UArgs2 = make_args(Fmt, [{unique,true}, {size,50} | XArgs]),
+ ok = file_sorter:keymerge(2, Fs1, Foo, UArgs2),
+ UMerged = from_files(Foo, Fmt),
+ List = rev([{a,1,x4},{b,2,x4},{c,3,x4}], Args),
+ FsL = to_files([List], Fmt, Config),
+ ok = file_sorter:keymerge(2, FsL, Foo, UArgs),
+ List = from_files(Foo, Fmt),
+ List1 = [{a,1,x4},{b,2,x4},{c,3,x4}],
+ List2 = [{a,3,x4},{b,4,x4},{c,5,x4}],
+ FsLL = to_files([rev(List1, Args), rev(List2, Args)], Fmt, Config),
+ ok = file_sorter:keymerge(2, FsLL, Foo, UArgs),
+ List1_2 = rev(lists:ukeymerge(2, List1, List2), Args),
+ List1_2 = from_files(Foo, Fmt),
+ delete_files(Foo)
end(),
%% Input is files. Output is a fun.
- ?line Fs3 = to_files(All, Fmt, Config),
- ?line [] = file_sorter:keysort(2, [], output([], Fmt), Args),
- ?line KS1 = file_sorter:keymerge(2, Fs3, output([], Fmt), Args),
- ?line Merged = KS1,
- ?line delete_files([Foo | Fs3]),
-
- ?line L2 = [[{a,1}],[{a,2}],[{a,3}],[{a,4}],[{a,5}],[{a,6}],[{a,7}]],
- ?line Fs2 = to_files(L2, Fmt, Config),
- ?line M = file_sorter:keymerge(1, Fs2, output([], Fmt), Args),
- ?line M = rev(lists:append(L2), Args),
- ?line delete_files(Fs2),
-
- ?line LL1 = [{d,4},{e,5},{f,6}],
- ?line LL2 = [{a,1},{b,2},{c,3}],
- ?line LL3 = [{j,10},{k,11},{l,12}],
- ?line LL4 = [{g,7},{h,8},{i,9}],
- ?line LL5 = [{p,16},{q,17},{r,18}],
- ?line LL6 = [{m,13},{n,14},{o,15}],
- ?line LLAll = [rev(LL1, Args),rev(LL2, Args),rev(LL3, Args),
- rev(LL4, Args),rev(LL5, Args),rev(LL6, Args)],
- ?line FsLL6 = to_files(LLAll, Fmt, Config),
- ?line LL = rev(lists:sort(lists:append(LLAll)), Args),
- ?line ok = file_sorter:keymerge(1, FsLL6, Foo, Args),
- ?line LL = from_files(Foo, Fmt),
- ?line ok = file_sorter:keymerge(1, FsLL6, Foo, [{unique,true} | Args]),
- ?line LL = from_files(Foo, Fmt),
- ?line delete_files([Foo | FsLL6]),
+ Fs3 = to_files(All, Fmt, Config),
+ [] = file_sorter:keysort(2, [], output([], Fmt), Args),
+ KS1 = file_sorter:keymerge(2, Fs3, output([], Fmt), Args),
+ Merged = KS1,
+ delete_files([Foo | Fs3]),
+
+ L2 = [[{a,1}],[{a,2}],[{a,3}],[{a,4}],[{a,5}],[{a,6}],[{a,7}]],
+ Fs2 = to_files(L2, Fmt, Config),
+ M = file_sorter:keymerge(1, Fs2, output([], Fmt), Args),
+ M = rev(lists:append(L2), Args),
+ delete_files(Fs2),
+
+ LL1 = [{d,4},{e,5},{f,6}],
+ LL2 = [{a,1},{b,2},{c,3}],
+ LL3 = [{j,10},{k,11},{l,12}],
+ LL4 = [{g,7},{h,8},{i,9}],
+ LL5 = [{p,16},{q,17},{r,18}],
+ LL6 = [{m,13},{n,14},{o,15}],
+ LLAll = [rev(LL1, Args),rev(LL2, Args),rev(LL3, Args),
+ rev(LL4, Args),rev(LL5, Args),rev(LL6, Args)],
+ FsLL6 = to_files(LLAll, Fmt, Config),
+ LL = rev(lists:sort(lists:append(LLAll)), Args),
+ ok = file_sorter:keymerge(1, FsLL6, Foo, Args),
+ LL = from_files(Foo, Fmt),
+ ok = file_sorter:keymerge(1, FsLL6, Foo, [{unique,true} | Args]),
+ LL = from_files(Foo, Fmt),
+ delete_files([Foo | FsLL6]),
ok.
@@ -902,84 +902,84 @@ funmerge(Fmt, XArgs, Config) ->
UArgs = [{unique,true} | Args],
Foo = outfile(foo, Config),
- ?line EFs = to_files([[]], Fmt, Config),
- ?line ok = file_sorter:merge(EFs, Foo, UArgs),
- ?line [] = from_files(Foo, Fmt),
+ EFs = to_files([[]], Fmt, Config),
+ ok = file_sorter:merge(EFs, Foo, UArgs),
+ [] = from_files(Foo, Fmt),
delete_files([Foo | EFs]),
- ?line L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
- ?line L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
- ?line L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
- ?line L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
- ?line CAll = [L11, L21, L31, L41],
- ?line CMerged1 = lists:merge(KComp, L11, L21),
- ?line CMerged2 = lists:merge(KComp, L31, L41),
- ?line CMerged = lists:merge(KComp, CMerged1, CMerged2),
- ?line CFs1 = to_files(CAll, Fmt, Config),
- ?line ok = file_sorter:merge(CFs1, Foo, Args),
- ?line CMerged = from_files(Foo, Fmt),
+ L11 = [{a,1,x4},{b,2,x4},{c,3,x4}],
+ L21 = [{a,1,x3},{b,2,x3},{c,3,x3}],
+ L31 = [{a,1,x2},{b,2,x2},{c,3,x2}],
+ L41 = [{a,1,x1},{b,2,x1},{c,3,x1}],
+ CAll = [L11, L21, L31, L41],
+ CMerged1 = lists:merge(KComp, L11, L21),
+ CMerged2 = lists:merge(KComp, L31, L41),
+ CMerged = lists:merge(KComp, CMerged1, CMerged2),
+ CFs1 = to_files(CAll, Fmt, Config),
+ ok = file_sorter:merge(CFs1, Foo, Args),
+ CMerged = from_files(Foo, Fmt),
Args4 = make_args(Fmt, [{size,50} | XArgs]),
- ?line ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | Args4]),
- ?line CMerged = from_files(Foo, Fmt),
-
- ?line UMerged1 = lists:umerge(KComp, L11, L21),
- ?line UMerged2 = lists:umerge(KComp, L31, L41),
- ?line UMerged = lists:umerge(KComp, UMerged1, UMerged2),
- ?line ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | UArgs]),
- ?line UMerged = from_files(Foo, Fmt),
+ ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | Args4]),
+ CMerged = from_files(Foo, Fmt),
+
+ UMerged1 = lists:umerge(KComp, L11, L21),
+ UMerged2 = lists:umerge(KComp, L31, L41),
+ UMerged = lists:umerge(KComp, UMerged1, UMerged2),
+ ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | UArgs]),
+ UMerged = from_files(Foo, Fmt),
UArgs2 =
lists:keydelete(order, 1,
make_args(Fmt, [{unique,true}, {size,50} | XArgs])),
- ?line ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | UArgs2]),
- ?line UMerged = from_files(Foo, Fmt),
- ?line delete_files(Foo),
-
- ?line List1 = [{a,1,x4},{b,2,x4},{c,3,x4}],
- ?line List2 = [{a,3,x4},{b,4,x4},{c,5,x4}],
- ?line List3 = [{a,5,x4},{b,6,x4},{c,7,x4}],
- ?line FsLL = to_files([List1, List2, List3], Fmt, Config),
- ?line ok = file_sorter:merge(FsLL, Foo, Args),
- ?line List1_2 = lists:merge(KComp,lists:merge(KComp,List1,List2),List3),
- ?line List1_2 = from_files(Foo, Fmt),
- ?line ok = file_sorter:merge(FsLL, Foo, [{order,KComp} | UArgs]),
- ?line UList1_2 =
+ ok = file_sorter:merge(CFs1, Foo, [{order,KComp} | UArgs2]),
+ UMerged = from_files(Foo, Fmt),
+ delete_files(Foo),
+
+ List1 = [{a,1,x4},{b,2,x4},{c,3,x4}],
+ List2 = [{a,3,x4},{b,4,x4},{c,5,x4}],
+ List3 = [{a,5,x4},{b,6,x4},{c,7,x4}],
+ FsLL = to_files([List1, List2, List3], Fmt, Config),
+ ok = file_sorter:merge(FsLL, Foo, Args),
+ List1_2 = lists:merge(KComp,lists:merge(KComp,List1,List2),List3),
+ List1_2 = from_files(Foo, Fmt),
+ ok = file_sorter:merge(FsLL, Foo, [{order,KComp} | UArgs]),
+ UList1_2 =
lists:umerge(KComp,lists:umerge(KComp, List1, List2),List3),
- ?line UList1_2 = from_files(Foo, Fmt),
- ?line delete_files([Foo | CFs1]),
+ UList1_2 = from_files(Foo, Fmt),
+ delete_files([Foo | CFs1]),
fun() ->
- ?line LL1 = [{d,4},{e,5},{f,6}],
- ?line LL2 = [{a,1},{b,2},{c,3}],
- ?line LL3 = [{j,10},{k,11},{l,12}],
- ?line LL4 = [{g,7},{h,8},{i,9}],
- ?line LL5 = [{p,16},{q,17},{r,18}],
- ?line LL6 = [{m,13},{n,14},{o,15}],
- ?line LLAll = [LL1,LL2,LL3,LL4,LL5,LL6],
- ?line FsLL6 = to_files(LLAll, Fmt, Config),
- ?line LL = lists:sort(lists:append(LLAll)),
- ?line ok = file_sorter:merge(FsLL6, Foo, Args),
- ?line LL = from_files(Foo, Fmt),
- ?line ok = file_sorter:merge(FsLL6, Foo, UArgs),
- ?line LL = from_files(Foo, Fmt),
- ?line delete_files([Foo | FsLL6])
+ LL1 = [{d,4},{e,5},{f,6}],
+ LL2 = [{a,1},{b,2},{c,3}],
+ LL3 = [{j,10},{k,11},{l,12}],
+ LL4 = [{g,7},{h,8},{i,9}],
+ LL5 = [{p,16},{q,17},{r,18}],
+ LL6 = [{m,13},{n,14},{o,15}],
+ LLAll = [LL1,LL2,LL3,LL4,LL5,LL6],
+ FsLL6 = to_files(LLAll, Fmt, Config),
+ LL = lists:sort(lists:append(LLAll)),
+ ok = file_sorter:merge(FsLL6, Foo, Args),
+ LL = from_files(Foo, Fmt),
+ ok = file_sorter:merge(FsLL6, Foo, UArgs),
+ LL = from_files(Foo, Fmt),
+ delete_files([Foo | FsLL6])
end(),
fun() ->
- ?line RLL1 = [{b,2},{h,8},{n,14}],
- ?line RLL2 = [{a,1},{g,7},{m,13}],
- ?line RLL3 = [{d,4},{j,10},{p,16}],
- ?line RLL4 = [{c,3},{i,9},{o,15}],
- ?line RLL5 = [{f,6},{l,12},{r,18}],
- ?line RLL6 = [{e,5},{k,11},{q,17}],
- ?line RLLAll = [RLL1,RLL2,RLL3,RLL4,RLL5,RLL6],
- ?line RFsLL6 = to_files(RLLAll, Fmt, Config),
- ?line RLL = lists:sort(lists:append(RLLAll)),
- ?line ok = file_sorter:merge(RFsLL6, Foo, Args),
- ?line RLL = from_files(Foo, Fmt),
- ?line ok = file_sorter:merge(RFsLL6, Foo, UArgs),
- ?line RLL = from_files(Foo, Fmt),
- ?line delete_files([Foo | RFsLL6])
+ RLL1 = [{b,2},{h,8},{n,14}],
+ RLL2 = [{a,1},{g,7},{m,13}],
+ RLL3 = [{d,4},{j,10},{p,16}],
+ RLL4 = [{c,3},{i,9},{o,15}],
+ RLL5 = [{f,6},{l,12},{r,18}],
+ RLL6 = [{e,5},{k,11},{q,17}],
+ RLLAll = [RLL1,RLL2,RLL3,RLL4,RLL5,RLL6],
+ RFsLL6 = to_files(RLLAll, Fmt, Config),
+ RLL = lists:sort(lists:append(RLLAll)),
+ ok = file_sorter:merge(RFsLL6, Foo, Args),
+ RLL = from_files(Foo, Fmt),
+ ok = file_sorter:merge(RFsLL6, Foo, UArgs),
+ RLL = from_files(Foo, Fmt),
+ delete_files([Foo | RFsLL6])
end(),
ok.
@@ -993,57 +993,57 @@ check(Fmt, Config) ->
L1 = [3,1,2,5,4],
[F1_0] = Fs1 = to_files([L1], Fmt, Config),
F1 = filename:absname(F1_0),
- ?line {ok, [{F1,2,1}]} = file_sorter:check(Fs1, Args),
- ?line {ok, [{F1,2,1}]} = file_sorter:check(Fs1, [{order,Fun} | Args]),
- ?line {ok, [{F1,2,1}]} = file_sorter:check(Fs1, [{unique,true} | Args]),
- ?line {ok, [{F1,2,1}]} =
+ {ok, [{F1,2,1}]} = file_sorter:check(Fs1, Args),
+ {ok, [{F1,2,1}]} = file_sorter:check(Fs1, [{order,Fun} | Args]),
+ {ok, [{F1,2,1}]} = file_sorter:check(Fs1, [{unique,true} | Args]),
+ {ok, [{F1,2,1}]} =
file_sorter:check(Fs1, [{order,Fun},{unique,true} | Args]),
- ?line {ok, [{F1,3,2}]} =
+ {ok, [{F1,3,2}]} =
file_sorter:check(Fs1, [{order,descending} | Args]),
- ?line {ok, [{F1,3,2}]} =
+ {ok, [{F1,3,2}]} =
file_sorter:check(Fs1, [{unique,true},{order,descending} | Args]),
- ?line delete_files(Fs1),
-
+ delete_files(Fs1),
+
L2 = [[1,2,2,3,3,4,5,5],[5,5,4,3,3,2,2,1]],
[F2_0,F3_0] = Fs2 = to_files(L2, Fmt, Config),
F2 = filename:absname(F2_0),
F3 = filename:absname(F3_0),
- ?line {ok, [{F3,3,4}]} = file_sorter:check(Fs2, Args),
- ?line {ok, [{F3,3,4}]} = file_sorter:check(Fs2, [{order,Fun} | Args]),
- ?line {ok, [{F2,3,2},{F3,2,5}]} =
+ {ok, [{F3,3,4}]} = file_sorter:check(Fs2, Args),
+ {ok, [{F3,3,4}]} = file_sorter:check(Fs2, [{order,Fun} | Args]),
+ {ok, [{F2,3,2},{F3,2,5}]} =
file_sorter:check(Fs2, [{unique, true} | Args]),
- ?line {ok, [{F2,3,2},{F3,2,5}]} =
+ {ok, [{F2,3,2},{F3,2,5}]} =
file_sorter:check(Fs2, [{order,Fun},{unique, true} | Args]),
- ?line {ok, [{F2,2,2}]} =
+ {ok, [{F2,2,2}]} =
file_sorter:check(Fs2, [{order,descending} | Args]),
- ?line {ok, [{F2,2,2},{F3,2,5}]} =
+ {ok, [{F2,2,2},{F3,2,5}]} =
file_sorter:check(Fs2, [{unique,true},{order,descending} | Args]),
- ?line delete_files(Fs2),
-
+ delete_files(Fs2),
+
L3 = [1,2,3,4],
- ?line Fs3 = to_files([L3], Fmt, Config),
- ?line {ok, []} = file_sorter:check(Fs3, [{unique,true} | Args]),
- ?line {ok, []} =
+ Fs3 = to_files([L3], Fmt, Config),
+ {ok, []} = file_sorter:check(Fs3, [{unique,true} | Args]),
+ {ok, []} =
file_sorter:check(Fs3, [{unique,true},{order,Fun} | Args]),
- ?line delete_files(Fs3),
+ delete_files(Fs3),
%% big objects
- ?line T1 = erlang:make_tuple(10000,foo),
- ?line T2 = erlang:make_tuple(10000,bar),
- ?line L4 = [T1,T2],
- ?line [FF_0] = Fs4 = to_files([L4], Fmt, Config),
+ T1 = erlang:make_tuple(10000,foo),
+ T2 = erlang:make_tuple(10000,bar),
+ L4 = [T1,T2],
+ [FF_0] = Fs4 = to_files([L4], Fmt, Config),
FF = filename:absname(FF_0),
- ?line {ok, [{FF,2,T2}]} = file_sorter:check(Fs4, [{unique,true} | Args]),
- ?line delete_files(Fs4),
+ {ok, [{FF,2,T2}]} = file_sorter:check(Fs4, [{unique,true} | Args]),
+ delete_files(Fs4),
CFun = key_compare(2),
L10 = [[{1,a},{2,b},T10_1={1,b},{3,c}], [{1,b},T10_2={2,a}]],
[F10_0,F11_0] = Fs10 = to_files(L10, Fmt, Config),
F10_1 = filename:absname(F10_0),
F11_1 = filename:absname(F11_0),
- ?line {ok, [{F10_1,3,T10_1},{F11_1,2,T10_2}]} =
+ {ok, [{F10_1,3,T10_1},{F11_1,2,T10_2}]} =
file_sorter:check(Fs10, [{unique,true},{order,CFun} | Args]),
- ?line delete_files(Fs10),
+ delete_files(Fs10),
ok.
@@ -1051,31 +1051,31 @@ keycheck(Fmt, Config) ->
Args0 = make_args(Fmt, [{size,5}]),
Args = Args0 ++ [{tmpdir,?privdir(Config)}],
- ?line L1 = [[{a,1},{b,2}], [{c,2},{b,1},{a,3}]],
- ?line [F1_0,F2_0] = Fs1 = to_files(L1, Fmt, Config),
+ L1 = [[{a,1},{b,2}], [{c,2},{b,1},{a,3}]],
+ [F1_0,F2_0] = Fs1 = to_files(L1, Fmt, Config),
F1 = filename:absname(F1_0),
F2 = filename:absname(F2_0),
- ?line {ok, [{F2,2,{b,1}}]} = file_sorter:keycheck(1, Fs1, Args),
- ?line {ok, [{F2,2,{b,1}}]} =
+ {ok, [{F2,2,{b,1}}]} = file_sorter:keycheck(1, Fs1, Args),
+ {ok, [{F2,2,{b,1}}]} =
file_sorter:keycheck(1, Fs1, [{unique,true} | Args]),
- ?line {ok, [{F1,2,{b,2}}]} =
+ {ok, [{F1,2,{b,2}}]} =
file_sorter:keycheck(1, Fs1, [{order,descending},{unique,true} | Args]),
- ?line delete_files(Fs1),
-
+ delete_files(Fs1),
+
L2 = [[{a,1},{a,2},{a,2},{b,2}], [{c,2},{b,1},{b,2},{b,2},{a,3}]],
- ?line [F3_0,F4_0] = Fs2 = to_files(L2, Fmt, Config),
+ [F3_0,F4_0] = Fs2 = to_files(L2, Fmt, Config),
F3 = filename:absname(F3_0),
F4 = filename:absname(F4_0),
- ?line {ok, [{F4,2,{b,1}}]} = file_sorter:keycheck(1, Fs2, Args),
- ?line {ok, [{F3,2,{a,2}},{F4,2,{b,1}}]} =
+ {ok, [{F4,2,{b,1}}]} = file_sorter:keycheck(1, Fs2, Args),
+ {ok, [{F3,2,{a,2}},{F4,2,{b,1}}]} =
file_sorter:keycheck(1, Fs2, [{unique,true} | Args]),
- ?line {ok, [{F3,4,{b,2}}]} =
+ {ok, [{F3,4,{b,2}}]} =
file_sorter:keycheck(1, Fs2, [{order,descending} | Args]),
- ?line {ok, [{F3,2,{a,2}},{F4,3,{b,2}}]} =
+ {ok, [{F3,2,{a,2}},{F4,3,{b,2}}]} =
file_sorter:keycheck(1, Fs2,
[{order,descending},{unique,true} | Args]),
- ?line delete_files(Fs2),
-
+ delete_files(Fs2),
+
ok.
rev(L, Args) ->
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 58a235e737..5b28c03270 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -64,14 +64,14 @@ end_per_group(_GroupName, Config) ->
wildcard_one(Config) when is_list(Config) ->
- ?line {ok,OldCwd} = file:get_cwd(),
- ?line Dir = filename:join(?config(priv_dir, Config), "wildcard_one"),
- ?line ok = file:make_dir(Dir),
+ {ok,OldCwd} = file:get_cwd(),
+ Dir = filename:join(?config(priv_dir, Config), "wildcard_one"),
+ ok = file:make_dir(Dir),
do_wildcard_1(Dir,
fun(Wc) ->
filelib:wildcard(Wc, Dir, erl_prim_loader)
end),
- ?line file:set_cwd(Dir),
+ file:set_cwd(Dir),
do_wildcard_1(Dir,
fun(Wc) ->
L = filelib:wildcard(Wc),
@@ -80,30 +80,30 @@ wildcard_one(Config) when is_list(Config) ->
L = filelib:wildcard(Wc, Dir),
L = filelib:wildcard(Wc, Dir++"/.")
end),
- ?line file:set_cwd(OldCwd),
- ?line ok = file:del_dir(Dir),
+ file:set_cwd(OldCwd),
+ ok = file:del_dir(Dir),
ok.
wildcard_two(Config) when is_list(Config) ->
- ?line Dir = filename:join(?config(priv_dir, Config), "wildcard_two"),
- ?line ok = file:make_dir(Dir),
- ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end),
- ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end),
- ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/.") end),
+ Dir = filename:join(?config(priv_dir, Config), "wildcard_two"),
+ ok = file:make_dir(Dir),
+ do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end),
+ do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end),
+ do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/.") end),
case os:type() of
{win32,_} ->
ok;
_ ->
- ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, "//"++Dir) end)
+ do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, "//"++Dir) end)
end,
- ?line ok = file:del_dir(Dir),
+ ok = file:del_dir(Dir),
ok.
wildcard_errors(Config) when is_list(Config) ->
- ?line wcc("{", missing_delimiter),
- ?line wcc("{a", missing_delimiter),
- ?line wcc("{a,", missing_delimiter),
- ?line wcc("{a,b", missing_delimiter),
+ wcc("{", missing_delimiter),
+ wcc("{a", missing_delimiter),
+ wcc("{a,", missing_delimiter),
+ wcc("{a,b", missing_delimiter),
ok.
wcc(Wc, Error) ->
@@ -130,70 +130,70 @@ subtract_dir("/"++Cs, []) -> Cs.
do_wildcard_2(Dir, Wcf) ->
%% Basic wildcards.
All = ["abc","abcdef","glurf"],
- ?line Files = mkfiles(lists:reverse(All), Dir),
- ?line All = Wcf("*"),
- ?line ["abc","abcdef"] = Wcf("a*"),
- ?line ["abc","abcdef"] = Wcf("abc*"),
- ?line ["abcdef"] = Wcf("abc???"),
- ?line ["abcdef"] = Wcf("abcd*"),
- ?line ["abcdef"] = Wcf("*def"),
- ?line ["abcdef","glurf"] = Wcf("{*def,gl*}"),
- ?line ["abc","abcdef"] = Wcf("a*{def,}"),
- ?line ["abc","abcdef"] = Wcf("a*{,def}"),
+ Files = mkfiles(lists:reverse(All), Dir),
+ All = Wcf("*"),
+ ["abc","abcdef"] = Wcf("a*"),
+ ["abc","abcdef"] = Wcf("abc*"),
+ ["abcdef"] = Wcf("abc???"),
+ ["abcdef"] = Wcf("abcd*"),
+ ["abcdef"] = Wcf("*def"),
+ ["abcdef","glurf"] = Wcf("{*def,gl*}"),
+ ["abc","abcdef"] = Wcf("a*{def,}"),
+ ["abc","abcdef"] = Wcf("a*{,def}"),
%% Constant wildcard.
["abcdef"] = Wcf("abcdef"),
%% Negative tests.
- ?line [] = Wcf("b*"),
- ?line [] = Wcf("bufflig"),
+ [] = Wcf("b*"),
+ [] = Wcf("bufflig"),
- ?line del(Files),
+ del(Files),
do_wildcard_3(Dir, Wcf).
-
+
do_wildcard_3(Dir, Wcf) ->
%% Some character sets.
All = ["a01","a02","a03","b00","c02","d19"],
- ?line Files = mkfiles(lists:reverse(All), Dir),
- ?line All = Wcf("[a-z]*"),
- ?line All = Wcf("[a-d]*"),
- ?line All = Wcf("[adbc]*"),
- ?line All = Wcf("?[0-9][0-9]"),
- ?line All = Wcf("?[0-1][0-39]"),
- ?line All = Wcf("[abcdefgh][10][01239]"),
- ?line ["a01","a02","a03","b00","c02"] = Wcf("[a-z]0[0-3]"),
- ?line [] = Wcf("?[a-z][0-39]"),
- ?line del(Files),
+ Files = mkfiles(lists:reverse(All), Dir),
+ All = Wcf("[a-z]*"),
+ All = Wcf("[a-d]*"),
+ All = Wcf("[adbc]*"),
+ All = Wcf("?[0-9][0-9]"),
+ All = Wcf("?[0-1][0-39]"),
+ All = Wcf("[abcdefgh][10][01239]"),
+ ["a01","a02","a03","b00","c02"] = Wcf("[a-z]0[0-3]"),
+ [] = Wcf("?[a-z][0-39]"),
+ del(Files),
do_wildcard_4(Dir, Wcf).
do_wildcard_4(Dir, Wcf) ->
%% More character sets: tricky characters.
All = ["a-","aA","aB","aC","a[","a]"],
- ?line Files = mkfiles(lists:reverse(All), Dir),
- ?line All = Wcf("a[][A-C-]"),
+ Files = mkfiles(lists:reverse(All), Dir),
+ All = Wcf("a[][A-C-]"),
["a-"] = Wcf("a[-]"),
["a["] = Wcf("a["),
- ?line del(Files),
+ del(Files),
do_wildcard_5(Dir, Wcf).
do_wildcard_5(Dir, Wcf) ->
Dirs = ["xa","blurf","yyy"],
- ?line foreach(fun(D) -> ok = file:make_dir(filename:join(Dir, D)) end, Dirs),
+ foreach(fun(D) -> ok = file:make_dir(filename:join(Dir, D)) end, Dirs),
All = ["blurf/nisse","xa/arne","xa/kalle","yyy/arne"],
- ?line Files = mkfiles(lists:reverse(All), Dir),
+ Files = mkfiles(lists:reverse(All), Dir),
%% Test.
- ?line All = Wcf("*/*"),
- ?line ["blurf/nisse","xa/arne","xa/kalle"] = Wcf("{blurf,xa}/*"),
- ?line ["xa/arne","yyy/arne"] = Wcf("*/arne"),
- ?line ["blurf/nisse"] = Wcf("*/nisse"),
- ?line [] = Wcf("mountain/*"),
- ?line [] = Wcf("xa/gurka"),
+ All = Wcf("*/*"),
+ ["blurf/nisse","xa/arne","xa/kalle"] = Wcf("{blurf,xa}/*"),
+ ["xa/arne","yyy/arne"] = Wcf("*/arne"),
+ ["blurf/nisse"] = Wcf("*/nisse"),
+ [] = Wcf("mountain/*"),
+ [] = Wcf("xa/gurka"),
["blurf/nisse"] = Wcf("blurf/nisse"),
%% Cleanup
- ?line del(Files),
- ?line foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs),
+ del(Files),
+ foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs),
do_wildcard_6(Dir, Wcf).
do_wildcard_6(Dir, Wcf) ->
@@ -270,45 +270,45 @@ do_wildcard_9(Dir, Wcf) ->
fold_files(Config) when is_list(Config) ->
- ?line Dir = filename:join(?config(priv_dir, Config), "fold_files"),
- ?line ok = file:make_dir(Dir),
- ?line Dirs = [filename:join(Dir, D) || D <- ["blurf","blurf/blarf"]],
- ?line foreach(fun(D) -> ok = file:make_dir(D) end, Dirs),
+ Dir = filename:join(?config(priv_dir, Config), "fold_files"),
+ ok = file:make_dir(Dir),
+ Dirs = [filename:join(Dir, D) || D <- ["blurf","blurf/blarf"]],
+ foreach(fun(D) -> ok = file:make_dir(D) end, Dirs),
All = ["fb.txt","ko.txt",
"blurf/nisse.text","blurf/blarf/aaa.txt","blurf/blarf/urfa.txt"],
- ?line Files = mkfiles(lists:reverse(All), Dir),
+ Files = mkfiles(lists:reverse(All), Dir),
%% Test.
- ?line Files0 = filelib:fold_files(Dir, "^", false,
- fun(H, T) -> [H|T] end, []),
- ?line same_lists(["fb.txt","ko.txt"], Files0, Dir),
+ Files0 = filelib:fold_files(Dir, "^", false,
+ fun(H, T) -> [H|T] end, []),
+ same_lists(["fb.txt","ko.txt"], Files0, Dir),
- ?line Files1 = filelib:fold_files(Dir, "^", true,
- fun(H, T) -> [H|T] end, []),
- ?line same_lists(All, Files1, Dir),
+ Files1 = filelib:fold_files(Dir, "^", true,
+ fun(H, T) -> [H|T] end, []),
+ same_lists(All, Files1, Dir),
- ?line Files2 = filelib:fold_files(Dir, "[.]text$", true,
- fun(H, T) -> [H|T] end, []),
- ?line same_lists(["blurf/nisse.text"], Files2, Dir),
+ Files2 = filelib:fold_files(Dir, "[.]text$", true,
+ fun(H, T) -> [H|T] end, []),
+ same_lists(["blurf/nisse.text"], Files2, Dir),
- ?line Files3 = filelib:fold_files(Dir, "^..[.]", true,
- fun(H, T) -> [H|T] end, []),
- ?line same_lists(["fb.txt","ko.txt"], Files3, Dir),
+ Files3 = filelib:fold_files(Dir, "^..[.]", true,
+ fun(H, T) -> [H|T] end, []),
+ same_lists(["fb.txt","ko.txt"], Files3, Dir),
- ?line Files4 = filelib:fold_files(Dir, "^ko[.]txt$", true,
- fun(H, T) -> [H|T] end, []),
- ?line same_lists(["ko.txt"], Files4, Dir),
- ?line Files4 = filelib:fold_files(Dir, "^ko[.]txt$", false,
- fun(H, T) -> [H|T] end, []),
+ Files4 = filelib:fold_files(Dir, "^ko[.]txt$", true,
+ fun(H, T) -> [H|T] end, []),
+ same_lists(["ko.txt"], Files4, Dir),
+ Files4 = filelib:fold_files(Dir, "^ko[.]txt$", false,
+ fun(H, T) -> [H|T] end, []),
- ?line [] = filelib:fold_files(Dir, "^$", true,
- fun(H, T) -> [H|T] end, []),
+ [] = filelib:fold_files(Dir, "^$", true,
+ fun(H, T) -> [H|T] end, []),
%% Cleanup
- ?line del(Files),
- ?line foreach(fun(D) -> ok = file:del_dir(D) end, lists:reverse(Dirs)),
- ?line ok = file:del_dir(Dir).
+ del(Files),
+ foreach(fun(D) -> ok = file:del_dir(D) end, lists:reverse(Dirs)),
+ ok = file:del_dir(Dir).
same_lists(Expected0, Actual0, BaseDir) ->
Expected = [filename:absname(N, BaseDir) || N <- lists:sort(Expected0)],
@@ -329,43 +329,43 @@ del([]) -> ok.
%% Test that filelib:ensure_dir/1 returns ok or {error,Reason}.
otp_5960(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Dir = filename:join(PrivDir, "otp_5960_dir"),
- ?line Name1 = filename:join(Dir, name1),
- ?line Name2 = filename:join(Dir, name2),
- ?line ok = filelib:ensure_dir(Name1), % parent is created
- ?line ok = filelib:ensure_dir(Name1), % repeating it should be OK
- ?line ok = filelib:ensure_dir(Name2), % parent already exists
- ?line ok = filelib:ensure_dir(Name2), % repeating it should be OK
- ?line Name3 = filename:join(Name1, name3),
- ?line {ok, FileInfo} = file:read_file_info(Dir),
+ PrivDir = ?config(priv_dir, Config),
+ Dir = filename:join(PrivDir, "otp_5960_dir"),
+ Name1 = filename:join(Dir, name1),
+ Name2 = filename:join(Dir, name2),
+ ok = filelib:ensure_dir(Name1), % parent is created
+ ok = filelib:ensure_dir(Name1), % repeating it should be OK
+ ok = filelib:ensure_dir(Name2), % parent already exists
+ ok = filelib:ensure_dir(Name2), % repeating it should be OK
+ Name3 = filename:join(Name1, name3),
+ {ok, FileInfo} = file:read_file_info(Dir),
case os:type() of
{win32,_} ->
%% Not possibly to write protect directories on Windows
%% (at least not using file:write_file_info/2).
ok;
_ ->
- ?line Mode = FileInfo#file_info.mode,
- ?line NoWriteMode = Mode - 8#00200 - 8#00020 - 8#00002,
- ?line ok = file:write_file_info(Dir, #file_info{mode=NoWriteMode}),
- ?line {error, _} = filelib:ensure_dir(Name3),
- ?line ok = file:write_file_info(Dir, #file_info{mode=Mode}),
+ Mode = FileInfo#file_info.mode,
+ NoWriteMode = Mode - 8#00200 - 8#00020 - 8#00002,
+ ok = file:write_file_info(Dir, #file_info{mode=NoWriteMode}),
+ {error, _} = filelib:ensure_dir(Name3),
+ ok = file:write_file_info(Dir, #file_info{mode=Mode}),
ok
end.
ensure_dir_eexist(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Dir = filename:join(PrivDir, "ensure_dir_eexist"),
- ?line Name = filename:join(Dir, "same_name_as_file_and_dir"),
- ?line ok = filelib:ensure_dir(Name),
- ?line ok = file:write_file(Name, <<"some string\n">>),
+ PrivDir = ?config(priv_dir, Config),
+ Dir = filename:join(PrivDir, "ensure_dir_eexist"),
+ Name = filename:join(Dir, "same_name_as_file_and_dir"),
+ ok = filelib:ensure_dir(Name),
+ ok = file:write_file(Name, <<"some string\n">>),
%% There already is a file with the name of the directory
%% we want to create.
- ?line NeedFile = filename:join(Name, "file"),
- ?line NeedFileB = filename:join(Name, <<"file">>),
- ?line {error, eexist} = filelib:ensure_dir(NeedFile),
- ?line {error, eexist} = filelib:ensure_dir(NeedFileB),
+ NeedFile = filename:join(Name, "file"),
+ NeedFileB = filename:join(Name, <<"file">>),
+ {error, eexist} = filelib:ensure_dir(NeedFile),
+ {error, eexist} = filelib:ensure_dir(NeedFileB),
ok.
ensure_dir_symlink(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/fixtable_SUITE.erl b/lib/stdlib/test/fixtable_SUITE.erl
index 270e4460e2..d681349fcd 100644
--- a/lib/stdlib/test/fixtable_SUITE.erl
+++ b/lib/stdlib/test/fixtable_SUITE.erl
@@ -100,15 +100,15 @@ show(Term, Line) ->
%% Check for bug OTP-5087; safe_fixtable for bags could give incorrect
%% lookups.
fixbag(Config) when is_list(Config) ->
- ?line T = ets:new(x,[bag]),
- ?line ets:insert(T,{a,1}),
- ?line ets:insert(T,{a,2}),
- ?line ets:safe_fixtable(T,true),
- ?line ets:match_delete(T,{a,2}),
- ?line ets:insert(T,{a,3}),
- ?line Res = ets:lookup(T,a),
- ?line ets:safe_fixtable(T,false),
- ?line Res = ets:lookup(T,a),
+ T = ets:new(x,[bag]),
+ ets:insert(T,{a,1}),
+ ets:insert(T,{a,2}),
+ ets:safe_fixtable(T,true),
+ ets:match_delete(T,{a,2}),
+ ets:insert(T,{a,3}),
+ Res = ets:lookup(T,a),
+ ets:safe_fixtable(T,false),
+ Res = ets:lookup(T,a),
ok.
@@ -116,255 +116,255 @@ fixbag(Config) when is_list(Config) ->
%% Check correct behaviour if a key is deleted and reinserted during
%% fixation.
insert_same_key(Config) when is_list(Config) ->
- ?line {ok,Dets1} = dets:open_file(?DETS_TMP1,
- [{file, dets_filename(?DETS_TMP1,Config)}]),
- ?line Ets1 = ets:new(ets,[]),
- ?line insert_same_key(Dets1,dets,Config),
- ?line insert_same_key(Ets1,ets,Config),
- ?line ets:insert(Ets1,{1,2}),
- ?line 1 = ets:info(Ets1,size),
- ?line dets:insert(Dets1,{1,2}),
- ?line 1 = dets:info(Dets1,size),
- ?line dets:close(Dets1),
- ?line (catch file:delete(dets_filename(Dets1,Config))),
- ?line ets:delete(Ets1),
- ?line {ok,Dets2} = dets:open_file(?DETS_TMP1,
- [{type,bag},{file, dets_filename(?DETS_TMP1,Config)}]),
- ?line Ets2 = ets:new(ets,[bag]),
- ?line insert_same_key(Dets2,dets,Config),
- ?line insert_same_key(Ets2,ets,Config),
- ?line ets:insert(Ets2,{1,2}),
- ?line 2 = ets:info(Ets2,size),
- ?line ets:insert(Ets2,{1,2}),
- ?line 2 = ets:info(Ets2,size),
- ?line dets:insert(Dets2,{1,2}),
- ?line 2 = dets:info(Dets2,size),
- ?line dets:insert(Dets2,{1,2}),
- ?line 2 = dets:info(Dets2,size),
- ?line dets:close(Dets2),
- ?line (catch file:delete(dets_filename(Dets2,Config))),
- ?line ets:delete(Ets2),
- ?line {ok,Dets3} = dets:open_file(?DETS_TMP1,
- [{type,duplicate_bag},
- {file, dets_filename(?DETS_TMP1,Config)}]),
- ?line Ets3 = ets:new(ets,[duplicate_bag]),
- ?line insert_same_key(Dets3,dets,Config),
- ?line insert_same_key(Ets3,ets,Config),
- ?line ets:insert(Ets3,{1,2}),
- ?line 2 = ets:info(Ets3,size),
- ?line ets:insert(Ets3,{1,2}),
- ?line 3 = ets:info(Ets3,size),
- ?line dets:insert(Dets3,{1,2}),
- ?line 2 = dets:info(Dets3,size),
- ?line dets:insert(Dets3,{1,2}),
- ?line 3 = dets:info(Dets3,size),
- ?line dets:close(Dets3),
- ?line (catch file:delete(dets_filename(Dets3,Config))),
- ?line ets:delete(Ets3),
+ {ok,Dets1} = dets:open_file(?DETS_TMP1,
+ [{file, dets_filename(?DETS_TMP1,Config)}]),
+ Ets1 = ets:new(ets,[]),
+ insert_same_key(Dets1,dets,Config),
+ insert_same_key(Ets1,ets,Config),
+ ets:insert(Ets1,{1,2}),
+ 1 = ets:info(Ets1,size),
+ dets:insert(Dets1,{1,2}),
+ 1 = dets:info(Dets1,size),
+ dets:close(Dets1),
+ (catch file:delete(dets_filename(Dets1,Config))),
+ ets:delete(Ets1),
+ {ok,Dets2} = dets:open_file(?DETS_TMP1,
+ [{type,bag},{file, dets_filename(?DETS_TMP1,Config)}]),
+ Ets2 = ets:new(ets,[bag]),
+ insert_same_key(Dets2,dets,Config),
+ insert_same_key(Ets2,ets,Config),
+ ets:insert(Ets2,{1,2}),
+ 2 = ets:info(Ets2,size),
+ ets:insert(Ets2,{1,2}),
+ 2 = ets:info(Ets2,size),
+ dets:insert(Dets2,{1,2}),
+ 2 = dets:info(Dets2,size),
+ dets:insert(Dets2,{1,2}),
+ 2 = dets:info(Dets2,size),
+ dets:close(Dets2),
+ (catch file:delete(dets_filename(Dets2,Config))),
+ ets:delete(Ets2),
+ {ok,Dets3} = dets:open_file(?DETS_TMP1,
+ [{type,duplicate_bag},
+ {file, dets_filename(?DETS_TMP1,Config)}]),
+ Ets3 = ets:new(ets,[duplicate_bag]),
+ insert_same_key(Dets3,dets,Config),
+ insert_same_key(Ets3,ets,Config),
+ ets:insert(Ets3,{1,2}),
+ 2 = ets:info(Ets3,size),
+ ets:insert(Ets3,{1,2}),
+ 3 = ets:info(Ets3,size),
+ dets:insert(Dets3,{1,2}),
+ 2 = dets:info(Dets3,size),
+ dets:insert(Dets3,{1,2}),
+ 3 = dets:info(Dets3,size),
+ dets:close(Dets3),
+ (catch file:delete(dets_filename(Dets3,Config))),
+ ets:delete(Ets3),
ok.
insert_same_key(Tab,Mod,_Config) ->
- ?line Mod:insert(Tab,{1,1}),
- ?line Mod:insert(Tab,{1,2}),
- ?line Mod:insert(Tab,{2,2}),
- ?line Mod:insert(Tab,{2,2}),
- ?line Mod:safe_fixtable(Tab,true),
- ?line Mod:delete(Tab,1),
- ?line Mod:insert(Tab,{1,1}),
- ?line Expect = case Mod:info(Tab,type) of
- bag ->
- Mod:insert(Tab,{1,2}),
- 2;
- _ ->
- 1
- end,
- ?line Mod:delete(Tab,2),
- ?line Mod:safe_fixtable(Tab,false),
- ?line case Mod:info(Tab,size) of
- Expect ->
- ok;
- _ ->
- exit({size_field_wrong,{Mod,Mod:info(Tab)}})
- end.
-
-
+ Mod:insert(Tab,{1,1}),
+ Mod:insert(Tab,{1,2}),
+ Mod:insert(Tab,{2,2}),
+ Mod:insert(Tab,{2,2}),
+ Mod:safe_fixtable(Tab,true),
+ Mod:delete(Tab,1),
+ Mod:insert(Tab,{1,1}),
+ Expect = case Mod:info(Tab,type) of
+ bag ->
+ Mod:insert(Tab,{1,2}),
+ 2;
+ _ ->
+ 1
+ end,
+ Mod:delete(Tab,2),
+ Mod:safe_fixtable(Tab,false),
+ case Mod:info(Tab,size) of
+ Expect ->
+ ok;
+ _ ->
+ exit({size_field_wrong,{Mod,Mod:info(Tab)}})
+ end.
+
+
%% Check correct behaviour if the table owner dies.
owner_dies(Config) when is_list(Config) ->
- ?line P1 = start_commander(),
- ?line Ets1 = command(P1,{ets,new,[ets,[]]}),
- ?line command(P1,{ets,safe_fixtable,[Ets1,true]}),
- ?line {_,[{P1,1}]} = ets:info(Ets1, safe_fixed),
- ?line stop_commander(P1),
- ?line undefined = ets:info(Ets1, safe_fixed),
- ?line P2 = start_commander(),
- ?line Ets2 = command(P2,{ets,new,[ets,[public]]}),
- ?line command(P2,{ets,safe_fixtable,[Ets2,true]}),
- ?line ets:safe_fixtable(Ets2,true),
- ?line true = ets:info(Ets2, fixed),
- ?line {_,[{_,1},{_,1}]} = ets:info(Ets2, safe_fixed),
- ?line stop_commander(P2),
- ?line undefined = ets:info(Ets2, safe_fixed),
- ?line undefined = ets:info(Ets2, fixed),
- ?line P3 = start_commander(),
- ?line {ok,Dets} = ?LOG(command(P3, {dets, open_file,
- [?DETS_TMP1,
- [{file,
- dets_filename(?DETS_TMP1,
- Config)}]]})),
- ?line command(P3, {dets, safe_fixtable, [Dets, true]}),
- ?line {_,[{P3,1}]} = dets:info(Dets, safe_fixed),
- ?line true = dets:info(Dets, fixed),
- ?line stop_commander(P3),
- ?line undefined = dets:info(Dets, safe_fixed),
- ?line undefined = dets:info(Dets, fixed),
- ?line P4 = start_commander(),
- ?line {ok,Dets} = command(P4, {dets, open_file,
+ P1 = start_commander(),
+ Ets1 = command(P1,{ets,new,[ets,[]]}),
+ command(P1,{ets,safe_fixtable,[Ets1,true]}),
+ {_,[{P1,1}]} = ets:info(Ets1, safe_fixed),
+ stop_commander(P1),
+ undefined = ets:info(Ets1, safe_fixed),
+ P2 = start_commander(),
+ Ets2 = command(P2,{ets,new,[ets,[public]]}),
+ command(P2,{ets,safe_fixtable,[Ets2,true]}),
+ ets:safe_fixtable(Ets2,true),
+ true = ets:info(Ets2, fixed),
+ {_,[{_,1},{_,1}]} = ets:info(Ets2, safe_fixed),
+ stop_commander(P2),
+ undefined = ets:info(Ets2, safe_fixed),
+ undefined = ets:info(Ets2, fixed),
+ P3 = start_commander(),
+ {ok,Dets} = ?LOG(command(P3, {dets, open_file,
+ [?DETS_TMP1,
+ [{file,
+ dets_filename(?DETS_TMP1,
+ Config)}]]})),
+ command(P3, {dets, safe_fixtable, [Dets, true]}),
+ {_,[{P3,1}]} = dets:info(Dets, safe_fixed),
+ true = dets:info(Dets, fixed),
+ stop_commander(P3),
+ undefined = dets:info(Dets, safe_fixed),
+ undefined = dets:info(Dets, fixed),
+ P4 = start_commander(),
+ {ok,Dets} = command(P4, {dets, open_file,
[?DETS_TMP1,
[{file, dets_filename(?DETS_TMP1,Config)}]]}),
- ?line {ok,Dets} = dets:open_file(?DETS_TMP1,
+ {ok,Dets} = dets:open_file(?DETS_TMP1,
[{file, dets_filename(?DETS_TMP1,Config)}]),
- ?line false = dets:info(Dets, safe_fixed),
- ?line command(P4, {dets, safe_fixtable, [Dets, true]}),
- ?line dets:safe_fixtable(Dets, true),
- ?line {_,[{_,1},{_,1}]} = dets:info(Dets, safe_fixed),
- ?line dets:safe_fixtable(Dets, true),
- ?line stop_commander(P4),
- ?line S = self(),
- ?line {_,[{S,2}]} = dets:info(Dets, safe_fixed),
- ?line true = dets:info(Dets, fixed),
- ?line dets:close(Dets),
- ?line undefined = dets:info(Dets, fixed),
- ?line undefined = dets:info(Dets, safe_fixed),
+ false = dets:info(Dets, safe_fixed),
+ command(P4, {dets, safe_fixtable, [Dets, true]}),
+ dets:safe_fixtable(Dets, true),
+ {_,[{_,1},{_,1}]} = dets:info(Dets, safe_fixed),
+ dets:safe_fixtable(Dets, true),
+ stop_commander(P4),
+ S = self(),
+ {_,[{S,2}]} = dets:info(Dets, safe_fixed),
+ true = dets:info(Dets, fixed),
+ dets:close(Dets),
+ undefined = dets:info(Dets, fixed),
+ undefined = dets:info(Dets, safe_fixed),
ok.
-
+
%% When another process closes an dets table, different things should
%% happen depending on if it has opened it before.
other_process_closes(Config) when is_list(Config) ->
- ?line {ok,Dets} = dets:open_file(?DETS_TMP1,
+ {ok,Dets} = dets:open_file(?DETS_TMP1,
[{file, dets_filename(tmp1,Config)}]),
- ?line P2 = start_commander(),
- ?line dets:safe_fixtable(Dets,true),
- ?line S = self(),
- ?line {_,[{S,1}]} = dets:info(Dets, safe_fixed),
- ?line command(P2,{dets, safe_fixtable, [Dets, true]}),
- ?line {_,[_,_]} = dets:info(Dets, safe_fixed),
- ?line {error, not_owner} = command(P2,{dets, close, [Dets]}),
- ?line {_,[_,_]} = dets:info(Dets, safe_fixed),
- ?line command(P2,{dets, open_file,[?DETS_TMP1,
+ P2 = start_commander(),
+ dets:safe_fixtable(Dets,true),
+ S = self(),
+ {_,[{S,1}]} = dets:info(Dets, safe_fixed),
+ command(P2,{dets, safe_fixtable, [Dets, true]}),
+ {_,[_,_]} = dets:info(Dets, safe_fixed),
+ {error, not_owner} = command(P2,{dets, close, [Dets]}),
+ {_,[_,_]} = dets:info(Dets, safe_fixed),
+ command(P2,{dets, open_file,[?DETS_TMP1,
[{file,
dets_filename(?DETS_TMP1, Config)}]]}),
- ?line {_,[_,_]} = dets:info(Dets, safe_fixed),
- ?line command(P2,{dets, close, [Dets]}),
- ?line stop_commander(P2),
- ?line {_,[{S,1}]} = dets:info(Dets, safe_fixed),
- ?line true = dets:info(Dets,fixed),
- ?line dets:close(Dets),
- ?line undefined = dets:info(Dets,fixed),
- ?line undefined = dets:info(Dets, safe_fixed),
+ {_,[_,_]} = dets:info(Dets, safe_fixed),
+ command(P2,{dets, close, [Dets]}),
+ stop_commander(P2),
+ {_,[{S,1}]} = dets:info(Dets, safe_fixed),
+ true = dets:info(Dets,fixed),
+ dets:close(Dets),
+ undefined = dets:info(Dets,fixed),
+ undefined = dets:info(Dets, safe_fixed),
ok.
-
+
%% Check that fixtable structures are cleaned up if another process
%% deletes an ets table.
other_process_deletes(Config) when is_list(Config) ->
- ?line Ets = ets:new(ets,[public]),
- ?line P = start_commander(),
- ?line ets:safe_fixtable(Ets,true),
- ?line ets:safe_fixtable(Ets,true),
- ?line true = ets:info(Ets, fixed),
- ?line {_,_} = ets:info(Ets, safe_fixed),
- ?line command(P,{ets,delete,[Ets]}),
- ?line stop_commander(P),
- ?line undefined = ets:info(Ets, fixed),
- ?line undefined = ets:info(Ets, safe_fixed),
+ Ets = ets:new(ets,[public]),
+ P = start_commander(),
+ ets:safe_fixtable(Ets,true),
+ ets:safe_fixtable(Ets,true),
+ true = ets:info(Ets, fixed),
+ {_,_} = ets:info(Ets, safe_fixed),
+ command(P,{ets,delete,[Ets]}),
+ stop_commander(P),
+ undefined = ets:info(Ets, fixed),
+ undefined = ets:info(Ets, safe_fixed),
ok.
%% Check that multiple safe_fixtable keeps the reference counter.
multiple_fixes(Config) when is_list(Config) ->
- ?line {ok,Dets} = dets:open_file(?DETS_TMP1,
+ {ok,Dets} = dets:open_file(?DETS_TMP1,
[{file, dets_filename(?DETS_TMP1,Config)}]),
- ?line Ets = ets:new(ets,[]),
- ?line multiple_fixes(Dets,dets),
- ?line multiple_fixes(Ets,ets),
- ?line dets:close(Dets),
+ Ets = ets:new(ets,[]),
+ multiple_fixes(Dets,dets),
+ multiple_fixes(Ets,ets),
+ dets:close(Dets),
ok.
multiple_fixes(Tab, Mod) ->
- ?line false = Mod:info(Tab,fixed),
- ?line false = Mod:info(Tab, safe_fixed),
- ?line Mod:safe_fixtable(Tab, true),
- ?line true = Mod:info(Tab,fixed),
- ?line S = self(),
- ?line {_,[{S,1}]} = Mod:info(Tab, safe_fixed),
- ?line Mod:safe_fixtable(Tab, true),
- ?line Mod:safe_fixtable(Tab, true),
- ?line {_,[{S,3}]} = Mod:info(Tab, safe_fixed),
- ?line true = Mod:info(Tab,fixed),
- ?line Mod:safe_fixtable(Tab, false),
- ?line {_,[{S,2}]} = Mod:info(Tab, safe_fixed),
- ?line true = Mod:info(Tab,fixed),
- ?line Mod:safe_fixtable(Tab, false),
- ?line {_,[{S,1}]} = Mod:info(Tab, safe_fixed),
- ?line true = Mod:info(Tab,fixed),
- ?line Mod:safe_fixtable(Tab, false),
- ?line false = Mod:info(Tab, safe_fixed),
- ?line false = Mod:info(Tab,fixed).
+ false = Mod:info(Tab,fixed),
+ false = Mod:info(Tab, safe_fixed),
+ Mod:safe_fixtable(Tab, true),
+ true = Mod:info(Tab,fixed),
+ S = self(),
+ {_,[{S,1}]} = Mod:info(Tab, safe_fixed),
+ Mod:safe_fixtable(Tab, true),
+ Mod:safe_fixtable(Tab, true),
+ {_,[{S,3}]} = Mod:info(Tab, safe_fixed),
+ true = Mod:info(Tab,fixed),
+ Mod:safe_fixtable(Tab, false),
+ {_,[{S,2}]} = Mod:info(Tab, safe_fixed),
+ true = Mod:info(Tab,fixed),
+ Mod:safe_fixtable(Tab, false),
+ {_,[{S,1}]} = Mod:info(Tab, safe_fixed),
+ true = Mod:info(Tab,fixed),
+ Mod:safe_fixtable(Tab, false),
+ false = Mod:info(Tab, safe_fixed),
+ false = Mod:info(Tab,fixed).
%% Check that multiple safe_fixtable across processes are reference
%% counted OK.
multiple_processes(Config) when is_list(Config) ->
- ?line {ok,Dets} = dets:open_file(?DETS_TMP1,[{file,
+ {ok,Dets} = dets:open_file(?DETS_TMP1,[{file,
dets_filename(?DETS_TMP1,
Config)}]),
- ?line Ets = ets:new(ets,[public]),
- ?line multiple_processes(Dets,dets),
- ?line multiple_processes(Ets,ets),
+ Ets = ets:new(ets,[public]),
+ multiple_processes(Dets,dets),
+ multiple_processes(Ets,ets),
ok.
multiple_processes(Tab, Mod) ->
- ?line io:format("Mod = ~p\n", [Mod]),
- ?line P1 = start_commander(),
- ?line P2 = start_commander(),
- ?line false = Mod:info(Tab,fixed),
- ?line false = Mod:info(Tab, safe_fixed),
- ?line command(P1, {Mod, safe_fixtable, [Tab,true]}),
- ?line true = Mod:info(Tab,fixed),
- ?line {_,[{P1,1}]} = Mod:info(Tab, safe_fixed),
- ?line command(P2, {Mod, safe_fixtable, [Tab,true]}),
- ?line true = Mod:info(Tab,fixed),
- ?line {_,L} = Mod:info(Tab,safe_fixed),
- ?line true = (lists:sort(L) == lists:sort([{P1,1},{P2,1}])),
- ?line command(P2, {Mod, safe_fixtable, [Tab,true]}),
- ?line {_,L2} = Mod:info(Tab,safe_fixed),
- ?line true = (lists:sort(L2) == lists:sort([{P1,1},{P2,2}])),
- ?line command(P2, {Mod, safe_fixtable, [Tab,false]}),
- ?line true = Mod:info(Tab,fixed),
- ?line {_,L3} = Mod:info(Tab,safe_fixed),
- ?line true = (lists:sort(L3) == lists:sort([{P1,1},{P2,1}])),
- ?line command(P2, {Mod, safe_fixtable, [Tab,false]}),
- ?line true = Mod:info(Tab,fixed),
- ?line {_,[{P1,1}]} = Mod:info(Tab, safe_fixed),
- ?line stop_commander(P1),
- ?line receive after 1000 -> ok end,
- ?line false = Mod:info(Tab,fixed),
- ?line false = Mod:info(Tab, safe_fixed),
- ?line command(P2, {Mod, safe_fixtable, [Tab,true]}),
- ?line true = Mod:info(Tab,fixed),
- ?line {_,[{P2,1}]} = Mod:info(Tab, safe_fixed),
+ io:format("Mod = ~p\n", [Mod]),
+ P1 = start_commander(),
+ P2 = start_commander(),
+ false = Mod:info(Tab,fixed),
+ false = Mod:info(Tab, safe_fixed),
+ command(P1, {Mod, safe_fixtable, [Tab,true]}),
+ true = Mod:info(Tab,fixed),
+ {_,[{P1,1}]} = Mod:info(Tab, safe_fixed),
+ command(P2, {Mod, safe_fixtable, [Tab,true]}),
+ true = Mod:info(Tab,fixed),
+ {_,L} = Mod:info(Tab,safe_fixed),
+ true = (lists:sort(L) == lists:sort([{P1,1},{P2,1}])),
+ command(P2, {Mod, safe_fixtable, [Tab,true]}),
+ {_,L2} = Mod:info(Tab,safe_fixed),
+ true = (lists:sort(L2) == lists:sort([{P1,1},{P2,2}])),
+ command(P2, {Mod, safe_fixtable, [Tab,false]}),
+ true = Mod:info(Tab,fixed),
+ {_,L3} = Mod:info(Tab,safe_fixed),
+ true = (lists:sort(L3) == lists:sort([{P1,1},{P2,1}])),
+ command(P2, {Mod, safe_fixtable, [Tab,false]}),
+ true = Mod:info(Tab,fixed),
+ {_,[{P1,1}]} = Mod:info(Tab, safe_fixed),
+ stop_commander(P1),
+ receive after 1000 -> ok end,
+ false = Mod:info(Tab,fixed),
+ false = Mod:info(Tab, safe_fixed),
+ command(P2, {Mod, safe_fixtable, [Tab,true]}),
+ true = Mod:info(Tab,fixed),
+ {_,[{P2,1}]} = Mod:info(Tab, safe_fixed),
case Mod of
dets ->
- ?line dets:close(Tab);
+ dets:close(Tab);
ets ->
- ?line ets:delete(Tab)
+ ets:delete(Tab)
end,
- ?line stop_commander(P2),
- ?line receive after 1000 -> ok end,
- ?line undefined = Mod:info(Tab, safe_fixed),
+ stop_commander(P2),
+ receive after 1000 -> ok end,
+ undefined = Mod:info(Tab, safe_fixed),
ok.
-
-
+
+
%%% Helpers
dets_filename(Base, Config) when is_atom(Base) ->
diff --git a/lib/stdlib/test/format_SUITE.erl b/lib/stdlib/test/format_SUITE.erl
index 86a9779ec3..b481d82ea6 100644
--- a/lib/stdlib/test/format_SUITE.erl
+++ b/lib/stdlib/test/format_SUITE.erl
@@ -58,6 +58,6 @@ end_per_group(_GroupName, Config) ->
%% OTP-2400. Bad args can hang.
hang_1(Config) when is_list(Config) ->
- ?line _ = (catch io:format(a, "", [])),
- ?line _ = (catch io:format({}, "", [])),
+ _ = (catch io:format(a, "", [])),
+ _ = (catch io:format({}, "", [])),
ok.
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index de76d5d6f9..4bad7801ff 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -62,47 +62,47 @@ end_per_group(_GroupName, Config) ->
start(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line dummy_via:reset(),
-
- ?line {ok, Pid0} = gen_event:start(), %anonymous
- ?line [] = gen_event:which_handlers(Pid0),
- ?line ok = gen_event:stop(Pid0),
-
- ?line {ok, Pid1} = gen_event:start_link(), %anonymous
- ?line [] = gen_event:which_handlers(Pid1),
- ?line ok = gen_event:stop(Pid1),
-
- ?line {ok, Pid2} = gen_event:start({local, my_dummy_name}),
- ?line [] = gen_event:which_handlers(my_dummy_name),
- ?line [] = gen_event:which_handlers(Pid2),
- ?line ok = gen_event:stop(my_dummy_name),
-
- ?line {ok, Pid3} = gen_event:start_link({local, my_dummy_name}),
- ?line [] = gen_event:which_handlers(my_dummy_name),
- ?line [] = gen_event:which_handlers(Pid3),
- ?line ok = gen_event:stop(my_dummy_name),
-
- ?line {ok, Pid4} = gen_event:start_link({global, my_dummy_name}),
- ?line [] = gen_event:which_handlers({global, my_dummy_name}),
- ?line [] = gen_event:which_handlers(Pid4),
- ?line ok = gen_event:stop({global, my_dummy_name}),
-
- ?line {ok, Pid5} = gen_event:start_link({via, dummy_via, my_dummy_name}),
- ?line [] = gen_event:which_handlers({via, dummy_via, my_dummy_name}),
- ?line [] = gen_event:which_handlers(Pid5),
- ?line ok = gen_event:stop({via, dummy_via, my_dummy_name}),
-
- ?line {ok, _} = gen_event:start_link({local, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ dummy_via:reset(),
+
+ {ok, Pid0} = gen_event:start(), %anonymous
+ [] = gen_event:which_handlers(Pid0),
+ ok = gen_event:stop(Pid0),
+
+ {ok, Pid1} = gen_event:start_link(), %anonymous
+ [] = gen_event:which_handlers(Pid1),
+ ok = gen_event:stop(Pid1),
+
+ {ok, Pid2} = gen_event:start({local, my_dummy_name}),
+ [] = gen_event:which_handlers(my_dummy_name),
+ [] = gen_event:which_handlers(Pid2),
+ ok = gen_event:stop(my_dummy_name),
+
+ {ok, Pid3} = gen_event:start_link({local, my_dummy_name}),
+ [] = gen_event:which_handlers(my_dummy_name),
+ [] = gen_event:which_handlers(Pid3),
+ ok = gen_event:stop(my_dummy_name),
+
+ {ok, Pid4} = gen_event:start_link({global, my_dummy_name}),
+ [] = gen_event:which_handlers({global, my_dummy_name}),
+ [] = gen_event:which_handlers(Pid4),
+ ok = gen_event:stop({global, my_dummy_name}),
+
+ {ok, Pid5} = gen_event:start_link({via, dummy_via, my_dummy_name}),
+ [] = gen_event:which_handlers({via, dummy_via, my_dummy_name}),
+ [] = gen_event:which_handlers(Pid5),
+ ok = gen_event:stop({via, dummy_via, my_dummy_name}),
+
+ {ok, _} = gen_event:start_link({local, my_dummy_name}),
+ {error, {already_started, _}} =
gen_event:start_link({local, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ {error, {already_started, _}} =
gen_event:start({local, my_dummy_name}),
- ?line ok = gen_event:stop(my_dummy_name),
+ ok = gen_event:stop(my_dummy_name),
- ?line {ok, Pid6} = gen_event:start_link({global, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ {ok, Pid6} = gen_event:start_link({global, my_dummy_name}),
+ {error, {already_started, _}} =
gen_event:start_link({global, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ {error, {already_started, _}} =
gen_event:start({global, my_dummy_name}),
ok = gen_event:stop({global, my_dummy_name}, shutdown, 10000),
@@ -112,10 +112,10 @@ start(Config) when is_list(Config) ->
ct:fail(exit_gen_event)
end,
- ?line {ok, Pid7} = gen_event:start_link({via, dummy_via, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ {ok, Pid7} = gen_event:start_link({via, dummy_via, my_dummy_name}),
+ {error, {already_started, _}} =
gen_event:start_link({via, dummy_via, my_dummy_name}),
- ?line {error, {already_started, _}} =
+ {error, {already_started, _}} =
gen_event:start({via, dummy_via, my_dummy_name}),
exit(Pid7, shutdown),
@@ -181,7 +181,7 @@ hibernate(Config) when is_list(Config) ->
{ok,Pid2} = gen_event:start({local, my_dummy_handler}),
ok = gen_event:add_handler(my_dummy_handler, dummy_h,
- [self(),hibernate]),
+ [self(),hibernate]),
is_in_erlang_hibernate(Pid2),
sys:suspend(my_dummy_handler),
is_in_erlang_hibernate(Pid2),
@@ -190,7 +190,7 @@ hibernate(Config) when is_list(Config) ->
Pid2 ! wake,
is_not_in_erlang_hibernate(Pid2),
-
+
ok = gen_event:stop(my_dummy_handler),
ok.
@@ -231,693 +231,693 @@ is_not_in_erlang_hibernate_1(N, Pid) ->
add_handler(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line {error, my_error} =
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ {error, my_error} =
gen_event:add_handler(my_dummy_handler, dummy_h, make_error),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, my_error} =
+ {error, my_error} =
gen_event:add_handler(my_dummy_handler, {dummy_h, self()}, make_error),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,self()},
- [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,self()},
+ [self()]),
Self = self(),
- ?line [{dummy_h, Self}, dummy_h] =
+ [{dummy_h, Self}, dummy_h] =
gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
add_sup_handler(Config) when is_list(Config) ->
- ?line {ok,Pid} = gen_event:start({local, my_dummy_handler}),
- ?line {error, my_error} =
+ {ok,Pid} = gen_event:start({local, my_dummy_handler}),
+ {error, my_error} =
gen_event:add_sup_handler(my_dummy_handler, dummy_h, make_error),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line exit(Pid, sup_died),
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ exit(Pid, sup_died),
ct:sleep(1000),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, my_error} =
+ {error, my_error} =
gen_event:add_handler(my_dummy_handler, {dummy_h, self()}, make_error),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, {dummy_h,self()},
- [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, {dummy_h,self()},
+ [self()]),
Self = self(),
- ?line [{dummy_h, Self}, dummy_h] =
+ [{dummy_h, Self}, dummy_h] =
gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:stop(my_dummy_handler),
-
- ?line receive
- {gen_event_EXIT, dummy_h, shutdown} ->
- ok
- after 1000 ->
- ct:fail({no,{gen_event_EXIT, dummy_h, shutdown}})
- end,
-
- ?line receive
- {gen_event_EXIT, {dummy_h,Self}, shutdown} ->
- ok
- after 1000 ->
- ct:fail({no,{gen_event_EXIT, {dummy_h,Self},
- shutdown}})
- end,
+ ok = gen_event:stop(my_dummy_handler),
+
+ receive
+ {gen_event_EXIT, dummy_h, shutdown} ->
+ ok
+ after 1000 ->
+ ct:fail({no,{gen_event_EXIT, dummy_h, shutdown}})
+ end,
+
+ receive
+ {gen_event_EXIT, {dummy_h,Self}, shutdown} ->
+ ok
+ after 1000 ->
+ ct:fail({no,{gen_event_EXIT, {dummy_h,Self},
+ shutdown}})
+ end,
ok.
delete_handler(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line {error, module_not_found} =
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ {error, module_not_found} =
gen_event:delete_handler(my_dummy_handler, duuuuuuuuumy, []),
- ?line return_hej =
+ return_hej =
gen_event:delete_handler(my_dummy_handler, dummy_h, return_hej),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok =
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ ok =
gen_event:delete_handler(my_dummy_handler, dummy_h, []),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,2}, [self()]),
- ?line {error, module_not_found} =
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,2}, [self()]),
+ {error, module_not_found} =
gen_event:delete_handler(my_dummy_handler, {duuuuuuuuumy,1}, []),
- ?line return_hej =
+ return_hej =
gen_event:delete_handler(my_dummy_handler, {dummy_h,1}, return_hej),
- ?line return_hej =
+ return_hej =
gen_event:delete_handler(my_dummy_handler, {dummy_h,2}, return_hej),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,2}, [self()]),
- ?line ok =
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,2}, [self()]),
+ ok =
gen_event:delete_handler(my_dummy_handler, {dummy_h,2}, []),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
swap_handler(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line {error, non_existing} =
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ {error, non_existing} =
gen_event:swap_handler(my_dummy_handler, {faulty_h, swap},
{dummy1_h, []}),
- ?line ok =
+ ok =
gen_event:swap_handler(my_dummy_handler, {dummy_h, swap},
{dummy1_h, swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:delete_handler(my_dummy_handler, dummy1_h, []),
+ ok = gen_event:delete_handler(my_dummy_handler, dummy1_h, []),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
- ?line {error, non_existing} =
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
+ {error, non_existing} =
gen_event:swap_handler(my_dummy_handler, {faulty_h, swap},
{dummy1_h, []}),
- ?line ok =
+ ok =
gen_event:swap_handler(my_dummy_handler, {{dummy_h,3}, swap},
{{dummy1_h,4}, swap}),
- ?line [{dummy1_h,4}] = gen_event:which_handlers(my_dummy_handler),
+ [{dummy1_h,4}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:delete_handler(my_dummy_handler, {dummy1_h,4}, []),
+ ok = gen_event:delete_handler(my_dummy_handler, {dummy1_h,4}, []),
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
-
+
swap_sup_handler(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line {error, non_existing} =
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ {error, non_existing} =
gen_event:swap_handler(my_dummy_handler, {faulty_h, swap},
{dummy1_h, []}),
- ?line ok =
+ ok =
gen_event:swap_handler(my_dummy_handler, {dummy_h, swap},
{dummy1_h, swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:delete_handler(my_dummy_handler, dummy1_h, []),
- ?line receive
- {gen_event_EXIT, dummy1_h, normal} ->
- ok
- after 1000 ->
- ct:fail({no,{gen_event_EXIT, dummy1_h, normal}})
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, {dummy_h,3},
- [self()]),
- ?line {error, non_existing} =
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:delete_handler(my_dummy_handler, dummy1_h, []),
+ receive
+ {gen_event_EXIT, dummy1_h, normal} ->
+ ok
+ after 1000 ->
+ ct:fail({no,{gen_event_EXIT, dummy1_h, normal}})
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, {dummy_h,3},
+ [self()]),
+ {error, non_existing} =
gen_event:swap_sup_handler(my_dummy_handler, {faulty_h, swap},
{dummy1_h, []}),
- ?line ok =
+ ok =
gen_event:swap_sup_handler(my_dummy_handler, {{dummy_h,3}, swap},
{{dummy1_h,4}, swap}),
- ?line [{dummy1_h,4}] = gen_event:which_handlers(my_dummy_handler),
+ [{dummy1_h,4}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:delete_handler(my_dummy_handler, {dummy1_h,4}, []),
- ?line receive
- {gen_event_EXIT, {dummy1_h,4}, normal} ->
- ok
- after 1000 ->
- ct:fail({no,{gen_event_EXIT, {dummy1_h,4}, normal}})
- end,
+ ok = gen_event:delete_handler(my_dummy_handler, {dummy1_h,4}, []),
+ receive
+ {gen_event_EXIT, {dummy1_h,4}, normal} ->
+ ok
+ after 1000 ->
+ ct:fail({no,{gen_event_EXIT, {dummy1_h,4}, normal}})
+ end,
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
-
+
notify(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
Event = {event, self()},
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
- ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:notify(my_dummy_handler, Event),
- ?line receive
- {dummy1_h, Event} ->
- ok
- end,
- ?line ok = gen_event:notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line ok = gen_event:notify(my_dummy_handler, error_event),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+ ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:notify(my_dummy_handler, Event),
+ receive
+ {dummy1_h, Event} ->
+ ok
+ end,
+ ok = gen_event:notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+
+ ok = gen_event:notify(my_dummy_handler, error_event),
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Handler with id, {Mod,Id}
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,5}, [self()]),
- ?line [{dummy_h,5}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
- ?line ok = gen_event:notify(my_dummy_handler,
- {swap_event, {dummy1_h, 9}, swap}),
- ?line [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:notify(my_dummy_handler, Event),
- ?line receive
- {dummy1_h, Event} ->
- ok
- end,
- ?line ok = gen_event:notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,a}, [self()]),
-
- ?line ok = gen_event:notify(my_dummy_handler, error_event),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,5}, [self()]),
+ [{dummy_h,5}] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+ ok = gen_event:notify(my_dummy_handler,
+ {swap_event, {dummy1_h, 9}, swap}),
+ [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:notify(my_dummy_handler, Event),
+ receive
+ {dummy1_h, Event} ->
+ ok
+ end,
+ ok = gen_event:notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,a}, [self()]),
+
+ ok = gen_event:notify(my_dummy_handler, error_event),
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Supervised handler.
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
-
- ?line ok = gen_event:notify(my_dummy_handler, do_crash),
- ?line receive
- {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
- ok
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:notify(my_dummy_handler, do_crash),
- ?line receive
- {gen_event_EXIT, dummy1_h, {'EXIT',_}} ->
- ok
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
-
- ?line receive
- {gen_event_EXIT, dummy1_h, normal} ->
- ok
- end,
-
- ?line [] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+
+ ok = gen_event:notify(my_dummy_handler, do_crash),
+ receive
+ {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
+ ok
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:notify(my_dummy_handler, do_crash),
+ receive
+ {gen_event_EXIT, dummy1_h, {'EXIT',_}} ->
+ ok
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+
+ receive
+ {gen_event_EXIT, dummy1_h, normal} ->
+ ok
+ end,
+
+ [] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:stop(my_dummy_handler),
ok.
sync_notify(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
Event = {event, self()},
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:sync_notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
- ?line ok = gen_event:sync_notify(my_dummy_handler,
- {swap_event, dummy1_h, swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:sync_notify(my_dummy_handler, Event),
- ?line receive
- {dummy1_h, Event} ->
- ok
- end,
- ?line ok = gen_event:sync_notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line ok = gen_event:sync_notify(my_dummy_handler, error_event),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:sync_notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+ ok = gen_event:sync_notify(my_dummy_handler,
+ {swap_event, dummy1_h, swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:sync_notify(my_dummy_handler, Event),
+ receive
+ {dummy1_h, Event} ->
+ ok
+ end,
+ ok = gen_event:sync_notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+
+ ok = gen_event:sync_notify(my_dummy_handler, error_event),
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Handler with id, {Mod,Id}
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,5}, [self()]),
- ?line [{dummy_h,5}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:sync_notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
- ?line ok = gen_event:sync_notify(my_dummy_handler,
- {swap_event, {dummy1_h, 9}, swap}),
- ?line [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:sync_notify(my_dummy_handler, Event),
- ?line receive
- {dummy1_h, Event} ->
- ok
- end,
- ?line ok = gen_event:sync_notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,a}, [self()]),
-
- ?line ok = gen_event:sync_notify(my_dummy_handler, error_event),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,5}, [self()]),
+ [{dummy_h,5}] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:sync_notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+ ok = gen_event:sync_notify(my_dummy_handler,
+ {swap_event, {dummy1_h, 9}, swap}),
+ [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:sync_notify(my_dummy_handler, Event),
+ receive
+ {dummy1_h, Event} ->
+ ok
+ end,
+ ok = gen_event:sync_notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,a}, [self()]),
+
+ ok = gen_event:sync_notify(my_dummy_handler, error_event),
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Supervised handler.
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:sync_notify(my_dummy_handler, Event),
- ?line receive
- {dummy_h, Event} ->
- ok
- end,
-
- ?line ok = gen_event:sync_notify(my_dummy_handler, do_crash),
- ?line receive
- {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
- ok
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok = gen_event:sync_notify(my_dummy_handler,
- {swap_event,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:sync_notify(my_dummy_handler, do_crash),
- ?line receive
- {gen_event_EXIT, dummy1_h, {'EXIT',_}} ->
- ok
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok = gen_event:sync_notify(my_dummy_handler,
- {swap_event,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:sync_notify(my_dummy_handler, delete_event),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
-
- ?line receive
- {gen_event_EXIT, dummy1_h, normal} ->
- ok
- end,
-
- ?line [] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:sync_notify(my_dummy_handler, Event),
+ receive
+ {dummy_h, Event} ->
+ ok
+ end,
+
+ ok = gen_event:sync_notify(my_dummy_handler, do_crash),
+ receive
+ {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
+ ok
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ ok = gen_event:sync_notify(my_dummy_handler,
+ {swap_event,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:sync_notify(my_dummy_handler, do_crash),
+ receive
+ {gen_event_EXIT, dummy1_h, {'EXIT',_}} ->
+ ok
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ ok = gen_event:sync_notify(my_dummy_handler,
+ {swap_event,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:sync_notify(my_dummy_handler, delete_event),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+
+ receive
+ {gen_event_EXIT, dummy1_h, normal} ->
+ ok
+ end,
+
+ [] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:stop(my_dummy_handler),
ok.
call(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h, 1}, [self()]),
- ?line [{dummy_h, 1}, dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {'EXIT',_} = (catch gen_event:call(non_exist, dummy_h, hejsan)),
- ?line {error, bad_module} =
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h, 1}, [self()]),
+ [{dummy_h, 1}, dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ {'EXIT',_} = (catch gen_event:call(non_exist, dummy_h, hejsan)),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, bad_h, hejsan),
- ?line {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan),
- ?line {ok, hejhopp} = gen_event:call(my_dummy_handler, {dummy_h, 1},
- hejsan),
- ?line {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan,
- 10000),
- ?line {'EXIT', {timeout, _}} =
+ {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan),
+ {ok, hejhopp} = gen_event:call(my_dummy_handler, {dummy_h, 1},
+ hejsan),
+ {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan,
+ 10000),
+ {'EXIT', {timeout, _}} =
(catch gen_event:call(my_dummy_handler, dummy_h, hejsan, 0)),
flush(),
- ?line ok = gen_event:delete_handler(my_dummy_handler, {dummy_h, 1}, []),
- ?line {ok, swapped} = gen_event:call(my_dummy_handler, dummy_h,
- {swap_call,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, bad_module} =
+ ok = gen_event:delete_handler(my_dummy_handler, {dummy_h, 1}, []),
+ {ok, swapped} = gen_event:call(my_dummy_handler, dummy_h,
+ {swap_call,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, dummy_h, hejsan),
- ?line ok = gen_event:call(my_dummy_handler, dummy1_h, delete_call),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line {error, {return, faulty}} =
+ ok = gen_event:call(my_dummy_handler, dummy1_h, delete_call),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+
+ {error, {return, faulty}} =
gen_event:call(my_dummy_handler, dummy_h, error_call),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line {error, {'EXIT', _}} =
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+
+ {error, {'EXIT', _}} =
gen_event:call(my_dummy_handler, dummy_h, exit_call),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Handler with id, {Mod,Id}
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
- ?line [{dummy_h,1}] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, bad_module} =
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
+ [{dummy_h,1}] = gen_event:which_handlers(my_dummy_handler),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, bad_h, hejsan),
- ?line {ok, hejhopp} = gen_event:call(my_dummy_handler, {dummy_h,1},
- hejsan),
- ?line {ok, swapped} = gen_event:call(my_dummy_handler, {dummy_h,1},
- {swap_call,{dummy1_h,2},swap}),
- ?line [{dummy1_h,2}] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, bad_module} =
+ {ok, hejhopp} = gen_event:call(my_dummy_handler, {dummy_h,1},
+ hejsan),
+ {ok, swapped} = gen_event:call(my_dummy_handler, {dummy_h,1},
+ {swap_call,{dummy1_h,2},swap}),
+ [{dummy1_h,2}] = gen_event:which_handlers(my_dummy_handler),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, dummy_h, hejsan),
- ?line ok = gen_event:call(my_dummy_handler, {dummy1_h,2}, delete_call),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
-
- ?line {error, {return, faulty}} =
+ ok = gen_event:call(my_dummy_handler, {dummy1_h,2}, delete_call),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
+
+ {error, {return, faulty}} =
gen_event:call(my_dummy_handler, {dummy_h,3}, error_call),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,4}, [self()]),
-
- ?line {error, {'EXIT', _}} =
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,4}, [self()]),
+
+ {error, {'EXIT', _}} =
gen_event:call(my_dummy_handler, {dummy_h,4}, exit_call),
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Supervised handler.
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, bad_module} =
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, bad_h, hejsan),
- ?line {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan),
- ?line {ok, swapped} = gen_event:call(my_dummy_handler, dummy_h,
- {swap_call,dummy1_h,swap}),
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line {error, bad_module} =
+ {ok, hejhopp} = gen_event:call(my_dummy_handler, dummy_h, hejsan),
+ {ok, swapped} = gen_event:call(my_dummy_handler, dummy_h,
+ {swap_call,dummy1_h,swap}),
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ {error, bad_module} =
gen_event:call(my_dummy_handler, dummy_h, hejsan),
- ?line ok = gen_event:call(my_dummy_handler, dummy1_h, delete_call),
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
+ ok = gen_event:call(my_dummy_handler, dummy1_h, delete_call),
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
- ?line receive
- {gen_event_EXIT, dummy1_h, normal} ->
- ok
- end,
+ receive
+ {gen_event_EXIT, dummy1_h, normal} ->
+ ok
+ end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line {error, {return, faulty}} =
+ {error, {return, faulty}} =
gen_event:call(my_dummy_handler, dummy_h, error_call),
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
-
- ?line receive
- {gen_event_EXIT, dummy_h, {return,faulty}} ->
- ok
- after 1000 ->
- ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}})
- end,
-
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line {error, {'EXIT', _}} =
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+
+ receive
+ {gen_event_EXIT, dummy_h, {return,faulty}} ->
+ ok
+ after 1000 ->
+ ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}})
+ end,
+
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+
+ {error, {'EXIT', _}} =
gen_event:call(my_dummy_handler, dummy_h, exit_call),
- ?line receive
- {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
- ok
- after 1000 ->
- ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}})
- end,
+ receive
+ {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
+ ok
+ after 1000 ->
+ ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}})
+ end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
flush() ->
receive _ -> flush() after 0 -> ok end.
info(Config) when is_list(Config) ->
- ?line {ok,_} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ {ok,_} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
Info = {info, self()},
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! {swap_info,dummy1_h,swap},
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy1_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! delete_info,
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line my_dummy_handler ! error_info,
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! {swap_info,dummy1_h,swap},
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy1_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! delete_info,
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+
+ my_dummy_handler ! error_info,
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Handler with id, {Mod,Id}
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
- ?line [{dummy_h,1}] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! {swap_info,{dummy1_h,2},swap},
- ?line [{dummy1_h,2}] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy1_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! delete_info,
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
- ?line ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
-
- ?line my_dummy_handler ! error_info,
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
- ?line [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,1}, [self()]),
+ [{dummy_h,1}] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! {swap_info,{dummy1_h,2},swap},
+ [{dummy1_h,2}] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy1_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! delete_info,
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
+ ok = gen_event:add_handler(my_dummy_handler, {dummy_h,3}, [self()]),
+
+ my_dummy_handler ! error_info,
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+ [] = gen_event:which_handlers(my_dummy_handler),
%% Supervised handler
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! {swap_info,dummy1_h,swap},
- ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
- ?line my_dummy_handler ! Info,
- ?line receive
- {dummy1_h, Info} ->
- ok
- end,
- ?line my_dummy_handler ! delete_info,
- ?line receive
- {dummy1_h, removed} ->
- ok
- end,
-
- ?line receive
- {gen_event_EXIT, dummy1_h, normal} ->
- ok
- after 1000 ->
- ct:fail({no, {gen_event_EXIT, dummy1_h, normal}})
- end,
-
- ?line [] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
-
- ?line my_dummy_handler ! error_info,
- ?line receive
- {dummy_h, returned_error} ->
- ok
- end,
-
- ?line receive
- {gen_event_EXIT, dummy_h, {return,faulty}} ->
- ok
- after 1000 ->
- ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}})
- end,
-
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
- ?line my_dummy_handler ! do_crash,
-
- ?line receive
- {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
- ok
- after 1000 ->
- ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}})
- end,
-
- ?line [] = gen_event:which_handlers(my_dummy_handler),
-
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! {swap_info,dummy1_h,swap},
+ [dummy1_h] = gen_event:which_handlers(my_dummy_handler),
+ my_dummy_handler ! Info,
+ receive
+ {dummy1_h, Info} ->
+ ok
+ end,
+ my_dummy_handler ! delete_info,
+ receive
+ {dummy1_h, removed} ->
+ ok
+ end,
+
+ receive
+ {gen_event_EXIT, dummy1_h, normal} ->
+ ok
+ after 1000 ->
+ ct:fail({no, {gen_event_EXIT, dummy1_h, normal}})
+ end,
+
+ [] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+
+ my_dummy_handler ! error_info,
+ receive
+ {dummy_h, returned_error} ->
+ ok
+ end,
+
+ receive
+ {gen_event_EXIT, dummy_h, {return,faulty}} ->
+ ok
+ after 1000 ->
+ ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}})
+ end,
+
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]),
+ my_dummy_handler ! do_crash,
+
+ receive
+ {gen_event_EXIT, dummy_h, {'EXIT',_}} ->
+ ok
+ after 1000 ->
+ ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}})
+ end,
+
+ [] = gen_event:which_handlers(my_dummy_handler),
+
+ ok = gen_event:stop(my_dummy_handler),
ok.
%% Test that sys:get_status/1,2 calls format_status/2.
call_format_status(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ {ok, Pid} = gen_event:start({local, my_dummy_handler}),
%% State here intentionally differs from what we expect from format_status
State = self(),
FmtState = "dummy1_h handler state",
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State]),
- ?line Status1 = sys:get_status(Pid),
- ?line Status2 = sys:get_status(Pid, 5000),
- ?line ok = gen_event:stop(Pid),
- ?line {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
- ?line HandlerInfo1 = proplists:get_value(items, Data1),
- ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo1,
- ?line {status, Pid, _, [_, _, Pid, [], Data2]} = Status2,
- ?line HandlerInfo2 = proplists:get_value(items, Data2),
- ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo2,
+ ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State]),
+ Status1 = sys:get_status(Pid),
+ Status2 = sys:get_status(Pid, 5000),
+ ok = gen_event:stop(Pid),
+ {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
+ HandlerInfo1 = proplists:get_value(items, Data1),
+ {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo1,
+ {status, Pid, _, [_, _, Pid, [], Data2]} = Status2,
+ HandlerInfo2 = proplists:get_value(items, Data2),
+ {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo2,
ok.
%% Test that sys:get_status/1,2 calls format_status/2 for anonymous
%% gen_event processes.
call_format_status_anon(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_event:start(),
+ {ok, Pid} = gen_event:start(),
%% The 'Name' of the gen_event process will be a pid() here, so
%% the next line will crash if format_status can't string-ify pids.
- ?line Status1 = sys:get_status(Pid),
- ?line ok = gen_event:stop(Pid),
+ Status1 = sys:get_status(Pid),
+ ok = gen_event:stop(Pid),
Header = "Status for event handler " ++ pid_to_list(Pid),
- ?line {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
- ?line Header = proplists:get_value(header, Data1),
+ {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
+ Header = proplists:get_value(header, Data1),
ok.
%% Test that a handler error calls format_status/2.
error_format_status(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
State = self(),
- ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy1_h, [State]),
- ?line ok = gen_event:notify(my_dummy_handler, do_crash),
- ?line receive
- {gen_event_EXIT,dummy1_h,{'EXIT',_}} -> ok
- after 5000 ->
- ct:fail(exit_gen_event)
- end,
+ {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_sup_handler(my_dummy_handler, dummy1_h, [State]),
+ ok = gen_event:notify(my_dummy_handler, do_crash),
+ receive
+ {gen_event_EXIT,dummy1_h,{'EXIT',_}} -> ok
+ after 5000 ->
+ ct:fail(exit_gen_event)
+ end,
FmtState = "dummy1_h handler state",
receive
{error,_GroupLeader, {Pid,
@@ -926,10 +926,10 @@ error_format_status(Config) when is_list(Config) ->
FmtState, _]}} ->
ok;
Other ->
- ?line io:format("Unexpected: ~p", [Other]),
+ io:format("Unexpected: ~p", [Other]),
ct:fail(failed)
end,
- ?line ok = gen_event:stop(Pid),
+ ok = gen_event:stop(Pid),
process_flag(trap_exit, OldFl),
ok.
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index 51de194800..f79a344c4e 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -54,7 +54,7 @@
wfor_conf/2, wfor_conf/3,
connected/2, connected/3]).
-export([state0/3]).
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -92,27 +92,27 @@ end_per_group(_GroupName, Config) ->
start1(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
+ {ok, Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
stop_it(Pid0),
-%% ?line stopped = gen_fsm:sync_send_all_state_event(Pid0, stop),
-%% ?line {'EXIT', {timeout,_}} =
-%% (catch gen_fsm:sync_send_event(Pid0, hej)),
+ %% stopped = gen_fsm:sync_send_all_state_event(Pid0, stop),
+ %% {'EXIT', {timeout,_}} =
+ %% (catch gen_fsm:sync_send_event(Pid0, hej)),
[] = get_messages(),
%%process_flag(trap_exit, OldFl),
- ok.
+ ok.
%% anonymous w. shutdown
start2(Config) when is_list(Config) ->
%% Dont link when shutdown
- ?line {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line shutdown_stopped =
+ {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ shutdown_stopped =
gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown),
- ?line {'EXIT', {noproc,_}} =
+ {'EXIT', {noproc,_}} =
(catch gen_fsm:sync_send_event(Pid0, hej)),
[] = get_messages(),
@@ -122,13 +122,13 @@ start2(Config) when is_list(Config) ->
start3(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], [{timeout,5}]),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line stop_it(Pid0),
-
- ?line {error, timeout} = gen_fsm:start(gen_fsm_SUITE, sleep,
- [{timeout,5}]),
+ {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], [{timeout,5}]),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ stop_it(Pid0),
+
+ {error, timeout} = gen_fsm:start(gen_fsm_SUITE, sleep,
+ [{timeout,5}]),
[] = get_messages(),
%%process_flag(trap_exit, OldFl),
@@ -138,7 +138,7 @@ start3(Config) when is_list(Config) ->
start4(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line ignore = gen_fsm:start(gen_fsm_SUITE, ignore, []),
+ ignore = gen_fsm:start(gen_fsm_SUITE, ignore, []),
[] = get_messages(),
process_flag(trap_exit, OldFl),
@@ -148,7 +148,7 @@ start4(Config) when is_list(Config) ->
start5(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {error, stopped} = gen_fsm:start(gen_fsm_SUITE, stop, []),
+ {error, stopped} = gen_fsm:start(gen_fsm_SUITE, stop, []),
[] = get_messages(),
process_flag(trap_exit, OldFl),
@@ -156,10 +156,10 @@ start5(Config) when is_list(Config) ->
%% anonymous linked
start6(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line stop_it(Pid),
+ {ok, Pid} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ stop_it(Pid),
[] = get_messages(),
@@ -167,19 +167,19 @@ start6(Config) when is_list(Config) ->
%% global register linked
start7(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
-
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({global, my_fsm}),
- ?line ok = do_sync_func_test({global, my_fsm}),
- ?line stop_it({global, my_fsm}),
-
+
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({global, my_fsm}),
+ ok = do_sync_func_test({global, my_fsm}),
+ stop_it({global, my_fsm}),
+
[] = get_messages(),
ok.
@@ -188,17 +188,17 @@ start7(Config) when is_list(Config) ->
start8(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test(my_fsm),
- ?line ok = do_sync_func_test(my_fsm),
- ?line stop_it(Pid),
-
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test(my_fsm),
+ ok = do_sync_func_test(my_fsm),
+ stop_it(Pid),
+
[] = get_messages(),
%%process_flag(trap_exit, OldFl),
ok.
@@ -207,78 +207,78 @@ start8(Config) when is_list(Config) ->
start9(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test(my_fsm),
- ?line ok = do_sync_func_test(my_fsm),
- ?line stop_it(Pid),
-
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test(my_fsm),
+ ok = do_sync_func_test(my_fsm),
+ stop_it(Pid),
+
[] = get_messages(),
%%process_flag(trap_exit, OldFl),
ok.
%% global register
start10(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
-
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({global, my_fsm}),
- ?line ok = do_sync_func_test({global, my_fsm}),
- ?line stop_it({global, my_fsm}),
-
+
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({global, my_fsm}),
+ ok = do_sync_func_test({global, my_fsm}),
+ stop_it({global, my_fsm}),
+
[] = get_messages(),
ok.
%% Stop registered processes
start11(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(Pid),
+ stop_it(Pid),
- ?line {ok, _Pid1} =
+ {ok, _Pid1} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(my_fsm),
-
- ?line {ok, Pid2} =
+ stop_it(my_fsm),
+
+ {ok, Pid2} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(Pid2),
+ stop_it(Pid2),
receive after 1 -> true end,
- ?line Result =
+ Result =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
io:format("Result = ~p~n",[Result]),
- ?line {ok, _Pid3} = Result,
- ?line stop_it({global, my_fsm}),
+ {ok, _Pid3} = Result,
+ stop_it({global, my_fsm}),
[] = get_messages(),
ok.
%% Via register linked
start12(Config) when is_list(Config) ->
- ?line dummy_via:reset(),
- ?line {ok, Pid} =
+ dummy_via:reset(),
+ {ok, Pid} =
gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({via, dummy_via, my_fsm}),
- ?line ok = do_sync_func_test({via, dummy_via, my_fsm}),
- ?line stop_it({via, dummy_via, my_fsm}),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({via, dummy_via, my_fsm}),
+ ok = do_sync_func_test({via, dummy_via, my_fsm}),
+ stop_it({via, dummy_via, my_fsm}),
[] = get_messages(),
ok.
@@ -336,7 +336,7 @@ stop6(_Config) ->
stop7(_Config) ->
dummy_via:reset(),
{ok, Pid} = gen_fsm:start({via, dummy_via, to_stop},
- ?MODULE, [], []),
+ ?MODULE, [], []),
ok = gen_fsm:stop({via, dummy_via, to_stop}),
false = erlang:is_process_alive(Pid),
{'EXIT',noproc} = (catch gen_fsm:stop({via, dummy_via, to_stop})),
@@ -390,7 +390,7 @@ abnormal1(Config) when is_list(Config) ->
%% timeout call.
delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100),
{'EXIT',{timeout,_}} =
- (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)),
+ (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)),
[] = get_messages(),
ok.
@@ -398,36 +398,36 @@ abnormal1(Config) when is_list(Config) ->
%% trap exit since we must link to get the real bad_return_ error
abnormal2(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link(gen_fsm_SUITE, [], []),
%% bad return value in the gen_fsm loop
- ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ {'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_fsm:sync_send_event(Pid, badreturn)),
-
+
[{'EXIT',Pid,{bad_return_value,badreturn}}] = get_messages(),
process_flag(trap_exit, OldFl),
ok.
shutdown(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
process_flag(trap_exit, true),
- ?line {ok,Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line {shutdown,reason} =
+ {ok,Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ {shutdown,reason} =
gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown_reason),
receive {'EXIT',Pid0,{shutdown,reason}} -> ok end,
process_flag(trap_exit, false),
- ?line {'EXIT', {noproc,_}} =
+ {'EXIT', {noproc,_}} =
(catch gen_fsm:sync_send_event(Pid0, hej)),
receive
Any ->
- ?line io:format("Unexpected: ~p", [Any]),
+ io:format("Unexpected: ~p", [Any]),
ct:fail(failed)
after 500 ->
ok
@@ -438,70 +438,70 @@ shutdown(Config) when is_list(Config) ->
sys1(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line {status, Pid, {module,gen_fsm}, _} = sys:get_status(Pid),
- ?line sys:suspend(Pid),
- ?line {'EXIT', {timeout,_}} =
+ {status, Pid, {module,gen_fsm}, _} = sys:get_status(Pid),
+ sys:suspend(Pid),
+ {'EXIT', {timeout,_}} =
(catch gen_fsm:sync_send_event(Pid, hej)),
- ?line sys:resume(Pid),
- ?line stop_it(Pid).
+ sys:resume(Pid),
+ stop_it(Pid).
call_format_status(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line Status = sys:get_status(Pid),
- ?line {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
- ?line [format_status_called | _] = lists:reverse(Data),
- ?line stop_it(Pid),
+ {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
+ Status = sys:get_status(Pid),
+ {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
+ [format_status_called | _] = lists:reverse(Data),
+ stop_it(Pid),
%% check that format_status can handle a name being an atom (pid is
%% already checked by the previous test)
- ?line {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
- ?line Status2 = sys:get_status(gfsm),
- ?line {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
- ?line [format_status_called | _] = lists:reverse(Data2),
- ?line stop_it(Pid2),
+ {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
+ Status2 = sys:get_status(gfsm),
+ {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
+ [format_status_called | _] = lists:reverse(Data2),
+ stop_it(Pid2),
%% check that format_status can handle a name being a term other than a
%% pid or atom
GlobalName1 = {global, "CallFormatStatus"},
- ?line {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
- ?line Status3 = sys:get_status(GlobalName1),
- ?line {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
- ?line [format_status_called | _] = lists:reverse(Data3),
- ?line stop_it(Pid3),
+ {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
+ Status3 = sys:get_status(GlobalName1),
+ {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
+ [format_status_called | _] = lists:reverse(Data3),
+ stop_it(Pid3),
GlobalName2 = {global, {name, "term"}},
- ?line {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
- ?line Status4 = sys:get_status(GlobalName2),
- ?line {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
- ?line [format_status_called | _] = lists:reverse(Data4),
- ?line stop_it(Pid4),
+ {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
+ Status4 = sys:get_status(GlobalName2),
+ {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
+ [format_status_called | _] = lists:reverse(Data4),
+ stop_it(Pid4),
%% check that format_status can handle a name being a term other than a
%% pid or atom
- ?line dummy_via:reset(),
+ dummy_via:reset(),
ViaName1 = {via, dummy_via, "CallFormatStatus"},
- ?line {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []),
- ?line Status5 = sys:get_status(ViaName1),
- ?line {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5,
- ?line [format_status_called | _] = lists:reverse(Data5),
- ?line stop_it(Pid5),
+ {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []),
+ Status5 = sys:get_status(ViaName1),
+ {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5,
+ [format_status_called | _] = lists:reverse(Data5),
+ stop_it(Pid5),
ViaName2 = {via, dummy_via, {name, "term"}},
- ?line {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []),
- ?line Status6 = sys:get_status(ViaName2),
- ?line {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6,
- ?line [format_status_called | _] = lists:reverse(Data6),
- ?line stop_it(Pid6).
+ {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []),
+ Status6 = sys:get_status(ViaName2),
+ {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6,
+ [format_status_called | _] = lists:reverse(Data6),
+ stop_it(Pid6).
error_format_status(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
StateData = "called format_status",
- ?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
+ {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
%% bad return value in the gen_fsm loop
- ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ {'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_fsm:sync_send_event(Pid, badreturn)),
receive
{error,_GroupLeader,{Pid,
@@ -509,7 +509,7 @@ error_format_status(Config) when is_list(Config) ->
[Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} ->
ok;
Other ->
- ?line io:format("Unexpected: ~p", [Other]),
+ io:format("Unexpected: ~p", [Other]),
ct:fail(failed)
end,
process_flag(trap_exit, OldFl),
@@ -718,13 +718,13 @@ is_not_in_erlang_hibernate_1(N, Pid) ->
enter_loop(Config) when is_list(Config) ->
OldFlag = process_flag(trap_exit, true),
- ?line dummy_via:reset(),
+ dummy_via:reset(),
%% Locally registered process + {local, Name}
- ?line {ok, Pid1a} =
+ {ok, Pid1a} =
proc_lib:start_link(?MODULE, enter_loop, [local, local]),
- ?line yes = gen_fsm:sync_send_event(Pid1a, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid1a, stop),
+ yes = gen_fsm:sync_send_event(Pid1a, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid1a, stop),
receive
{'EXIT', Pid1a, normal} ->
ok
@@ -733,7 +733,7 @@ enter_loop(Config) when is_list(Config) ->
end,
%% Unregistered process + {local, Name}
- ?line {ok, Pid1b} =
+ {ok, Pid1b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
receive
{'EXIT', Pid1b, process_not_registered} ->
@@ -743,10 +743,10 @@ enter_loop(Config) when is_list(Config) ->
end,
%% Globally registered process + {global, Name}
- ?line {ok, Pid2a} =
+ {ok, Pid2a} =
proc_lib:start_link(?MODULE, enter_loop, [global, global]),
- ?line yes = gen_fsm:sync_send_event(Pid2a, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid2a, stop),
+ yes = gen_fsm:sync_send_event(Pid2a, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid2a, stop),
receive
{'EXIT', Pid2a, normal} ->
ok
@@ -755,7 +755,7 @@ enter_loop(Config) when is_list(Config) ->
end,
%% Unregistered process + {global, Name}
- ?line {ok, Pid2b} =
+ {ok, Pid2b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
receive
{'EXIT', Pid2b, process_not_registered_globally} ->
@@ -765,10 +765,10 @@ enter_loop(Config) when is_list(Config) ->
end,
%% Unregistered process + no name
- ?line {ok, Pid3} =
+ {ok, Pid3} =
proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
- ?line yes = gen_fsm:sync_send_event(Pid3, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid3, stop),
+ yes = gen_fsm:sync_send_event(Pid3, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid3, stop),
receive
{'EXIT', Pid3, normal} ->
ok
@@ -777,7 +777,7 @@ enter_loop(Config) when is_list(Config) ->
end,
%% Process not started using proc_lib
- ?line Pid4 =
+ Pid4 =
spawn_link(gen_fsm, enter_loop, [?MODULE, [], state0, []]),
receive
{'EXIT', Pid4, process_was_not_started_by_proc_lib} ->
@@ -788,10 +788,10 @@ enter_loop(Config) when is_list(Config) ->
%% Make sure I am the parent, ie that ordering a shutdown will
%% result in the process terminating with Reason==shutdown
- ?line {ok, Pid5} =
+ {ok, Pid5} =
proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
- ?line yes = gen_fsm:sync_send_event(Pid5, 'alive?'),
- ?line exit(Pid5, shutdown),
+ yes = gen_fsm:sync_send_event(Pid5, 'alive?'),
+ exit(Pid5, shutdown),
receive
{'EXIT', Pid5, shutdown} ->
ok
@@ -803,7 +803,7 @@ enter_loop(Config) when is_list(Config) ->
%% when it's another process than the calling one which is
%% registered under that name
register(armitage, self()),
- ?line {ok, Pid6a} =
+ {ok, Pid6a} =
proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
receive
{'EXIT', Pid6a, process_not_registered} ->
@@ -817,7 +817,7 @@ enter_loop(Config) when is_list(Config) ->
%% when it's another process than the calling one which is
%% registered under that name
global:register_name(armitage, self()),
- ?line {ok, Pid6b} =
+ {ok, Pid6b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
receive
{'EXIT', Pid6b, process_not_registered_globally} ->
@@ -828,7 +828,7 @@ enter_loop(Config) when is_list(Config) ->
global:unregister_name(armitage),
dummy_via:register_name(armitage, self()),
- ?line {ok, Pid6c} =
+ {ok, Pid6c} =
proc_lib:start_link(?MODULE, enter_loop, [anon, via]),
receive
{'EXIT', Pid6c, {process_not_registered_via, dummy_via}} ->
@@ -875,8 +875,8 @@ wfor(Msg) ->
stop_it(FSM) ->
- ?line stopped = gen_fsm:sync_send_all_state_event(FSM, stop),
- ?line {'EXIT',_} = (catch gen_fsm:sync_send_event(FSM, hej)),
+ stopped = gen_fsm:sync_send_all_state_event(FSM, stop),
+ {'EXIT',_} = (catch gen_fsm:sync_send_event(FSM, hej)),
ok.
@@ -956,7 +956,7 @@ do_sync_disconnect(FSM) ->
yes = gen_fsm:sync_send_event(FSM, disconnect),
check_state(FSM, idle).
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
@@ -1076,7 +1076,7 @@ hiber_wakeup(wakeup_async,Data) ->
{next_state,hiber_idle,Data};
hiber_wakeup(snooze_async,Data) ->
{next_state,hiber_wakeup,Data,hibernate}.
-
+
handle_info(hibernate_now, _SName, _State) ->
%% Arrive here from by direct ! from testcase
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 028810b873..916fbc4e84 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -114,125 +114,125 @@ start(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
%% anonymous
- ?line {ok, Pid0} = gen_server:start(gen_server_SUITE, [], []),
- ?line ok = gen_server:call(Pid0, started_p),
- ?line ok = gen_server:call(Pid0, stop),
- ?line busy_wait_for_process(Pid0,600),
- ?line {'EXIT', {noproc,_}} = (catch gen_server:call(Pid0, started_p, 1)),
+ {ok, Pid0} = gen_server:start(gen_server_SUITE, [], []),
+ ok = gen_server:call(Pid0, started_p),
+ ok = gen_server:call(Pid0, stop),
+ busy_wait_for_process(Pid0,600),
+ {'EXIT', {noproc,_}} = (catch gen_server:call(Pid0, started_p, 1)),
%% anonymous with timeout
- ?line {ok, Pid00} = gen_server:start(gen_server_SUITE, [],
- [{timeout,1000}]),
- ?line ok = gen_server:call(Pid00, started_p),
- ?line ok = gen_server:call(Pid00, stop),
- ?line {error, timeout} = gen_server:start(gen_server_SUITE, sleep,
- [{timeout,100}]),
+ {ok, Pid00} = gen_server:start(gen_server_SUITE, [],
+ [{timeout,1000}]),
+ ok = gen_server:call(Pid00, started_p),
+ ok = gen_server:call(Pid00, stop),
+ {error, timeout} = gen_server:start(gen_server_SUITE, sleep,
+ [{timeout,100}]),
%% anonymous with ignore
- ?line ignore = gen_server:start(gen_server_SUITE, ignore, []),
+ ignore = gen_server:start(gen_server_SUITE, ignore, []),
%% anonymous with stop
- ?line {error, stopped} = gen_server:start(gen_server_SUITE, stop, []),
+ {error, stopped} = gen_server:start(gen_server_SUITE, stop, []),
%% anonymous linked
- ?line {ok, Pid1} =
+ {ok, Pid1} =
gen_server:start_link(gen_server_SUITE, [], []),
- ?line ok = gen_server:call(Pid1, started_p),
- ?line ok = gen_server:call(Pid1, stop),
- ?line receive
- {'EXIT', Pid1, stopped} ->
- ok
- after 5000 ->
- ct:fail(not_stopped)
- end,
+ ok = gen_server:call(Pid1, started_p),
+ ok = gen_server:call(Pid1, stop),
+ receive
+ {'EXIT', Pid1, stopped} ->
+ ok
+ after 5000 ->
+ ct:fail(not_stopped)
+ end,
%% local register
- ?line {ok, Pid2} =
+ {ok, Pid2} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
- ?line {error, {already_started, Pid2}} =
+ ok = gen_server:call(my_test_name, started_p),
+ {error, {already_started, Pid2}} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, stop),
+ ok = gen_server:call(my_test_name, stop),
- ?line busy_wait_for_process(Pid2,600),
+ busy_wait_for_process(Pid2,600),
- ?line {'EXIT', {noproc,_}} = (catch gen_server:call(Pid2, started_p, 10)),
+ {'EXIT', {noproc,_}} = (catch gen_server:call(Pid2, started_p, 10)),
%% local register linked
- ?line {ok, Pid3} =
+ {ok, Pid3} =
gen_server:start_link({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
- ?line {error, {already_started, Pid3}} =
+ ok = gen_server:call(my_test_name, started_p),
+ {error, {already_started, Pid3}} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, stop),
- ?line receive
- {'EXIT', Pid3, stopped} ->
- ok
- after 5000 ->
- ct:fail(not_stopped)
- end,
+ ok = gen_server:call(my_test_name, stop),
+ receive
+ {'EXIT', Pid3, stopped} ->
+ ok
+ after 5000 ->
+ ct:fail(not_stopped)
+ end,
%% global register
- ?line {ok, Pid4} =
+ {ok, Pid4} =
gen_server:start({global, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({global, my_test_name}, started_p),
- ?line {error, {already_started, Pid4}} =
+ ok = gen_server:call({global, my_test_name}, started_p),
+ {error, {already_started, Pid4}} =
gen_server:start({global, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({global, my_test_name}, stop),
+ ok = gen_server:call({global, my_test_name}, stop),
ct:sleep(1),
- ?line {'EXIT', {noproc,_}} = (catch gen_server:call(Pid4, started_p, 10)),
+ {'EXIT', {noproc,_}} = (catch gen_server:call(Pid4, started_p, 10)),
%% global register linked
- ?line {ok, Pid5} =
+ {ok, Pid5} =
gen_server:start_link({global, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({global, my_test_name}, started_p),
- ?line {error, {already_started, Pid5}} =
+ ok = gen_server:call({global, my_test_name}, started_p),
+ {error, {already_started, Pid5}} =
gen_server:start({global, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({global, my_test_name}, stop),
- ?line receive
- {'EXIT', Pid5, stopped} ->
- ok
- after 5000 ->
- ct:fail(not_stopped)
- end,
+ ok = gen_server:call({global, my_test_name}, stop),
+ receive
+ {'EXIT', Pid5, stopped} ->
+ ok
+ after 5000 ->
+ ct:fail(not_stopped)
+ end,
%% via register
- ?line dummy_via:reset(),
- ?line {ok, Pid6} =
+ dummy_via:reset(),
+ {ok, Pid6} =
gen_server:start({via, dummy_via, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({via, dummy_via, my_test_name}, started_p),
- ?line {error, {already_started, Pid6}} =
+ ok = gen_server:call({via, dummy_via, my_test_name}, started_p),
+ {error, {already_started, Pid6}} =
gen_server:start({via, dummy_via, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({via, dummy_via, my_test_name}, stop),
+ ok = gen_server:call({via, dummy_via, my_test_name}, stop),
ct:sleep(1),
- ?line {'EXIT', {noproc,_}} = (catch gen_server:call(Pid6, started_p, 10)),
+ {'EXIT', {noproc,_}} = (catch gen_server:call(Pid6, started_p, 10)),
%% via register linked
- ?line dummy_via:reset(),
- ?line {ok, Pid7} =
+ dummy_via:reset(),
+ {ok, Pid7} =
gen_server:start_link({via, dummy_via, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({via, dummy_via, my_test_name}, started_p),
- ?line {error, {already_started, Pid7}} =
+ ok = gen_server:call({via, dummy_via, my_test_name}, started_p),
+ {error, {already_started, Pid7}} =
gen_server:start({via, dummy_via, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call({via, dummy_via, my_test_name}, stop),
- ?line receive
- {'EXIT', Pid7, stopped} ->
- ok
- after 5000 ->
- ct:fail(not_stopped)
- end,
+ ok = gen_server:call({via, dummy_via, my_test_name}, stop),
+ receive
+ {'EXIT', Pid7, stopped} ->
+ ok
+ after 5000 ->
+ ct:fail(not_stopped)
+ end,
receive
Msg -> ct:fail({unexpected,Msg})
after 1 -> ok
@@ -293,7 +293,7 @@ stop6(_Config) ->
stop7(_Config) ->
dummy_via:reset(),
{ok, Pid} = gen_server:start({via, dummy_via, to_stop},
- ?MODULE, [], []),
+ ?MODULE, [], []),
ok = gen_server:stop({via, dummy_via, to_stop}),
false = erlang:is_process_alive(Pid),
{'EXIT',noproc} = (catch gen_server:stop({via, dummy_via, to_stop})),
@@ -341,31 +341,31 @@ stop10(_Config) ->
ok.
crash(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
process_flag(trap_exit, true),
%% This crash should not generate a crash report.
- ?line {ok,Pid0} = gen_server:start_link(?MODULE, [], []),
- ?line {'EXIT',{{shutdown,reason},_}} =
+ {ok,Pid0} = gen_server:start_link(?MODULE, [], []),
+ {'EXIT',{{shutdown,reason},_}} =
(catch gen_server:call(Pid0, shutdown_reason)),
receive {'EXIT',Pid0,{shutdown,reason}} -> ok end,
%% This crash should not generate a crash report.
- ?line {ok,Pid1} = gen_server:start_link(?MODULE, {state,state1}, []),
- ?line {'EXIT',{{shutdown,stop_reason},_}} =
+ {ok,Pid1} = gen_server:start_link(?MODULE, {state,state1}, []),
+ {'EXIT',{{shutdown,stop_reason},_}} =
(catch gen_server:call(Pid1, stop_shutdown_reason)),
receive {'EXIT',Pid1,{shutdown,stop_reason}} -> ok end,
%% This crash should not generate a crash report.
- ?line {ok,Pid2} = gen_server:start_link(?MODULE, [], []),
- ?line {'EXIT',{shutdown,_}} =
+ {ok,Pid2} = gen_server:start_link(?MODULE, [], []),
+ {'EXIT',{shutdown,_}} =
(catch gen_server:call(Pid2, exit_shutdown)),
receive {'EXIT',Pid2,shutdown} -> ok end,
%% This crash should not generate a crash report.
- ?line {ok,Pid3} = gen_server:start_link(?MODULE, {state,state3}, []),
- ?line {'EXIT',{shutdown,_}} =
+ {ok,Pid3} = gen_server:start_link(?MODULE, {state,state3}, []),
+ {'EXIT',{shutdown,_}} =
(catch gen_server:call(Pid3, stop_shutdown)),
receive {'EXIT',Pid3,shutdown} -> ok end,
@@ -373,8 +373,8 @@ crash(Config) when is_list(Config) ->
%% This crash should generate a crash report and a report
%% from gen_server.
- ?line {ok,Pid4} = gen_server:start(?MODULE, {state,state4}, []),
- ?line {'EXIT',{crashed,_}} = (catch gen_server:call(Pid4, crash)),
+ {ok,Pid4} = gen_server:start(?MODULE, {state,state4}, []),
+ {'EXIT',{crashed,_}} = (catch gen_server:call(Pid4, crash)),
receive
{error,_GroupLeader4,{Pid4,
"** Generic server"++_,
@@ -383,7 +383,7 @@ crash(Config) when is_list(Config) ->
|_Stacktrace]}]}} ->
ok;
Other4a ->
- ?line io:format("Unexpected: ~p", [Other4a]),
+ io:format("Unexpected: ~p", [Other4a]),
ct:fail(failed)
end,
receive
@@ -391,13 +391,13 @@ crash(Config) when is_list(Config) ->
{exit,crashed,_} = proplists:get_value(error_info, List4),
Pid4 = proplists:get_value(pid, List4);
Other4 ->
- ?line io:format("Unexpected: ~p", [Other4]),
+ io:format("Unexpected: ~p", [Other4]),
ct:fail(failed)
end,
receive
Any ->
- ?line io:format("Unexpected: ~p", [Any]),
+ io:format("Unexpected: ~p", [Any]),
ct:fail(failed)
after 500 ->
ok
@@ -414,28 +414,28 @@ crash(Config) when is_list(Config) ->
call(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, _Pid} =
+ {ok, _Pid} =
gen_server:start_link({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
- ?line delayed = gen_server:call(my_test_name, {delayed_answer,1}),
+ ok = gen_server:call(my_test_name, started_p),
+ delayed = gen_server:call(my_test_name, {delayed_answer,1}),
%% two requests within a specified time.
- ?line ok = gen_server:call(my_test_name, {call_within, 1000}),
+ ok = gen_server:call(my_test_name, {call_within, 1000}),
timer:sleep(500),
- ?line ok = gen_server:call(my_test_name, next_call),
- ?line ok = gen_server:call(my_test_name, {call_within, 1000}),
+ ok = gen_server:call(my_test_name, next_call),
+ ok = gen_server:call(my_test_name, {call_within, 1000}),
timer:sleep(1500),
- ?line false = gen_server:call(my_test_name, next_call),
-
+ false = gen_server:call(my_test_name, next_call),
+
%% timeout call.
- ?line delayed = gen_server:call(my_test_name, {delayed_answer,1}, 30),
- ?line {'EXIT',{timeout,_}} =
+ delayed = gen_server:call(my_test_name, {delayed_answer,1}, 30),
+ {'EXIT',{timeout,_}} =
(catch gen_server:call(my_test_name, {delayed_answer,30}, 1)),
%% bad return value in the gen_server loop from handle_call.
- ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ {'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_server:call(my_test_name, badreturn)),
process_flag(trap_exit, OldFl),
@@ -446,8 +446,8 @@ call(Config) when is_list(Config) ->
%% --------------------------------------
start_node(Name) ->
- ?line Pa = filename:dirname(code:which(?MODULE)),
- ?line N = test_server:start_node(Name, slave, [{args, " -pa " ++ Pa}]),
+ Pa = filename:dirname(code:which(?MODULE)),
+ N = test_server:start_node(Name, slave, [{args, " -pa " ++ Pa}]),
%% After starting a slave, it takes a little while until global knows
%% about it, even if nodes() includes it, so we make sure that global
%% knows about it before registering something on all nodes.
@@ -456,39 +456,39 @@ start_node(Name) ->
call_remote1(Config) when is_list(Config) ->
N = hubba,
- ?line Node = proplists:get_value(node,Config),
- ?line {ok, Pid} = rpc:call(Node, gen_server, start,
- [{global, N}, ?MODULE, [], []]),
- ?line ok = (catch gen_server:call({global, N}, started_p, infinity)),
- ?line exit(Pid, boom),
- ?line {'EXIT', {Reason, _}} = (catch gen_server:call({global, N},
- started_p, infinity)),
- ?line true = (Reason == noproc) orelse (Reason == boom),
+ Node = proplists:get_value(node,Config),
+ {ok, Pid} = rpc:call(Node, gen_server, start,
+ [{global, N}, ?MODULE, [], []]),
+ ok = (catch gen_server:call({global, N}, started_p, infinity)),
+ exit(Pid, boom),
+ {'EXIT', {Reason, _}} = (catch gen_server:call({global, N},
+ started_p, infinity)),
+ true = (Reason == noproc) orelse (Reason == boom),
ok.
call_remote2(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line Node = proplists:get_value(node,Config),
-
- ?line {ok, Pid} = rpc:call(Node, gen_server, start,
- [{global, N}, ?MODULE, [], []]),
- ?line ok = (catch gen_server:call(Pid, started_p, infinity)),
- ?line exit(Pid, boom),
- ?line {'EXIT', {Reason, _}} = (catch gen_server:call(Pid,
- started_p, infinity)),
- ?line true = (Reason == noproc) orelse (Reason == boom),
+ N = hubba,
+ Node = proplists:get_value(node,Config),
+
+ {ok, Pid} = rpc:call(Node, gen_server, start,
+ [{global, N}, ?MODULE, [], []]),
+ ok = (catch gen_server:call(Pid, started_p, infinity)),
+ exit(Pid, boom),
+ {'EXIT', {Reason, _}} = (catch gen_server:call(Pid,
+ started_p, infinity)),
+ true = (Reason == noproc) orelse (Reason == boom),
ok.
call_remote3(Config) when is_list(Config) ->
- ?line Node = proplists:get_value(node,Config),
-
- ?line {ok, Pid} = rpc:call(Node, gen_server, start,
- [{local, piller}, ?MODULE, [], []]),
- ?line ok = (catch gen_server:call({piller, Node}, started_p, infinity)),
- ?line exit(Pid, boom),
- ?line {'EXIT', {Reason, _}} = (catch gen_server:call({piller, Node},
- started_p, infinity)),
- ?line true = (Reason == noproc) orelse (Reason == boom),
+ Node = proplists:get_value(node,Config),
+
+ {ok, Pid} = rpc:call(Node, gen_server, start,
+ [{local, piller}, ?MODULE, [], []]),
+ ok = (catch gen_server:call({piller, Node}, started_p, infinity)),
+ exit(Pid, boom),
+ {'EXIT', {Reason, _}} = (catch gen_server:call({piller, Node},
+ started_p, infinity)),
+ true = (Reason == noproc) orelse (Reason == boom),
ok.
%% --------------------------------------
@@ -496,36 +496,36 @@ call_remote3(Config) when is_list(Config) ->
%% --------------------------------------
call_remote_n1(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line Node = proplists:get_value(node,Config),
- ?line {ok, _Pid} = rpc:call(Node, gen_server, start,
- [{global, N}, ?MODULE, [], []]),
- ?line _ = test_server:stop_node(Node),
- ?line {'EXIT', {noproc, _}} =
+ N = hubba,
+ Node = proplists:get_value(node,Config),
+ {ok, _Pid} = rpc:call(Node, gen_server, start,
+ [{global, N}, ?MODULE, [], []]),
+ _ = test_server:stop_node(Node),
+ {'EXIT', {noproc, _}} =
(catch gen_server:call({global, N}, started_p, infinity)),
ok.
call_remote_n2(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line Node = proplists:get_value(node,Config),
+ N = hubba,
+ Node = proplists:get_value(node,Config),
- ?line {ok, Pid} = rpc:call(Node, gen_server, start,
- [{global, N}, ?MODULE, [], []]),
- ?line _ = test_server:stop_node(Node),
- ?line {'EXIT', {{nodedown, Node}, _}} = (catch gen_server:call(Pid,
- started_p, infinity)),
+ {ok, Pid} = rpc:call(Node, gen_server, start,
+ [{global, N}, ?MODULE, [], []]),
+ _ = test_server:stop_node(Node),
+ {'EXIT', {{nodedown, Node}, _}} = (catch gen_server:call(Pid,
+ started_p, infinity)),
ok.
call_remote_n3(Config) when is_list(Config) ->
- ?line Node = proplists:get_value(node,Config),
+ Node = proplists:get_value(node,Config),
- ?line {ok, _Pid} = rpc:call(Node, gen_server, start,
- [{local, piller}, ?MODULE, [], []]),
- ?line _ = test_server:stop_node(Node),
- ?line {'EXIT', {{nodedown, Node}, _}} = (catch gen_server:call({piller, Node},
- started_p, infinity)),
+ {ok, _Pid} = rpc:call(Node, gen_server, start,
+ [{local, piller}, ?MODULE, [], []]),
+ _ = test_server:stop_node(Node),
+ {'EXIT', {{nodedown, Node}, _}} = (catch gen_server:call({piller, Node},
+ started_p, infinity)),
ok.
@@ -536,46 +536,46 @@ call_remote_n3(Config) when is_list(Config) ->
%% --------------------------------------
cast(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
-
- ?line ok = gen_server:cast(my_test_name, {self(),handle_cast}),
- ?line receive
- {Pid, handled_cast} ->
- ok
- after 1000 ->
- ct:fail(handle_cast)
- end,
-
- ?line ok = gen_server:cast(my_test_name, {self(),delayed_cast,1}),
- ?line receive
- {Pid, delayed} ->
- ok
- after 1000 ->
- ct:fail(delayed_cast)
- end,
-
- ?line ok = gen_server:cast(my_test_name, {self(),stop}),
- ?line receive
- {Pid, stopped} ->
- ok
- after 1000 ->
- ct:fail(stop)
- end,
+ ok = gen_server:call(my_test_name, started_p),
+
+ ok = gen_server:cast(my_test_name, {self(),handle_cast}),
+ receive
+ {Pid, handled_cast} ->
+ ok
+ after 1000 ->
+ ct:fail(handle_cast)
+ end,
+
+ ok = gen_server:cast(my_test_name, {self(),delayed_cast,1}),
+ receive
+ {Pid, delayed} ->
+ ok
+ after 1000 ->
+ ct:fail(delayed_cast)
+ end,
+
+ ok = gen_server:cast(my_test_name, {self(),stop}),
+ receive
+ {Pid, stopped} ->
+ ok
+ after 1000 ->
+ ct:fail(stop)
+ end,
ok.
%% Test that cast really return immediately.
cast_fast(Config) when is_list(Config) ->
- ?line {ok,Node} = start_node(hubba),
- ?line {_,"@"++Host} = lists:splitwith(fun ($@) -> false; (_) -> true end,
- atom_to_list(Node)),
- ?line FalseNode = list_to_atom("hopp@"++Host),
- ?line true = rpc:cast(Node, ?MODULE, cast_fast_messup, []),
+ {ok,Node} = start_node(hubba),
+ {_,"@"++Host} = lists:splitwith(fun ($@) -> false; (_) -> true end,
+ atom_to_list(Node)),
+ FalseNode = list_to_atom("hopp@"++Host),
+ true = rpc:cast(Node, ?MODULE, cast_fast_messup, []),
ct:sleep(1000),
- ?line [Node] = nodes(),
+ [Node] = nodes(),
{Time,ok} = timer:tc(fun() ->
gen_server:cast({hopp,FalseNode}, hopp)
end),
@@ -600,35 +600,35 @@ cast_fast_messup() ->
%% --------------------------------------
info(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
-
- ?line Pid ! {self(),handle_info},
- ?line receive
- {Pid, handled_info} ->
- ok
- after 1000 ->
- ct:fail(handle_info)
- end,
-
- ?line Pid ! {self(),delayed_info,1},
- ?line receive
- {Pid, delayed_info} ->
- ok
- after 1000 ->
- ct:fail(delayed_info)
- end,
-
- ?line Pid ! {self(),stop},
- ?line receive
- {Pid, stopped_info} ->
- ok
- after 1000 ->
- ct:fail(stop_info)
- end,
+ ok = gen_server:call(my_test_name, started_p),
+
+ Pid ! {self(),handle_info},
+ receive
+ {Pid, handled_info} ->
+ ok
+ after 1000 ->
+ ct:fail(handle_info)
+ end,
+
+ Pid ! {self(),delayed_info,1},
+ receive
+ {Pid, delayed_info} ->
+ ok
+ after 1000 ->
+ ct:fail(delayed_info)
+ end,
+
+ Pid ! {self(),stop},
+ receive
+ {Pid, stopped_info} ->
+ ok
+ after 1000 ->
+ ct:fail(stop_info)
+ end,
ok.
hibernate(Config) when is_list(Config) ->
@@ -738,36 +738,36 @@ is_in_erlang_hibernate_1(N, Pid) ->
%% --------------------------------------
abcast(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_server:start({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
-
- ?line abcast = gen_server:abcast(my_test_name, {self(),handle_cast}),
- ?line receive
- {Pid, handled_cast} ->
- ok
- after 1000 ->
- ct:fail(abcast)
- end,
-
- ?line abcast = gen_server:abcast([node()], my_test_name,
- {self(),delayed_cast,1}),
- ?line receive
- {Pid, delayed} ->
- ok
- after 1000 ->
- ct:fail(delayed_abcast)
- end,
-
- ?line abcast = gen_server:abcast(my_test_name, {self(),stop}),
- ?line receive
- {Pid, stopped} ->
- ok
- after 1000 ->
- ct:fail(abcast_stop)
- end,
+ ok = gen_server:call(my_test_name, started_p),
+
+ abcast = gen_server:abcast(my_test_name, {self(),handle_cast}),
+ receive
+ {Pid, handled_cast} ->
+ ok
+ after 1000 ->
+ ct:fail(abcast)
+ end,
+
+ abcast = gen_server:abcast([node()], my_test_name,
+ {self(),delayed_cast,1}),
+ receive
+ {Pid, delayed} ->
+ ok
+ after 1000 ->
+ ct:fail(delayed_abcast)
+ end,
+
+ abcast = gen_server:abcast(my_test_name, {self(),stop}),
+ receive
+ {Pid, stopped} ->
+ ok
+ after 1000 ->
+ ct:fail(abcast_stop)
+ end,
ok.
%% --------------------------------------
@@ -779,37 +779,37 @@ abcast(Config) when is_list(Config) ->
multicall(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_server:start_link({local, my_test_name},
gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name, started_p),
+ ok = gen_server:call(my_test_name, started_p),
Nodes = nodes(),
Node = node(),
- ?line {[{Node,delayed}],Nodes} =
- gen_server:multi_call(my_test_name, {delayed_answer,1}),
+ {[{Node,delayed}],Nodes} =
+ gen_server:multi_call(my_test_name, {delayed_answer,1}),
%% two requests within a specified time.
- ?line {[{Node,ok}],[]} =
- gen_server:multi_call([Node], my_test_name, {call_within, 1000}),
+ {[{Node,ok}],[]} =
+ gen_server:multi_call([Node], my_test_name, {call_within, 1000}),
timer:sleep(500),
- ?line {[{Node,ok}],[]} =
- gen_server:multi_call([Node], my_test_name, next_call),
- ?line {[{Node,ok}],[]} =
- gen_server:multi_call([Node], my_test_name, {call_within, 1000}),
+ {[{Node,ok}],[]} =
+ gen_server:multi_call([Node], my_test_name, next_call),
+ {[{Node,ok}],[]} =
+ gen_server:multi_call([Node], my_test_name, {call_within, 1000}),
timer:sleep(1500),
- ?line {[{Node,false}],[]} =
- gen_server:multi_call([Node],my_test_name, next_call),
+ {[{Node,false}],[]} =
+ gen_server:multi_call([Node],my_test_name, next_call),
%% Stop the server.
- ?line {[{Node,ok}],[]} =
- gen_server:multi_call([Node],my_test_name, stop),
+ {[{Node,ok}],[]} =
+ gen_server:multi_call([Node],my_test_name, stop),
receive
{'EXIT', Pid, stopped} -> ok
after 1000 ->
ct:fail(multicall_stop)
end,
-
+
process_flag(trap_exit, OldFl),
ok.
@@ -817,15 +817,15 @@ multicall(Config) when is_list(Config) ->
%% OTP-3587
multicall_down(Config) when is_list(Config) ->
%% We need a named host which is inaccessible.
- ?line Name = node@test01,
+ Name = node@test01,
%% We use 'global' as a gen_server to call.
- ?line {Good, Bad} = gen_server:multi_call([Name, node()],
- global_name_server,
- info,
- 3000),
+ {Good, Bad} = gen_server:multi_call([Name, node()],
+ global_name_server,
+ info,
+ 3000),
io:format("good = ~p, bad = ~p~n", [Good, Bad]),
- ?line [Name] = Bad,
+ [Name] = Bad,
ok.
busy_wait_for_process(Pid,N) ->
@@ -843,38 +843,38 @@ busy_wait_for_process(Pid,N) ->
%% Test gen_server:enter_loop/[3,4,5]. Used when you want to write
%% your own special init-phase.
spec_init(Config) when is_list(Config) ->
-
+
OldFlag = process_flag(trap_exit, true),
- ?line {ok, Pid0} = start_link(spec_init_local, [{ok, my_server}, []]),
- ?line ok = gen_server:call(Pid0, started_p),
- ?line ok = gen_server:call(Pid0, stop),
+ {ok, Pid0} = start_link(spec_init_local, [{ok, my_server}, []]),
+ ok = gen_server:call(Pid0, started_p),
+ ok = gen_server:call(Pid0, stop),
receive
{'EXIT', Pid0, stopped} ->
ok
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid01} = start_link(spec_init_local, [{not_ok, my_server}, []]),
+
+ {ok, Pid01} = start_link(spec_init_local, [{not_ok, my_server}, []]),
receive
{'EXIT', Pid01, process_not_registered} ->
ok
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid1} = start_link(spec_init_global, [{ok, my_server}, []]),
- ?line ok = gen_server:call(Pid1, started_p),
- ?line ok = gen_server:call(Pid1, stop),
+
+ {ok, Pid1} = start_link(spec_init_global, [{ok, my_server}, []]),
+ ok = gen_server:call(Pid1, started_p),
+ ok = gen_server:call(Pid1, stop),
receive
{'EXIT', Pid1, stopped} ->
ok
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid11} =
+
+ {ok, Pid11} =
start_link(spec_init_global, [{not_ok, my_server}, []]),
receive
@@ -883,31 +883,31 @@ spec_init(Config) when is_list(Config) ->
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid2} = start_link(spec_init_anonymous, [[]]),
- ?line ok = gen_server:call(Pid2, started_p),
- ?line ok = gen_server:call(Pid2, stop),
+
+ {ok, Pid2} = start_link(spec_init_anonymous, [[]]),
+ ok = gen_server:call(Pid2, started_p),
+ ok = gen_server:call(Pid2, stop),
receive
{'EXIT', Pid2, stopped} ->
ok
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid3} = start_link(spec_init_anonymous_default_timeout, [[]]),
- ?line ok = gen_server:call(Pid3, started_p),
- ?line ok = gen_server:call(Pid3, stop),
+
+ {ok, Pid3} = start_link(spec_init_anonymous_default_timeout, [[]]),
+ ok = gen_server:call(Pid3, started_p),
+ ok = gen_server:call(Pid3, stop),
receive
{'EXIT', Pid3, stopped} ->
ok
after 5000 ->
ct:fail(gen_server_did_not_die)
end,
-
- ?line {ok, Pid4} =
+
+ {ok, Pid4} =
start_link(spec_init_default_timeout, [{ok, my_server}, []]),
- ?line ok = gen_server:call(Pid4, started_p),
- ?line ok = gen_server:call(Pid4, stop),
+ ok = gen_server:call(Pid4, started_p),
+ ok = gen_server:call(Pid4, stop),
receive
{'EXIT', Pid4, stopped} ->
ok
@@ -922,8 +922,8 @@ spec_init(Config) when is_list(Config) ->
start_link(spec_init_global_default_timeout, [{ok, hurra}, []]),
timer:sleep(1000),
ok = gen_server:call(_PidHurra, started_p),
-
- ?line Pid5 =
+
+ Pid5 =
erlang:spawn_link(?MODULE, spec_init_not_proc_lib, [[]]),
receive
{'EXIT', Pid5, process_was_not_started_by_proc_lib} ->
@@ -941,16 +941,16 @@ spec_init_local_registered_parent(Config) when is_list(Config) ->
register(foobar, self()),
process_flag(trap_exit, true),
-
- ?line {ok, Pid} = start_link(spec_init_local, [{ok, my_server}, []]),
-
- ?line ok = gen_server:cast(my_server, {self(),stop}),
- ?line receive
- {Pid, stopped} ->
- ok
- after 1000 ->
- ct:fail(stop)
- end,
+
+ {ok, Pid} = start_link(spec_init_local, [{ok, my_server}, []]),
+
+ ok = gen_server:cast(my_server, {self(),stop}),
+ receive
+ {Pid, stopped} ->
+ ok
+ after 1000 ->
+ ct:fail(stop)
+ end,
unregister(foobar),
ok.
@@ -961,18 +961,18 @@ spec_init_global_registered_parent(Config) when is_list(Config) ->
global:register_name(foobar, self()),
process_flag(trap_exit, true),
-
- ?line {ok, Pid} = start_link(spec_init_global, [{ok, my_server}, []]),
-
- ?line ok = gen_server:call(Pid, started_p),
- ?line ok = gen_server:cast(Pid, {self(),stop}),
-
- ?line receive
- {Pid, stopped} ->
- ok
- after 1000 ->
- ct:fail(stop)
- end,
+
+ {ok, Pid} = start_link(spec_init_global, [{ok, my_server}, []]),
+
+ ok = gen_server:call(Pid, started_p),
+ ok = gen_server:cast(Pid, {self(),stop}),
+
+ receive
+ {Pid, stopped} ->
+ ok
+ after 1000 ->
+ ct:fail(stop)
+ end,
global:unregister_name(foobar),
ok.
@@ -982,13 +982,13 @@ spec_init_global_registered_parent(Config) when is_list(Config) ->
otp_5854(Config) when is_list(Config) ->
OldFlag = process_flag(trap_exit, true),
- ?line dummy_via:reset(),
+ dummy_via:reset(),
%% Make sure gen_server:enter_loop does not accept {local,Name}
%% when it's another process than the calling one which is
%% registered under that name
register(armitage, self()),
- ?line {ok, Pid1} =
+ {ok, Pid1} =
start_link(spec_init_local, [{not_ok, armitage}, []]),
receive
{'EXIT', Pid1, process_not_registered} ->
@@ -1002,7 +1002,7 @@ otp_5854(Config) when is_list(Config) ->
%% when it's another process than the calling one which is
%% registered under that name
global:register_name(armitage, self()),
- ?line {ok, Pid2} =
+ {ok, Pid2} =
start_link(spec_init_global, [{not_ok, armitage}, []]),
receive
{'EXIT', Pid2, process_not_registered_globally} ->
@@ -1014,7 +1014,7 @@ otp_5854(Config) when is_list(Config) ->
%% (same for {via, Mod, Name})
dummy_via:register_name(armitage, self()),
- ?line {ok, Pid3} =
+ {ok, Pid3} =
start_link(spec_init_via, [{not_ok, armitage}, []]),
receive
{'EXIT', Pid3, {process_not_registered_via, dummy_via}} ->
@@ -1046,71 +1046,71 @@ do_times(N, Fun) ->
do_otp_7669_local_ignore() ->
%% The name should never be registered after the return
%% from gen_server:start/3.
- ?line ignore = gen_server:start({local,?MODULE}, ?MODULE, ignore, []),
- ?line undefined = whereis(?MODULE),
- ?line ignore = gen_server:start({local,?MODULE}, ?MODULE, ignore, []),
- ?line undefined = whereis(?MODULE),
- ?line ignore = gen_server:start_link({local,?MODULE}, ?MODULE, ignore, []),
- ?line undefined = whereis(?MODULE).
+ ignore = gen_server:start({local,?MODULE}, ?MODULE, ignore, []),
+ undefined = whereis(?MODULE),
+ ignore = gen_server:start({local,?MODULE}, ?MODULE, ignore, []),
+ undefined = whereis(?MODULE),
+ ignore = gen_server:start_link({local,?MODULE}, ?MODULE, ignore, []),
+ undefined = whereis(?MODULE).
do_otp_7669_global_ignore() ->
- ?line ignore = gen_server:start({global,?MODULE}, ?MODULE, ignore, []),
- ?line undefined = global:whereis_name(?MODULE),
- ?line ignore = gen_server:start_link({global,?MODULE}, ?MODULE, ignore, []),
- ?line undefined = global:whereis_name(?MODULE).
+ ignore = gen_server:start({global,?MODULE}, ?MODULE, ignore, []),
+ undefined = global:whereis_name(?MODULE),
+ ignore = gen_server:start_link({global,?MODULE}, ?MODULE, ignore, []),
+ undefined = global:whereis_name(?MODULE).
do_otp_7669_stop() ->
%% The name should never be registered after the return
%% from gen_server:start/3.
- ?line {error,stopped} = gen_server:start({local,?MODULE},
- ?MODULE, stop, []),
- ?line undefined = whereis(?MODULE),
+ {error,stopped} = gen_server:start({local,?MODULE},
+ ?MODULE, stop, []),
+ undefined = whereis(?MODULE),
- ?line {error,stopped} = gen_server:start({global,?MODULE},
- ?MODULE, stop, []),
- ?line undefined = global:whereis_name(?MODULE).
+ {error,stopped} = gen_server:start({global,?MODULE},
+ ?MODULE, stop, []),
+ undefined = global:whereis_name(?MODULE).
%% Verify that sys:get_status correctly calls our format_status/2 fun.
call_format_status(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_server:start_link({local, call_format_status},
- ?MODULE, [], []),
- ?line Status1 = sys:get_status(call_format_status),
- ?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data1]} = Status1,
- ?line [format_status_called | _] = lists:reverse(Data1),
- ?line Status2 = sys:get_status(call_format_status, 5000),
- ?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data2]} = Status2,
- ?line [format_status_called | _] = lists:reverse(Data2),
+ {ok, Pid} = gen_server:start_link({local, call_format_status},
+ ?MODULE, [], []),
+ Status1 = sys:get_status(call_format_status),
+ {status, Pid, _Mod, [_PDict, running, _Parent, _, Data1]} = Status1,
+ [format_status_called | _] = lists:reverse(Data1),
+ Status2 = sys:get_status(call_format_status, 5000),
+ {status, Pid, _Mod, [_PDict, running, _Parent, _, Data2]} = Status2,
+ [format_status_called | _] = lists:reverse(Data2),
%% check that format_status can handle a name being a pid (atom is
%% already checked by the previous test)
- ?line {ok, Pid3} = gen_server:start_link(gen_server_SUITE, [], []),
- ?line Status3 = sys:get_status(Pid3),
- ?line {status, Pid3, _Mod, [_PDict3, running, _Parent, _, Data3]} = Status3,
- ?line [format_status_called | _] = lists:reverse(Data3),
+ {ok, Pid3} = gen_server:start_link(gen_server_SUITE, [], []),
+ Status3 = sys:get_status(Pid3),
+ {status, Pid3, _Mod, [_PDict3, running, _Parent, _, Data3]} = Status3,
+ [format_status_called | _] = lists:reverse(Data3),
%% check that format_status can handle a name being a term other than a
%% pid or atom
GlobalName1 = {global, "CallFormatStatus"},
- ?line {ok, Pid4} = gen_server:start_link(GlobalName1,
- gen_server_SUITE, [], []),
- ?line Status4 = sys:get_status(Pid4),
- ?line {status, Pid4, _Mod, [_PDict4, running, _Parent, _, Data4]} = Status4,
- ?line [format_status_called | _] = lists:reverse(Data4),
+ {ok, Pid4} = gen_server:start_link(GlobalName1,
+ gen_server_SUITE, [], []),
+ Status4 = sys:get_status(Pid4),
+ {status, Pid4, _Mod, [_PDict4, running, _Parent, _, Data4]} = Status4,
+ [format_status_called | _] = lists:reverse(Data4),
GlobalName2 = {global, {name, "term"}},
- ?line {ok, Pid5} = gen_server:start_link(GlobalName2,
- gen_server_SUITE, [], []),
- ?line Status5 = sys:get_status(GlobalName2),
- ?line {status, Pid5, _Mod, [_PDict5, running, _Parent, _, Data5]} = Status5,
- ?line [format_status_called | _] = lists:reverse(Data5),
+ {ok, Pid5} = gen_server:start_link(GlobalName2,
+ gen_server_SUITE, [], []),
+ Status5 = sys:get_status(GlobalName2),
+ {status, Pid5, _Mod, [_PDict5, running, _Parent, _, Data5]} = Status5,
+ [format_status_called | _] = lists:reverse(Data5),
ok.
%% Verify that error termination correctly calls our format_status/2 fun.
error_format_status(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
State = "called format_status",
- ?line {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []),
- ?line {'EXIT',{crashed,_}} = (catch gen_server:call(Pid, crash)),
+ {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []),
+ {'EXIT',{crashed,_}} = (catch gen_server:call(Pid, crash)),
receive
{'EXIT', Pid, crashed} ->
ok
@@ -1123,7 +1123,7 @@ error_format_status(Config) when is_list(Config) ->
|_Stacktrace]}]}} ->
ok;
Other ->
- ?line io:format("Unexpected: ~p", [Other]),
+ io:format("Unexpected: ~p", [Other]),
ct:fail(failed)
end,
process_flag(trap_exit, OldFl),
@@ -1143,7 +1143,7 @@ terminate_crash_format(Config) when is_list(Config) ->
"** Generic server"++_,
[Pid,stop, {formatted, State},
{{crash, terminate},[{?MODULE,terminate,2,_}
- |_Stacktrace]}]}} ->
+ |_Stacktrace]}]}} ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
@@ -1159,7 +1159,7 @@ terminate_crash_format(Config) when is_list(Config) ->
get_state(Config) when is_list(Config) ->
State = self(),
{ok, _Pid} = gen_server:start_link({local, get_state},
- ?MODULE, {state,State}, []),
+ ?MODULE, {state,State}, []),
State = sys:get_state(get_state),
State = sys:get_state(get_state, 5000),
{ok, Pid} = gen_server:start_link(?MODULE, {state,State}, []),
@@ -1174,7 +1174,7 @@ get_state(Config) when is_list(Config) ->
replace_state(Config) when is_list(Config) ->
State = self(),
{ok, _Pid} = gen_server:start_link({local, replace_state},
- ?MODULE, {state,State}, []),
+ ?MODULE, {state,State}, []),
State = sys:get_state(replace_state),
NState1 = "replaced",
Replace1 = fun(_) -> NState1 end,
@@ -1213,16 +1213,16 @@ call_with_huge_message_queue(Config) when is_list(Config) ->
"is not implemented"};
false ->
do_call_with_huge_message_queue()
- end.
+ end.
do_call_with_huge_message_queue() ->
- ?line Pid = spawn_link(fun echo_loop/0),
+ Pid = spawn_link(fun echo_loop/0),
- ?line {Time,ok} = tc(fun() -> calls(10000, Pid) end),
+ {Time,ok} = tc(fun() -> calls(10000, Pid) end),
- ?line [self() ! {msg,N} || N <- lists:seq(1, 500000)],
+ [self() ! {msg,N} || N <- lists:seq(1, 500000)],
erlang:garbage_collect(),
- ?line {NewTime,ok} = tc(fun() -> calls(10000, Pid) end),
+ {NewTime,ok} = tc(fun() -> calls(10000, Pid) end),
io:format("Time for empty message queue: ~p", [Time]),
io:format("Time for huge message queue: ~p", [NewTime]),
@@ -1398,11 +1398,11 @@ handle_info(timeout, {reply_to, From}) ->
gen_server:reply(From, delayed),
{noreply, []};
handle_info(timeout, hibernate_me) -> % Arrive here from
- % handle_info(hibernate_later,...)
+ % handle_info(hibernate_later,...)
{noreply, [], hibernate};
handle_info(hibernate_now, _State) -> % Arrive here from
- % handle_cast({_,hibernate_later},...)
- % and by direct ! from testcase
+ % handle_cast({_,hibernate_later},...)
+ % and by direct ! from testcase
{noreply, [], hibernate};
handle_info(hibernate_later, _State) ->
{noreply, hibernate_me, 1000};
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 66a0818bb6..17c2488b5b 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -92,101 +92,99 @@ end_per_group(_GroupName, Config) ->
error_1(Config) when is_list(Config) ->
%% We don't do erroneous output on stdout - the test server
%% seems to catch that somehow.
- ?line PrivDir = ?privdir(Config),
- ?line File = filename:join(PrivDir, "slask"),
- ?line {ok, F1} = file:open(File, [write]),
- ?line {'EXIT', _} = (catch io:format(muttru, "hej", [])),
- ?line {'EXIT', _} = (catch io:format(F1, pelle, "hej")),
- ?line {'EXIT', _} = (catch io:format(F1, 1, "hej")),
- ?line {'EXIT', _} = (catch io:format(F1, "~p~", [kaka])),
- ?line {'EXIT', _} = (catch io:format(F1, "~m~n", [kaka])),
+ PrivDir = ?privdir(Config),
+ File = filename:join(PrivDir, "slask"),
+ {ok, F1} = file:open(File, [write]),
+ {'EXIT', _} = (catch io:format(muttru, "hej", [])),
+ {'EXIT', _} = (catch io:format(F1, pelle, "hej")),
+ {'EXIT', _} = (catch io:format(F1, 1, "hej")),
+ {'EXIT', _} = (catch io:format(F1, "~p~", [kaka])),
+ {'EXIT', _} = (catch io:format(F1, "~m~n", [kaka])),
%% This causes the file process to die, and it is linked to us,
%% so we can't catch the error this easily.
-%% ?line {'EXIT', _} = (catch io:put_chars(F1, 666)),
+ %% {'EXIT', _} = (catch io:put_chars(F1, 666)),
- ?line file:close(F1),
- ?line {'EXIT', _} = (catch io:format(F1, "~p", ["hej"])),
+ file:close(F1),
+ {'EXIT', _} = (catch io:format(F1, "~p", ["hej"])),
ok.
float_g(Config) when is_list(Config) ->
- ?line ["5.00000e-2",
- "0.500000",
- "5.00000",
- "50.0000",
- "500.000",
- "5000.00",
- "5.00000e+4",
- "5.00000e+5"] = float_g_1("~g", 5.0, -2, 5),
-
- ?line ["-5.0000e-2",
- "-0.50000",
- "-5.0000",
- "-50.000",
- "-500.00",
- "-5000.0",
- "-5.0000e+4",
- "-5.0000e+5"] = float_g_1("~.5g", -5.0, -2, 5),
-
- ?line ["5.000e-2",
- "0.5000",
- "5.000",
- "50.00",
- "500.0",
- "5.000e+3",
- "5.000e+4",
- "5.000e+5"] = float_g_1("~.4g", 5.0, -2, 5),
-
- ?line ["-5.00e-2",
- "-0.500",
- "-5.00",
- "-50.0",
- "-5.00e+2",
- "-5.00e+3",
- "-5.00e+4",
- "-5.00e+5"] = float_g_1("~.3g", -5.0, -2, 5),
-
- ?line ["5.0e-2",
- "0.50",
- "5.0",
- "5.0e+1",
- "5.0e+2",
- "5.0e+3",
- "5.0e+4",
- "5.0e+5"] = float_g_1("~.2g", 5.0, -2, 5),
-
- ?line
- case catch fmt("~.1g", [0.5]) of
- "0.5" ->
- ?line
- ["5.0e-2",
- "0.5",
- "5.0e+0",
- "5.0e+1",
- "5.0e+2",
- "5.0e+3",
- "5.0e+4",
- "5.0e+5"] = float_g_1("~.1g", 5.0, -2, 5);
- {'EXIT',_} -> ok
- end,
-
- ?line ["4.99999e-2",
- "0.499999",
- "4.99999",
- "49.9999",
- "499.999",
- "4999.99",
- "4.99999e+4",
- "4.99999e+5"] = float_g_1("~g", 4.9999949999, -2, 5),
-
- ?line ["-5.00000e-2",
- "-0.500000",
- "-5.00000",
- "-50.0000",
- "-500.000",
- "-5000.00",
- "-5.00000e+4",
- "-5.00000e+5"] = float_g_1("~g", -4.9999950001, -2, 5),
+ ["5.00000e-2",
+ "0.500000",
+ "5.00000",
+ "50.0000",
+ "500.000",
+ "5000.00",
+ "5.00000e+4",
+ "5.00000e+5"] = float_g_1("~g", 5.0, -2, 5),
+
+ ["-5.0000e-2",
+ "-0.50000",
+ "-5.0000",
+ "-50.000",
+ "-500.00",
+ "-5000.0",
+ "-5.0000e+4",
+ "-5.0000e+5"] = float_g_1("~.5g", -5.0, -2, 5),
+
+ ["5.000e-2",
+ "0.5000",
+ "5.000",
+ "50.00",
+ "500.0",
+ "5.000e+3",
+ "5.000e+4",
+ "5.000e+5"] = float_g_1("~.4g", 5.0, -2, 5),
+
+ ["-5.00e-2",
+ "-0.500",
+ "-5.00",
+ "-50.0",
+ "-5.00e+2",
+ "-5.00e+3",
+ "-5.00e+4",
+ "-5.00e+5"] = float_g_1("~.3g", -5.0, -2, 5),
+
+ ["5.0e-2",
+ "0.50",
+ "5.0",
+ "5.0e+1",
+ "5.0e+2",
+ "5.0e+3",
+ "5.0e+4",
+ "5.0e+5"] = float_g_1("~.2g", 5.0, -2, 5),
+
+ case catch fmt("~.1g", [0.5]) of
+ "0.5" ->
+ ["5.0e-2",
+ "0.5",
+ "5.0e+0",
+ "5.0e+1",
+ "5.0e+2",
+ "5.0e+3",
+ "5.0e+4",
+ "5.0e+5"] = float_g_1("~.1g", 5.0, -2, 5);
+ {'EXIT',_} -> ok
+ end,
+
+ ["4.99999e-2",
+ "0.499999",
+ "4.99999",
+ "49.9999",
+ "499.999",
+ "4999.99",
+ "4.99999e+4",
+ "4.99999e+5"] = float_g_1("~g", 4.9999949999, -2, 5),
+
+ ["-5.00000e-2",
+ "-0.500000",
+ "-5.00000",
+ "-50.0000",
+ "-500.000",
+ "-5000.00",
+ "-5.00000e+4",
+ "-5.00000e+5"] = float_g_1("~g", -4.9999950001, -2, 5),
ok.
float_g_1(Fmt, V, Min, Max) ->
@@ -194,28 +192,28 @@ float_g_1(Fmt, V, Min, Max) ->
%% OTP-5403. ~s formats I/O lists and a single binary.
otp_5403(Config) when is_list(Config) ->
- ?line "atom" = fmt("~s", [atom]),
- ?line "binary" = fmt("~s", [<<"binary">>]),
- ?line "atail" = fmt("~s", [["a" | <<"tail">>]]),
- ?line "deepcharlist" = fmt("~s", [["deep",["char",["list"]]]]),
- ?line "somebinaries" = fmt("~s", [[<<"some">>,[<<"binaries">>]]]),
+ "atom" = fmt("~s", [atom]),
+ "binary" = fmt("~s", [<<"binary">>]),
+ "atail" = fmt("~s", [["a" | <<"tail">>]]),
+ "deepcharlist" = fmt("~s", [["deep",["char",["list"]]]]),
+ "somebinaries" = fmt("~s", [[<<"some">>,[<<"binaries">>]]]),
ok.
%% OTP-5813. read/3 is new.
otp_5813(Config) when is_list(Config) ->
- ?line PrivDir = ?privdir(Config),
- ?line File = filename:join(PrivDir, "test"),
+ PrivDir = ?privdir(Config),
+ File = filename:join(PrivDir, "test"),
- ?line ok = file:write_file(File, <<"a. ">>),
- ?line {ok, Fd} = file:open(File, [read]),
- ?line {ok, a, 1} = io:read(Fd, '', 1),
- ?line {eof,1} = io:read(Fd, '', 1),
+ ok = file:write_file(File, <<"a. ">>),
+ {ok, Fd} = file:open(File, [read]),
+ {ok, a, 1} = io:read(Fd, '', 1),
+ {eof,1} = io:read(Fd, '', 1),
ok = file:close(Fd),
- ?line ok = file:write_file(File, <<"[}.">>),
- ?line {ok, Fd2} = file:open(File, [read]),
- ?line {error,{1,_,_},1} = io:read(Fd2, '', 1),
- ?line ok = file:close(Fd),
+ ok = file:write_file(File, <<"[}.">>),
+ {ok, Fd2} = file:open(File, [read]),
+ {error,{1,_,_},1} = io:read(Fd2, '', 1),
+ ok = file:close(Fd),
file:delete(File),
ok.
@@ -224,455 +222,454 @@ otp_5813(Config) when is_list(Config) ->
otp_6230(Config) when is_list(Config) ->
%% The problem is actually huge binaries, but the small tests here
%% just run through most of the modified code.
- ?line "<<>>" = fmt("~P", [<<"">>,-1]),
- ?line "<<\"hej\">>" = fmt("~P", [<<"hej">>,-1]),
- ?line "{hej,...}" = fmt("~P", [{hej,<<"hej">>},2]),
- ?line "{hej,<<...>>}" = fmt("~P", [{hej,<<"hej">>},3]),
- ?line "{hej,<<\"hejs\"...>>}" = fmt("~P", [{hej,<<"hejsan">>},4]),
- ?line "{hej,<<\"hej\">>}" = fmt("~P", [{hej,<<"hej">>},6]),
- ?line "<<...>>" = fmt("~P", [<<"hej">>,1]),
- ?line "<<\"hejs\"...>>" = fmt("~P", [<<"hejsan">>,2]),
- ?line "<<\"hej\">>" = fmt("~P", [<<"hej">>,4]),
- ?line "{hej,<<127,...>>}" =
+ "<<>>" = fmt("~P", [<<"">>,-1]),
+ "<<\"hej\">>" = fmt("~P", [<<"hej">>,-1]),
+ "{hej,...}" = fmt("~P", [{hej,<<"hej">>},2]),
+ "{hej,<<...>>}" = fmt("~P", [{hej,<<"hej">>},3]),
+ "{hej,<<\"hejs\"...>>}" = fmt("~P", [{hej,<<"hejsan">>},4]),
+ "{hej,<<\"hej\">>}" = fmt("~P", [{hej,<<"hej">>},6]),
+ "<<...>>" = fmt("~P", [<<"hej">>,1]),
+ "<<\"hejs\"...>>" = fmt("~P", [<<"hejsan">>,2]),
+ "<<\"hej\">>" = fmt("~P", [<<"hej">>,4]),
+ "{hej,<<127,...>>}" =
fmt("~P", [{hej,<<127:8,<<"hej">>/binary>>},4]),
- ?line "{hej,<<127,104,101,...>>}" =
+ "{hej,<<127,104,101,...>>}" =
fmt("~P", [{hej,<<127:8,<<"hej">>/binary>>},6]),
B = list_to_binary(lists:duplicate(30000, $a)),
- ?line "<<\"aaaa"++_ = fmt("~P", [B, 20000]),
+ "<<\"aaaa"++_ = fmt("~P", [B, 20000]),
ok.
%% OTP-6282. ~p truncates strings (like binaries) depending on depth.
otp_6282(Config) when is_list(Config) ->
- ?line "[]" = p("", 1, 20, 1),
- ?line "[]" = p("", 1, 20, -1),
- ?line "[...]" = p("a", 1, 20, 1),
- ?line "\"a\"" = p("a", 1, 20, 2),
- ?line "\"aa\"" = p("aa", 1, 20, 2),
- ?line "\"aaa\"" = p("aaa", 1, 20, 2),
- ?line "\"aaaa\"" = p("aaaa", 1, 20, 2),
- ?line "\"a\"" = p("a", 1, 20, -1),
- ?line "[97,97,1000]" = p([$a,$a,1000], 1, 20, 4),
+ "[]" = p("", 1, 20, 1),
+ "[]" = p("", 1, 20, -1),
+ "[...]" = p("a", 1, 20, 1),
+ "\"a\"" = p("a", 1, 20, 2),
+ "\"aa\"" = p("aa", 1, 20, 2),
+ "\"aaa\"" = p("aaa", 1, 20, 2),
+ "\"aaaa\"" = p("aaaa", 1, 20, 2),
+ "\"a\"" = p("a", 1, 20, -1),
+ "[97,97,1000]" = p([$a,$a,1000], 1, 20, 4),
S1 = lists:duplicate(200,$a),
- ?line "[...]" = p(S1, 1, 20, 1),
- ?line true = "\"" ++ S1 ++ "\"" =:= p(S1, 1, 205, -1),
- ?line "[97,97,1000|...]" = p([$a,$a,1000,1000], 1, 20, 4),
-
- ?line "[[]]" = p([""], 1, 20, 2),
- ?line "[[]]" = p([""], 1, 20, -1),
- ?line "[[...]]" = p(["a"], 1, 20, 2),
- ?line "[\"a\"]" = p(["a"], 1, 20, 3),
- ?line "[\"aa\"]" = p(["aa"], 1, 20, 3),
- ?line "[\"aaa\"]" = p(["aaa"], 1, 20, 3),
- ?line "[\"a\"]" = p(["a"], 1, 20, -1),
- ?line "[[97,97,1000]]" = p([[$a,$a,1000]], 1, 20, 5),
- ?line "[[...]]" = p([S1], 1, 20, 2),
- ?line true = "[\"" ++ S1 ++ "\"]" =:= p([S1], 1, 210, -1),
- ?line "[[97,97,1000|...]]" = p([[$a,$a,1000,1000]], 1, 20, 5),
-
- ?line "[\"aaaaa\"]" = p(["aaaaa"], 1, 10, 6),
+ "[...]" = p(S1, 1, 20, 1),
+ true = "\"" ++ S1 ++ "\"" =:= p(S1, 1, 205, -1),
+ "[97,97,1000|...]" = p([$a,$a,1000,1000], 1, 20, 4),
+
+ "[[]]" = p([""], 1, 20, 2),
+ "[[]]" = p([""], 1, 20, -1),
+ "[[...]]" = p(["a"], 1, 20, 2),
+ "[\"a\"]" = p(["a"], 1, 20, 3),
+ "[\"aa\"]" = p(["aa"], 1, 20, 3),
+ "[\"aaa\"]" = p(["aaa"], 1, 20, 3),
+ "[\"a\"]" = p(["a"], 1, 20, -1),
+ "[[97,97,1000]]" = p([[$a,$a,1000]], 1, 20, 5),
+ "[[...]]" = p([S1], 1, 20, 2),
+ true = "[\"" ++ S1 ++ "\"]" =:= p([S1], 1, 210, -1),
+ "[[97,97,1000|...]]" = p([[$a,$a,1000,1000]], 1, 20, 5),
+
+ "[\"aaaaa\"]" = p(["aaaaa"], 1, 10, 6),
ok.
%% OTP-6354. io_lib_pretty rewritten.
otp_6354(Config) when is_list(Config) ->
%% A few tuples:
- ?line "{}" = p({}, 1, 20, -1),
- ?line "..." = p({}, 1, 20, 0),
- ?line "{}" = p({}, 1, 20, 1),
- ?line "{}" = p({}, 1, 20, 2),
- ?line "{a}" = p({a}, 1, 20, -1),
- ?line "..." = p({a}, 1, 20, 0),
- ?line "{...}" = p({a}, 1, 20, 1),
- ?line "{a}" = p({a}, 1, 20, 2),
- ?line "{a,b}" = p({a,b}, 1, 20, -1),
- ?line "..." = p({a,b}, 1, 20, 0),
- ?line "{...}" = p({a,b}, 1, 20, 1),
- ?line "{a,...}" = p({a,b}, 1, 20, 2),
- ?line "{a,b}" = p({a,b}, 1, 20, 3),
- ?line "{}" = p({}, 1, 1, -1),
- ?line "..." = p({}, 1, 1, 0),
- ?line "{}" = p({}, 1, 1, 1),
- ?line "{}" = p({}, 1, 1, 2),
- ?line "{a}" = p({a}, 1, 1, -1),
- ?line "..." = p({a}, 1, 1, 0),
- ?line "{...}" = p({a}, 1, 1, 1),
- ?line "{a}" = p({a}, 1, 1, 2),
- ?line "{a,\n b}" = p({a,b}, 1, 1, -1),
- ?line "{1,\n b}" = p({1,b}, 1, 1, -1),
- ?line "..." = p({a,b}, 1, 1, 0),
- ?line "{...}" = p({a,b}, 1, 1, 1),
- ?line "{a,...}" = p({a,b}, 1, 1, 2),
- ?line "{a,\n b}" = p({a,b}, 1, 1, 3),
- ?line "{{}}" = p({{}}, 1, 1, 2),
- ?line "{[]}" = p({[]}, 1, 1, 2),
- ?line bt(<<"{1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}">>,
- p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, -1)),
- ?line bt(<<"{abcd,ddddd,\n ddddd}">>,
- p({abcd,ddddd,ddddd}, 1,16, -1)),
- ?line bt(<<"{1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]}">>,
- p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
- ?line "{1,{1,{2,3}}}" = p({1,{1,{2,3}}}, 1, 80, 100),
-
- ?line bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,\n"
- " sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}">>,
- p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
- sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
-
- ?line bt(<<"{wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {lkjsldfj,\n"
- " {klsdjfjklds,\n"
- " {klajsljls,\n"
- " #aaaaaaaaaaaaaaaaaaaaa"
- "aaaaaaaaaaaaaaaaaaaaaaaaaaaaa{}}}}}}}}}">>,
- p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,{lkjsldfj,
- {klsdjfjklds,{klajsljls,
- {aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa}}}}}}}}},
- -1)),
- ?line "{{...},...}" = p({{a,b},{a,b,c},{d,e,f}},1,8,2),
+ "{}" = p({}, 1, 20, -1),
+ "..." = p({}, 1, 20, 0),
+ "{}" = p({}, 1, 20, 1),
+ "{}" = p({}, 1, 20, 2),
+ "{a}" = p({a}, 1, 20, -1),
+ "..." = p({a}, 1, 20, 0),
+ "{...}" = p({a}, 1, 20, 1),
+ "{a}" = p({a}, 1, 20, 2),
+ "{a,b}" = p({a,b}, 1, 20, -1),
+ "..." = p({a,b}, 1, 20, 0),
+ "{...}" = p({a,b}, 1, 20, 1),
+ "{a,...}" = p({a,b}, 1, 20, 2),
+ "{a,b}" = p({a,b}, 1, 20, 3),
+ "{}" = p({}, 1, 1, -1),
+ "..." = p({}, 1, 1, 0),
+ "{}" = p({}, 1, 1, 1),
+ "{}" = p({}, 1, 1, 2),
+ "{a}" = p({a}, 1, 1, -1),
+ "..." = p({a}, 1, 1, 0),
+ "{...}" = p({a}, 1, 1, 1),
+ "{a}" = p({a}, 1, 1, 2),
+ "{a,\n b}" = p({a,b}, 1, 1, -1),
+ "{1,\n b}" = p({1,b}, 1, 1, -1),
+ "..." = p({a,b}, 1, 1, 0),
+ "{...}" = p({a,b}, 1, 1, 1),
+ "{a,...}" = p({a,b}, 1, 1, 2),
+ "{a,\n b}" = p({a,b}, 1, 1, 3),
+ "{{}}" = p({{}}, 1, 1, 2),
+ "{[]}" = p({[]}, 1, 1, 2),
+ bt(<<"{1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}">>,
+ p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, -1)),
+ bt(<<"{abcd,ddddd,\n ddddd}">>,
+ p({abcd,ddddd,ddddd}, 1,16, -1)),
+ bt(<<"{1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]}">>,
+ p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
+ "{1,{1,{2,3}}}" = p({1,{1,{2,3}}}, 1, 80, 100),
+
+ bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,\n"
+ " sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}">>,
+ p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
+ sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
+
+ bt(<<"{wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {lkjsldfj,\n"
+ " {klsdjfjklds,\n"
+ " {klajsljls,\n"
+ " #aaaaaaaaaaaaaaaaaaaaa"
+ "aaaaaaaaaaaaaaaaaaaaaaaaaaaaa{}}}}}}}}}">>,
+ p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,{lkjsldfj,
+ {klsdjfjklds,{klajsljls,
+ {aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa}}}}}}}}},
+ -1)),
+ "{{...},...}" = p({{a,b},{a,b,c},{d,e,f}},1,8,2),
%% Closing brackets and parentheses count:
- ?line "{{a,b,c},\n {{1,2,\n 3}}}" = p({{a,b,c},{{1,2,3}}},1,11,-1),
- %% With line breaks:
- ?line "{{a,b,c},\n [1,2,\n 3]}" = p({{a,b,c},[1,2,3]},1,10,-1),
+ "{{a,b,c},\n {{1,2,\n 3}}}" = p({{a,b,c},{{1,2,3}}},1,11,-1),
%% With line breaks:
- ?line "[{{a,b,c},\n {1,2,\n 3}}]" = p([{{a,b,c},{1,2,3}}],1,12,-1),
+ "{{a,b,c},\n [1,2,\n 3]}" = p({{a,b,c},[1,2,3]},1,10,-1),
%% With line breaks:
+ "[{{a,b,c},\n {1,2,\n 3}}]" = p([{{a,b,c},{1,2,3}}],1,12,-1),
%% A few lists:
- ?line "[]" = p([], 1, 20, -1),
- ?line "..." = p([], 1, 20, 0),
- ?line "[]" = p([], 1, 20, 1),
- ?line "[]" = p([], 1, 20, 2),
- ?line "[a]" = p([a], 1, 20, -1),
- ?line "..." = p([a], 1, 20, 0),
- ?line "[...]" = p([a], 1, 20, 1),
- ?line "[a]" = p([a], 1, 20, 2),
- ?line "[a,b]" = p([a,b], 1, 20, -1),
- ?line "..." = p([a,b], 1, 20, 0),
- ?line "[...]" = p([a,b], 1, 20, 1),
- ?line "[a|...]" = p([a,b], 1, 20, 2),
- ?line "[a,b]" = p([a,b], 1, 20, 3),
- ?line "[a|b]" = p([a|b], 1, 20, -1),
- ?line "..." = p([a|b], 1, 20, 0),
- ?line "[...]" = p([a|b], 1, 20, 1),
- ?line "[a|...]" = p([a|b], 1, 20, 2),
- ?line "[a|b]" = p([a|b], 1, 20, 3),
- ?line "[]" = p([], 1, 1, -1),
- ?line "..." = p([], 1, 1, 0),
- ?line "[]" = p([], 1, 1, 1),
- ?line "[]" = p([], 1, 1, 2),
- ?line "[a]" = p([a], 1, 1, -1),
- ?line "..." = p([a], 1, 1, 0),
- ?line "[...]" = p([a], 1, 1, 1),
- ?line "[a]" = p([a], 1, 1, 2),
- ?line "[a,\n b]" = p([a,b], 1, 1, -1),
- ?line "..." = p([a,b], 1, 1, 0),
- ?line "[...]" = p([a,b], 1, 1, 1),
- ?line "[a|...]" = p([a,b], 1, 1, 2),
- ?line "[a,\n b]" = p([a,b], 1, 1, 3),
- ?line "[a|\n b]" = p([a|b], 1, 1, -1),
- ?line "..." = p([a|b], 1, 1, 0),
- ?line "[...]" = p([a|b], 1, 1, 1),
- ?line "[a|...]" = p([a|b], 1, 1, 2),
- ?line "[a|\n b]" = p([a|b], 1, 1, 3),
- ?line "[{}]" = p([{}], 1, 1, 2),
- ?line "[[]]" = p([[]], 1, 1, 2),
- ?line bt(<<"[1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]]">>,
- p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], -1)),
- ?line bt(<<"[1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]]">>,
- p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
+ "[]" = p([], 1, 20, -1),
+ "..." = p([], 1, 20, 0),
+ "[]" = p([], 1, 20, 1),
+ "[]" = p([], 1, 20, 2),
+ "[a]" = p([a], 1, 20, -1),
+ "..." = p([a], 1, 20, 0),
+ "[...]" = p([a], 1, 20, 1),
+ "[a]" = p([a], 1, 20, 2),
+ "[a,b]" = p([a,b], 1, 20, -1),
+ "..." = p([a,b], 1, 20, 0),
+ "[...]" = p([a,b], 1, 20, 1),
+ "[a|...]" = p([a,b], 1, 20, 2),
+ "[a,b]" = p([a,b], 1, 20, 3),
+ "[a|b]" = p([a|b], 1, 20, -1),
+ "..." = p([a|b], 1, 20, 0),
+ "[...]" = p([a|b], 1, 20, 1),
+ "[a|...]" = p([a|b], 1, 20, 2),
+ "[a|b]" = p([a|b], 1, 20, 3),
+ "[]" = p([], 1, 1, -1),
+ "..." = p([], 1, 1, 0),
+ "[]" = p([], 1, 1, 1),
+ "[]" = p([], 1, 1, 2),
+ "[a]" = p([a], 1, 1, -1),
+ "..." = p([a], 1, 1, 0),
+ "[...]" = p([a], 1, 1, 1),
+ "[a]" = p([a], 1, 1, 2),
+ "[a,\n b]" = p([a,b], 1, 1, -1),
+ "..." = p([a,b], 1, 1, 0),
+ "[...]" = p([a,b], 1, 1, 1),
+ "[a|...]" = p([a,b], 1, 1, 2),
+ "[a,\n b]" = p([a,b], 1, 1, 3),
+ "[a|\n b]" = p([a|b], 1, 1, -1),
+ "..." = p([a|b], 1, 1, 0),
+ "[...]" = p([a|b], 1, 1, 1),
+ "[a|...]" = p([a|b], 1, 1, 2),
+ "[a|\n b]" = p([a|b], 1, 1, 3),
+ "[{}]" = p([{}], 1, 1, 2),
+ "[[]]" = p([[]], 1, 1, 2),
+ bt(<<"[1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]]">>,
+ p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], -1)),
+ bt(<<"[1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]]">>,
+ p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
%% Element #8 is not printable:
- ?line "[49," ++ _ = p("1234567"++[3,4,5,6,7], 1, 100, 9),
- %% ?line "\"1234567\"..." = p("1234567"++[3,4,5,6,7], 1, 100, 8),
+ "[49," ++ _ = p("1234567"++[3,4,5,6,7], 1, 100, 9),
+ %% "\"1234567\"..." = p("1234567"++[3,4,5,6,7], 1, 100, 8),
%% A few records:
%% -record(a, {}).
%% -record(a, {}).
- ?line "..." = p({a}, 0),
- ?line "{...}" = p({a}, 1),
- ?line "#a{}" = p({a}, 2),
- ?line "#a{}" = p({a}, -1),
+ "..." = p({a}, 0),
+ "{...}" = p({a}, 1),
+ "#a{}" = p({a}, 2),
+ "#a{}" = p({a}, -1),
%% -record(b, {f}).
- ?line "{...}" = p({b}, 1),
- ?line "..." = p({b,c}, 0),
- ?line "{...}" = p({b,c}, 1),
- ?line "#b{...}" = p({b,c}, 2),
- ?line "#b{f = c}" = p({b,c}, 3),
- ?line "#b{f = c}" = p({b,c}, -1),
- ?line "..." = p({b,{c,d}}, 0),
- ?line "{...}" = p({b,{c,d}}, 1),
- ?line "#b{...}" = p({b,{c,d}}, 2),
- ?line "#b{f = {...}}" = p({b,{c,d}}, 3),
- ?line "#b{f = {c,...}}" = p({b,{c,d}}, 4),
- ?line "#b{f = {c,d}}" = p({b,{c,d}}, 5),
- ?line "#b{f = {...}}" = p({b,{b,c}}, 3),
- ?line "#b{f = #b{...}}" = p({b,{b,c}}, 4),
- ?line "#b{f = #b{f = c}}" = p({b,{b,c}}, 5),
+ "{...}" = p({b}, 1),
+ "..." = p({b,c}, 0),
+ "{...}" = p({b,c}, 1),
+ "#b{...}" = p({b,c}, 2),
+ "#b{f = c}" = p({b,c}, 3),
+ "#b{f = c}" = p({b,c}, -1),
+ "..." = p({b,{c,d}}, 0),
+ "{...}" = p({b,{c,d}}, 1),
+ "#b{...}" = p({b,{c,d}}, 2),
+ "#b{f = {...}}" = p({b,{c,d}}, 3),
+ "#b{f = {c,...}}" = p({b,{c,d}}, 4),
+ "#b{f = {c,d}}" = p({b,{c,d}}, 5),
+ "#b{f = {...}}" = p({b,{b,c}}, 3),
+ "#b{f = #b{...}}" = p({b,{b,c}}, 4),
+ "#b{f = #b{f = c}}" = p({b,{b,c}}, 5),
%% -record(c, {f1, f2}).
- ?line "#c{f1 = d,f2 = e}" = p({c,d,e}, -1),
- ?line "..." = p({c,d,e}, 0),
- ?line "{...}" = p({c,d,e}, 1),
- ?line "#c{...}" = p({c,d,e}, 2),
- ?line "#c{f1 = d,...}" = p({c,d,e}, 3),
- ?line "#c{f1 = d,f2 = e}" = p({c,d,e}, 4),
+ "#c{f1 = d,f2 = e}" = p({c,d,e}, -1),
+ "..." = p({c,d,e}, 0),
+ "{...}" = p({c,d,e}, 1),
+ "#c{...}" = p({c,d,e}, 2),
+ "#c{f1 = d,...}" = p({c,d,e}, 3),
+ "#c{f1 = d,f2 = e}" = p({c,d,e}, 4),
%% -record(d, {a..., b..., c.., d...}).
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,2,3,4,5}, -1)),
- ?line "..." = p({d,1,2,3,4,5}, 0),
- ?line "{...}" = p({d,1,2,3,4,5}, 1),
- ?line "#d{...}" = p({d,1,2,3,4,5}, 2),
- ?line "#d{aaaaaaaaaaaaaaaaaaaa = 1,...}" = p({d,1,2,3,4,5}, 3),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,...}">>,
- p({d,1,2,3,4,5}, 4)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,...}">>,
- p({d,1,2,3,4,5}, 5)), % longer than 80 characters...
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,...}">>,
- p({d,1,2,3,4,5}, 6)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,2,3,4,5}, 7)),
- ?line bt(<<"#rrrrr{\n"
- " f1 = 1,\n"
- " f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
- " f3 = \n"
- " #rrrrr{\n"
- " f1 = h,f2 = i,\n"
- " f3 = \n"
- " #rrrrr{\n"
- " f1 = aa,\n"
- " f2 = \n"
- " #rrrrr{\n"
- " f1 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
- " f2 = 2,f3 = 3},\n"
- " f3 = bb}}}">>,
- p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
- {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
- 2,3},bb}}},
- -1)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
- " bbbbbbbbbbbbbbbbbbbb = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = a,bbbbbbbbbbbbbbbbbbbb = b,\n"
- " cccccccccccccccccccc = c,dddddddddddddddddddd = d,\n"
- " eeeeeeeeeeeeeeeeeeee = e},\n"
- " cccccccccccccccccccc = 3,\n"
- " dddddddddddddddddddd = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = h,bbbbbbbbbbbbbbbbbbbb = i,\n"
- " cccccccccccccccccccc = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = aa,"
- "bbbbbbbbbbbbbbbbbbbb = bb,\n"
- " cccccccccccccccccccc = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = 1,"
- "bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,"
- "dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5},\n"
- " dddddddddddddddddddd = dd,"
- "eeeeeeeeeeeeeeeeeeee = ee},\n"
- " dddddddddddddddddddd = k,"
- "eeeeeeeeeeeeeeeeeeee = l},\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,{d,a,b,c,d,e},3,{d,h,i,{d,aa,bb,{d,1,2,3,4,5},dd,ee},
- k,l},5}, -1)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,2,3,4,5}, -1)),
+ "..." = p({d,1,2,3,4,5}, 0),
+ "{...}" = p({d,1,2,3,4,5}, 1),
+ "#d{...}" = p({d,1,2,3,4,5}, 2),
+ "#d{aaaaaaaaaaaaaaaaaaaa = 1,...}" = p({d,1,2,3,4,5}, 3),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,...}">>,
+ p({d,1,2,3,4,5}, 4)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,...}">>,
+ p({d,1,2,3,4,5}, 5)), % longer than 80 characters...
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,...}">>,
+ p({d,1,2,3,4,5}, 6)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,2,3,4,5}, 7)),
+ bt(<<"#rrrrr{\n"
+ " f1 = 1,\n"
+ " f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
+ " f3 = \n"
+ " #rrrrr{\n"
+ " f1 = h,f2 = i,\n"
+ " f3 = \n"
+ " #rrrrr{\n"
+ " f1 = aa,\n"
+ " f2 = \n"
+ " #rrrrr{\n"
+ " f1 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
+ " f2 = 2,f3 = 3},\n"
+ " f3 = bb}}}">>,
+ p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
+ {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
+ 2,3},bb}}},
+ -1)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
+ " bbbbbbbbbbbbbbbbbbbb = \n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = a,bbbbbbbbbbbbbbbbbbbb = b,\n"
+ " cccccccccccccccccccc = c,dddddddddddddddddddd = d,\n"
+ " eeeeeeeeeeeeeeeeeeee = e},\n"
+ " cccccccccccccccccccc = 3,\n"
+ " dddddddddddddddddddd = \n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = h,bbbbbbbbbbbbbbbbbbbb = i,\n"
+ " cccccccccccccccccccc = \n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = aa,"
+ "bbbbbbbbbbbbbbbbbbbb = bb,\n"
+ " cccccccccccccccccccc = \n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = 1,"
+ "bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,"
+ "dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5},\n"
+ " dddddddddddddddddddd = dd,"
+ "eeeeeeeeeeeeeeeeeeee = ee},\n"
+ " dddddddddddddddddddd = k,"
+ "eeeeeeeeeeeeeeeeeeee = l},\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,{d,a,b,c,d,e},3,{d,h,i,{d,aa,bb,{d,1,2,3,4,5},dd,ee},
+ k,l},5}, -1)),
A = aaaaaaaaaaaaa,
%% Print the record with dots at the end of the line (Ll = 80).
- ?line "{aaaaaaa" ++ _ =
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{d,1,2,3,4,5}
- }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
- }}}}}}}}}}}}}}}}, 146),
- ?line "{aaaaaaa" ++ _ =
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{a}
- }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
- }}}}}}}}}}}}}}}}}}}, 152),
-
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {g,{h,{i,{j,{k,{l,{m,{n,{o,#"
- "d{...}}}}}}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,
- {g,{h,{i,{j,{k,{l,{m,{n,{o,{d,1,2,3,4,5}}}}}}}}}}}}}}}}, 32)),
- ?line bt(<<"{a,#b{f = {c,{d,{e,{f,...}}}}}}">>,
- p({a,{b,{c,{d,{e,{f,g}}}}}}, 12)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,#c{f1 = ddd,"
- "f2 = eee}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{c,ddd,eee}}}}}}}}}}, 100)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}">>,
- p({A,{A,{A,{A,{b}}}}}, 8)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}}">>,
- p({A,{A,{A,{A,{A,{b}}}}}}, 10)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,"
- "{aaaaaaaaaaaaa,#a{}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{a}}}}}}}}}}}, 23)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n",
- " #rrrrr{\n"
- " f1 = kljlkjlksfdgkljlsdkjf,"
- "f2 = kljkljsdaflkjlkjsdf,...}}}}">>,
- p({A,{A,{A,{rrrrr, kljlkjlksfdgkljlsdkjf,
- kljkljsdaflkjlkjsdf,
- asdfkldsjfklkljsdklfds}}}}, 10)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {g,{h,{i,{j,{k,{l,{m,{n,"
- "{o,#a{}}}}}}}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,
- {g,{h,{i,{j,{k,{l,{m,{n,{o,{a}}}}}}}}}}}}}}}}}, 100)),
- ?line bt(<<"#c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = #c{f1 = #c{f1 = #c{f1 = a,"
- "f2 = b},f2 = b},f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b}">>,
- p({c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,a,b},b},b},b},b},b},
- b},b},b},b},b},b}, -1)),
- ?line bt(<<"#rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
- "f3 = b}},b},\n"
- " f2 = {rrrrr,c,d},\n"
- " f3 = {rrrrr,1,2}},\n"
- " f2 = 1,f3 = 2},\n"
- " f2 = 3,f3 = 4},\n"
- " f2 = 5,f3 = 6}">>,
- p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
- {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
- 1,2},3,4},5,6}, -1)),
- ?line "{aaa,\n {aaa," ++ _ =
+ "{aaaaaaa" ++ _ =
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{d,1,2,3,4,5}
+ }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
+ }}}}}}}}}}}}}}}}, 146),
+ "{aaaaaaa" ++ _ =
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{a}
+ }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
+ }}}}}}}}}}}}}}}}}}}, 152),
+
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {g,{h,{i,{j,{k,{l,{m,{n,{o,#"
+ "d{...}}}}}}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,
+ {g,{h,{i,{j,{k,{l,{m,{n,{o,{d,1,2,3,4,5}}}}}}}}}}}}}}}}, 32)),
+ bt(<<"{a,#b{f = {c,{d,{e,{f,...}}}}}}">>,
+ p({a,{b,{c,{d,{e,{f,g}}}}}}, 12)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,#c{f1 = ddd,"
+ "f2 = eee}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{c,ddd,eee}}}}}}}}}}, 100)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}">>,
+ p({A,{A,{A,{A,{b}}}}}, 8)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}}">>,
+ p({A,{A,{A,{A,{A,{b}}}}}}, 10)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,"
+ "{aaaaaaaaaaaaa,#a{}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{a}}}}}}}}}}}, 23)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n",
+ " #rrrrr{\n"
+ " f1 = kljlkjlksfdgkljlsdkjf,"
+ "f2 = kljkljsdaflkjlkjsdf,...}}}}">>,
+ p({A,{A,{A,{rrrrr, kljlkjlksfdgkljlsdkjf,
+ kljkljsdaflkjlkjsdf,
+ asdfkldsjfklkljsdklfds}}}}, 10)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {g,{h,{i,{j,{k,{l,{m,{n,"
+ "{o,#a{}}}}}}}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,
+ {g,{h,{i,{j,{k,{l,{m,{n,{o,{a}}}}}}}}}}}}}}}}}, 100)),
+ bt(<<"#c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = \n"
+ " #c{\n"
+ " f1 = #c{f1 = #c{f1 = #c{f1 = a,"
+ "f2 = b},f2 = b},f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b}">>,
+ p({c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,a,b},b},b},b},b},b},
+ b},b},b},b},b},b}, -1)),
+ bt(<<"#rrrrr{\n"
+ " f1 = \n"
+ " #rrrrr{\n"
+ " f1 = \n"
+ " #rrrrr{\n"
+ " f1 = \n"
+ " #rrrrr{\n"
+ " f1 = \n"
+ " {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
+ "f3 = b}},b},\n"
+ " f2 = {rrrrr,c,d},\n"
+ " f3 = {rrrrr,1,2}},\n"
+ " f2 = 1,f3 = 2},\n"
+ " f2 = 3,f3 = 4},\n"
+ " f2 = 5,f3 = 6}">>,
+ p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
+ {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
+ 1,2},3,4},5,6}, -1)),
+ "{aaa,\n {aaa," ++ _ =
p({aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,a}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}},
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,a}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}},
1, 80, -1),
%% A few other cases...
- ?line "{a,#Fun<" ++ _ = lists:flatten(io_lib_pretty:print({a,fun fmt/2})),
- ?line "#Fun<" ++ _ = io_lib_pretty:print(fun() -> foo end),
+ "{a,#Fun<" ++ _ = lists:flatten(io_lib_pretty:print({a,fun fmt/2})),
+ "#Fun<" ++ _ = io_lib_pretty:print(fun() -> foo end),
%% No support for negative columns any more:
- ?line "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
- p([a,[b,c,d,[e,f]],c], -1, 2, 10),
- ?line "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
- p([a,[b,c,d,[e,f]],c], 0, 2, 10),
+ "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
+ p([a,[b,c,d,[e,f]],c], -1, 2, 10),
+ "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
+ p([a,[b,c,d,[e,f]],c], 0, 2, 10),
%% 20 bytes are tried first, then the rest. Try 21 bytes:
L = lists:duplicate(20, $a),
- %% ?line bt(<<"<<\"aaaaaa\"\n \"aaaaaa\"\n \"aaaaaa\"\n \"aaa\">>">>,
- ?line bt(<<"<<\"aaaaaaaaaaaaaaaaaaaaa\">>">>,
- p(list_to_binary([$a | L]), 1, 10, -1)),
- ?line "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, -1),
- ?line "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, 22),
-
- ?line "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
- p([8,9,10,11,12,13,27,168], 1, 40, -1),
- %% ?line "\"\\b\\t\\n\"\n \"\\v\\f\\r\"\n \"\\e\250\"" =
- ?line "\"\\b\\t\\n\\v\\f\\r\\e¨\"" =
- p([8,9,10,11,12,13,27,168], 1, 10, -1),
- ?line "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
- p([8,9,10,11,12,13,27,168], 1, 40, 100),
- %% ?line "\"\\e\\t\\nab\"\n \"cd\"" =
- ?line "\"\\e\\t\\nabcd\"" =
- p("\e\t\nabcd", 1, 12, -1),
+ %% bt(<<"<<\"aaaaaa\"\n \"aaaaaa\"\n \"aaaaaa\"\n \"aaa\">>">>,
+ bt(<<"<<\"aaaaaaaaaaaaaaaaaaaaa\">>">>,
+ p(list_to_binary([$a | L]), 1, 10, -1)),
+ "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, -1),
+ "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, 22),
+
+ "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
+ p([8,9,10,11,12,13,27,168], 1, 40, -1),
+ %% "\"\\b\\t\\n\"\n \"\\v\\f\\r\"\n \"\\e\250\"" =
+ "\"\\b\\t\\n\\v\\f\\r\\e¨\"" =
+ p([8,9,10,11,12,13,27,168], 1, 10, -1),
+ "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
+ p([8,9,10,11,12,13,27,168], 1, 40, 100),
+ %% "\"\\e\\t\\nab\"\n \"cd\"" =
+ "\"\\e\\t\\nabcd\"" =
+ p("\e\t\nabcd", 1, 12, -1),
%% DEL (127) is special...
- ?line "[127]" = p("\d", 1, 10, -1),
- ?line "[127]" = p([127], 1, 10, 100),
+ "[127]" = p("\d", 1, 10, -1),
+ "[127]" = p([127], 1, 10, 100),
- ?line "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
- p(<<8,9,10,11,12,13,27,168>>, 1, 40, -1),
- ?line "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
- p(<<8,9,10,11,12,13,27,168>>, 1, 10, -1),
- ?line "<<127>>" = p(<<127>>, 1, 10, 100),
+ "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
+ p(<<8,9,10,11,12,13,27,168>>, 1, 40, -1),
+ "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
+ p(<<8,9,10,11,12,13,27,168>>, 1, 10, -1),
+ "<<127>>" = p(<<127>>, 1, 10, 100),
%% "Partial" string binaries:
- ?line "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 2),
- ?line "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 3),
- ?line "<<104,101,3>>" = p(list_to_binary("he"++[3]), 1, 80, 4),
- ?line "<<...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 1),
- ?line "<<3,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 2),
- ?line "<<3,104,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 3),
-
- ?line "<<\"12345678901234567890\"...>>" =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 8),
- ?line "<<\"12345678901234567890\"...>>" =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 21),
- ?line "<<49," ++ _ =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 22),
-
- ?line "{sdfsdfj,\n 23" ++ _ =
- p({sdfsdfj,23423423342.23432423}, 1, 17, -1),
-
- ?line bt(<<"kljkljlksdjjlf kljalkjlsdajafasjdfj [kjljklasdf,kjlljsfd,sdfsdkjfsd,kjjsdf,jl,
+ "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 2),
+ "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 3),
+ "<<104,101,3>>" = p(list_to_binary("he"++[3]), 1, 80, 4),
+ "<<...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 1),
+ "<<3,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 2),
+ "<<3,104,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 3),
+
+ "<<\"12345678901234567890\"...>>" =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 8),
+ "<<\"12345678901234567890\"...>>" =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 21),
+ "<<49," ++ _ =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 22),
+
+ "{sdfsdfj,\n 23" ++ _ =
+ p({sdfsdfj,23423423342.23432423}, 1, 17, -1),
+
+ bt(<<"kljkljlksdjjlf kljalkjlsdajafasjdfj [kjljklasdf,kjlljsfd,sdfsdkjfsd,kjjsdf,jl,
lkjjlajsfd|jsdf]">>,
fmt("~w ~w ~p",
[kljkljlksdjjlf,
@@ -681,36 +678,36 @@ otp_6354(Config) when is_list(Config) ->
jsdf]])),
%% Binaries are split as well:
- ?line bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
+ bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
"55,55,55,55,55,55,55,...>>">>,
p(<<80,100,0,55,55,55,55,55,55,55,55,55,55,55,55,55,55,55,
55,55,55,55,55,55,55,55,55,55,55,55>>,1,40,20)),
- ?line bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
+ bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
"55,55,55,55,55,55,55,55,55,55,55,55,\n 55,55,55,55,55,55>>">>,
p(<<80,100,0,55,55,55,55,55,55,55,55,55,55,55,55,55,55,55,
55,55,55,55,55,55,55,55,55,55,55,55>>,1,40,-1)),
- ?line "<<0,0,0,\n ...>>" = p(<<0,0,0,0,0>>, 1, 10, 4),
+ "<<0,0,0,\n ...>>" = p(<<0,0,0,0,0>>, 1, 10, 4),
%% ~W now uses ",..." when printing tuples
- ?line "[a,b|...]" = fmt("~W", [[a,b,c,d,e], 3]),
- ?line "{a,b,...}" = fmt("~W", [{a,b,c,d,e}, 3]),
+ "[a,b|...]" = fmt("~W", [[a,b,c,d,e], 3]),
+ "{a,b,...}" = fmt("~W", [{a,b,c,d,e}, 3]),
ok.
%% OTP-6495. io_lib_pretty bugfix.
otp_6495(Config) when is_list(Config) ->
- ?line bt(<<"[120,120,120,120,120,120,120,120,120,120,120,120,120,120,"
+ bt(<<"[120,120,120,120,120,120,120,120,120,120,120,120,120,120,"
"120,120,120,120,120]<<1>>">>,
fmt("~w~p", ["xxxxxxxxxxxxxxxxxxx", <<1>>])),
ok.
%% OTP-6517. The Format argument of fwrite can be a binary.
otp_6517(Config) when is_list(Config) ->
- ?line "string" = fmt(<<"~s">>, [<<"string">>]),
+ "string" = fmt(<<"~s">>, [<<"string">>]),
ok.
%% OTP-6502. Bits.
otp_6502(Config) when is_list(Config) ->
- ?line bt(<<
+ bt(<<
"[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25]"
"<<0,0,8,\n"
" "
@@ -790,24 +787,24 @@ rfd(_, _) ->
manpage(Config) when is_list(Config) ->
%% The examples that write or print only, not the ones that read...
- ?line bt(<<"Hello world!\n">>,
+ bt(<<"Hello world!\n">>,
fmt("Hello world!~n", [])),
- ?line bt(<<"| aaaaa|bbbbb |ccccc|\n">>, % bugfix
+ bt(<<"| aaaaa|bbbbb |ccccc|\n">>, % bugfix
fmt("|~10.5c|~-10.5c|~5c|~n", [$a, $b, $c])),
- ?line bt(<<"|**********|\n">>,
+ bt(<<"|**********|\n">>,
fmt("|~10w|~n", [{hey, hey, hey}])),
- ?line bt(<<"|{hey,hey,h|\n">>,
+ bt(<<"|{hey,hey,h|\n">>,
fmt("|~10s|~n", [io_lib:write({hey, hey, hey})])),
T = [{attributes,[[{id,age,1.50000},{mode,explicit},
{typename,"INTEGER"}], [{id,cho},{mode,explicit},{typename,'Cho'}]]},
{typename,'Person'},{tag,{'PRIVATE',3}},{mode,implicit}],
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,"
"[73,78,84,69,71,69,82]}],[{id,cho},{mode,explicit},"
"{typename,'Cho'}]]},{typename,'Person'},{tag,{'PRIVATE',3}},"
"{mode,implicit}]\n">>,
fmt("~w~n", [T])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},\n"
+ bt(<<"[{attributes,[[{id,age,1.5},\n"
" {mode,explicit},\n"
" {typename,\"INTEGER\"}],\n"
" [{id,cho},{mode,explicit},{typename,'Cho'}]]},\n"
@@ -815,7 +812,7 @@ manpage(Config) when is_list(Config) ->
" {tag,{'PRIVATE',3}},\n"
" {mode,implicit}]\n">>,
fmt("~62p~n", [T])),
- ?line bt(<<"Here T = [{attributes,[[{id,age,1.5},\n"
+ bt(<<"Here T = [{attributes,[[{id,age,1.5},\n"
" {mode,explicit},\n"
" {typename,\"INTEGER\"}],\n"
" [{id,cho},\n"
@@ -825,64 +822,64 @@ manpage(Config) when is_list(Config) ->
" {tag,{'PRIVATE',3}},\n"
" {mode,implicit}]\n">>,
fmt("Here T = ~62p~n", [T])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},"
"{typename,...}],[{id,cho},{mode,...},{...}]]},"
"{typename,'Person'},{tag,{'PRIVATE',3}},{mode,implicit}]\n">>,
fmt("~W~n", [T,9])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],"
"\n "
"[{id,cho},{mode,...},{...}]]},\n {typename,'Person'},\n "
"{tag,{'PRIVATE',3}},\n {mode,implicit}]\n">>,
fmt("~62P~n", [T,9])),
- ?line "1F\n" = fmt("~.16B~n", [31]),
- ?line "-10011\n" = fmt("~.2B~n", [-19]),
- ?line "5Z\n" = fmt("~.36B~n", [5*36+35]),
- ?line "10#31\n" = fmt("~X~n", [31,"10#"]),
- ?line "-0x1F\n" = fmt("~.16X~n", [-31,"0x"]),
- ?line "10#31\n" = fmt("~.10#~n", [31]),
- ?line "-16#1F\n" = fmt("~.16#~n", [-31]),
- ?line "abc def 'abc def' {foo,1} A \n" =
+ "1F\n" = fmt("~.16B~n", [31]),
+ "-10011\n" = fmt("~.2B~n", [-19]),
+ "5Z\n" = fmt("~.36B~n", [5*36+35]),
+ "10#31\n" = fmt("~X~n", [31,"10#"]),
+ "-0x1F\n" = fmt("~.16X~n", [-31,"0x"]),
+ "10#31\n" = fmt("~.10#~n", [31]),
+ "-16#1F\n" = fmt("~.16#~n", [-31]),
+ "abc def 'abc def' {foo,1} A \n" =
fmt("~s ~w ~i ~w ~c ~n",
['abc def', 'abc def', {foo, 1},{foo, 1}, 65]),
%% fmt("~s", [65]),
%% io_lib(3)
- ?line bt(<<"{1,[2],[3],[...],...}">>,
+ bt(<<"{1,[2],[3],[...],...}">>,
lists:flatten(io_lib:write({1,[2],[3],[4,5],6,7,8,9}, 5))),
ok.
%% OTP-6708. Fewer newlines when pretty-printing.
otp_6708(Config) when is_list(Config) ->
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23,24,25,26,27,28,29|...]">>,
p(lists:seq(1,1000), 30)),
- ?line bt(<<"{lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,\n"
+ bt(<<"{lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,\n"
" jklsdjfklsd,masdfjkkl}">>,
p({lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,
jklsdjfklsd, masdfjkkl}, -1)),
- ?line bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
+ bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
" kjdd}}">>,
p({b, {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,kjdd}},
-1)),
- ?line bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
+ bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
" kdd}}">>,
p({b, {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,kdd}},
-1)),
- ?line bt(<<"#e{f = undefined,g = undefined,\n"
+ bt(<<"#e{f = undefined,g = undefined,\n"
" h = #e{f = 11,g = 22,h = 333}}">>,
p({e,undefined,undefined,{e,11,22,333}}, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21|\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21|\n"
" apa11]">>,
p(lists:seq(1,21) ++ apa11, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23,\n"
" {{abadalkjlasdjflksdajfksdklfsdjlkfdlskjflsdj"
"flsdjfldsdsdddd}}]">>,
p(lists:seq(1,23) ++
[{{abadalkjlasdjflksdajfksdklfsdjlkfdlskjflsdjflsdjfldsdsdddd}}],
-1)),
- ?line bt(<<"{lkjasdf,\n"
+ bt(<<"{lkjasdf,\n"
" {kjkjsd,\n"
" {kjsd,\n"
" {kljsdf,\n"
@@ -894,7 +891,7 @@ otp_6708(Config) when is_list(Config) ->
{dkjsdf,{kjlds,
{kljsd,{kljs,{kljlkjsd}}}}}}}}}},
-1)),
- ?line bt(<<"{lkjasdf,\n"
+ bt(<<"{lkjasdf,\n"
" {kjkjsd,\n"
" {kjsd,{kljsdf,{kjlsd,{dkjsdf,{kjlds,"
"{kljsd,{kljs}}}}}}}}}">>,
@@ -902,24 +899,24 @@ otp_6708(Config) when is_list(Config) ->
{kljsdf,{kjlsd,{dkjsdf,
{kjlds,{kljsd,{kljs}}}}}}}}},
-1)),
- ?line bt(<<"<<1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,\n"
+ bt(<<"<<1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,\n"
" 22,23>>">>,
p(list_to_binary(lists:seq(1,23)), -1)),
- ?line bt(<<"<<100,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,\n"
+ bt(<<"<<100,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,\n"
" 27>>">>,
p(list_to_binary([100|lists:seq(10,27)]), -1)),
- ?line bt(<<"<<100,101,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,\n"
+ bt(<<"<<100,101,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,\n"
" 26>>">>,
p(list_to_binary([100,101|lists:seq(10,26)]), -1)),
- ?line bt(<<"{{<<100,101,102,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"{{<<100,101,102,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23>>}}">>,
p({{list_to_binary([100,101,102|lists:seq(10,23)])}}, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22|\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22|\n"
" ap]">>,
p(lists:seq(1,22) ++ ap, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,{},[],\n <<>>,11,12,13,14,15]">>,
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,{},[],\n <<>>,11,12,13,14,15]">>,
p(lists:seq(1,10) ++ [{},[],<<>>] ++ lists:seq(11,15),1,30,-1)),
- ?line bt(<<"[ddd,ddd,\n"
+ bt(<<"[ddd,ddd,\n"
" {1},\n"
" [1,2],\n"
" ddd,kdfd,\n"
@@ -929,7 +926,7 @@ otp_6708(Config) when is_list(Config) ->
p([ddd,ddd,{1},[1,2],ddd,kdfd,[[1,2],a,b,c],<<"foo">>,<<"bar">>,
1,{2}],1,50,-1)),
- ?line bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,jksd,\n"
+ bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,jksd,\n"
" "
"lkjsdf,kljsdf,kljsf,kljsdf,kljsdf,jkldf,jklsdf,kljsdf,\n"
" "
@@ -940,7 +937,7 @@ otp_6708(Config) when is_list(Config) ->
lkjsdf,kljsdf,kljsf,kljsdf,kljsdf,jkldf,jklsdf,kljsdf,
kljsdf,jklsdf,lkjfd,lkjsdf,kljsdf,kljsdf,lkjsdf,kljsdf,
lkjsdfsd,kljsdf,kjsfj}, 1, 110, -1)),
- ?line bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,"
+ bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,"
"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
" "
"bbbbbbbbbbbbbbbbbbbb = 2,cccccccccccccccccccc = 3,\n"
@@ -1507,10 +1504,10 @@ pack(Sign, Exp, Frac) ->
%% Whitebox test of io_lib:collect_line/3.
io_lib_collect_line_3_wb(Config) when is_list(Config) ->
- ?line do_collect_line(binary, "\n"),
- ?line do_collect_line(binary, "\r\n"),
- ?line do_collect_line(list, "\n"),
- ?line do_collect_line(list, "\r\n"),
+ do_collect_line(binary, "\n"),
+ do_collect_line(binary, "\r\n"),
+ do_collect_line(list, "\n"),
+ do_collect_line(list, "\r\n"),
ok.
do_collect_line(Mode, Eol) ->
@@ -1569,44 +1566,44 @@ do_collect_line_adjust_rest(Rest, [List|T]) when is_list(List) ->
cr_whitespace_in_string(Config) when is_list(Config) ->
- ?line {ok,["abc"],[]} = io_lib:fread("~s", "\rabc").
+ {ok,["abc"],[]} = io_lib:fread("~s", "\rabc").
io_fread_newlines(Config) when is_list(Config) ->
- ?line PrivDir = ?privdir(Config),
- ?line Fname = filename:join(PrivDir, "io_fread_newlines.txt"),
- ?line F0 = [[0,1,2,3,4,5,6,7,8,9]],
- ?line F1 = [[0,1,2,3,4,5,6,7,8],[9]],
- ?line F2 = [[0,1,2,3,4,5,6,7],[8,9]],
- ?line F3 = [[0,1,2,3,4,5,6],[7,8,9]],
- ?line F4 = [[0,1,2,3,4,5],[6,7,8,9]],
- ?line F5 = [[0,1,2,3,4],[5,6,7,8,9]],
- ?line F6 = [[0,1,2,3],[4,5,6,7],[8,9]],
- ?line F7 = [[0,1,2],[3,4,5],[6,7,8],[9]],
- ?line F8 = [[0,1],[2,3],[4,5],[6,7],[8,9]],
- ?line F9 = [[0],[1],[2],[3],[4],[5],[6],[7],[8],[9]],
- ?line Newlines = ["\n", "\r\n", "\r"],
+ PrivDir = ?privdir(Config),
+ Fname = filename:join(PrivDir, "io_fread_newlines.txt"),
+ F0 = [[0,1,2,3,4,5,6,7,8,9]],
+ F1 = [[0,1,2,3,4,5,6,7,8],[9]],
+ F2 = [[0,1,2,3,4,5,6,7],[8,9]],
+ F3 = [[0,1,2,3,4,5,6],[7,8,9]],
+ F4 = [[0,1,2,3,4,5],[6,7,8,9]],
+ F5 = [[0,1,2,3,4],[5,6,7,8,9]],
+ F6 = [[0,1,2,3],[4,5,6,7],[8,9]],
+ F7 = [[0,1,2],[3,4,5],[6,7,8],[9]],
+ F8 = [[0,1],[2,3],[4,5],[6,7],[8,9]],
+ F9 = [[0],[1],[2],[3],[4],[5],[6],[7],[8],[9]],
+ Newlines = ["\n", "\r\n", "\r"],
try
- ?line io_fread_newlines_1([F0,F1,F2,F3,F4,F5,F6,F7,F8,F9],
+ io_fread_newlines_1([F0,F1,F2,F3,F4,F5,F6,F7,F8,F9],
Fname, Newlines)
after
file:delete(Fname)
end.
io_fread_newlines_1(Fs, Fname, [Newline|Newlines]) ->
- ?line ok = io_fread_newlines_2(Fs, Fname, Newline),
- ?line io_fread_newlines_1(Fs, Fname, Newlines);
+ ok = io_fread_newlines_2(Fs, Fname, Newline),
+ io_fread_newlines_1(Fs, Fname, Newlines);
io_fread_newlines_1(_, _, []) -> ok.
io_fread_newlines_2([F|Fs], Fname, Newline) ->
- ?line N1 = write_newlines_file(Fname, F, Newline),
- ?line {F2,N2} = read_newlines_file(Fname),
- ?line io:format("~w ~p ~w~n~n", [N1,F,N2]),
- ?line F2 = lists:flatten(F),
+ N1 = write_newlines_file(Fname, F, Newline),
+ {F2,N2} = read_newlines_file(Fname),
+ io:format("~w ~p ~w~n~n", [N1,F,N2]),
+ F2 = lists:flatten(F),
%% Intermediate newlines are not counted
- ?line N2 = N1 - (length(F) - 1)*length(Newline),
- ?line io_fread_newlines_2(Fs, Fname, Newline);
+ N2 = N1 - (length(F) - 1)*length(Newline),
+ io_fread_newlines_2(Fs, Fname, Newline);
io_fread_newlines_2([], _, _) -> ok.
@@ -1651,101 +1648,101 @@ read_newlines(Fd, Acc, N0) ->
%% OTP-8989 io:format for ~F.Ps ignores P in some cases.
otp_8989(Suite) when is_list(Suite) ->
Hello = "Hello",
- ?line " Hello" = fmt("~6.6s", [Hello]),
- ?line " Hello" = fmt("~*.6s", [6,Hello]),
- ?line " Hello" = fmt("~6.*s", [6,Hello]),
- ?line " Hello" = fmt("~*.*s", [6,6,Hello]),
+ " Hello" = fmt("~6.6s", [Hello]),
+ " Hello" = fmt("~*.6s", [6,Hello]),
+ " Hello" = fmt("~6.*s", [6,Hello]),
+ " Hello" = fmt("~*.*s", [6,6,Hello]),
%%
- ?line " Hello" = fmt("~6.5s", [Hello]),
- ?line " Hello" = fmt("~*.5s", [6,Hello]),
- ?line " Hello" = fmt("~6.*s", [5,Hello]),
- ?line " Hello" = fmt("~*.*s", [6,5,Hello]),
+ " Hello" = fmt("~6.5s", [Hello]),
+ " Hello" = fmt("~*.5s", [6,Hello]),
+ " Hello" = fmt("~6.*s", [5,Hello]),
+ " Hello" = fmt("~*.*s", [6,5,Hello]),
%%
- ?line " Hell" = fmt("~6.4s", [Hello]),
- ?line " Hell" = fmt("~*.4s", [6,Hello]),
- ?line " Hell" = fmt("~6.*s", [4,Hello]),
- ?line " Hell" = fmt("~*.*s", [6,4,Hello]),
+ " Hell" = fmt("~6.4s", [Hello]),
+ " Hell" = fmt("~*.4s", [6,Hello]),
+ " Hell" = fmt("~6.*s", [4,Hello]),
+ " Hell" = fmt("~*.*s", [6,4,Hello]),
%%
- ?line "Hello" = fmt("~5.5s", [Hello]),
- ?line "Hello" = fmt("~*.5s", [5,Hello]),
- ?line "Hello" = fmt("~5.*s", [5,Hello]),
- ?line "Hello" = fmt("~*.*s", [5,5,Hello]),
+ "Hello" = fmt("~5.5s", [Hello]),
+ "Hello" = fmt("~*.5s", [5,Hello]),
+ "Hello" = fmt("~5.*s", [5,Hello]),
+ "Hello" = fmt("~*.*s", [5,5,Hello]),
%%
- ?line " Hell" = fmt("~5.4s", [Hello]),
- ?line " Hell" = fmt("~*.4s", [5,Hello]),
- ?line " Hell" = fmt("~5.*s", [4,Hello]),
- ?line " Hell" = fmt("~*.*s", [5,4,Hello]),
+ " Hell" = fmt("~5.4s", [Hello]),
+ " Hell" = fmt("~*.4s", [5,Hello]),
+ " Hell" = fmt("~5.*s", [4,Hello]),
+ " Hell" = fmt("~*.*s", [5,4,Hello]),
%%
- ?line "Hell" = fmt("~4.4s", [Hello]),
- ?line "Hell" = fmt("~*.4s", [4,Hello]),
- ?line "Hell" = fmt("~4.*s", [4,Hello]),
- ?line "Hell" = fmt("~*.*s", [4,4,Hello]),
+ "Hell" = fmt("~4.4s", [Hello]),
+ "Hell" = fmt("~*.4s", [4,Hello]),
+ "Hell" = fmt("~4.*s", [4,Hello]),
+ "Hell" = fmt("~*.*s", [4,4,Hello]),
%%
- ?line " Hel" = fmt("~4.3s", [Hello]),
- ?line " Hel" = fmt("~*.3s", [4,Hello]),
- ?line " Hel" = fmt("~4.*s", [3,Hello]),
- ?line " Hel" = fmt("~*.*s", [4,3,Hello]),
+ " Hel" = fmt("~4.3s", [Hello]),
+ " Hel" = fmt("~*.3s", [4,Hello]),
+ " Hel" = fmt("~4.*s", [3,Hello]),
+ " Hel" = fmt("~*.*s", [4,3,Hello]),
%%
%%
- ?line "Hello " = fmt("~-6.6s", [Hello]),
- ?line "Hello " = fmt("~*.6s", [-6,Hello]),
- ?line "Hello " = fmt("~-6.*s", [6,Hello]),
- ?line "Hello " = fmt("~*.*s", [-6,6,Hello]),
+ "Hello " = fmt("~-6.6s", [Hello]),
+ "Hello " = fmt("~*.6s", [-6,Hello]),
+ "Hello " = fmt("~-6.*s", [6,Hello]),
+ "Hello " = fmt("~*.*s", [-6,6,Hello]),
%%
- ?line "Hello " = fmt("~-6.5s", [Hello]),
- ?line "Hello " = fmt("~*.5s", [-6,Hello]),
- ?line "Hello " = fmt("~-6.*s", [5,Hello]),
- ?line "Hello " = fmt("~*.*s", [-6,5,Hello]),
+ "Hello " = fmt("~-6.5s", [Hello]),
+ "Hello " = fmt("~*.5s", [-6,Hello]),
+ "Hello " = fmt("~-6.*s", [5,Hello]),
+ "Hello " = fmt("~*.*s", [-6,5,Hello]),
%%
- ?line "Hell " = fmt("~-6.4s", [Hello]),
- ?line "Hell " = fmt("~*.4s", [-6,Hello]),
- ?line "Hell " = fmt("~-6.*s", [4,Hello]),
- ?line "Hell " = fmt("~*.*s", [-6,4,Hello]),
+ "Hell " = fmt("~-6.4s", [Hello]),
+ "Hell " = fmt("~*.4s", [-6,Hello]),
+ "Hell " = fmt("~-6.*s", [4,Hello]),
+ "Hell " = fmt("~*.*s", [-6,4,Hello]),
%%
- ?line "Hello" = fmt("~-5.5s", [Hello]),
- ?line "Hello" = fmt("~*.5s", [-5,Hello]),
- ?line "Hello" = fmt("~-5.*s", [5,Hello]),
- ?line "Hello" = fmt("~*.*s", [-5,5,Hello]),
+ "Hello" = fmt("~-5.5s", [Hello]),
+ "Hello" = fmt("~*.5s", [-5,Hello]),
+ "Hello" = fmt("~-5.*s", [5,Hello]),
+ "Hello" = fmt("~*.*s", [-5,5,Hello]),
%%
- ?line "Hell " = fmt("~-5.4s", [Hello]),
- ?line "Hell " = fmt("~*.4s", [-5,Hello]),
- ?line "Hell " = fmt("~-5.*s", [4,Hello]),
- ?line "Hell " = fmt("~*.*s", [-5,4,Hello]),
+ "Hell " = fmt("~-5.4s", [Hello]),
+ "Hell " = fmt("~*.4s", [-5,Hello]),
+ "Hell " = fmt("~-5.*s", [4,Hello]),
+ "Hell " = fmt("~*.*s", [-5,4,Hello]),
%%
- ?line "Hell" = fmt("~-4.4s", [Hello]),
- ?line "Hell" = fmt("~*.4s", [-4,Hello]),
- ?line "Hell" = fmt("~-4.*s", [4,Hello]),
- ?line "Hell" = fmt("~*.*s", [-4,4,Hello]),
+ "Hell" = fmt("~-4.4s", [Hello]),
+ "Hell" = fmt("~*.4s", [-4,Hello]),
+ "Hell" = fmt("~-4.*s", [4,Hello]),
+ "Hell" = fmt("~*.*s", [-4,4,Hello]),
%%
- ?line "Hel " = fmt("~-4.3s", [Hello]),
- ?line "Hel " = fmt("~*.3s", [-4,Hello]),
- ?line "Hel " = fmt("~-4.*s", [3,Hello]),
- ?line "Hel " = fmt("~*.*s", [-4,3,Hello]),
+ "Hel " = fmt("~-4.3s", [Hello]),
+ "Hel " = fmt("~*.3s", [-4,Hello]),
+ "Hel " = fmt("~-4.*s", [3,Hello]),
+ "Hel " = fmt("~*.*s", [-4,3,Hello]),
ok.
%% OTP-9439 io_lib:fread bug for literate at end.
io_lib_fread_literal(Suite) when is_list(Suite) ->
- ?line {more,"~d",0,""} = io_lib:fread("~d", ""),
- ?line {error,{fread,integer}} = io_lib:fread("~d", " "),
- ?line {more,"~d",1,""} = io_lib:fread(" ~d", " "),
- ?line {ok,[17],"X"} = io_lib:fread(" ~d", " 17X"),
+ {more,"~d",0,""} = io_lib:fread("~d", ""),
+ {error,{fread,integer}} = io_lib:fread("~d", " "),
+ {more,"~d",1,""} = io_lib:fread(" ~d", " "),
+ {ok,[17],"X"} = io_lib:fread(" ~d", " 17X"),
%%
- ?line {more,"d",0,""} = io_lib:fread("d", ""),
- ?line {error,{fread,input}} = io_lib:fread("d", " "),
- ?line {more,"d",1,""} = io_lib:fread(" d", " "),
- ?line {ok,[],"X"} = io_lib:fread(" d", " dX"),
+ {more,"d",0,""} = io_lib:fread("d", ""),
+ {error,{fread,input}} = io_lib:fread("d", " "),
+ {more,"d",1,""} = io_lib:fread(" d", " "),
+ {ok,[],"X"} = io_lib:fread(" d", " dX"),
%%
- ?line {done,eof,_} = io_lib:fread([], eof, "~d"),
- ?line {done,eof,_} = io_lib:fread([], eof, " ~d"),
- ?line {more,C1} = io_lib:fread([], " \n", " ~d"),
- ?line {done,{error,{fread,input}},_} = io_lib:fread(C1, eof, " ~d"),
- ?line {done,{ok,[18]},""} = io_lib:fread(C1, "18\n", " ~d"),
+ {done,eof,_} = io_lib:fread([], eof, "~d"),
+ {done,eof,_} = io_lib:fread([], eof, " ~d"),
+ {more,C1} = io_lib:fread([], " \n", " ~d"),
+ {done,{error,{fread,input}},_} = io_lib:fread(C1, eof, " ~d"),
+ {done,{ok,[18]},""} = io_lib:fread(C1, "18\n", " ~d"),
%%
- ?line {done,eof,_} = io_lib:fread([], eof, "d"),
- ?line {done,eof,_} = io_lib:fread([], eof, " d"),
- ?line {more,C2} = io_lib:fread([], " \n", " d"),
- ?line {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"),
- ?line {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"),
+ {done,eof,_} = io_lib:fread([], eof, "d"),
+ {done,eof,_} = io_lib:fread([], eof, " d"),
+ {more,C2} = io_lib:fread([], " \n", " d"),
+ {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"),
+ {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"),
ok.
@@ -1853,12 +1850,12 @@ flush_from_port(P) ->
%% Test binaries printed with a depth of one behave correctly.
io_lib_print_binary_depth_one(Suite) when is_list(Suite) ->
- ?line "<<>>" = fmt("~W", [<<>>, 1]),
- ?line "<<>>" = fmt("~P", [<<>>, 1]),
- ?line "<<...>>" = fmt("~W", [<<1>>, 1]),
- ?line "<<...>>" = fmt("~P", [<<1>>, 1]),
- ?line "<<...>>" = fmt("~W", [<<1:7>>, 1]),
- ?line "<<...>>" = fmt("~P", [<<1:7>>, 1]),
+ "<<>>" = fmt("~W", [<<>>, 1]),
+ "<<>>" = fmt("~P", [<<>>, 1]),
+ "<<...>>" = fmt("~W", [<<1>>, 1]),
+ "<<...>>" = fmt("~P", [<<1>>, 1]),
+ "<<...>>" = fmt("~W", [<<1:7>>, 1]),
+ "<<...>>" = fmt("~P", [<<1:7>>, 1]),
ok.
%% OTP-10302. Unicode.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index c16d301279..6c0e4241a9 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -57,7 +57,7 @@
-define(format(S, A), io:format(S, A)).
-define(dbg(Data),io:format(standard_error, "DBG: ~p\r\n",[Data])).
-define(RM_RF(Dir),begin io:format(standard_error, "Not Removed: ~p\r\n",[Dir]),
- ok end).
+ ok end).
-else.
-define(format(S, A), ok).
-define(dbg(Data),noop).
@@ -105,171 +105,171 @@ end_per_group(_GroupName, Config) ->
q = [],
nxt = eof,
mode = list
- }).
+ }).
uprompt(_L) ->
[1050,1072,1082,1074,1086,32,1077,32,85,110,105,99,111,100,101,32,63].
%% Test that an Unicode prompt does not crash the shell.
unicode_prompt(Config) when is_list(Config) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
+ PA = filename:dirname(code:which(?MODULE)),
case proplists:get_value(default_shell,Config) of
old ->
ok;
new ->
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline, "2"},
- {putline, "shell:prompt_func({io_proto_SUITE,uprompt})."},
- {getline, "default"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "\"hej\\n\""},
- {putline, "io:setopts([{binary,true}])."},
- {getline, "ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "<<\"hej\\n\">>"}
- ],[],[],"-pa \""++ PA++"\"")
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline, "2"},
+ {putline, "shell:prompt_func({io_proto_SUITE,uprompt})."},
+ {getline, "default"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "\"hej\\n\""},
+ {putline, "io:setopts([{binary,true}])."},
+ {getline, "ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "<<\"hej\\n\">>"}
+ ],[],[],"-pa \""++ PA++"\"")
end,
%% And one with oldshell
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline_re, ".*2$"},
- {putline, "shell:prompt_func({io_proto_SUITE,uprompt})."},
- {getline_re, ".*default"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*\"hej\\\\n\""},
- {putline, "io:setopts([{binary,true}])."},
- {getline_re, ".*ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*<<\"hej\\\\n\">>"}
- ],[],[],"-oldshell -pa \""++PA++"\""),
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline_re, ".*2$"},
+ {putline, "shell:prompt_func({io_proto_SUITE,uprompt})."},
+ {getline_re, ".*default"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*\"hej\\\\n\""},
+ {putline, "io:setopts([{binary,true}])."},
+ {getline_re, ".*ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*<<\"hej\\\\n\">>"}
+ ],[],[],"-oldshell -pa \""++PA++"\""),
ok.
-
+
%% Check io:setopts and io:getopts functions.
setopts_getopts(Config) when is_list(Config) ->
- ?line FileName = filename:join([?config(priv_dir,Config),
- "io_proto_SUITE_setopts_getopts.dat"]),
- ?line {ok,WFile} = file:open(FileName,[write]),
- ?line Server = start_io_server_proxy(),
- ?line [{binary, false}] = io:getopts(Server),
- ?line [getopts] = proxy_getall(Server),
- ?line [{binary,false},{encoding,latin1}] = lists:sort(io:getopts(WFile)),
- ?line proxy_setnext(Server,"Hej"),
- ?line "Hej" = io:get_line(Server,''),
- ?line proxy_setnext(Server,"Hej"++[532]),
- ?line [$H,$e,$j,532] = io:get_line(Server,''),
- ?line ok = io:setopts(Server,[{binary,true}]),
- ?line proxy_setnext(Server,"Hej"),
- ?line <<"Hej">> = io:get_line(Server,''),
- ?line proxy_setnext(Server,"Hej"++[532]),
- ?line <<72,101,106,200,148>> = io:get_line(Server,''),
- ?line [$H,$e,$j,532] = lists:flatten(io_lib:format("~ts",[<<72,101,106,200,148>>])),
- ?line file:write(WFile,<<"HejA">>),
- ?line file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,unicode)),
- ?line file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf16,big})),
- ?line file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf16,little})),
- ?line file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf32,big})),
- ?line file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf32,little})),
- ?line file:close(WFile),
- ?line {ok,RFile} = file:open(FileName,[read]),
- ?line [{binary,false},{encoding,latin1}] = lists:sort(io:getopts(RFile)),
- ?line [$H,$e,$j,$A] = io:get_chars(RFile,'',4),
- ?line io:setopts(RFile,[{encoding,unicode}]),
- ?line [$H,$e,$j,532] = io:get_chars(RFile,'',4),
- ?line [{binary,false},{encoding,unicode}] = lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf16,big}}]),
- ?line [$H,$e,$j,532] = io:get_chars(RFile,'',4),
- ?line [{binary,false},{encoding,{utf16,big}}] =
+ FileName = filename:join([?config(priv_dir,Config),
+ "io_proto_SUITE_setopts_getopts.dat"]),
+ {ok,WFile} = file:open(FileName,[write]),
+ Server = start_io_server_proxy(),
+ [{binary, false}] = io:getopts(Server),
+ [getopts] = proxy_getall(Server),
+ [{binary,false},{encoding,latin1}] = lists:sort(io:getopts(WFile)),
+ proxy_setnext(Server,"Hej"),
+ "Hej" = io:get_line(Server,''),
+ proxy_setnext(Server,"Hej"++[532]),
+ [$H,$e,$j,532] = io:get_line(Server,''),
+ ok = io:setopts(Server,[{binary,true}]),
+ proxy_setnext(Server,"Hej"),
+ <<"Hej">> = io:get_line(Server,''),
+ proxy_setnext(Server,"Hej"++[532]),
+ <<72,101,106,200,148>> = io:get_line(Server,''),
+ [$H,$e,$j,532] = lists:flatten(io_lib:format("~ts",[<<72,101,106,200,148>>])),
+ file:write(WFile,<<"HejA">>),
+ file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,unicode)),
+ file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf16,big})),
+ file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf16,little})),
+ file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf32,big})),
+ file:write(WFile,unicode:characters_to_binary("Hej"++[532],unicode,{utf32,little})),
+ file:close(WFile),
+ {ok,RFile} = file:open(FileName,[read]),
+ [{binary,false},{encoding,latin1}] = lists:sort(io:getopts(RFile)),
+ [$H,$e,$j,$A] = io:get_chars(RFile,'',4),
+ io:setopts(RFile,[{encoding,unicode}]),
+ [$H,$e,$j,532] = io:get_chars(RFile,'',4),
+ [{binary,false},{encoding,unicode}] = lists:sort(io:getopts(RFile)),
+ io:setopts(RFile,[{encoding,{utf16,big}}]),
+ [$H,$e,$j,532] = io:get_chars(RFile,'',4),
+ [{binary,false},{encoding,{utf16,big}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf16,little}}]),
- ?line [$H,$e,$j,532] = io:get_chars(RFile,'',4),
- ?line [{binary,false},{encoding,{utf16,little}}] =
+ io:setopts(RFile,[{encoding,{utf16,little}}]),
+ [$H,$e,$j,532] = io:get_chars(RFile,'',4),
+ [{binary,false},{encoding,{utf16,little}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf32,big}}]),
- ?line [$H,$e,$j,532] = io:get_chars(RFile,'',4),
- ?line [{binary,false},{encoding,{utf32,big}}] =
+ io:setopts(RFile,[{encoding,{utf32,big}}]),
+ [$H,$e,$j,532] = io:get_chars(RFile,'',4),
+ [{binary,false},{encoding,{utf32,big}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf32,little}}]),
- ?line [$H,$e,$j,532] = io:get_chars(RFile,'',4),
- ?line [{binary,false},{encoding,{utf32,little}}] =
+ io:setopts(RFile,[{encoding,{utf32,little}}]),
+ [$H,$e,$j,532] = io:get_chars(RFile,'',4),
+ [{binary,false},{encoding,{utf32,little}}] =
lists:sort(io:getopts(RFile)),
- ?line eof = io:get_line(RFile,''),
- ?line file:position(RFile,0),
- ?line io:setopts(RFile,[{binary,true},{encoding,latin1}]),
- ?line <<$H,$e,$j,$A>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,latin1}] = lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,unicode}]),
- ?line <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,unicode}] = lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf16,big}}]),
- ?line <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,{utf16,big}}] =
+ eof = io:get_line(RFile,''),
+ file:position(RFile,0),
+ io:setopts(RFile,[{binary,true},{encoding,latin1}]),
+ <<$H,$e,$j,$A>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,latin1}] = lists:sort(io:getopts(RFile)),
+ io:setopts(RFile,[{encoding,unicode}]),
+ <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,unicode}] = lists:sort(io:getopts(RFile)),
+ io:setopts(RFile,[{encoding,{utf16,big}}]),
+ <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,{utf16,big}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf16,little}}]),
- ?line <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,{utf16,little}}] =
+ io:setopts(RFile,[{encoding,{utf16,little}}]),
+ <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,{utf16,little}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf32,big}}]),
- ?line <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,{utf32,big}}] =
+ io:setopts(RFile,[{encoding,{utf32,big}}]),
+ <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,{utf32,big}}] =
lists:sort(io:getopts(RFile)),
- ?line io:setopts(RFile,[{encoding,{utf32,little}}]),
- ?line <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
- ?line [{binary,true},{encoding,{utf32,little}}] =
+ io:setopts(RFile,[{encoding,{utf32,little}}]),
+ <<$H,$e,$j,532/utf8>> = io:get_chars(RFile,'',4),
+ [{binary,true},{encoding,{utf32,little}}] =
lists:sort(io:getopts(RFile)),
- ?line eof = io:get_line(RFile,''),
- ?line file:close(RFile),
+ eof = io:get_line(RFile,''),
+ file:close(RFile),
case proplists:get_value(default_shell,Config) of
old ->
ok;
new ->
%% So, lets test another node with new interactive shell
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline, "2"},
- {putline, "lists:keyfind(binary,1,io:getopts())."},
- {getline, "{binary,false}"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "\"hej\\n\""},
- {putline, "io:setopts([{binary,true}])."},
- {getline, "ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "<<\"hej\\n\">>"}
- ],[])
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline, "2"},
+ {putline, "lists:keyfind(binary,1,io:getopts())."},
+ {getline, "{binary,false}"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "\"hej\\n\""},
+ {putline, "io:setopts([{binary,true}])."},
+ {getline, "ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "<<\"hej\\n\">>"}
+ ],[])
end,
%% And one with oldshell
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline_re, ".*2$"},
- {putline, "lists:keyfind(binary,1,io:getopts())."},
- {getline_re, ".*{binary,false}"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*\"hej\\\\n\""},
- {putline, "io:setopts([{binary,true}])."},
- {getline_re, ".*ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*<<\"hej\\\\n\">>"}
- ],[],[],"-oldshell"),
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline_re, ".*2$"},
+ {putline, "lists:keyfind(binary,1,io:getopts())."},
+ {getline_re, ".*{binary,false}"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*\"hej\\\\n\""},
+ {putline, "io:setopts([{binary,true}])."},
+ {getline_re, ".*ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*<<\"hej\\\\n\">>"}
+ ],[],[],"-oldshell"),
ok.
get_lc_ctype() ->
- case {os:type(),os:version()} of
- {{unix,sunos},{5,N,_}} when N =< 8 ->
- "iso_8859_1";
- _ ->
- "ISO-8859-1"
- end.
-
+ case {os:type(),os:version()} of
+ {{unix,sunos},{5,N,_}} when N =< 8 ->
+ "iso_8859_1";
+ _ ->
+ "ISO-8859-1"
+ end.
+
%% Test various unicode options.
unicode_options(Config) when is_list(Config) ->
DataDir = ?config(data_dir,Config),
@@ -312,7 +312,6 @@ unicode_options(Config) when is_list(Config) ->
[read,binary]),
{ok,Bin} = file:read(F,4),
{Type,Bytes} = unicode:bom_to_encoding(Bin),
-
file:position(F,Bytes),
io:setopts(F,[{encoding,Type}]),
R = unicode:characters_to_list(
@@ -330,26 +329,26 @@ unicode_options(Config) when is_list(Config) ->
R
end,
ReadBomlessFileList = fun({Type,File},DataLen,Dir) ->
- {ok,F} = file:open(filename:join([Dir,File]),
- [read,
- {encoding,Type}]),
- R = io:get_chars(F,'',DataLen),
- file:close(F),
- R
- end,
+ {ok,F} = file:open(filename:join([Dir,File]),
+ [read,
+ {encoding,Type}]),
+ R = io:get_chars(F,'',DataLen),
+ file:close(F),
+ R
+ end,
ReadBomlessFileListLine = fun({Type,File},Dir) ->
- {ok,F} = file:open(filename:join([Dir,File]),
- [read,
- {encoding,Type}]),
- R = io:get_line(F,''),
- file:close(F),
- R
- end,
- ?line [TestData = ReadBomFile(F,DataDir) || F <- InternalBomFiles ],
- ?line [ExternalTestData = ReadBomFile(F,DataDir) || F <- ExternalBomFiles ],
- ?line [TestData = ReadBomlessFile(F,length(TestData),DataDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomlessFileList(F,length(TestData),DataDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomlessFileListLine(F,DataDir) || F <- AllNoBom ],
+ {ok,F} = file:open(filename:join([Dir,File]),
+ [read,
+ {encoding,Type}]),
+ R = io:get_line(F,''),
+ file:close(F),
+ R
+ end,
+ [TestData = ReadBomFile(F,DataDir) || F <- InternalBomFiles ],
+ [ExternalTestData = ReadBomFile(F,DataDir) || F <- ExternalBomFiles ],
+ [TestData = ReadBomlessFile(F,length(TestData),DataDir) || F <- AllNoBom ],
+ [TestData = ReadBomlessFileList(F,length(TestData),DataDir) || F <- AllNoBom ],
+ [TestData = ReadBomlessFileListLine(F,DataDir) || F <- AllNoBom ],
BomDir = filename:join([PrivDir,"BOMDATA"]),
BomlessDir = filename:join([PrivDir,"BOMLESSDATA"]),
@@ -365,8 +364,8 @@ unicode_options(Config) when is_list(Config) ->
file:close(F),
ok
end,
- ?line [ ok = WriteBomFile(F,BomDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomFile(F,BomDir) || {_,F} <- AllNoBom ],
+ [ ok = WriteBomFile(F,BomDir) || F <- AllNoBom ],
+ [TestData = ReadBomFile(F,BomDir) || {_,F} <- AllNoBom ],
WriteBomlessFile = fun({Enc,File},TData,Dir) ->
{ok,F} = file:open(
filename:join([Dir,File]),
@@ -375,11 +374,11 @@ unicode_options(Config) when is_list(Config) ->
file:close(F),
ok
end,
- ?line [ ok = WriteBomlessFile(F,TestData,BomlessDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomlessFile(F,length(TestData),BomlessDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomlessFileList(F,length(TestData),BomlessDir) || F <- AllNoBom ],
- ?line [TestData = ReadBomlessFileListLine(F,BomlessDir) || F <- AllNoBom ],
-
+ [ ok = WriteBomlessFile(F,TestData,BomlessDir) || F <- AllNoBom ],
+ [TestData = ReadBomlessFile(F,length(TestData),BomlessDir) || F <- AllNoBom ],
+ [TestData = ReadBomlessFileList(F,length(TestData),BomlessDir) || F <- AllNoBom ],
+ [TestData = ReadBomlessFileListLine(F,BomlessDir) || F <- AllNoBom ],
+
CannotReadFile = fun({Enc,File},Dir) ->
%%io:format(standard_error,"~s\r\n",[filename:join([Dir,File])]),
{ok,F} = file:open(
@@ -398,14 +397,14 @@ unicode_options(Config) when is_list(Config) ->
{error,terminated} = io:get_chars(F,'',10),
ok
end,
- ?line [ ok = CannotReadFile(F,DataDir) || F <- AllNoBom ],
- ?line [ ok = CannotReadFile(F,BomlessDir) || F <- AllNoBom ],
- ?line [ ok = CannotReadFile(F,BomDir) || F <- AllNoBom ],
+ [ ok = CannotReadFile(F,DataDir) || F <- AllNoBom ],
+ [ ok = CannotReadFile(F,BomlessDir) || F <- AllNoBom ],
+ [ ok = CannotReadFile(F,BomDir) || F <- AllNoBom ],
- ?line [ ok = WriteBomlessFile(F,TestData2,BomlessDir) || F <- AllNoBom ],
- ?line [TestData2 = ReadBomlessFile(F,length(TestData2),BomlessDir) || F <- AllNoBom ],
- ?line [TestData2 = ReadBomlessFileList(F,length(TestData2),BomlessDir) || F <- AllNoBom ],
- ?line [TestData2 = ReadBomlessFileListLine(F,BomlessDir) || F <- AllNoBom ],
+ [ ok = WriteBomlessFile(F,TestData2,BomlessDir) || F <- AllNoBom ],
+ [TestData2 = ReadBomlessFile(F,length(TestData2),BomlessDir) || F <- AllNoBom ],
+ [TestData2 = ReadBomlessFileList(F,length(TestData2),BomlessDir) || F <- AllNoBom ],
+ [TestData2 = ReadBomlessFileListLine(F,BomlessDir) || F <- AllNoBom ],
FailDir = filename:join([PrivDir,"FAIL"]),
@@ -415,52 +414,52 @@ unicode_options(Config) when is_list(Config) ->
{ok,F} = file:open(
filename:join([Dir,File]),
[write,binary]),
- ?line {'EXIT', {no_translation,_}} =
+ {'EXIT', {no_translation,_}} =
(catch io:put_chars(F,TestData)),
- ?line {'EXIT', {terminated,_}} = (catch io:put_chars(F,TestData)),
+ {'EXIT', {terminated,_}} = (catch io:put_chars(F,TestData)),
ok
end,
- ?line [ ok = CannotWriteFile(F,FailDir) || F <- AllNoBom ],
+ [ ok = CannotWriteFile(F,FailDir) || F <- AllNoBom ],
case proplists:get_value(default_shell,Config) of
old ->
ok;
new ->
%% OK, time for the group_leaders...
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline, "2"},
- {putline, "lists:keyfind(encoding,1,io:getopts())."},
- {getline, "{encoding,latin1}"},
- {putline, "io:format(\"~ts~n\",[[1024]])."},
- {getline, "\\x{400}"},
- {putline, "io:setopts([unicode])."},
- {getline, "ok"},
- {putline, "io:format(\"~ts~n\",[[1024]])."},
- {getline,
- binary_to_list(unicode:characters_to_binary(
- [1024],unicode,utf8))}
- ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; "
- "export LC_CTYPE; ")
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline, "2"},
+ {putline, "lists:keyfind(encoding,1,io:getopts())."},
+ {getline, "{encoding,latin1}"},
+ {putline, "io:format(\"~ts~n\",[[1024]])."},
+ {getline, "\\x{400}"},
+ {putline, "io:setopts([unicode])."},
+ {getline, "ok"},
+ {putline, "io:format(\"~ts~n\",[[1024]])."},
+ {getline,
+ binary_to_list(unicode:characters_to_binary(
+ [1024],unicode,utf8))}
+ ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; "
+ "export LC_CTYPE; ")
end,
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline_re, ".*2$"},
- {putline, "lists:keyfind(encoding,1,io:getopts())."},
- {getline_re, ".*{encoding,latin1}"},
- {putline, "io:format(\"~ts~n\",[[1024]])."},
- {getline_re, ".*\\\\x{400\\}"},
- {putline, "io:setopts([{encoding,unicode}])."},
- {getline_re, ".*ok"},
- {putline, "io:format(\"~ts~n\",[[1024]])."},
- {getline_re,
- ".*"++binary_to_list(unicode:characters_to_binary(
- [1024],unicode,utf8))}
- ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; ",
- " -oldshell "),
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline_re, ".*2$"},
+ {putline, "lists:keyfind(encoding,1,io:getopts())."},
+ {getline_re, ".*{encoding,latin1}"},
+ {putline, "io:format(\"~ts~n\",[[1024]])."},
+ {getline_re, ".*\\\\x{400\\}"},
+ {putline, "io:setopts([{encoding,unicode}])."},
+ {getline_re, ".*ok"},
+ {putline, "io:format(\"~ts~n\",[[1024]])."},
+ {getline_re,
+ ".*"++binary_to_list(unicode:characters_to_binary(
+ [1024],unicode,utf8))}
+ ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; ",
+ " -oldshell "),
ok.
-
+
%% Tests various unicode options on random generated files.
unicode_options_gen(Config) when is_list(Config) ->
random:seed(1240, 900586, 553728),
@@ -605,7 +604,7 @@ do_read_whole_file(Fname, Options, Fun) ->
Res = do_read_whole_file_1(Fun, F),
ok = file:close(F),
unicode:characters_to_list(Res, unicode).
-
+
do_read_whole_file_1(Fun, F) ->
case Fun(F) of
eof ->
@@ -630,7 +629,7 @@ do_write_read_file(Fname, Options, Encoding, Writer) ->
{ok,Bin} = file:read_file(Fname),
ok = file:delete(Fname),
Bin.
-
+
enc2str(Atom) when is_atom(Atom) ->
atom_to_list(Atom);
enc2str({A1,A2}) when is_atom(A1), is_atom(A2) ->
@@ -642,12 +641,12 @@ random_unicode(0) ->
random_unicode(N) ->
%% Favour large unicode and make linebreaks
X = case random:uniform(20) of
- A when A =< 1 -> $\n;
- A0 when A0 =< 3 -> random:uniform(16#10FFFF);
- A1 when A1 =< 6 -> random:uniform(16#10FFFF - 16#7F) + 16#7F;
- A2 when A2 =< 12 -> random:uniform(16#10FFFF - 16#7FF) + 16#7FF;
- _ -> random:uniform(16#10FFFF - 16#FFFF) + 16#FFFF
- end,
+ A when A =< 1 -> $\n;
+ A0 when A0 =< 3 -> random:uniform(16#10FFFF);
+ A1 when A1 =< 6 -> random:uniform(16#10FFFF - 16#7F) + 16#7F;
+ A2 when A2 =< 12 -> random:uniform(16#10FFFF - 16#7FF) + 16#7FF;
+ _ -> random:uniform(16#10FFFF - 16#FFFF) + 16#FFFF
+ end,
case X of
Inv1 when Inv1 >= 16#D800, Inv1 =< 16#DFFF;
Inv1 =:= 16#FFFE;
@@ -656,7 +655,7 @@ random_unicode(N) ->
_ ->
[X | random_unicode(N-1)]
end.
-
+
%% Test variants with binary option.
binary_options(Config) when is_list(Config) ->
@@ -672,73 +671,74 @@ binary_options(Config) when is_list(Config) ->
First10List = binary_to_list(First10),
Second10List = binary_to_list(Second10),
TestFile = filename:join([DataDir, "testdata_utf8.dat"]),
- ?line {ok, F} = file:open(TestFile,[read]),
- ?line {ok, First10List} = file:read(F,10),
- ?line io:setopts(F,[binary]),
- ?line {ok, Second10} = file:read(F,10),
- ?line file:close(F),
- ?line {ok, F2} = file:open(TestFile,[read,binary]),
- ?line {ok, First10} = file:read(F2,10),
- ?line io:setopts(F2,[list]),
- ?line {ok, Second10List} = file:read(F2,10),
- ?line file:position(F2,0),
- ?line First10List = io:get_chars(F2,'',10),
- ?line io:setopts(F2,[binary]),
- ?line Second10 = unicode:characters_to_binary(io:get_chars(F2,'',10),unicode,latin1),
- ?line file:close(F2),
- ?line LineBreakFileName = filename:join([PrivDir, "testdata.dat"]),
- ?line LineBreakTestData = <<TestData/binary,$\n>>,
- ?line LineBreakTestDataList = binary_to_list(LineBreakTestData),
- ?line file:write_file(LineBreakFileName,[LineBreakTestData,LineBreakTestData,LineBreakTestData,TestData]),
- ?line {ok, F3} = file:open(LineBreakFileName,[read]),
- ?line LineBreakTestDataList = io:get_line(F3,''),
- ?line io:setopts(F3,[binary]),
- ?line LineBreakTestData = unicode:characters_to_binary(io:get_line(F3,''),unicode,latin1),
- ?line io:setopts(F3,[list]),
- ?line LineBreakTestDataList = io:get_line(F3,''),
- ?line io:setopts(F3,[binary]),
- ?line TestData = unicode:characters_to_binary(io:get_line(F3,''),unicode,latin1),
- ?line eof = io:get_line(F3,''),
- ?line file:close(F3),
+ {ok, F} = file:open(TestFile,[read]),
+ {ok, First10List} = file:read(F,10),
+ io:setopts(F,[binary]),
+ {ok, Second10} = file:read(F,10),
+ file:close(F),
+ {ok, F2} = file:open(TestFile,[read,binary]),
+ {ok, First10} = file:read(F2,10),
+ io:setopts(F2,[list]),
+ {ok, Second10List} = file:read(F2,10),
+ file:position(F2,0),
+ First10List = io:get_chars(F2,'',10),
+ io:setopts(F2,[binary]),
+ Second10 = unicode:characters_to_binary(io:get_chars(F2,'',10),unicode,latin1),
+ file:close(F2),
+ LineBreakFileName = filename:join([PrivDir, "testdata.dat"]),
+ LineBreakTestData = <<TestData/binary,$\n>>,
+ LineBreakTestDataList = binary_to_list(LineBreakTestData),
+ file:write_file(LineBreakFileName,[LineBreakTestData,LineBreakTestData,LineBreakTestData,TestData]),
+ {ok, F3} = file:open(LineBreakFileName,[read]),
+ LineBreakTestDataList = io:get_line(F3,''),
+ io:setopts(F3,[binary]),
+ LineBreakTestData = unicode:characters_to_binary(io:get_line(F3,''),unicode,latin1),
+ io:setopts(F3,[list]),
+ LineBreakTestDataList = io:get_line(F3,''),
+ io:setopts(F3,[binary]),
+ TestData = unicode:characters_to_binary(io:get_line(F3,''),unicode,latin1),
+ eof = io:get_line(F3,''),
+ file:close(F3),
+
%% OK, time for the group_leaders...
case proplists:get_value(default_shell,Config) of
old ->
ok;
new ->
- ?line rtnode([{putline, "2."},
- {getline, "2"},
- {putline, "lists:keyfind(binary,1,io:getopts())."},
- {getline, "{binary,false}"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "\"hej\\n\""},
- {putline, "io:setopts([{binary,true},unicode])."},
- {getline, "ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline, "<<\"hej\\n\">>"},
- {putline, "io:get_line('')."},
- {putline, binary_to_list(<<"\345\344\366"/utf8>>)},
- {getline, "<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\n\"/utf8>>"}
- ],[])
+ rtnode([{putline, "2."},
+ {getline, "2"},
+ {putline, "lists:keyfind(binary,1,io:getopts())."},
+ {getline, "{binary,false}"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "\"hej\\n\""},
+ {putline, "io:setopts([{binary,true},unicode])."},
+ {getline, "ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline, "<<\"hej\\n\">>"},
+ {putline, "io:get_line('')."},
+ {putline, binary_to_list(<<"\345\344\366"/utf8>>)},
+ {getline, "<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\n\"/utf8>>"}
+ ],[])
end,
- %% And one with oldshell
- ?line rtnode([{putline, "2."},
- {getline_re, ".*2$"},
- {putline, "lists:keyfind(binary,1,io:getopts())."},
- {getline_re, ".*{binary,false}"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*\"hej\\\\n\""},
- {putline, "io:setopts([{binary,true},unicode])."},
- {getline_re, ".*ok"},
- {putline, "io:get_line('')."},
- {putline, "hej"},
- {getline_re, ".*<<\"hej\\\\n\">>"},
- {putline, "io:get_line('')."},
- {putline, binary_to_list(<<"\345\344\366"/utf8>>)},
- {getline_re, ".*<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\\\n\"/utf8>>"}
- ],[],[],"-oldshell"),
+ %% And one with oldshell
+ rtnode([{putline, "2."},
+ {getline_re, ".*2$"},
+ {putline, "lists:keyfind(binary,1,io:getopts())."},
+ {getline_re, ".*{binary,false}"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*\"hej\\\\n\""},
+ {putline, "io:setopts([{binary,true},unicode])."},
+ {getline_re, ".*ok"},
+ {putline, "io:get_line('')."},
+ {putline, "hej"},
+ {getline_re, ".*<<\"hej\\\\n\">>"},
+ {putline, "io:get_line('')."},
+ {putline, binary_to_list(<<"\345\344\366"/utf8>>)},
+ {getline_re, ".*<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\\\n\"/utf8>>"}
+ ],[],[],"-oldshell"),
ok.
%% Test io protocol compatibility with R12 nodes.
@@ -751,132 +751,132 @@ bc_with_r12(Config) when is_list(Config) ->
bc_with_r12_1(Config) ->
PA = filename:dirname(code:which(?MODULE)),
Name1 = io_proto_r12_1,
- ?line N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
+ N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
test_server:start_node(Name1, peer, [{args, "-pz \""++PA++"\""},
{erl,[{release,"r12b"}]}]),
DataDir = ?config(data_dir,Config),
FileName1 = filename:join([DataDir,"testdata_latin1.dat"]),
TestDataLine1 = [229,228,246],
TestDataLine2 = [197,196,214],
- ?line SPid1 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
- ?line {ok,F1} = receive
- {SPid1,Res1} ->
- Res1
- after 5000 ->
- exit(timeout)
- end,
- ?line TestDataLine1 = chomp(io:get_line(F1,'')),
- ?line SPid1 ! die,
+ SPid1 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
+ {ok,F1} = receive
+ {SPid1,Res1} ->
+ Res1
+ after 5000 ->
+ exit(timeout)
+ end,
+ TestDataLine1 = chomp(io:get_line(F1,'')),
+ SPid1 ! die,
receive after 1000 -> ok end,
- ?line SPid2 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read,binary]]]),
- ?line {ok,F2} = receive
- {SPid2,Res2} ->
- Res2
- after 5000 ->
- exit(timeout)
- end,
+ SPid2 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read,binary]]]),
+ {ok,F2} = receive
+ {SPid2,Res2} ->
+ Res2
+ after 5000 ->
+ exit(timeout)
+ end,
TestDataLine1BinUtf = unicode:characters_to_binary(TestDataLine1),
TestDataLine1BinLatin = list_to_binary(TestDataLine1),
TestDataLine2BinUtf = unicode:characters_to_binary(TestDataLine2),
TestDataLine2BinLatin = list_to_binary(TestDataLine2),
- ?line TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
- ?line TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
+ TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
+ TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
%%io:format(standard_error,"Exec:~s\r\n",[rpc:call(N1,os,find_executable,["erl"])]),
%%io:format(standard_error,"Io:~s\r\n",[rpc:call(N1,code,which,[io])]),
%%io:format(standard_error,"File_io_server:~s\r\n",[rpc:call(N1,code,which,[file_io_server])]),
- ?line file:position(F2,0),
- ?line TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- ?line TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
- ?line file:position(F2,0),
- ?line TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
- ?line TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- ?line eof = chomp(rpc:call(N1,io,get_line,[F2,''])),
- ?line file:position(F2,0),
- ?line TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F2,'',3]),
+ file:position(F2,0),
+ TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
+ TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
+ file:position(F2,0),
+ TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
+ TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
+ eof = chomp(rpc:call(N1,io,get_line,[F2,''])),
+ file:position(F2,0),
+ TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F2,'',3]),
io:get_chars(F2,'',1),
- ?line TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- ?line file:position(F2,0),
- ?line {ok,[TestDataLine1]} = io:fread(F2,'',"~s"),
- ?line {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F2,'',"~s"]),
-
- ?line DataLen1 = length(TestDataLine1),
- ?line DataLen2 = length(TestDataLine2),
-
- ?line file:position(F2,0),
- ?line {ok,TestDataLine1BinLatin} = file:read(F2,DataLen1),
- ?line {ok,_} = file:read(F2,1),
- ?line {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F2,DataLen2]),
- ?line {ok,_} = file:read(F2,1),
- ?line eof = rpc:call(N1,file,read,[F2,1]),
+ TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
+ file:position(F2,0),
+ {ok,[TestDataLine1]} = io:fread(F2,'',"~s"),
+ {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F2,'',"~s"]),
+
+ DataLen1 = length(TestDataLine1),
+ DataLen2 = length(TestDataLine2),
+
+ file:position(F2,0),
+ {ok,TestDataLine1BinLatin} = file:read(F2,DataLen1),
+ {ok,_} = file:read(F2,1),
+ {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F2,DataLen2]),
+ {ok,_} = file:read(F2,1),
+ eof = rpc:call(N1,file,read,[F2,1]),
%% As r12 has a bug when setting options with setopts, we need
%% to reopen the file...
- ?line SPid2 ! die,
+ SPid2 ! die,
receive after 1000 -> ok end,
- ?line SPid3 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
- ?line {ok,F3} = receive
- {SPid3,Res3} ->
- Res3
- after 5000 ->
- exit(timeout)
- end,
-
- ?line file:position(F3,0),
- ?line {ok,[TestDataLine1]} = io:fread(F3,'',"~s"),
- ?line {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F3,'',"~s"]),
-
-
- ?line file:position(F3,0),
- ?line {ok,TestDataLine1} = file:read(F3,DataLen1),
- ?line {ok,_} = file:read(F3,1),
- ?line {ok,TestDataLine2} = rpc:call(N1,file,read,[F3,DataLen2]),
- ?line {ok,_} = file:read(F3,1),
- ?line eof = rpc:call(N1,file,read,[F3,1]),
-
+ SPid3 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
+ {ok,F3} = receive
+ {SPid3,Res3} ->
+ Res3
+ after 5000 ->
+ exit(timeout)
+ end,
+
+ file:position(F3,0),
+ {ok,[TestDataLine1]} = io:fread(F3,'',"~s"),
+ {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F3,'',"~s"]),
+
+
+ file:position(F3,0),
+ {ok,TestDataLine1} = file:read(F3,DataLen1),
+ {ok,_} = file:read(F3,1),
+ {ok,TestDataLine2} = rpc:call(N1,file,read,[F3,DataLen2]),
+ {ok,_} = file:read(F3,1),
+ eof = rpc:call(N1,file,read,[F3,1]),
+
%% So, lets do it all again, but the other way around
{ok,F4} = file:open(FileName1,[read]),
- ?line TestDataLine1 = chomp(io:get_line(F4,'')),
- ?line file:position(F4,0),
- ?line io:setopts(F4,[binary]),
- ?line TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- ?line TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- ?line file:position(F4,0),
- ?line TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- ?line TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- ?line file:position(F4,0),
- ?line TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- ?line TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- ?line file:position(F4,0),
- ?line TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- ?line TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- ?line eof = chomp(rpc:call(N1,io,get_line,[F4,''])),
- ?line file:position(F4,0),
- ?line TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F4,'',3]),
+ TestDataLine1 = chomp(io:get_line(F4,'')),
+ file:position(F4,0),
+ io:setopts(F4,[binary]),
+ TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
+ TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
+ file:position(F4,0),
+ TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
+ TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
+ file:position(F4,0),
+ TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
+ TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
+ file:position(F4,0),
+ TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
+ TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
+ eof = chomp(rpc:call(N1,io,get_line,[F4,''])),
+ file:position(F4,0),
+ TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F4,'',3]),
io:get_chars(F4,'',1),
- ?line TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- ?line file:position(F4,0),
- ?line {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
- ?line {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
- ?line file:position(F4,0),
- ?line {ok,TestDataLine1BinLatin} = file:read(F4,DataLen1),
- ?line {ok,_} = file:read(F4,1),
- ?line {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F4,DataLen2]),
- ?line {ok,_} = file:read(F4,1),
- ?line eof = rpc:call(N1,file,read,[F4,1]),
- ?line io:setopts(F4,[list]),
-
- ?line file:position(F4,0),
- ?line {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
- ?line {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
-
-
- ?line file:position(F4,0),
- ?line {ok,TestDataLine1} = file:read(F4,DataLen1),
- ?line {ok,_} = file:read(F4,1),
- ?line {ok,TestDataLine2} = rpc:call(N1,file,read,[F4,DataLen2]),
- ?line {ok,_} = file:read(F4,1),
- ?line eof = rpc:call(N1,file,read,[F4,1]),
-
+ TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
+ file:position(F4,0),
+ {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
+ {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
+ file:position(F4,0),
+ {ok,TestDataLine1BinLatin} = file:read(F4,DataLen1),
+ {ok,_} = file:read(F4,1),
+ {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F4,DataLen2]),
+ {ok,_} = file:read(F4,1),
+ eof = rpc:call(N1,file,read,[F4,1]),
+ io:setopts(F4,[list]),
+
+ file:position(F4,0),
+ {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
+ {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
+
+
+ file:position(F4,0),
+ {ok,TestDataLine1} = file:read(F4,DataLen1),
+ {ok,_} = file:read(F4,1),
+ {ok,TestDataLine2} = rpc:call(N1,file,read,[F4,DataLen2]),
+ {ok,_} = file:read(F4,1),
+ eof = rpc:call(N1,file,read,[F4,1]),
+
file:close(F4),
test_server:stop_node(N1),
ok.
@@ -887,7 +887,7 @@ hold_the_line(Parent,Filename,Options) ->
die ->
ok
end.
-
+
%% Test io protocol compatibility with R12 nodes (terminals).
bc_with_r12_gl(Config) when is_list(Config) ->
@@ -920,7 +920,7 @@ bc_with_r12_ogl(Config) when is_list(Config) ->
bc_with_r12_gl_1(_Config,Machine) ->
PA = filename:dirname(code:which(?MODULE)),
Name1 = io_proto_r12_gl_1,
- ?line N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
+ N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
test_server:start_node(Name1, peer, [{args, "-pz \""++PA++"\""},
{erl,[{release,"r12b"}]}]),
TestDataLine1 = [229,228,246],
@@ -932,141 +932,141 @@ bc_with_r12_gl_1(_Config,Machine) ->
register(io_proto_suite,self()),
AM1 = spawn(?MODULE,Machine,
[MyNodeList, "io_proto_suite", N2List]),
-
- ?line GL = receive X when is_pid(X) -> X end,
+
+ GL = receive X when is_pid(X) -> X end,
%% get_line
- ?line "Hej\n" = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line <<"Hej\n">> = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- ?line io:setopts(GL,[{encoding,unicode}]),
-
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
-
+ "Hej\n" = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ <<"Hej\n">> = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
+ io:setopts(GL,[{encoding,unicode}]),
+
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
+
%%get_chars
- ?line "Hej" = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line <<"Hej">> = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[{encoding,unicode}]),
-
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
+ "Hej" = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ <<"Hej">> = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[{encoding,unicode}]),
+
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
%%fread
- ?line {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[{encoding,unicode}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
-
-
- ?line receive
- {AM1,done} ->
- ok
- after 5000 ->
- exit(timeout)
- end,
+ {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[{encoding,unicode}]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
+
+
+ receive
+ {AM1,done} ->
+ ok
+ after 5000 ->
+ exit(timeout)
+ end,
test_server:stop_node(N1),
ok.
-
+
answering_machine1(OthNode,OthReg,Me) ->
TestDataLine1 = [229,228,246],
TestDataUtf = binary_to_list(unicode:characters_to_binary(TestDataLine1)),
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline, "2"},
- {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
- {getline, "<"},
- %% get_line
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- %% get_chars
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- %% fread
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"}
-
- ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "),
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline, "2"},
+ {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
+ {getline, "<"},
+ %% get_line
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ %% get_chars
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ %% fread
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"}
+
+ ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
@@ -1074,74 +1074,74 @@ answering_machine1(OthNode,OthReg,Me) ->
answering_machine2(OthNode,OthReg,Me) ->
TestDataLine1 = [229,228,246],
TestDataUtf = binary_to_list(unicode:characters_to_binary(TestDataLine1)),
- ?line rtnode([{putline,""},
- {putline, "2."},
- {getline, "2"},
- {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
- {getline_re, ".*<[0-9].*"},
- %% get_line
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- %% get_chars
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- %% fread
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, "Hej"},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataLine1},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"},
- {getline_re, ".*Prompt"},
- {putline, TestDataUtf},
- {getline_re, ".*Okej"}
-
- ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "," -oldshell "),
+ rtnode([{putline,""},
+ {putline, "2."},
+ {getline, "2"},
+ {putline, "{"++OthReg++","++OthNode++"} ! group_leader()."},
+ {getline_re, ".*<[0-9].*"},
+ %% get_line
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ %% get_chars
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ %% fread
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, "Hej"},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataLine1},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"},
+ {getline_re, ".*Prompt"},
+ {putline, TestDataUtf},
+ {getline_re, ".*Okej"}
+
+ ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "," -oldshell "),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
-
+
%% Test various modes when reading from the group leade from another machine.
read_modes_ogl(Config) when is_list(Config) ->
@@ -1173,72 +1173,72 @@ read_modes_gl_1(_Config,Machine) ->
register(io_proto_suite,self()),
AM1 = spawn(?MODULE,Machine,
[MyNodeList, "io_proto_suite", N2List]),
-
- ?line GL = receive X when is_pid(X) -> X end,
+
+ GL = receive X when is_pid(X) -> X end,
?dbg({group_leader,X}),
%% get_line
- ?line receive after 500 -> ok end, % Dont clash with the new shell...
- ?line "Hej\n" = io:get_line(GL,"Prompt\n"),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line <<"Hej\n">> = io:get_line(GL,"Prompt\n"),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = chomp(io:request(GL,{get_line,latin1,"Prompt\n"})),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- ?line io:setopts(GL,[{encoding,unicode}]),
-
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = chomp(io:request(GL,{get_line,latin1,"Prompt\n"})),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
-
+ receive after 500 -> ok end, % Dont clash with the new shell...
+ "Hej\n" = io:get_line(GL,"Prompt\n"),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ <<"Hej\n">> = io:get_line(GL,"Prompt\n"),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = chomp(io:request(GL,{get_line,latin1,"Prompt\n"})),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
+ io:setopts(GL,[{encoding,unicode}]),
+
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = chomp(io:request(GL,{get_line,latin1,"Prompt\n"})),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
+
%%get_chars
- ?line "Hej" = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line <<"Hej">> = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = io:request(GL,{get_chars,latin1,"Prompt\n",3}),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[{encoding,unicode}]),
-
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinLatin = io:request(GL,{get_chars,latin1,"Prompt\n",3}),
- ?line io:format(GL,"Okej~n",[]),
- ?line TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
+ "Hej" = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ <<"Hej">> = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = io:request(GL,{get_chars,latin1,"Prompt\n",3}),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[{encoding,unicode}]),
+
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinLatin = io:request(GL,{get_chars,latin1,"Prompt\n",3}),
+ io:format(GL,"Okej~n",[]),
+ TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
%%fread
- ?line {ok,["Hej"]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[binary]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,["Hej"]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[{encoding,latin1}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[{encoding,unicode}]),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:format(GL,"Okej~n",[]),
- ?line {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- ?line io:setopts(GL,[list]),
- ?line io:format(GL,"Okej~n",[]),
-
-
- ?line receive
- {AM1,done} ->
- ok
- after 5000 ->
- exit(timeout)
- end,
+ {ok,["Hej"]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[binary]),
+ io:format(GL,"Okej~n",[]),
+ {ok,["Hej"]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[{encoding,latin1}]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[{encoding,unicode}]),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:format(GL,"Okej~n",[]),
+ {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
+ io:setopts(GL,[list]),
+ io:format(GL,"Okej~n",[]),
+
+
+ receive
+ {AM1,done} ->
+ ok
+ after 5000 ->
+ exit(timeout)
+ end,
ok.
@@ -1252,10 +1252,10 @@ broken_unicode(Config) when is_list(Config) ->
lists:duplicate(10,lists:seq(0,255))),
file:write_file(Latin1Name,Latin1Data),
file:write_file(Utf8Name,Utf8Data),
- ?line [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf8) || N <- lists:seq(1,100)++[1024,2048,10000]],
- ?line [ utf8 = heuristic_encoding_file2(Utf8Name,N,utf8) || N <- lists:seq(1,100)++[1024,2048,10000]],
- ?line [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf16) || N <- lists:seq(1,100)++[1024,2048,10000]],
- ?line [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf32) || N <- lists:seq(1,100)++[1024,2048,10000]],
+ [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf8) || N <- lists:seq(1,100)++[1024,2048,10000]],
+ [ utf8 = heuristic_encoding_file2(Utf8Name,N,utf8) || N <- lists:seq(1,100)++[1024,2048,10000]],
+ [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf16) || N <- lists:seq(1,100)++[1024,2048,10000]],
+ [ latin1 = heuristic_encoding_file2(Latin1Name,N,utf32) || N <- lists:seq(1,100)++[1024,2048,10000]],
ok.
@@ -1294,10 +1294,10 @@ eof_on_pipe(Config) when is_list(Config) ->
end
end,
CommandLine1 = EchoLine ++
- "\""++Erl++"\" -noshell -eval "
- "'io:format(\"~p\",[io:get_line(\"\")]),"
- "io:format(\"~p\",[io:get_line(\"\")]),"
- "io:format(\"~p\",[io:get_line(\"\")]).' -run init stop",
+ "\""++Erl++"\" -noshell -eval "
+ "'io:format(\"~p\",[io:get_line(\"\")]),"
+ "io:format(\"~p\",[io:get_line(\"\")]),"
+ "io:format(\"~p\",[io:get_line(\"\")]).' -run init stop",
case os:cmd(CommandLine1) of
"\"a\\n\"\"bu\"eof" ->
ok;
@@ -1305,10 +1305,10 @@ eof_on_pipe(Config) when is_list(Config) ->
exit({unexpected1,Other1})
end,
CommandLine2 = EchoLine ++
- "\""++Erl++"\" -noshell -eval "
- "'io:setopts([binary]),io:format(\"~p\",[io:get_line(\"\")]),"
- "io:format(\"~p\",[io:get_line(\"\")]),"
- "io:format(\"~p\",[io:get_line(\"\")]).' -run init stop",
+ "\""++Erl++"\" -noshell -eval "
+ "'io:setopts([binary]),io:format(\"~p\",[io:get_line(\"\")]),"
+ "io:format(\"~p\",[io:get_line(\"\")]),"
+ "io:format(\"~p\",[io:get_line(\"\")]).' -run init stop",
case os:cmd(CommandLine2) of
"<<\"a\\n\">><<\"bu\">>eof" ->
ok;
@@ -1317,12 +1317,12 @@ eof_on_pipe(Config) when is_list(Config) ->
end
catch
throw:skip ->
- {skipped,"unsupported echo program"}
+ {skipped,"unsupported echo program"}
end;
{_,_} ->
{skipped,"Only on linux"}
end.
-
+
%%
%% Tool for running interactive shell (stolen from the kernel
@@ -1392,16 +1392,16 @@ timeout(normal) ->
-ifndef(debug).
rm_rf(Dir) ->
try
- {ok,List} = file:list_dir(Dir),
- Files = [filename:join([Dir,X]) || X <- List],
- [case file:list_dir(Y) of
- {error, enotdir} ->
- ok = file:delete(Y);
- _ ->
- ok = rm_rf(Y)
- end || Y <- Files],
- ok = file:del_dir(Dir),
- ok
+ {ok,List} = file:list_dir(Dir),
+ Files = [filename:join([Dir,X]) || X <- List],
+ [case file:list_dir(Y) of
+ {error, enotdir} ->
+ ok = file:delete(Y);
+ _ ->
+ ok = rm_rf(Y)
+ end || Y <- Files],
+ ok = file:del_dir(Dir),
+ ok
catch
_:Exception -> {error, {Exception,Dir}}
end.
@@ -1466,7 +1466,7 @@ get_and_put(CPid, [{putline_raw, Line}|T],N) ->
Timeout = timeout(normal),
receive
{send_line, ok} ->
- get_and_put(CPid, T,N+1)
+ get_and_put(CPid, T,N+1)
after Timeout ->
error_logger:error_msg("~p: putline_raw timeout (~p) sending "
"\"~s\" (command number ~p)~n",
@@ -1480,7 +1480,7 @@ get_and_put(CPid, [{putline, Line}|T],N) ->
Timeout = timeout(normal),
receive
{send_line, ok} ->
- get_and_put(CPid, [{getline, []}|T],N)
+ get_and_put(CPid, [{getline, []}|T],N)
after Timeout ->
error_logger:error_msg("~p: putline timeout (~p) sending "
"\"~s\" (command number ~p)~n[~p]~n",
@@ -1497,8 +1497,8 @@ wait_for_runerl_server(SPid) ->
after Timeout ->
{error, timeout}
end.
-
-
+
+
stop_runerl_node(CPid) ->
Ref = erlang:monitor(process, CPid),
@@ -1549,8 +1549,8 @@ create_tempdir(Dir,X) when X > $Z, X < $a ->
create_tempdir(Dir,$a);
create_tempdir(Dir,X) when X > $z ->
Estr = lists:flatten(
- io_lib:format("Unable to create ~s, reason eexist",
- [Dir++[$z]])),
+ io_lib:format("Unable to create ~s, reason eexist",
+ [Dir++[$z]])),
{error, Estr};
create_tempdir(Dir0, Ch) ->
%% Expect fairly standard unix.
@@ -1591,8 +1591,8 @@ start_runerl_node(RunErl,Erl,Tempdir,Nodename,Extra) ->
[];
_ ->
" -sname "++(if is_atom(Nodename) -> atom_to_list(Nodename);
- true -> Nodename
- end)++
+ true -> Nodename
+ end)++
" -setcookie "++atom_to_list(erlang:get_cookie())
end,
XXArg = case Extra of
@@ -1603,9 +1603,9 @@ start_runerl_node(RunErl,Erl,Tempdir,Nodename,Extra) ->
end,
spawn(fun() ->
?dbg("\""++RunErl++"\" "++Tempdir++"/ "++Tempdir++
- " \""++Erl++XArg++XXArg++"\""),
+ " \""++Erl++XArg++XXArg++"\""),
os:cmd("\""++RunErl++"\" "++Tempdir++"/ "++Tempdir++
- " \""++Erl++XArg++XXArg++"\"")
+ " \""++Erl++XArg++XXArg++"\"")
end).
start_toerl_server(ToErl,Tempdir) ->
@@ -1663,7 +1663,7 @@ toerl_loop(Port,Acc) ->
_ ->
toerl_loop(Port,[{Tag0,Data}|Acc])
end;
- {Pid,{get_line,Timeout}} ->
+ {Pid,{get_line,Timeout}} ->
case Acc of
[] ->
case get_data_within(Port,Timeout,[]) of
@@ -1712,10 +1712,10 @@ toerl_loop(Port,Acc) ->
Other ->
{error, {unexpected, Other}}
end.
-
+
millistamp() ->
erlang:monotonic_time(milli_seconds).
-
+
get_data_within(Port, X, Acc) when X =< 0 ->
?dbg({get_data_within, X, Acc, ?LINE}),
receive
@@ -1834,8 +1834,8 @@ request({get_until, Encoding, Prompt, M, F, As}, State) ->
{ok, convert(State#state.nxt, Encoding, State#state.mode), State#state{nxt = eof, q = [{get_until, Encoding, Prompt, M, F, As} | State#state.q]}};
request({get_chars, Encoding, Prompt, N}, State) ->
{ok, convert(State#state.nxt, Encoding, State#state.mode), State#state{nxt = eof,
- q = [{get_chars, Encoding, Prompt, N} |
- State#state.q]}};
+ q = [{get_chars, Encoding, Prompt, N} |
+ State#state.q]}};
request({get_line, Encoding, Prompt}, State) ->
{ok, convert(State#state.nxt, Encoding, State#state.mode),
State#state{nxt = eof,
@@ -1867,7 +1867,7 @@ request(getopts, State) ->
binary -> [{binary, true}]
end, State#state{q=[getopts | State#state.q ]}};
request({requests, Reqs}, State) ->
- multi_request(Reqs, {ok, ok, State}).
+ multi_request(Reqs, {ok, ok, State}).
multi_request([R|Rs], {ok, _Res, State}) ->
multi_request(Rs, request(R, State));
@@ -1898,7 +1898,7 @@ convert(Data, latin1, binary) ->
_ ->
{error, {cannot_convert, unicode, latin1}}
end.
-
+
hostname() ->
from($@, atom_to_list(node())).
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 14ac9ce874..b21eb37ee3 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -35,7 +35,7 @@
keystore/1, keytake/1, keyreplace/1,
append_1/1, append_2/1,
seq_loop/1, seq_2/1, seq_3/1, seq_2_e/1, seq_3_e/1,
-
+
sublist_2/1, sublist_3/1, sublist_2_e/1, sublist_3_e/1,
flatten_1/1, flatten_2/1, flatten_1_e/1, flatten_2_e/1,
dropwhile/1, takewhile/1,
@@ -147,38 +147,38 @@ end_per_testcase(_Case, _Config) ->
%%
append_1(Config) when is_list(Config) ->
- ?line "abcdef"=lists:append(["abc","def"]),
- ?line [hej, du,[glade, [bagare]]]=
+ "abcdef"=lists:append(["abc","def"]),
+ [hej, du,[glade, [bagare]]]=
lists:append([[hej], [du], [[glade, [bagare]]]]),
- ?line [10, [elem]]=lists:append([[10], [[elem]]]),
+ [10, [elem]]=lists:append([[10], [[elem]]]),
ok.
append_2(Config) when is_list(Config) ->
- ?line "abcdef"=lists:append("abc", "def"),
- ?line [hej, du]=lists:append([hej], [du]),
- ?line [10, [elem]]=lists:append([10], [[elem]]),
+ "abcdef"=lists:append("abc", "def"),
+ [hej, du]=lists:append([hej], [du]),
+ [10, [elem]]=lists:append([10], [[elem]]),
ok.
%% Tests the lists:reverse() implementation. The function is
%% `non-blocking', and only processes a fixed number of elements at a
%% time.
reverse(Config) when is_list(Config) ->
- ?line reverse_test(0),
- ?line reverse_test(1),
- ?line reverse_test(2),
- ?line reverse_test(128),
- ?line reverse_test(256),
- ?line reverse_test(1000),
- ?line reverse_test(1998),
- ?line reverse_test(1999),
- ?line reverse_test(2000),
- ?line reverse_test(2001),
- ?line reverse_test(3998),
- ?line reverse_test(3999),
- ?line reverse_test(4000),
- ?line reverse_test(4001),
- ?line reverse_test(60001),
- ?line reverse_test(100007),
+ reverse_test(0),
+ reverse_test(1),
+ reverse_test(2),
+ reverse_test(128),
+ reverse_test(256),
+ reverse_test(1000),
+ reverse_test(1998),
+ reverse_test(1999),
+ reverse_test(2000),
+ reverse_test(2001),
+ reverse_test(3998),
+ reverse_test(3999),
+ reverse_test(4000),
+ reverse_test(4001),
+ reverse_test(60001),
+ reverse_test(100007),
ok.
reverse_test(0) ->
@@ -199,22 +199,22 @@ reverse_test(Num) ->
%% Test the lists:member() implementation. This test case depends on
%% lists:reverse() to work, wich is tested in a separate test case.
member(Config) when is_list(Config) ->
- ?line {'EXIT',{badarg,_}} = (catch lists:member(45, {a,b,c})),
- ?line {'EXIT',{badarg,_}} = (catch lists:member(45, [0|non_list_tail])),
- ?line false = lists:member(4233, []),
- ?line member_test(1),
- ?line member_test(100),
- ?line member_test(256),
- ?line member_test(1000),
- ?line member_test(1998),
- ?line member_test(1999),
- ?line member_test(2000),
- ?line member_test(2001),
- ?line member_test(3998),
- ?line member_test(3999),
- ?line member_test(4000),
- ?line member_test(4001),
- ?line member_test(100008),
+ {'EXIT',{badarg,_}} = (catch lists:member(45, {a,b,c})),
+ {'EXIT',{badarg,_}} = (catch lists:member(45, [0|non_list_tail])),
+ false = lists:member(4233, []),
+ member_test(1),
+ member_test(100),
+ member_test(256),
+ member_test(1000),
+ member_test(1998),
+ member_test(1999),
+ member_test(2000),
+ member_test(2001),
+ member_test(3998),
+ member_test(3999),
+ member_test(4000),
+ member_test(4001),
+ member_test(100008),
ok.
member_test(Num) ->
@@ -230,78 +230,78 @@ member_test(Num) ->
false = lists:member({a,b,c}, List).
keymember(Config) when is_list(Config) ->
- ?line false = lists:keymember(anything_goes, 1, []),
- ?line {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, -1, [])),
- ?line {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, 0, [])),
- ?line {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, 1, {1,2,3})),
+ false = lists:keymember(anything_goes, 1, []),
+ {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, -1, [])),
+ {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, 0, [])),
+ {'EXIT',{badarg,_}} = (catch lists:keymember(anything_goes, 1, {1,2,3})),
List = [{52.0,a},{-19,b,c},{37.5,d},an_atom,42.0,{39},{45,{x,y,z}}],
- ?line false = lists:keymember(333, 5, List),
- ?line false = lists:keymember(333, 999, List),
- ?line false = lists:keymember(37, 1, List),
-
- ?line true = lists:keymember(52.0, 1, List),
- ?line true = lists:keymember(52, 1, List),
- ?line true = lists:keymember(-19, 1, List),
- ?line true = lists:keymember(-19.0, 1, List),
- ?line true = lists:keymember(37.5, 1, List),
- ?line true = lists:keymember(39, 1, List),
- ?line true = lists:keymember(39.0, 1, List),
- ?line true = lists:keymember(45, 1, List),
- ?line true = lists:keymember(45.0, 1, List),
-
- ?line true = lists:keymember(a, 2, List),
- ?line true = lists:keymember(b, 2, List),
- ?line true = lists:keymember(c, 3, List),
- ?line true = lists:keymember(d, 2, List),
- ?line true = lists:keymember({x,y,z}, 2, List),
-
- ?line Long0 = lists:seq(1, 100007),
- ?line false = lists:keymember(kalle, 1, Long0),
- ?line Long = lists:foldl(fun(E, A) -> [{1/E,E}|A] end, [], Long0),
- ?line true = lists:keymember(1, 2, Long),
- ?line true = lists:keymember(2, 2, Long),
- ?line true = lists:keymember(1.0, 2, Long),
- ?line true = lists:keymember(2.0, 2, Long),
- ?line true = lists:keymember(100006, 2, Long),
+ false = lists:keymember(333, 5, List),
+ false = lists:keymember(333, 999, List),
+ false = lists:keymember(37, 1, List),
+
+ true = lists:keymember(52.0, 1, List),
+ true = lists:keymember(52, 1, List),
+ true = lists:keymember(-19, 1, List),
+ true = lists:keymember(-19.0, 1, List),
+ true = lists:keymember(37.5, 1, List),
+ true = lists:keymember(39, 1, List),
+ true = lists:keymember(39.0, 1, List),
+ true = lists:keymember(45, 1, List),
+ true = lists:keymember(45.0, 1, List),
+
+ true = lists:keymember(a, 2, List),
+ true = lists:keymember(b, 2, List),
+ true = lists:keymember(c, 3, List),
+ true = lists:keymember(d, 2, List),
+ true = lists:keymember({x,y,z}, 2, List),
+
+ Long0 = lists:seq(1, 100007),
+ false = lists:keymember(kalle, 1, Long0),
+ Long = lists:foldl(fun(E, A) -> [{1/E,E}|A] end, [], Long0),
+ true = lists:keymember(1, 2, Long),
+ true = lists:keymember(2, 2, Long),
+ true = lists:keymember(1.0, 2, Long),
+ true = lists:keymember(2.0, 2, Long),
+ true = lists:keymember(100006, 2, Long),
ok.
keysearch_keyfind(Config) when is_list(Config) ->
- ?line false = key_search_find(anything_goes, 1, []),
- ?line {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, -1, [])),
- ?line {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, 0, [])),
- ?line {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, 1, {1,2,3})),
+ false = key_search_find(anything_goes, 1, []),
+ {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, -1, [])),
+ {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, 0, [])),
+ {'EXIT',{badarg,_}} = (catch key_search_find(anything_goes, 1, {1,2,3})),
First = {x,42.0},
Second = {y,-77},
Third = {z,[a,b,c],{5.0}},
List = [First,Second,Third],
-
- ?line false = key_search_find(333, 1, []),
- ?line false = key_search_find(333, 5, List),
- ?line false = key_search_find(333, 999, List),
- ?line false = key_search_find(37, 1, List),
-
- ?line {value,First} = key_search_find(42, 2, List),
- ?line {value,First} = key_search_find(42.0, 2, List),
-
- ?line {value,Second} = key_search_find(-77, 2, List),
- ?line {value,Second} = key_search_find(-77.0, 2, List),
-
- ?line {value,Third} = key_search_find(z, 1, List),
- ?line {value,Third} = key_search_find([a,b,c], 2, List),
- ?line {value,Third} = key_search_find({5}, 3, List),
- ?line {value,Third} = key_search_find({5.0}, 3, List),
-
- ?line Long0 = lists:seq(1, 100007),
- ?line false = key_search_find(kalle, 1, Long0),
- ?line Long = lists:foldl(fun(E, A) -> [{1/E,float(E)}|A] end, [], Long0),
- ?line {value,{_,1.0}} = key_search_find(1, 2, Long),
- ?line {value,{_,1.0}} = key_search_find(1.0, 2, Long),
- ?line {value,{_,2.0}} = key_search_find(2, 2, Long),
- ?line {value,{_,2.0}} = key_search_find(2.0, 2, Long),
- ?line {value,{_,33988.0}} = key_search_find(33988, 2, Long),
- ?line {value,{_,33988.0}} = key_search_find(33988.0, 2, Long),
+
+ false = key_search_find(333, 1, []),
+ false = key_search_find(333, 5, List),
+ false = key_search_find(333, 999, List),
+ false = key_search_find(37, 1, List),
+
+ {value,First} = key_search_find(42, 2, List),
+ {value,First} = key_search_find(42.0, 2, List),
+
+ {value,Second} = key_search_find(-77, 2, List),
+ {value,Second} = key_search_find(-77.0, 2, List),
+
+ {value,Third} = key_search_find(z, 1, List),
+ {value,Third} = key_search_find([a,b,c], 2, List),
+ {value,Third} = key_search_find({5}, 3, List),
+ {value,Third} = key_search_find({5.0}, 3, List),
+
+ Long0 = lists:seq(1, 100007),
+ false = key_search_find(kalle, 1, Long0),
+ Long = lists:foldl(fun(E, A) -> [{1/E,float(E)}|A] end, [], Long0),
+ {value,{_,1.0}} = key_search_find(1, 2, Long),
+ {value,{_,1.0}} = key_search_find(1.0, 2, Long),
+ {value,{_,2.0}} = key_search_find(2, 2, Long),
+ {value,{_,2.0}} = key_search_find(2.0, 2, Long),
+ {value,{_,33988.0}} = key_search_find(33988, 2, Long),
+ {value,{_,33988.0}} = key_search_find(33988.0, 2, Long),
ok.
%% Test both lists:keysearch/3 and lists:keyfind/3. The only
@@ -317,29 +317,29 @@ key_search_find(Key, Pos, List) ->
end.
dropwhile(Config) when is_list(Config) ->
- ?line F = fun(C) -> C =:= $@ end,
+ F = fun(C) -> C =:= $@ end,
- ?line [] = lists:dropwhile(F, []),
- ?line [a] = lists:dropwhile(F, [a]),
- ?line [a,b] = lists:dropwhile(F, [a,b]),
- ?line [a,b,c] = lists:dropwhile(F, [a,b,c]),
+ [] = lists:dropwhile(F, []),
+ [a] = lists:dropwhile(F, [a]),
+ [a,b] = lists:dropwhile(F, [a,b]),
+ [a,b,c] = lists:dropwhile(F, [a,b,c]),
- ?line [] = lists:dropwhile(F, [$@]),
- ?line [] = lists:dropwhile(F, [$@,$@]),
- ?line [a,$@] = lists:dropwhile(F, [$@,a,$@]),
+ [] = lists:dropwhile(F, [$@]),
+ [] = lists:dropwhile(F, [$@,$@]),
+ [a,$@] = lists:dropwhile(F, [$@,a,$@]),
- ?line [$k] = lists:dropwhile(F, [$@,$k]),
- ?line [$k,$l] = lists:dropwhile(F, [$@,$@,$k,$l]),
- ?line [a] = lists:dropwhile(F, [$@,$@,$@,a]),
+ [$k] = lists:dropwhile(F, [$@,$k]),
+ [$k,$l] = lists:dropwhile(F, [$@,$@,$k,$l]),
+ [a] = lists:dropwhile(F, [$@,$@,$@,a]),
- ?line [a,$@,b] = lists:dropwhile(F, [$@,a,$@,b]),
- ?line [a,$@,b] = lists:dropwhile(F, [$@,$@,a,$@,b]),
- ?line [a,$@,b] = lists:dropwhile(F, [$@,$@,$@,a,$@,b]),
+ [a,$@,b] = lists:dropwhile(F, [$@,a,$@,b]),
+ [a,$@,b] = lists:dropwhile(F, [$@,$@,a,$@,b]),
+ [a,$@,b] = lists:dropwhile(F, [$@,$@,$@,a,$@,b]),
Long = lists:seq(1, 1024),
Shorter = lists:seq(800, 1024),
- ?line Shorter = lists:dropwhile(fun(E) -> E < 800 end, Long),
+ Shorter = lists:dropwhile(fun(E) -> E < 800 end, Long),
ok.
@@ -371,34 +371,34 @@ takewhile(Config) when is_list(Config) ->
ok.
keystore(Config) when is_list(Config) ->
- ?line {'EXIT',_} = (catch lists:keystore(key, 0, [], {1})),
- ?line {'EXIT',_} = (catch lists:keystore(key, 1, {}, {})),
- ?line {'EXIT',_} = (catch lists:keystore(key, 1, {a,b}, {})),
- ?line {'EXIT', _} = (catch lists:keystore(a, 2, [{1,a}], b)),
+ {'EXIT',_} = (catch lists:keystore(key, 0, [], {1})),
+ {'EXIT',_} = (catch lists:keystore(key, 1, {}, {})),
+ {'EXIT',_} = (catch lists:keystore(key, 1, {a,b}, {})),
+ {'EXIT', _} = (catch lists:keystore(a, 2, [{1,a}], b)),
T = {k,17},
- ?line [T] = lists:keystore(a, 2, [], T),
- ?line [{1,a},{2,b},{k,17}] = lists:keystore(c, 2, [{1,a},{2,b}],T),
+ [T] = lists:keystore(a, 2, [], T),
+ [{1,a},{2,b},{k,17}] = lists:keystore(c, 2, [{1,a},{2,b}],T),
L = [{1,a},{2,b},{3,c}],
- ?line [{k,17},{2,b},{3,c}] = lists:keystore(a, 2, L, T),
- ?line [{1,a},{k,17},{3,c}] = lists:keystore(b, 2, L, T),
- ?line [{1,a},{2,b},{k,17}] = lists:keystore(c, 2, L, T),
- ?line [{2,b}] = lists:keystore(a, 2, [{1,a}], {2,b}),
- ?line [{1,a}] = lists:keystore(foo, 1, [], {1,a}),
+ [{k,17},{2,b},{3,c}] = lists:keystore(a, 2, L, T),
+ [{1,a},{k,17},{3,c}] = lists:keystore(b, 2, L, T),
+ [{1,a},{2,b},{k,17}] = lists:keystore(c, 2, L, T),
+ [{2,b}] = lists:keystore(a, 2, [{1,a}], {2,b}),
+ [{1,a}] = lists:keystore(foo, 1, [], {1,a}),
ok.
keytake(Config) when is_list(Config) ->
- ?line {'EXIT',_} = (catch lists:keytake(key, 0, [])),
- ?line {'EXIT',_} = (catch lists:keytake(key, 1, {})),
- ?line {'EXIT',_} = (catch lists:keytake(key, 1, {a,b})),
- ?line false = lists:keytake(key, 2, [{a}]),
- ?line false = lists:keytake(key, 1, [a]),
- ?line false = lists:keytake(k, 1, []),
- ?line false = lists:keytake(k, 1, [{a},{b},{c}]),
+ {'EXIT',_} = (catch lists:keytake(key, 0, [])),
+ {'EXIT',_} = (catch lists:keytake(key, 1, {})),
+ {'EXIT',_} = (catch lists:keytake(key, 1, {a,b})),
+ false = lists:keytake(key, 2, [{a}]),
+ false = lists:keytake(key, 1, [a]),
+ false = lists:keytake(k, 1, []),
+ false = lists:keytake(k, 1, [{a},{b},{c}]),
L = [{a,1},{b,2},{c,3}],
- ?line {value,{a,1},[{b,2},{c,3}]} = lists:keytake(1, 2, L),
- ?line {value,{b,2},[{a,1},{c,3}]} = lists:keytake(2, 2, L),
- ?line {value,{c,3},[{a,1},{b,2}]} = lists:keytake(3, 2, L),
- ?line false = lists:keytake(4, 2, L),
+ {value,{a,1},[{b,2},{c,3}]} = lists:keytake(1, 2, L),
+ {value,{b,2},[{a,1},{c,3}]} = lists:keytake(2, 2, L),
+ {value,{c,3},[{a,1},{b,2}]} = lists:keytake(3, 2, L),
+ false = lists:keytake(4, 2, L),
ok.
%% Test lists:keyreplace/4.
@@ -415,61 +415,61 @@ keyreplace(Config) when is_list(Config) ->
merge(Config) when is_list(Config) ->
%% merge list of lists
- ?line [] = lists:merge([]),
- ?line [] = lists:merge([[]]),
- ?line [] = lists:merge([[],[]]),
- ?line [] = lists:merge([[],[],[]]),
- ?line [1] = lists:merge([[1]]),
- ?line [1,1,2,2] = lists:merge([[1,2],[1,2]]),
- ?line [1] = lists:merge([[1],[],[]]),
- ?line [1] = lists:merge([[],[1],[]]),
- ?line [1] = lists:merge([[],[],[1]]),
- ?line [1,2] = lists:merge([[1],[2],[]]),
- ?line [1,2] = lists:merge([[1],[],[2]]),
- ?line [1,2] = lists:merge([[],[1],[2]]),
- ?line [1,2,3,4,5,6] = lists:merge([[1,2],[],[5,6],[],[3,4],[]]),
- ?line [1,2,3,4] = lists:merge([[4],[3],[2],[1]]),
- ?line [1,2,3,4,5] = lists:merge([[1],[2],[3],[4],[5]]),
- ?line [1,2,3,4,5,6] = lists:merge([[1],[2],[3],[4],[5],[6]]),
- ?line [1,2,3,4,5,6,7,8,9] =
+ [] = lists:merge([]),
+ [] = lists:merge([[]]),
+ [] = lists:merge([[],[]]),
+ [] = lists:merge([[],[],[]]),
+ [1] = lists:merge([[1]]),
+ [1,1,2,2] = lists:merge([[1,2],[1,2]]),
+ [1] = lists:merge([[1],[],[]]),
+ [1] = lists:merge([[],[1],[]]),
+ [1] = lists:merge([[],[],[1]]),
+ [1,2] = lists:merge([[1],[2],[]]),
+ [1,2] = lists:merge([[1],[],[2]]),
+ [1,2] = lists:merge([[],[1],[2]]),
+ [1,2,3,4,5,6] = lists:merge([[1,2],[],[5,6],[],[3,4],[]]),
+ [1,2,3,4] = lists:merge([[4],[3],[2],[1]]),
+ [1,2,3,4,5] = lists:merge([[1],[2],[3],[4],[5]]),
+ [1,2,3,4,5,6] = lists:merge([[1],[2],[3],[4],[5],[6]]),
+ [1,2,3,4,5,6,7,8,9] =
lists:merge([[1],[2],[3],[4],[5],[6],[7],[8],[9]]),
Seq = lists:seq(1,100),
- ?line true = Seq == lists:merge(lists:map(fun(E) -> [E] end, Seq)),
+ true = Seq == lists:merge(lists:map(fun(E) -> [E] end, Seq)),
Two = [1,2],
Six = [1,2,3,4,5,6],
%% 2-way merge
- ?line [] = lists:merge([], []),
- ?line Two = lists:merge(Two, []),
- ?line Two = lists:merge([], Two),
- ?line Six = lists:merge([1,3,5], [2,4,6]),
- ?line Six = lists:merge([2,4,6], [1,3,5]),
- ?line Six = lists:merge([1,2,3], [4,5,6]),
- ?line Six = lists:merge([4,5,6], [1,2,3]),
- ?line Six = lists:merge([1,2,5],[3,4,6]),
- ?line [1,2,3,5,7] = lists:merge([1,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:merge([1,3,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:merge([1,3,5,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:merge([2], [1,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:merge([2,4], [1,3,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:merge([2,4,6], [1,3,5,7]),
+ [] = lists:merge([], []),
+ Two = lists:merge(Two, []),
+ Two = lists:merge([], Two),
+ Six = lists:merge([1,3,5], [2,4,6]),
+ Six = lists:merge([2,4,6], [1,3,5]),
+ Six = lists:merge([1,2,3], [4,5,6]),
+ Six = lists:merge([4,5,6], [1,2,3]),
+ Six = lists:merge([1,2,5],[3,4,6]),
+ [1,2,3,5,7] = lists:merge([1,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:merge([1,3,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:merge([1,3,5,7], [2,4,6]),
+ [1,2,3,5,7] = lists:merge([2], [1,3,5,7]),
+ [1,2,3,4,5,7] = lists:merge([2,4], [1,3,5,7]),
+ [1,2,3,4,5,6,7] = lists:merge([2,4,6], [1,3,5,7]),
%% 3-way merge
- ?line [] = lists:merge3([], [], []),
- ?line Two = lists:merge3([], [], Two),
- ?line Two = lists:merge3([], Two, []),
- ?line Two = lists:merge3(Two, [], []),
- ?line Six = lists:merge3([], [1,3,5], [2,4,6]),
- ?line Six = lists:merge3([1,3,5], [], [2,4,6]),
- ?line Six = lists:merge3([1,3,5], [2,4,6], []),
- ?line Nine = lists:merge3([1,4,7],[2,5,8],[3,6,9]),
- ?line Nine = lists:merge3([1,4,7],[3,6,9],[2,5,8]),
- ?line Nine = lists:merge3([3,6,9],[1,4,7],[2,5,8]),
- ?line Nine = lists:merge3([4,5,6],[1,2,3],[7,8,9]),
- ?line Nine = lists:merge3([1,2,3],[4,5,6],[7,8,9]),
- ?line Nine = lists:merge3([7,8,9],[4,5,6],[1,2,3]),
- ?line Nine = lists:merge3([4,5,6],[7,8,9],[1,2,3]),
+ [] = lists:merge3([], [], []),
+ Two = lists:merge3([], [], Two),
+ Two = lists:merge3([], Two, []),
+ Two = lists:merge3(Two, [], []),
+ Six = lists:merge3([], [1,3,5], [2,4,6]),
+ Six = lists:merge3([1,3,5], [], [2,4,6]),
+ Six = lists:merge3([1,3,5], [2,4,6], []),
+ Nine = lists:merge3([1,4,7],[2,5,8],[3,6,9]),
+ Nine = lists:merge3([1,4,7],[3,6,9],[2,5,8]),
+ Nine = lists:merge3([3,6,9],[1,4,7],[2,5,8]),
+ Nine = lists:merge3([4,5,6],[1,2,3],[7,8,9]),
+ Nine = lists:merge3([1,2,3],[4,5,6],[7,8,9]),
+ Nine = lists:merge3([7,8,9],[4,5,6],[1,2,3]),
+ Nine = lists:merge3([4,5,6],[7,8,9],[1,2,3]),
ok.
@@ -480,64 +480,64 @@ rmerge(Config) when is_list(Config) ->
Six = [6,5,4,3,2,1],
%% 2-way reversed merge
- ?line [] = lists:rmerge([], []),
- ?line Two = lists:rmerge(Two, []),
- ?line Two = lists:rmerge([], Two),
- ?line Six = lists:rmerge([5,3,1], [6,4,2]),
- ?line Six = lists:rmerge([6,4,2], [5,3,1]),
- ?line Six = lists:rmerge([3,2,1], [6,5,4]),
- ?line Six = lists:rmerge([6,5,4], [3,2,1]),
- ?line Six = lists:rmerge([4,3,2],[6,5,1]),
- ?line [7,6,5,3,1] = lists:rmerge([7,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rmerge([7,5,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rmerge([7,5,3,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rmerge([2], [7,5,3,1]),
- ?line [7,5,4,3,2,1] = lists:rmerge([4,2], [7,5,3,1]),
- ?line [7,6,5,4,3,2,1] = lists:rmerge([6,4,2], [7,5,3,1]),
+ [] = lists:rmerge([], []),
+ Two = lists:rmerge(Two, []),
+ Two = lists:rmerge([], Two),
+ Six = lists:rmerge([5,3,1], [6,4,2]),
+ Six = lists:rmerge([6,4,2], [5,3,1]),
+ Six = lists:rmerge([3,2,1], [6,5,4]),
+ Six = lists:rmerge([6,5,4], [3,2,1]),
+ Six = lists:rmerge([4,3,2],[6,5,1]),
+ [7,6,5,3,1] = lists:rmerge([7,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rmerge([7,5,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rmerge([7,5,3,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rmerge([2], [7,5,3,1]),
+ [7,5,4,3,2,1] = lists:rmerge([4,2], [7,5,3,1]),
+ [7,6,5,4,3,2,1] = lists:rmerge([6,4,2], [7,5,3,1]),
Nine = [9,8,7,6,5,4,3,2,1],
%% 3-way reversed merge
- ?line [] = lists:rmerge3([], [], []),
- ?line Two = lists:rmerge3([], [], Two),
- ?line Two = lists:rmerge3([], Two, []),
- ?line Two = lists:rmerge3(Two, [], []),
- ?line Six = lists:rmerge3([], [5,3,1], [6,4,2]),
- ?line Six = lists:rmerge3([5,3,1], [], [6,4,2]),
- ?line Six = lists:rmerge3([5,3,1], [6,4,2], []),
- ?line Nine = lists:rmerge3([7,4,1],[8,5,2],[9,6,3]),
- ?line Nine = lists:rmerge3([7,4,1],[9,6,3],[8,5,2]),
- ?line Nine = lists:rmerge3([9,6,3],[7,4,1],[8,5,2]),
- ?line Nine = lists:rmerge3([6,5,4],[3,2,1],[9,8,7]),
- ?line Nine = lists:rmerge3([3,2,1],[6,5,4],[9,8,7]),
- ?line Nine = lists:rmerge3([9,8,7],[6,5,4],[3,2,1]),
- ?line Nine = lists:rmerge3([6,5,4],[9,8,7],[3,2,1]),
+ [] = lists:rmerge3([], [], []),
+ Two = lists:rmerge3([], [], Two),
+ Two = lists:rmerge3([], Two, []),
+ Two = lists:rmerge3(Two, [], []),
+ Six = lists:rmerge3([], [5,3,1], [6,4,2]),
+ Six = lists:rmerge3([5,3,1], [], [6,4,2]),
+ Six = lists:rmerge3([5,3,1], [6,4,2], []),
+ Nine = lists:rmerge3([7,4,1],[8,5,2],[9,6,3]),
+ Nine = lists:rmerge3([7,4,1],[9,6,3],[8,5,2]),
+ Nine = lists:rmerge3([9,6,3],[7,4,1],[8,5,2]),
+ Nine = lists:rmerge3([6,5,4],[3,2,1],[9,8,7]),
+ Nine = lists:rmerge3([3,2,1],[6,5,4],[9,8,7]),
+ Nine = lists:rmerge3([9,8,7],[6,5,4],[3,2,1]),
+ Nine = lists:rmerge3([6,5,4],[9,8,7],[3,2,1]),
ok.
sort_1(Config) when is_list(Config) ->
- ?line [] = lists:sort([]),
- ?line [a] = lists:sort([a]),
- ?line [a,a] = lists:sort([a,a]),
- ?line [a,b] = lists:sort([a,b]),
- ?line [a,b] = lists:sort([b,a]),
- ?line [1,1] = lists:sort([1,1]),
- ?line [1,1,2,3] = lists:sort([1,1,3,2]),
- ?line [1,2,3,3] = lists:sort([3,3,1,2]),
- ?line [1,1,1,1] = lists:sort([1,1,1,1]),
- ?line [1,1,1,2,2,2,3,3,3] = lists:sort([3,3,3,2,2,2,1,1,1]),
- ?line [1,1,1,2,2,2,3,3,3] = lists:sort([1,1,1,2,2,2,3,3,3]),
-
- ?line lists:foreach(fun check/1, perms([1,2,3])),
- ?line lists:foreach(fun check/1, perms([1,2,3,4,5,6,7,8])),
+ [] = lists:sort([]),
+ [a] = lists:sort([a]),
+ [a,a] = lists:sort([a,a]),
+ [a,b] = lists:sort([a,b]),
+ [a,b] = lists:sort([b,a]),
+ [1,1] = lists:sort([1,1]),
+ [1,1,2,3] = lists:sort([1,1,3,2]),
+ [1,2,3,3] = lists:sort([3,3,1,2]),
+ [1,1,1,1] = lists:sort([1,1,1,1]),
+ [1,1,1,2,2,2,3,3,3] = lists:sort([3,3,3,2,2,2,1,1,1]),
+ [1,1,1,2,2,2,3,3,3] = lists:sort([1,1,1,2,2,2,3,3,3]),
+
+ lists:foreach(fun check/1, perms([1,2,3])),
+ lists:foreach(fun check/1, perms([1,2,3,4,5,6,7,8])),
ok.
%% sort/1 on big randomized lists
sort_rand(Config) when is_list(Config) ->
- ?line ok = check(biglist(10)),
- ?line ok = check(biglist(100)),
- ?line ok = check(biglist(1000)),
- ?line ok = check(biglist(10000)),
+ ok = check(biglist(10)),
+ ok = check(biglist(100)),
+ ok = check(biglist(1000)),
+ ok = check(biglist(10000)),
ok.
%% sort/1 was really stable for a while - the order of equal elements
@@ -546,13 +546,13 @@ sort_rand(Config) when is_list(Config) ->
%% sort/1 should be stable for equal terms.
sort_stable(Config) when is_list(Config) ->
- ?line ok = check_stability(bigfunlist(10)),
- ?line ok = check_stability(bigfunlist(100)),
- ?line ok = check_stability(bigfunlist(1000)),
- ?line case erlang:system_info(modified_timing_level) of
- undefined -> ok = check_stability(bigfunlist(10000));
- _ -> ok
- end,
+ ok = check_stability(bigfunlist(10)),
+ ok = check_stability(bigfunlist(100)),
+ ok = check_stability(bigfunlist(1000)),
+ case erlang:system_info(modified_timing_level) of
+ undefined -> ok = check_stability(bigfunlist(10000));
+ _ -> ok
+ end,
ok.
check([]) ->
@@ -592,96 +592,96 @@ expl_pid([], L) ->
usort_1(Conf) when is_list(Conf) ->
- ?line [] = lists:usort([]),
- ?line [1] = lists:usort([1]),
- ?line [1] = lists:usort([1,1]),
- ?line [1] = lists:usort([1,1,1,1,1]),
- ?line [1,2] = lists:usort([1,2]),
- ?line [1,2] = lists:usort([1,2,1]),
- ?line [1,2] = lists:usort([1,2,2]),
- ?line [1,2,3] = lists:usort([1,3,2]),
- ?line [1,3] = lists:usort([3,1,3]),
- ?line [0,1,3] = lists:usort([3,1,0]),
- ?line [1,2,3] = lists:usort([3,1,2]),
- ?line [1,2] = lists:usort([2,1,1]),
- ?line [1,2] = lists:usort([2,1]),
- ?line [0,3,4,8,9] = lists:usort([3,8,9,0,9,4]),
-
- ?line lists:foreach(fun ucheck/1, perms([1,2,3])),
- ?line lists:foreach(fun ucheck/1, perms([1,2,3,4,5,6,2,1])),
+ [] = lists:usort([]),
+ [1] = lists:usort([1]),
+ [1] = lists:usort([1,1]),
+ [1] = lists:usort([1,1,1,1,1]),
+ [1,2] = lists:usort([1,2]),
+ [1,2] = lists:usort([1,2,1]),
+ [1,2] = lists:usort([1,2,2]),
+ [1,2,3] = lists:usort([1,3,2]),
+ [1,3] = lists:usort([3,1,3]),
+ [0,1,3] = lists:usort([3,1,0]),
+ [1,2,3] = lists:usort([3,1,2]),
+ [1,2] = lists:usort([2,1,1]),
+ [1,2] = lists:usort([2,1]),
+ [0,3,4,8,9] = lists:usort([3,8,9,0,9,4]),
+
+ lists:foreach(fun ucheck/1, perms([1,2,3])),
+ lists:foreach(fun ucheck/1, perms([1,2,3,4,5,6,2,1])),
ok.
umerge(Conf) when is_list(Conf) ->
%% merge list of lists
- ?line [] = lists:umerge([]),
- ?line [] = lists:umerge([[]]),
- ?line [] = lists:umerge([[],[]]),
- ?line [] = lists:umerge([[],[],[]]),
- ?line [1] = lists:umerge([[1]]),
- ?line [1,2] = lists:umerge([[1,2],[1,2]]),
- ?line [1] = lists:umerge([[1],[],[]]),
- ?line [1] = lists:umerge([[],[1],[]]),
- ?line [1] = lists:umerge([[],[],[1]]),
- ?line [1,2] = lists:umerge([[1],[2],[]]),
- ?line [1,2] = lists:umerge([[1],[],[2]]),
- ?line [1,2] = lists:umerge([[],[1],[2]]),
- ?line [1,2,3,4,5,6] = lists:umerge([[1,2],[],[5,6],[],[3,4],[]]),
- ?line [1,2,3,4] = lists:umerge([[4],[3],[2],[1]]),
- ?line [1,2,3,4,5] = lists:umerge([[1],[2],[3],[4],[5]]),
- ?line [1,2,3,4,5,6] = lists:umerge([[1],[2],[3],[4],[5],[6]]),
- ?line [1,2,3,4,5,6,7,8,9] =
+ [] = lists:umerge([]),
+ [] = lists:umerge([[]]),
+ [] = lists:umerge([[],[]]),
+ [] = lists:umerge([[],[],[]]),
+ [1] = lists:umerge([[1]]),
+ [1,2] = lists:umerge([[1,2],[1,2]]),
+ [1] = lists:umerge([[1],[],[]]),
+ [1] = lists:umerge([[],[1],[]]),
+ [1] = lists:umerge([[],[],[1]]),
+ [1,2] = lists:umerge([[1],[2],[]]),
+ [1,2] = lists:umerge([[1],[],[2]]),
+ [1,2] = lists:umerge([[],[1],[2]]),
+ [1,2,3,4,5,6] = lists:umerge([[1,2],[],[5,6],[],[3,4],[]]),
+ [1,2,3,4] = lists:umerge([[4],[3],[2],[1]]),
+ [1,2,3,4,5] = lists:umerge([[1],[2],[3],[4],[5]]),
+ [1,2,3,4,5,6] = lists:umerge([[1],[2],[3],[4],[5],[6]]),
+ [1,2,3,4,5,6,7,8,9] =
lists:umerge([[1],[2],[3],[4],[5],[6],[7],[8],[9]]),
- ?line [1,2,4,6,8] = lists:umerge([[1,2],[2,4,6,8]]),
+ [1,2,4,6,8] = lists:umerge([[1,2],[2,4,6,8]]),
Seq = lists:seq(1,100),
- ?line true = Seq == lists:umerge(lists:map(fun(E) -> [E] end, Seq)),
+ true = Seq == lists:umerge(lists:map(fun(E) -> [E] end, Seq)),
Two = [1,2],
Six = [1,2,3,4,5,6],
%% 2-way unique merge
- ?line [] = lists:umerge([], []),
- ?line Two = lists:umerge(Two, []),
- ?line Two = lists:umerge([], Two),
- ?line Six = lists:umerge([1,3,5], [2,4,6]),
- ?line Six = lists:umerge([2,4,6], [1,3,5]),
- ?line Six = lists:umerge([1,2,3], [4,5,6]),
- ?line Six = lists:umerge([4,5,6], [1,2,3]),
- ?line Six = lists:umerge([1,2,5],[3,4,6]),
- ?line [1,2,3,5,7] = lists:umerge([1,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:umerge([1,3,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:umerge([1,3,5,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:umerge([2], [1,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:umerge([2,4], [1,3,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:umerge([2,4,6], [1,3,5,7]),
-
- ?line [1,2,3,5,7] = lists:umerge([1,2,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:umerge([1,2,3,4,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:umerge([1,2,3,4,5,6,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:umerge([2], [1,2,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:umerge([2,4], [1,2,3,4,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:umerge([2,4,6], [1,2,3,4,5,6,7]),
+ [] = lists:umerge([], []),
+ Two = lists:umerge(Two, []),
+ Two = lists:umerge([], Two),
+ Six = lists:umerge([1,3,5], [2,4,6]),
+ Six = lists:umerge([2,4,6], [1,3,5]),
+ Six = lists:umerge([1,2,3], [4,5,6]),
+ Six = lists:umerge([4,5,6], [1,2,3]),
+ Six = lists:umerge([1,2,5],[3,4,6]),
+ [1,2,3,5,7] = lists:umerge([1,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:umerge([1,3,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:umerge([1,3,5,7], [2,4,6]),
+ [1,2,3,5,7] = lists:umerge([2], [1,3,5,7]),
+ [1,2,3,4,5,7] = lists:umerge([2,4], [1,3,5,7]),
+ [1,2,3,4,5,6,7] = lists:umerge([2,4,6], [1,3,5,7]),
+
+ [1,2,3,5,7] = lists:umerge([1,2,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:umerge([1,2,3,4,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:umerge([1,2,3,4,5,6,7], [2,4,6]),
+ [1,2,3,5,7] = lists:umerge([2], [1,2,3,5,7]),
+ [1,2,3,4,5,7] = lists:umerge([2,4], [1,2,3,4,5,7]),
+ [1,2,3,4,5,6,7] = lists:umerge([2,4,6], [1,2,3,4,5,6,7]),
%% 3-way unique merge
- ?line [] = lists:umerge3([], [], []),
- ?line Two = lists:umerge3([], [], Two),
- ?line Two = lists:umerge3([], Two, []),
- ?line Two = lists:umerge3(Two, [], []),
- ?line Six = lists:umerge3([], [1,3,5], [2,4,6]),
- ?line Six = lists:umerge3([1,3,5], [], [2,4,6]),
- ?line Six = lists:umerge3([1,3,5], [2,4,6], []),
- ?line Nine = lists:umerge3([1,4,7],[2,5,8],[3,6,9]),
- ?line Nine = lists:umerge3([1,4,7],[3,6,9],[2,5,8]),
- ?line Nine = lists:umerge3([3,6,9],[1,4,7],[2,5,8]),
- ?line Nine = lists:umerge3([4,5,6],[1,2,3],[7,8,9]),
- ?line Nine = lists:umerge3([1,2,3],[4,5,6],[7,8,9]),
- ?line Nine = lists:umerge3([7,8,9],[4,5,6],[1,2,3]),
- ?line Nine = lists:umerge3([4,5,6],[7,8,9],[1,2,3]),
-
- ?line [1,2,3] = lists:umerge3([1,2,3],[1,2,3],[1,2,3]),
- ?line [1,2,3,4] = lists:umerge3([2,3,4],[1,2,3],[2,3,4]),
- ?line [1,2,3] = lists:umerge3([1,2,3],[2,3],[1,2,3]),
- ?line [1,2,3,4] = lists:umerge3([2,3,4],[3,4],[1,2,3]),
+ [] = lists:umerge3([], [], []),
+ Two = lists:umerge3([], [], Two),
+ Two = lists:umerge3([], Two, []),
+ Two = lists:umerge3(Two, [], []),
+ Six = lists:umerge3([], [1,3,5], [2,4,6]),
+ Six = lists:umerge3([1,3,5], [], [2,4,6]),
+ Six = lists:umerge3([1,3,5], [2,4,6], []),
+ Nine = lists:umerge3([1,4,7],[2,5,8],[3,6,9]),
+ Nine = lists:umerge3([1,4,7],[3,6,9],[2,5,8]),
+ Nine = lists:umerge3([3,6,9],[1,4,7],[2,5,8]),
+ Nine = lists:umerge3([4,5,6],[1,2,3],[7,8,9]),
+ Nine = lists:umerge3([1,2,3],[4,5,6],[7,8,9]),
+ Nine = lists:umerge3([7,8,9],[4,5,6],[1,2,3]),
+ Nine = lists:umerge3([4,5,6],[7,8,9],[1,2,3]),
+
+ [1,2,3] = lists:umerge3([1,2,3],[1,2,3],[1,2,3]),
+ [1,2,3,4] = lists:umerge3([2,3,4],[1,2,3],[2,3,4]),
+ [1,2,3] = lists:umerge3([1,2,3],[2,3],[1,2,3]),
+ [1,2,3,4] = lists:umerge3([2,3,4],[3,4],[1,2,3]),
ok.
@@ -690,81 +690,81 @@ rumerge(Conf) when is_list(Conf) ->
Six = [6,5,4,3,2,1],
%% 2-way reversed unique merge
- ?line [] = lists:rumerge([], []),
- ?line Two = lists:rumerge(Two, []),
- ?line Two = lists:rumerge([], Two),
- ?line Six = lists:rumerge([5,3,1], [6,4,2]),
- ?line Six = lists:rumerge([6,4,2], [5,3,1]),
- ?line Six = lists:rumerge([3,2,1], [6,5,4]),
- ?line Six = lists:rumerge([6,5,4], [3,2,1]),
- ?line Six = lists:rumerge([4,3,2],[6,5,1]),
- ?line [7,6,5,3,1] = lists:rumerge([7,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rumerge([7,5,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge([7,5,3,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rumerge([2], [7,5,3,1]),
- ?line [7,5,4,3,2,1] = lists:rumerge([4,2], [7,5,3,1]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge([6,4,2], [7,5,3,1]),
-
- ?line [7,6,5,3,1] = lists:rumerge([7,6,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rumerge([7,6,5,4,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge([7,6,5,4,3,2,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rumerge([2], [7,5,3,2,1]),
- ?line [7,5,4,3,2,1] = lists:rumerge([4,2], [7,5,4,3,2,1]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge([6,4,2], [7,6,5,4,3,2,1]),
+ [] = lists:rumerge([], []),
+ Two = lists:rumerge(Two, []),
+ Two = lists:rumerge([], Two),
+ Six = lists:rumerge([5,3,1], [6,4,2]),
+ Six = lists:rumerge([6,4,2], [5,3,1]),
+ Six = lists:rumerge([3,2,1], [6,5,4]),
+ Six = lists:rumerge([6,5,4], [3,2,1]),
+ Six = lists:rumerge([4,3,2],[6,5,1]),
+ [7,6,5,3,1] = lists:rumerge([7,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rumerge([7,5,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rumerge([7,5,3,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rumerge([2], [7,5,3,1]),
+ [7,5,4,3,2,1] = lists:rumerge([4,2], [7,5,3,1]),
+ [7,6,5,4,3,2,1] = lists:rumerge([6,4,2], [7,5,3,1]),
+
+ [7,6,5,3,1] = lists:rumerge([7,6,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rumerge([7,6,5,4,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rumerge([7,6,5,4,3,2,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rumerge([2], [7,5,3,2,1]),
+ [7,5,4,3,2,1] = lists:rumerge([4,2], [7,5,4,3,2,1]),
+ [7,6,5,4,3,2,1] = lists:rumerge([6,4,2], [7,6,5,4,3,2,1]),
Nine = [9,8,7,6,5,4,3,2,1],
%% 3-way reversed unique merge
- ?line [] = lists:rumerge3([], [], []),
- ?line Two = lists:rumerge3([], [], Two),
- ?line Two = lists:rumerge3([], Two, []),
- ?line Two = lists:rumerge3(Two, [], []),
- ?line Six = lists:rumerge3([], [5,3,1], [6,4,2]),
- ?line Six = lists:rumerge3([5,3,1], [], [6,4,2]),
- ?line Six = lists:rumerge3([5,3,1], [6,4,2], []),
- ?line Nine = lists:rumerge3([7,4,1],[8,5,2],[9,6,3]),
- ?line Nine = lists:rumerge3([7,4,1],[9,6,3],[8,5,2]),
- ?line Nine = lists:rumerge3([9,6,3],[7,4,1],[8,5,2]),
- ?line Nine = lists:rumerge3([6,5,4],[3,2,1],[9,8,7]),
- ?line Nine = lists:rumerge3([3,2,1],[6,5,4],[9,8,7]),
- ?line Nine = lists:rumerge3([9,8,7],[6,5,4],[3,2,1]),
- ?line Nine = lists:rumerge3([6,5,4],[9,8,7],[3,2,1]),
-
- ?line [3,2,1] = lists:rumerge3([3,2,1],[3,2,1],[3,2,1]),
- ?line [4,3,2,1] = lists:rumerge3([4,3,2],[3,2,1],[3,2,1]),
- ?line [5,4,3,2,1] = lists:rumerge3([4,3,2],[5,4,3,2],[5,4,3,2,1]),
- ?line [6,5,4,3,2] = lists:rumerge3([4,3,2],[5,4,3,2],[6,5,4,3]),
+ [] = lists:rumerge3([], [], []),
+ Two = lists:rumerge3([], [], Two),
+ Two = lists:rumerge3([], Two, []),
+ Two = lists:rumerge3(Two, [], []),
+ Six = lists:rumerge3([], [5,3,1], [6,4,2]),
+ Six = lists:rumerge3([5,3,1], [], [6,4,2]),
+ Six = lists:rumerge3([5,3,1], [6,4,2], []),
+ Nine = lists:rumerge3([7,4,1],[8,5,2],[9,6,3]),
+ Nine = lists:rumerge3([7,4,1],[9,6,3],[8,5,2]),
+ Nine = lists:rumerge3([9,6,3],[7,4,1],[8,5,2]),
+ Nine = lists:rumerge3([6,5,4],[3,2,1],[9,8,7]),
+ Nine = lists:rumerge3([3,2,1],[6,5,4],[9,8,7]),
+ Nine = lists:rumerge3([9,8,7],[6,5,4],[3,2,1]),
+ Nine = lists:rumerge3([6,5,4],[9,8,7],[3,2,1]),
+
+ [3,2,1] = lists:rumerge3([3,2,1],[3,2,1],[3,2,1]),
+ [4,3,2,1] = lists:rumerge3([4,3,2],[3,2,1],[3,2,1]),
+ [5,4,3,2,1] = lists:rumerge3([4,3,2],[5,4,3,2],[5,4,3,2,1]),
+ [6,5,4,3,2] = lists:rumerge3([4,3,2],[5,4,3,2],[6,5,4,3]),
L1 = [c,d,e],
L2 = [b,c,d],
- ?line true =
+ true =
lists:umerge(L1, L2) ==
lists:reverse(lists:rumerge(lists:reverse(L1), lists:reverse(L2))),
ok.
%% usort/1 on big randomized lists.
usort_rand(Config) when is_list(Config) ->
- ?line ok = ucheck(biglist(10)),
- ?line ok = ucheck(biglist(100)),
- ?line ok = ucheck(biglist(1000)),
- ?line ok = ucheck(biglist(10000)),
+ ok = ucheck(biglist(10)),
+ ok = ucheck(biglist(100)),
+ ok = ucheck(biglist(1000)),
+ ok = ucheck(biglist(10000)),
- ?line ok = ucheck(ubiglist(10)),
- ?line ok = ucheck(ubiglist(100)),
- ?line ok = ucheck(ubiglist(1000)),
- ?line ok = ucheck(ubiglist(10000)),
+ ok = ucheck(ubiglist(10)),
+ ok = ucheck(ubiglist(100)),
+ ok = ucheck(ubiglist(1000)),
+ ok = ucheck(ubiglist(10000)),
ok.
%% usort/1 should keep the first duplicate.
usort_stable(Config) when is_list(Config) ->
- ?line ok = ucheck_stability(bigfunlist(3)),
- ?line ok = ucheck_stability(bigfunlist(10)),
- ?line ok = ucheck_stability(bigfunlist(100)),
- ?line ok = ucheck_stability(bigfunlist(1000)),
- ?line case erlang:system_info(modified_timing_level) of
- undefined -> ok = ucheck_stability(bigfunlist(10000));
- _ -> ok
- end,
+ ok = ucheck_stability(bigfunlist(3)),
+ ok = ucheck_stability(bigfunlist(10)),
+ ok = ucheck_stability(bigfunlist(100)),
+ ok = ucheck_stability(bigfunlist(1000)),
+ case erlang:system_info(modified_timing_level) of
+ undefined -> ok = ucheck_stability(bigfunlist(10000));
+ _ -> ok
+ end,
ok.
ucheck([]) ->
@@ -800,28 +800,28 @@ keymerge(Config) when is_list(Config) ->
Six = [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f}],
%% 2-way keymerge
- ?line [] = lists:keymerge(1, [], []),
- ?line Two = lists:keymerge(1, Two, []),
- ?line Two = lists:keymerge(1, [], Two),
- ?line Six = lists:keymerge(1, [{1,a},{3,c},{5,e}], [{2,b},{4,d},{6,f}]),
- ?line Six = lists:keymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e}]),
- ?line Six = lists:keymerge(1, [{1,a},{2,b},{3,c}], [{4,d},{5,e},{6,f}]),
- ?line Six = lists:keymerge(1, [{4,d},{5,e},{6,f}], [{1,a},{2,b},{3,c}]),
- ?line Six = lists:keymerge(1, [{1,a},{2,b},{5,e}],[{3,c},{4,d},{6,f}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [] = lists:keymerge(1, [], []),
+ Two = lists:keymerge(1, Two, []),
+ Two = lists:keymerge(1, [], Two),
+ Six = lists:keymerge(1, [{1,a},{3,c},{5,e}], [{2,b},{4,d},{6,f}]),
+ Six = lists:keymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e}]),
+ Six = lists:keymerge(1, [{1,a},{2,b},{3,c}], [{4,d},{5,e},{6,f}]),
+ Six = lists:keymerge(1, [{4,d},{5,e},{6,f}], [{1,a},{2,b},{3,c}]),
+ Six = lists:keymerge(1, [{1,a},{2,b},{5,e}],[{3,c},{4,d},{6,f}]),
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:keymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:keymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b},{4,d}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:keymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b},{4,d},{6,f}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:keymerge(1, [{2,b}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:keymerge(1, [{2,b},{4,d}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:keymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{b,2},{c,11},{c,12},{c,21},{c,22},{e,5}] =
+ [{b,2},{c,11},{c,12},{c,21},{c,22},{e,5}] =
lists:keymerge(1,[{c,11},{c,12},{e,5}], [{b,2},{c,21},{c,22}]),
ok.
@@ -833,30 +833,30 @@ rkeymerge(Config) when is_list(Config) ->
Six = [{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}],
%% 2-way reversed keymerge
- ?line [] = lists:rkeymerge(1, [], []),
- ?line Two = lists:rkeymerge(1, Two, []),
- ?line Two = lists:rkeymerge(1, [], Two),
- ?line Six = lists:rkeymerge(1, [{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
- ?line Six = lists:rkeymerge(1, [{6,f},{4,d},{2,b}], [{5,e},{3,c},{1,a}]),
- ?line Six = lists:rkeymerge(1, [{3,c},{2,b},{1,a}], [{6,f},{5,e},{4,d}]),
- ?line Six = lists:rkeymerge(1, [{6,f},{5,e},{4,d}], [{3,c},{2,b},{1,a}]),
- ?line Six = lists:rkeymerge(1, [{4,d},{3,c},{2,b}],[{6,f},{5,e},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{3,c},{1,a}] =
+ [] = lists:rkeymerge(1, [], []),
+ Two = lists:rkeymerge(1, Two, []),
+ Two = lists:rkeymerge(1, [], Two),
+ Six = lists:rkeymerge(1, [{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
+ Six = lists:rkeymerge(1, [{6,f},{4,d},{2,b}], [{5,e},{3,c},{1,a}]),
+ Six = lists:rkeymerge(1, [{3,c},{2,b},{1,a}], [{6,f},{5,e},{4,d}]),
+ Six = lists:rkeymerge(1, [{6,f},{5,e},{4,d}], [{3,c},{2,b},{1,a}]),
+ Six = lists:rkeymerge(1, [{4,d},{3,c},{2,b}],[{6,f},{5,e},{1,a}]),
+ [{7,g},{6,f},{5,e},{3,c},{1,a}] =
lists:rkeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
lists:rkeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f},{4,d}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rkeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
- ?line [{7,g},{5,e},{3,c},{2,b},{1,a}] =
+ [{7,g},{5,e},{3,c},{2,b},{1,a}] =
lists:rkeymerge(1, [{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
- ?line [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rkeymerge(1, [{4,d},{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rkeymerge(1, [{6,f},{4,d},{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
L1 = [{c,11},{c,12},{e,5}],
L2 = [{b,2},{c,21},{c,22}],
- ?line true =
+ true =
lists:keymerge(1, L1, L2) ==
lists:reverse(lists:rkeymerge(1,lists:reverse(L1),
lists:reverse(L2))),
@@ -864,84 +864,84 @@ rkeymerge(Config) when is_list(Config) ->
ok.
keysort_1(Config) when is_list(Config) ->
- ?line ok = keysort_check(1, [], []),
- ?line ok = keysort_check(1, [{a,b}], [{a,b}]),
- ?line ok = keysort_check(1, [{a,b},{a,b}], [{a,b},{a,b}]),
- ?line ok = keysort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
- ?line ok = keysort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
- ?line ok = keysort_check(1,
- [{1,e},{3,f},{2,y},{0,z},{x,14}],
- [{0,z},{1,e},{2,y},{3,f},{x,14}]),
- ?line ok = keysort_check(1,
- [{1,a},{1,a},{1,a},{1,a}],
- [{1,a},{1,a},{1,a},{1,a}]),
-
- ?line [{b,1},{c,1}] = lists:keysort(1, [{c,1},{b,1}]),
- ?line [{a,0},{b,2},{c,3},{d,4}] =
- lists:keysort(1, [{d,4},{c,3},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{b,2},{c,1}] =
- lists:keysort(1, [{c,1},{b,1},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{b,2},{c,1},{d,4}] =
- lists:keysort(1, [{c,1},{b,1},{b,2},{a,0},{d,4}]),
+ ok = keysort_check(1, [], []),
+ ok = keysort_check(1, [{a,b}], [{a,b}]),
+ ok = keysort_check(1, [{a,b},{a,b}], [{a,b},{a,b}]),
+ ok = keysort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
+ ok = keysort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
+ ok = keysort_check(1,
+ [{1,e},{3,f},{2,y},{0,z},{x,14}],
+ [{0,z},{1,e},{2,y},{3,f},{x,14}]),
+ ok = keysort_check(1,
+ [{1,a},{1,a},{1,a},{1,a}],
+ [{1,a},{1,a},{1,a},{1,a}]),
+
+ [{b,1},{c,1}] = lists:keysort(1, [{c,1},{b,1}]),
+ [{a,0},{b,2},{c,3},{d,4}] =
+ lists:keysort(1, [{d,4},{c,3},{b,2},{a,0}]),
+ [{a,0},{b,1},{b,2},{c,1}] =
+ lists:keysort(1, [{c,1},{b,1},{b,2},{a,0}]),
+ [{a,0},{b,1},{b,2},{c,1},{d,4}] =
+ lists:keysort(1, [{c,1},{b,1},{b,2},{a,0},{d,4}]),
SFun = fun(L) -> fun(X) -> keysort_check(1, X, L) end end,
L1 = [{1,a},{2,b},{3,c}],
- ?line lists:foreach(SFun(L1), perms(L1)),
+ lists:foreach(SFun(L1), perms(L1)),
L2 = [{1,a},{1,a},{2,b}],
- ?line lists:foreach(SFun(L2), perms(L2)),
+ lists:foreach(SFun(L2), perms(L2)),
L3 = [{1,a},{1,a},{1,a},{2,b}],
- ?line lists:foreach(SFun(L3), perms(L3)),
+ lists:foreach(SFun(L3), perms(L3)),
L4 = [{a,1},{a,1},{b,2},{b,2},{c,3},{d,4},{e,5},{f,6}],
- ?line lists:foreach(SFun(L4), perms(L4)),
+ lists:foreach(SFun(L4), perms(L4)),
ok.
%% keysort should be stable
keysort_stable(Config) when is_list(Config) ->
- ?line ok = keysort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]),
- ?line ok = keysort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]),
- ?line ok = keysort_check(1,
- [{1,c},{1,b},{2,x},{3,p},{2,a}],
- [{1,c},{1,b},{2,x},{2,a},{3,p}]),
- ?line ok = keysort_check(1,
- [{1,a},{1,b},{1,a},{1,a}],
- [{1,a},{1,b},{1,a},{1,a}]),
+ ok = keysort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]),
+ ok = keysort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]),
+ ok = keysort_check(1,
+ [{1,c},{1,b},{2,x},{3,p},{2,a}],
+ [{1,c},{1,b},{2,x},{2,a},{3,p}]),
+ ok = keysort_check(1,
+ [{1,a},{1,b},{1,a},{1,a}],
+ [{1,a},{1,b},{1,a},{1,a}]),
ok.
%% keysort should exit when given bad arguments
keysort_error(Config) when is_list(Config) ->
- ?line {'EXIT', _} = (catch lists:keysort(0, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:keysort(3, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:keysort(1.5, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:keysort(x, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:keysort(x, [])),
- ?line {'EXIT', _} = (catch lists:keysort(x, [{1,b}])),
- ?line {'EXIT', _} = (catch lists:keysort(1, [a,b])),
- ?line {'EXIT', _} = (catch lists:keysort(1, [{1,b} | {1,c}])),
+ {'EXIT', _} = (catch lists:keysort(0, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:keysort(3, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:keysort(1.5, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:keysort(x, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:keysort(x, [])),
+ {'EXIT', _} = (catch lists:keysort(x, [{1,b}])),
+ {'EXIT', _} = (catch lists:keysort(1, [a,b])),
+ {'EXIT', _} = (catch lists:keysort(1, [{1,b} | {1,c}])),
ok.
%% keysort with other key than first element
keysort_i(Config) when is_list(Config) ->
- ?line ok = keysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]),
+ ok = keysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]),
ok.
%% keysort on big randomized lists
keysort_rand(Config) when is_list(Config) ->
- ?line ok = keysort_check3(1, biglist(10)),
- ?line ok = keysort_check3(1, biglist(100)),
- ?line ok = keysort_check3(1, biglist(1000)),
- ?line ok = keysort_check3(1, biglist(10000)),
+ ok = keysort_check3(1, biglist(10)),
+ ok = keysort_check3(1, biglist(100)),
+ ok = keysort_check3(1, biglist(1000)),
+ ok = keysort_check3(1, biglist(10000)),
- ?line ok = keysort_check3(2, biglist(10)),
- ?line ok = keysort_check3(2, biglist(100)),
- ?line ok = keysort_check3(2, biglist(1000)),
- ?line ok = keysort_check3(2, biglist(10000)),
+ ok = keysort_check3(2, biglist(10)),
+ ok = keysort_check3(2, biglist(100)),
+ ok = keysort_check3(2, biglist(1000)),
+ ok = keysort_check3(2, biglist(10000)),
ok.
%%% Keysort a list, check that the returned list is what we expected,
%%% and that it is actually sorted.
keysort_check(I, Input, Expected) ->
- ?line Expected = lists:keysort(I, Input),
+ Expected = lists:keysort(I, Input),
check_sorted(I, Input, Expected).
keysort_check3(I, Input) ->
@@ -983,50 +983,50 @@ ukeymerge(Conf) when is_list(Conf) ->
Six = [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f}],
%% 2-way unique keymerge
- ?line [] = lists:ukeymerge(1, [], []),
- ?line Two = lists:ukeymerge(1, Two, []),
- ?line Two = lists:ukeymerge(1, [], Two),
- ?line [] = lists:ukeymerge(1, [], []),
- ?line Two = lists:ukeymerge(1, Two, []),
- ?line Two = lists:ukeymerge(1, [], Two),
- ?line Six = lists:ukeymerge(1, [{1,a},{3,c},{5,e}], [{2,b},{4,d},{6,f}]),
- ?line Six = lists:ukeymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e}]),
- ?line Six = lists:ukeymerge(1, [{1,a},{2,b},{3,c}], [{4,d},{5,e},{6,f}]),
- ?line Six = lists:ukeymerge(1, [{4,d},{5,e},{6,f}], [{1,a},{2,b},{3,c}]),
- ?line Six = lists:ukeymerge(1, [{1,a},{2,b},{5,e}],[{3,c},{4,d},{6,f}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [] = lists:ukeymerge(1, [], []),
+ Two = lists:ukeymerge(1, Two, []),
+ Two = lists:ukeymerge(1, [], Two),
+ [] = lists:ukeymerge(1, [], []),
+ Two = lists:ukeymerge(1, Two, []),
+ Two = lists:ukeymerge(1, [], Two),
+ Six = lists:ukeymerge(1, [{1,a},{3,c},{5,e}], [{2,b},{4,d},{6,f}]),
+ Six = lists:ukeymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e}]),
+ Six = lists:ukeymerge(1, [{1,a},{2,b},{3,c}], [{4,d},{5,e},{6,f}]),
+ Six = lists:ukeymerge(1, [{4,d},{5,e},{6,f}], [{1,a},{2,b},{3,c}]),
+ Six = lists:ukeymerge(1, [{1,a},{2,b},{5,e}],[{3,c},{4,d},{6,f}]),
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:ukeymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:ukeymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b},{4,d}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:ukeymerge(1, [{1,a},{3,c},{5,e},{7,g}], [{2,b},{4,d},{6,f}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:ukeymerge(1, [{2,b}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:ukeymerge(1, [{2,b},{4,d}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:ukeymerge(1, [{2,b},{4,d},{6,f}], [{1,a},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:ukeymerge(1, [{1,a},{2,b},{3,c},{5,e},{7,g}], [{2,b}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:ukeymerge(1, [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}],
[{2,b},{4,d}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:ukeymerge(1, [{1,a},{3,c},{5,e},{6,f},{7,g}],
[{2,b},{4,d},{6,f}]),
- ?line [{1,a},{2,b},{3,c},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{5,e},{7,g}] =
lists:ukeymerge(1, [{2,b}], [{1,a},{2,b},{3,c},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}] =
lists:ukeymerge(1, [{2,b},{4,d}],
[{1,a},{2,b},{3,c},{4,d},{5,e},{7,g}]),
- ?line [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}] =
lists:ukeymerge(1, [{2,b},{4,d},{6,f}],
- [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}]),
+ [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g}]),
L1 = [{a,1},{a,3},{a,5},{a,7}],
L2 = [{b,1},{b,3},{b,5},{b,7}],
- ?line L1 = lists:ukeymerge(2, L1, L2),
+ L1 = lists:ukeymerge(2, L1, L2),
ok.
@@ -1037,47 +1037,47 @@ rukeymerge(Conf) when is_list(Conf) ->
Six = [{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}],
%% 2-way reversed unique keymerge
- ?line [] = lists:rukeymerge(1, [], []),
- ?line Two = lists:rukeymerge(1, Two, []),
- ?line Two = lists:rukeymerge(1, [], Two),
- ?line Six = lists:rukeymerge(1, [{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
- ?line Six = lists:rukeymerge(1, [{6,f},{4,d},{2,b}], [{5,e},{3,c},{1,a}]),
- ?line Six = lists:rukeymerge(1, [{3,c},{2,b},{1,a}], [{6,f},{5,e},{4,d}]),
- ?line Six = lists:rukeymerge(1, [{6,f},{5,e},{4,d}], [{3,c},{2,b},{1,a}]),
- ?line Six = lists:rukeymerge(1, [{4,d},{3,c},{2,b}],[{6,f},{5,e},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{3,c},{1,a}] =
+ [] = lists:rukeymerge(1, [], []),
+ Two = lists:rukeymerge(1, Two, []),
+ Two = lists:rukeymerge(1, [], Two),
+ Six = lists:rukeymerge(1, [{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
+ Six = lists:rukeymerge(1, [{6,f},{4,d},{2,b}], [{5,e},{3,c},{1,a}]),
+ Six = lists:rukeymerge(1, [{3,c},{2,b},{1,a}], [{6,f},{5,e},{4,d}]),
+ Six = lists:rukeymerge(1, [{6,f},{5,e},{4,d}], [{3,c},{2,b},{1,a}]),
+ Six = lists:rukeymerge(1, [{4,d},{3,c},{2,b}],[{6,f},{5,e},{1,a}]),
+ [{7,g},{6,f},{5,e},{3,c},{1,a}] =
lists:rukeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
lists:rukeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f},{4,d}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{7,g},{5,e},{3,c},{1,a}], [{6,f},{4,d},{2,b}]),
- ?line [{7,g},{5,e},{3,c},{2,b},{1,a}] =
+ [{7,g},{5,e},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
- ?line [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{4,d},{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{6,f},{4,d},{2,b}], [{7,g},{5,e},{3,c},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{3,c},{1,a}] =
+ [{7,g},{6,f},{5,e},{3,c},{1,a}] =
lists:rukeymerge(1, [{7,g},{6,f},{5,e},{3,c},{1,a}], [{6,f}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}] =
lists:rukeymerge(1, [{7,g},{6,f},{5,e},{4,d},{3,c},{1,a}],
[{6,f},{4,d}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}],
- [{6,f},{4,d},{2,b}]),
- ?line [{7,g},{5,e},{3,c},{2,b},{1,a}] =
+ [{6,f},{4,d},{2,b}]),
+ [{7,g},{5,e},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{2,b}], [{7,g},{5,e},{3,c},{2,b},{1,a}]),
- ?line [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{4,d},{2,b}],
[{7,g},{5,e},{4,d},{3,c},{2,b},{1,a}]),
- ?line [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}] =
lists:rukeymerge(1, [{6,f},{4,d},{2,b}],
- [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}]),
+ [{7,g},{6,f},{5,e},{4,d},{3,c},{2,b},{1,a}]),
L1 = [{a,1},{a,3},{a,5},{a,7}],
L2 = [{b,1},{b,3},{b,5},{b,7}],
- ?line true =
+ true =
lists:ukeymerge(2, L1, L2) ==
lists:reverse(lists:rukeymerge(2, lists:reverse(L1),
lists:reverse(L2))),
@@ -1085,114 +1085,114 @@ rukeymerge(Conf) when is_list(Conf) ->
ok.
ukeysort_1(Config) when is_list(Config) ->
- ?line ok = ukeysort_check(1, [], []),
- ?line ok = ukeysort_check(1, [{a,b}], [{a,b}]),
- ?line ok = ukeysort_check(1, [{a,b},{a,b}], [{a,b}]),
- ?line ok = ukeysort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
- ?line ok = ukeysort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
- ?line ok = ukeysort_check(1,
- [{1,e},{3,f},{2,y},{0,z},{x,14}],
- [{0,z},{1,e},{2,y},{3,f},{x,14}]),
- ?line ok = ukeysort_check(1, [{1,a},{1,a},{1,a},{1,a}], [{1,a}]),
+ ok = ukeysort_check(1, [], []),
+ ok = ukeysort_check(1, [{a,b}], [{a,b}]),
+ ok = ukeysort_check(1, [{a,b},{a,b}], [{a,b}]),
+ ok = ukeysort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
+ ok = ukeysort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
+ ok = ukeysort_check(1,
+ [{1,e},{3,f},{2,y},{0,z},{x,14}],
+ [{0,z},{1,e},{2,y},{3,f},{x,14}]),
+ ok = ukeysort_check(1, [{1,a},{1,a},{1,a},{1,a}], [{1,a}]),
L1 = [{1,a},{1,b},{1,a}],
L1u = lists:ukeysort(1, L1),
L2 = [{1,a},{1,b},{1,a}],
L2u = lists:ukeysort(1, L2),
- ?line ok = ukeysort_check(1, lists:keymerge(1, L1, L2),
- lists:ukeymerge(1, L1u, L2u)),
+ ok = ukeysort_check(1, lists:keymerge(1, L1, L2),
+ lists:ukeymerge(1, L1u, L2u)),
L3 = [{1,a},{1,b},{1,a},{2,a}],
L3u = lists:ukeysort(1, L3),
- ?line ok = ukeysort_check(1, lists:keymerge(1, L3, L2),
- lists:ukeymerge(1, L3u, L2u)),
+ ok = ukeysort_check(1, lists:keymerge(1, L3, L2),
+ lists:ukeymerge(1, L3u, L2u)),
L4 = [{1,b},{1,a}],
L4u = lists:ukeysort(1, L4),
- ?line ok = ukeysort_check(1, lists:keymerge(1, L1, L4),
- lists:ukeymerge(1, L1u, L4u)),
+ ok = ukeysort_check(1, lists:keymerge(1, L1, L4),
+ lists:ukeymerge(1, L1u, L4u)),
L5 = [{1,a},{1,b},{1,a},{2,a}],
L5u = lists:ukeysort(1, L5),
- ?line ok = ukeysort_check(1, lists:keymerge(1, [], L5),
- lists:ukeymerge(1, [], L5u)),
- ?line ok = ukeysort_check(1, lists:keymerge(1, L5, []),
- lists:ukeymerge(1, L5u, [])),
+ ok = ukeysort_check(1, lists:keymerge(1, [], L5),
+ lists:ukeymerge(1, [], L5u)),
+ ok = ukeysort_check(1, lists:keymerge(1, L5, []),
+ lists:ukeymerge(1, L5u, [])),
L6 = [{3,a}],
L6u = lists:ukeysort(1, L6),
- ?line ok = ukeysort_check(1, lists:keymerge(1, L5, L6),
- lists:ukeymerge(1, L5u, L6u)),
+ ok = ukeysort_check(1, lists:keymerge(1, L5, L6),
+ lists:ukeymerge(1, L5u, L6u)),
- ?line [{b,1},{c,1}] = lists:ukeysort(1, [{c,1},{c,1},{c,1},{c,1},{b,1}]),
- ?line [{a,0},{b,2},{c,3},{d,4}] =
- lists:ukeysort(1, [{d,4},{c,3},{b,2},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{c,1}] =
- lists:ukeysort(1, [{c,1},{b,1},{b,1},{b,2},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{c,1},{d,4}] =
- lists:ukeysort(1, [{c,1},{b,1},{b,2},{a,0},{a,0},{d,4},{d,4}]),
+ [{b,1},{c,1}] = lists:ukeysort(1, [{c,1},{c,1},{c,1},{c,1},{b,1}]),
+ [{a,0},{b,2},{c,3},{d,4}] =
+ lists:ukeysort(1, [{d,4},{c,3},{b,2},{b,2},{a,0}]),
+ [{a,0},{b,1},{c,1}] =
+ lists:ukeysort(1, [{c,1},{b,1},{b,1},{b,2},{b,2},{a,0}]),
+ [{a,0},{b,1},{c,1},{d,4}] =
+ lists:ukeysort(1, [{c,1},{b,1},{b,2},{a,0},{a,0},{d,4},{d,4}]),
SFun = fun(L) -> fun(X) -> ukeysort_check(2, X, L) end end,
PL = [{a,1},{b,2},{c,3},{d,4},{e,5},{f,6}],
Ps = perms([{a,1},{b,2},{c,3},{d,4},{e,5},{f,6},{b,2},{a,1}]),
- ?line lists:foreach(SFun(PL), Ps),
+ lists:foreach(SFun(PL), Ps),
M1L = [{1,a},{1,a},{2,b}],
M1s = [{1,a},{2,b}],
- ?line lists:foreach(SFun(M1s), perms(M1L)),
+ lists:foreach(SFun(M1s), perms(M1L)),
M2L = [{1,a},{2,b},{2,b}],
M2s = [{1,a},{2,b}],
- ?line lists:foreach(SFun(M2s), perms(M2L)),
+ lists:foreach(SFun(M2s), perms(M2L)),
M3 = [{1,a},{2,b},{3,c}],
- ?line lists:foreach(SFun(M3), perms(M3)),
+ lists:foreach(SFun(M3), perms(M3)),
ok.
%% ukeysort should keep the first duplicate.
ukeysort_stable(Config) when is_list(Config) ->
- ?line ok = ukeysort_check(1, [{1,b},{1,c}], [{1,b}]),
- ?line ok = ukeysort_check(1, [{1,c},{1,b}], [{1,c}]),
- ?line ok = ukeysort_check(1,
- [{1,c},{1,b},{2,x},{3,p},{2,a}],
- [{1,c},{2,x},{3,p}]),
+ ok = ukeysort_check(1, [{1,b},{1,c}], [{1,b}]),
+ ok = ukeysort_check(1, [{1,c},{1,b}], [{1,c}]),
+ ok = ukeysort_check(1,
+ [{1,c},{1,b},{2,x},{3,p},{2,a}],
+ [{1,c},{2,x},{3,p}]),
- ?line ok = ukeysort_check(1, [{1,a},{1,b},{1,b}], [{1,a}]),
- ?line ok = ukeysort_check(1, [{2,a},{1,b},{2,a}], [{1,b},{2,a}]),
+ ok = ukeysort_check(1, [{1,a},{1,b},{1,b}], [{1,a}]),
+ ok = ukeysort_check(1, [{2,a},{1,b},{2,a}], [{1,b},{2,a}]),
- ?line ok = ukeysort_check_stability(bigfunlist(3)),
- ?line ok = ukeysort_check_stability(bigfunlist(10)),
- ?line ok = ukeysort_check_stability(bigfunlist(100)),
- ?line ok = ukeysort_check_stability(bigfunlist(1000)),
- ?line case erlang:system_info(modified_timing_level) of
- undefined -> ok = ukeysort_check_stability(bigfunlist(10000));
- _ -> ok
- end,
+ ok = ukeysort_check_stability(bigfunlist(3)),
+ ok = ukeysort_check_stability(bigfunlist(10)),
+ ok = ukeysort_check_stability(bigfunlist(100)),
+ ok = ukeysort_check_stability(bigfunlist(1000)),
+ case erlang:system_info(modified_timing_level) of
+ undefined -> ok = ukeysort_check_stability(bigfunlist(10000));
+ _ -> ok
+ end,
ok.
%% ukeysort should exit when given bad arguments.
ukeysort_error(Config) when is_list(Config) ->
- ?line {'EXIT', _} = (catch lists:ukeysort(0, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:ukeysort(3, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:ukeysort(1.5, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:ukeysort(x, [{1,b},{1,c}])),
- ?line {'EXIT', _} = (catch lists:ukeysort(x, [])),
- ?line {'EXIT', _} = (catch lists:ukeysort(x, [{1,b}])),
- ?line {'EXIT', _} = (catch lists:ukeysort(1, [a,b])),
- ?line {'EXIT', _} = (catch lists:ukeysort(1, [{1,b} | {1,c}])),
+ {'EXIT', _} = (catch lists:ukeysort(0, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:ukeysort(3, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:ukeysort(1.5, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:ukeysort(x, [{1,b},{1,c}])),
+ {'EXIT', _} = (catch lists:ukeysort(x, [])),
+ {'EXIT', _} = (catch lists:ukeysort(x, [{1,b}])),
+ {'EXIT', _} = (catch lists:ukeysort(1, [a,b])),
+ {'EXIT', _} = (catch lists:ukeysort(1, [{1,b} | {1,c}])),
ok.
%% ukeysort with other key than first element.
ukeysort_i(Config) when is_list(Config) ->
- ?line ok = ukeysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]),
+ ok = ukeysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]),
ok.
%% ukeysort on big randomized lists.
ukeysort_rand(Config) when is_list(Config) ->
- ?line ok = ukeysort_check3(2, biglist(10)),
- ?line ok = ukeysort_check3(2, biglist(100)),
- ?line ok = ukeysort_check3(2, biglist(1000)),
- ?line ok = ukeysort_check3(2, biglist(10000)),
+ ok = ukeysort_check3(2, biglist(10)),
+ ok = ukeysort_check3(2, biglist(100)),
+ ok = ukeysort_check3(2, biglist(1000)),
+ ok = ukeysort_check3(2, biglist(10000)),
- ?line ok = gen_ukeysort_check(1, ubiglist(10)),
- ?line ok = gen_ukeysort_check(1, ubiglist(100)),
- ?line ok = gen_ukeysort_check(1, ubiglist(1000)),
- ?line ok = gen_ukeysort_check(1, ubiglist(10000)),
+ ok = gen_ukeysort_check(1, ubiglist(10)),
+ ok = gen_ukeysort_check(1, ubiglist(100)),
+ ok = gen_ukeysort_check(1, ubiglist(1000)),
+ ok = gen_ukeysort_check(1, ubiglist(10000)),
ok.
%% Check that ukeysort/2 is stable and correct relative keysort/2.
@@ -1219,7 +1219,7 @@ ukeysort_check_stability(L) ->
%%% Uniquely keysort a list, check that the returned list is what we
%%% expected, and that it is actually sorted.
ukeysort_check(I, Input, Expected) ->
- ?line Expected = lists:ukeysort(I, Input),
+ Expected = lists:ukeysort(I, Input),
ucheck_sorted(I, Input, Expected).
ukeysort_check3(I, Input) ->
@@ -1264,23 +1264,23 @@ funmerge(Config) when is_list(Config) ->
F = fun(X, Y) -> X =< Y end,
%% 2-way merge
- ?line [] = lists:merge(F, [], []),
- ?line Two = lists:merge(F, Two, []),
- ?line Two = lists:merge(F, [], Two),
- ?line Six = lists:merge(F, [1,3,5], [2,4,6]),
- ?line Six = lists:merge(F, [2,4,6], [1,3,5]),
- ?line Six = lists:merge(F, [1,2,3], [4,5,6]),
- ?line Six = lists:merge(F, [4,5,6], [1,2,3]),
- ?line Six = lists:merge(F, [1,2,5],[3,4,6]),
- ?line [1,2,3,5,7] = lists:merge(F, [1,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:merge(F, [1,3,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:merge(F, [1,3,5,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:merge(F, [2], [1,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:merge(F, [2,4], [1,3,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:merge(F, [2,4,6], [1,3,5,7]),
+ [] = lists:merge(F, [], []),
+ Two = lists:merge(F, Two, []),
+ Two = lists:merge(F, [], Two),
+ Six = lists:merge(F, [1,3,5], [2,4,6]),
+ Six = lists:merge(F, [2,4,6], [1,3,5]),
+ Six = lists:merge(F, [1,2,3], [4,5,6]),
+ Six = lists:merge(F, [4,5,6], [1,2,3]),
+ Six = lists:merge(F, [1,2,5],[3,4,6]),
+ [1,2,3,5,7] = lists:merge(F, [1,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:merge(F, [1,3,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:merge(F, [1,3,5,7], [2,4,6]),
+ [1,2,3,5,7] = lists:merge(F, [2], [1,3,5,7]),
+ [1,2,3,4,5,7] = lists:merge(F, [2,4], [1,3,5,7]),
+ [1,2,3,4,5,6,7] = lists:merge(F, [2,4,6], [1,3,5,7]),
F2 = fun(X,Y) -> element(1,X) =< element(1,Y) end,
- ?line [{b,2},{c,11},{c,12},{c,21},{c,22},{e,5}] =
+ [{b,2},{c,11},{c,12},{c,21},{c,22},{e,5}] =
lists:merge(F2,[{c,11},{c,12},{e,5}], [{b,2},{c,21},{c,22}]),
ok.
@@ -1293,25 +1293,25 @@ rfunmerge(Config) when is_list(Config) ->
F = fun(X, Y) -> X =< Y end,
%% 2-way reversed merge
- ?line [] = lists:rmerge(F, [], []),
- ?line Two = lists:rmerge(F, Two, []),
- ?line Two = lists:rmerge(F, [], Two),
- ?line Six = lists:rmerge(F, [5,3,1], [6,4,2]),
- ?line Six = lists:rmerge(F, [6,4,2], [5,3,1]),
- ?line Six = lists:rmerge(F, [3,2,1], [6,5,4]),
- ?line Six = lists:rmerge(F, [6,5,4], [3,2,1]),
- ?line Six = lists:rmerge(F, [4,3,2],[6,5,1]),
- ?line [7,6,5,3,1] = lists:rmerge(F, [7,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rmerge(F, [7,5,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rmerge(F, [7,5,3,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rmerge(F, [2], [7,5,3,1]),
- ?line [7,5,4,3,2,1] = lists:rmerge(F, [4,2], [7,5,3,1]),
- ?line [7,6,5,4,3,2,1] = lists:rmerge(F, [6,4,2], [7,5,3,1]),
+ [] = lists:rmerge(F, [], []),
+ Two = lists:rmerge(F, Two, []),
+ Two = lists:rmerge(F, [], Two),
+ Six = lists:rmerge(F, [5,3,1], [6,4,2]),
+ Six = lists:rmerge(F, [6,4,2], [5,3,1]),
+ Six = lists:rmerge(F, [3,2,1], [6,5,4]),
+ Six = lists:rmerge(F, [6,5,4], [3,2,1]),
+ Six = lists:rmerge(F, [4,3,2],[6,5,1]),
+ [7,6,5,3,1] = lists:rmerge(F, [7,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rmerge(F, [7,5,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rmerge(F, [7,5,3,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rmerge(F, [2], [7,5,3,1]),
+ [7,5,4,3,2,1] = lists:rmerge(F, [4,2], [7,5,3,1]),
+ [7,6,5,4,3,2,1] = lists:rmerge(F, [6,4,2], [7,5,3,1]),
F2 = fun(X,Y) -> element(1,X) =< element(1,Y) end,
L1 = [{c,11},{c,12},{e,5}],
L2 = [{b,2},{c,21},{c,22}],
- ?line true =
+ true =
lists:merge(F2, L1, L2) ==
lists:reverse(lists:rmerge(F2,lists:reverse(L1), lists:reverse(L2))),
@@ -1319,52 +1319,52 @@ rfunmerge(Config) when is_list(Config) ->
funsort_1(Config) when is_list(Config) ->
- ?line ok = funsort_check(1, [], []),
- ?line ok = funsort_check(1, [{a,b}], [{a,b}]),
- ?line ok = funsort_check(1, [{a,b},{a,b}], [{a,b},{a,b}]),
- ?line ok = funsort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
- ?line ok = funsort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
- ?line ok = funsort_check(1,
- [{1,e},{3,f},{2,y},{0,z},{x,14}],
- [{0,z},{1,e},{2,y},{3,f},{x,14}]),
+ ok = funsort_check(1, [], []),
+ ok = funsort_check(1, [{a,b}], [{a,b}]),
+ ok = funsort_check(1, [{a,b},{a,b}], [{a,b},{a,b}]),
+ ok = funsort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
+ ok = funsort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
+ ok = funsort_check(1,
+ [{1,e},{3,f},{2,y},{0,z},{x,14}],
+ [{0,z},{1,e},{2,y},{3,f},{x,14}]),
F = funsort_fun(1),
- ?line [{b,1},{c,1}] = lists:sort(F, [{c,1},{b,1}]),
- ?line [{a,0},{b,2},{c,3},{d,4}] =
- lists:sort(F, [{d,4},{c,3},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{b,2},{c,1}] =
- lists:sort(F, [{c,1},{b,1},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{b,2},{c,1},{d,4}] =
- lists:sort(F, [{c,1},{b,1},{b,2},{a,0},{d,4}]),
+ [{b,1},{c,1}] = lists:sort(F, [{c,1},{b,1}]),
+ [{a,0},{b,2},{c,3},{d,4}] =
+ lists:sort(F, [{d,4},{c,3},{b,2},{a,0}]),
+ [{a,0},{b,1},{b,2},{c,1}] =
+ lists:sort(F, [{c,1},{b,1},{b,2},{a,0}]),
+ [{a,0},{b,1},{b,2},{c,1},{d,4}] =
+ lists:sort(F, [{c,1},{b,1},{b,2},{a,0},{d,4}]),
SFun = fun(L) -> fun(X) -> funsort_check(1, X, L) end end,
L1 = [{1,a},{1,a},{2,b},{2,b},{3,c},{4,d},{5,e},{6,f}],
- ?line lists:foreach(SFun(L1), perms(L1)),
+ lists:foreach(SFun(L1), perms(L1)),
ok.
%% sort/2 should be stable.
funsort_stable(Config) when is_list(Config) ->
- ?line ok = funsort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]),
- ?line ok = funsort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]),
- ?line ok = funsort_check(1,
- [{1,c},{1,b},{2,x},{3,p},{2,a}],
- [{1,c},{1,b},{2,x},{2,a},{3,p}]),
+ ok = funsort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]),
+ ok = funsort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]),
+ ok = funsort_check(1,
+ [{1,c},{1,b},{2,x},{3,p},{2,a}],
+ [{1,c},{1,b},{2,x},{2,a},{3,p}]),
ok.
%% sort/2 should exit when given bad arguments.
funsort_error(Config) when is_list(Config) ->
- ?line {'EXIT', _} = (catch lists:sort(1, [{1,b} , {1,c}])),
- ?line {'EXIT', _} = (catch lists:sort(fun(X,Y) -> X =< Y end,
- [{1,b} | {1,c}])),
+ {'EXIT', _} = (catch lists:sort(1, [{1,b} , {1,c}])),
+ {'EXIT', _} = (catch lists:sort(fun(X,Y) -> X =< Y end,
+ [{1,b} | {1,c}])),
ok.
%% sort/2 on big randomized lists.
funsort_rand(Config) when is_list(Config) ->
- ?line ok = funsort_check3(1, biglist(10)),
- ?line ok = funsort_check3(1, biglist(100)),
- ?line ok = funsort_check3(1, biglist(1000)),
- ?line ok = funsort_check3(1, biglist(10000)),
+ ok = funsort_check3(1, biglist(10)),
+ ok = funsort_check3(1, biglist(100)),
+ ok = funsort_check3(1, biglist(1000)),
+ ok = funsort_check3(1, biglist(10000)),
ok.
%% Do a keysort
@@ -1377,7 +1377,7 @@ funsort_check3(I, Input) ->
%%% Keysort a list, check that the returned list is what we expected,
%%% and that it is actually sorted.
funsort_check(I, Input, Expected) ->
- ?line Expected = funsort(I, Input),
+ Expected = funsort(I, Input),
check_sorted(I, Input, Expected).
@@ -1389,33 +1389,33 @@ ufunmerge(Conf) when is_list(Conf) ->
F = fun(X, Y) -> X =< Y end,
%% 2-way unique merge
- ?line [] = lists:umerge(F, [], []),
- ?line Two = lists:umerge(F, Two, []),
- ?line Two = lists:umerge(F, [], Two),
- ?line Six = lists:umerge(F, [1,3,5], [2,4,6]),
- ?line Six = lists:umerge(F, [2,4,6], [1,3,5]),
- ?line Six = lists:umerge(F, [1,2,3], [4,5,6]),
- ?line Six = lists:umerge(F, [4,5,6], [1,2,3]),
- ?line Six = lists:umerge(F, [1,2,5],[3,4,6]),
- ?line [1,2,3,5,7] = lists:umerge(F, [1,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:umerge(F, [1,3,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:umerge(F, [1,3,5,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:umerge(F, [2], [1,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:umerge(F, [2,4], [1,3,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:umerge(F, [2,4,6], [1,3,5,7]),
-
- ?line [1,2,3,5,7] = lists:umerge(F, [1,2,3,5,7], [2]),
- ?line [1,2,3,4,5,7] = lists:umerge(F, [1,2,3,4,5,7], [2,4]),
- ?line [1,2,3,4,5,6,7] = lists:umerge(F, [1,3,5,6,7], [2,4,6]),
- ?line [1,2,3,5,7] = lists:umerge(F, [2], [1,2,3,5,7]),
- ?line [1,2,3,4,5,7] = lists:umerge(F, [2,4], [1,2,3,4,5,7]),
- ?line [1,2,3,4,5,6,7] = lists:umerge(F, [2,4,6], [1,2,3,4,5,6,7]),
+ [] = lists:umerge(F, [], []),
+ Two = lists:umerge(F, Two, []),
+ Two = lists:umerge(F, [], Two),
+ Six = lists:umerge(F, [1,3,5], [2,4,6]),
+ Six = lists:umerge(F, [2,4,6], [1,3,5]),
+ Six = lists:umerge(F, [1,2,3], [4,5,6]),
+ Six = lists:umerge(F, [4,5,6], [1,2,3]),
+ Six = lists:umerge(F, [1,2,5],[3,4,6]),
+ [1,2,3,5,7] = lists:umerge(F, [1,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:umerge(F, [1,3,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:umerge(F, [1,3,5,7], [2,4,6]),
+ [1,2,3,5,7] = lists:umerge(F, [2], [1,3,5,7]),
+ [1,2,3,4,5,7] = lists:umerge(F, [2,4], [1,3,5,7]),
+ [1,2,3,4,5,6,7] = lists:umerge(F, [2,4,6], [1,3,5,7]),
+
+ [1,2,3,5,7] = lists:umerge(F, [1,2,3,5,7], [2]),
+ [1,2,3,4,5,7] = lists:umerge(F, [1,2,3,4,5,7], [2,4]),
+ [1,2,3,4,5,6,7] = lists:umerge(F, [1,3,5,6,7], [2,4,6]),
+ [1,2,3,5,7] = lists:umerge(F, [2], [1,2,3,5,7]),
+ [1,2,3,4,5,7] = lists:umerge(F, [2,4], [1,2,3,4,5,7]),
+ [1,2,3,4,5,6,7] = lists:umerge(F, [2,4,6], [1,2,3,4,5,6,7]),
L1 = [{a,1},{a,3},{a,5},{a,7}],
L2 = [{b,1},{b,3},{b,5},{b,7}],
F2 = fun(X,Y) -> element(2,X) =< element(2,Y) end,
- ?line L1 = lists:umerge(F2, L1, L2),
- ?line [{b,2},{e,5},{c,11},{c,12},{c,21},{c,22}] =
+ L1 = lists:umerge(F2, L1, L2),
+ [{b,2},{e,5},{c,11},{c,12},{c,21},{c,22}] =
lists:umerge(F2, [{e,5},{c,11},{c,12}], [{b,2},{c,21},{c,22}]),
ok.
@@ -1427,130 +1427,130 @@ rufunmerge(Conf) when is_list(Conf) ->
F = fun(X, Y) -> X =< Y end,
%% 2-way reversed unique merge
- ?line [] = lists:rumerge(F, [], []),
- ?line Two = lists:rumerge(F, Two, []),
- ?line Two = lists:rumerge(F, [], Two),
- ?line Six = lists:rumerge(F, [5,3,1], [6,4,2]),
- ?line Six = lists:rumerge(F, [6,4,2], [5,3,1]),
- ?line Six = lists:rumerge(F, [3,2,1], [6,5,4]),
- ?line Six = lists:rumerge(F, [6,5,4], [3,2,1]),
- ?line Six = lists:rumerge(F, [4,3,2],[6,5,1]),
- ?line [7,6,5,3,1] = lists:rumerge(F, [7,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rumerge(F, [7,5,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge(F, [7,5,3,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rumerge(F, [2], [7,5,3,1]),
- ?line [7,5,4,3,2,1] = lists:rumerge(F, [4,2], [7,5,3,1]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge(F, [6,4,2], [7,5,3,1]),
-
- ?line [7,6,5,3,1] = lists:rumerge(F, [7,6,5,3,1], [6]),
- ?line [7,6,5,4,3,1] = lists:rumerge(F, [7,6,5,4,3,1], [6,4]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge(F, [7,6,5,4,3,2,1], [6,4,2]),
- ?line [7,5,3,2,1] = lists:rumerge(F, [2], [7,5,3,2,1]),
- ?line [7,5,4,3,2,1] = lists:rumerge(F, [4,2], [7,5,4,3,2,1]),
- ?line [7,6,5,4,3,2,1] = lists:rumerge(F, [6,4,2], [7,6,5,4,3,2,1]),
+ [] = lists:rumerge(F, [], []),
+ Two = lists:rumerge(F, Two, []),
+ Two = lists:rumerge(F, [], Two),
+ Six = lists:rumerge(F, [5,3,1], [6,4,2]),
+ Six = lists:rumerge(F, [6,4,2], [5,3,1]),
+ Six = lists:rumerge(F, [3,2,1], [6,5,4]),
+ Six = lists:rumerge(F, [6,5,4], [3,2,1]),
+ Six = lists:rumerge(F, [4,3,2],[6,5,1]),
+ [7,6,5,3,1] = lists:rumerge(F, [7,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rumerge(F, [7,5,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rumerge(F, [7,5,3,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rumerge(F, [2], [7,5,3,1]),
+ [7,5,4,3,2,1] = lists:rumerge(F, [4,2], [7,5,3,1]),
+ [7,6,5,4,3,2,1] = lists:rumerge(F, [6,4,2], [7,5,3,1]),
+
+ [7,6,5,3,1] = lists:rumerge(F, [7,6,5,3,1], [6]),
+ [7,6,5,4,3,1] = lists:rumerge(F, [7,6,5,4,3,1], [6,4]),
+ [7,6,5,4,3,2,1] = lists:rumerge(F, [7,6,5,4,3,2,1], [6,4,2]),
+ [7,5,3,2,1] = lists:rumerge(F, [2], [7,5,3,2,1]),
+ [7,5,4,3,2,1] = lists:rumerge(F, [4,2], [7,5,4,3,2,1]),
+ [7,6,5,4,3,2,1] = lists:rumerge(F, [6,4,2], [7,6,5,4,3,2,1]),
F2 = fun(X,Y) -> element(1,X) =< element(1,Y) end,
L1 = [{1,a},{1,b},{1,a}],
L2 = [{1,a},{1,b},{1,a}],
- ?line true = lists:umerge(F2, L1, L2) ==
+ true = lists:umerge(F2, L1, L2) ==
lists:reverse(lists:rumerge(F, lists:reverse(L2), lists:reverse(L1))),
L3 = [{c,11},{c,12},{e,5}],
L4 = [{b,2},{c,21},{c,22}],
- ?line true =
+ true =
lists:umerge(F2, L3, L4) ==
lists:reverse(lists:rumerge(F2,lists:reverse(L3), lists:reverse(L4))),
ok.
ufunsort_1(Config) when is_list(Config) ->
- ?line ok = ufunsort_check(1, [], []),
- ?line ok = ufunsort_check(1, [{a,b}], [{a,b}]),
- ?line ok = ufunsort_check(1, [{a,b},{a,b}], [{a,b}]),
- ?line ok = ufunsort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
- ?line ok = ufunsort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
- ?line ok = ufunsort_check(1,
- [{1,e},{3,f},{2,y},{0,z},{x,14}],
- [{0,z},{1,e},{2,y},{3,f},{x,14}]),
- ?line ok = ufunsort_check(1,
- [{1,a},{2,b},{3,c},{2,b},{1,a},{2,b},{3,c},
- {2,b},{1,a}],
- [{1,a},{2,b},{3,c}]),
- ?line ok = ufunsort_check(1,
- [{1,a},{1,a},{1,b},{1,b},{1,a},{2,a}],
- [{1,a},{2,a}]),
+ ok = ufunsort_check(1, [], []),
+ ok = ufunsort_check(1, [{a,b}], [{a,b}]),
+ ok = ufunsort_check(1, [{a,b},{a,b}], [{a,b}]),
+ ok = ufunsort_check(1, [{a,b},{b,c}], [{a,b},{b,c}]),
+ ok = ufunsort_check(1, [{b,c},{a,b}], [{a,b},{b,c}]),
+ ok = ufunsort_check(1,
+ [{1,e},{3,f},{2,y},{0,z},{x,14}],
+ [{0,z},{1,e},{2,y},{3,f},{x,14}]),
+ ok = ufunsort_check(1,
+ [{1,a},{2,b},{3,c},{2,b},{1,a},{2,b},{3,c},
+ {2,b},{1,a}],
+ [{1,a},{2,b},{3,c}]),
+ ok = ufunsort_check(1,
+ [{1,a},{1,a},{1,b},{1,b},{1,a},{2,a}],
+ [{1,a},{2,a}]),
F = funsort_fun(1),
L1 = [{1,a},{1,b},{1,a}],
L2 = [{1,a},{1,b},{1,a}],
- ?line ok = ufunsort_check(1, lists:keymerge(1, L1, L2),
- lists:umerge(F, lists:usort(F, L1),
- lists:usort(F, L2))),
+ ok = ufunsort_check(1, lists:keymerge(1, L1, L2),
+ lists:umerge(F, lists:usort(F, L1),
+ lists:usort(F, L2))),
L3 = [{1,a},{1,b},{1,a},{2,a}],
- ?line ok = ufunsort_check(1, lists:keymerge(1, L3, L2),
- lists:umerge(F, lists:usort(F, L3),
- lists:usort(F, L2))),
+ ok = ufunsort_check(1, lists:keymerge(1, L3, L2),
+ lists:umerge(F, lists:usort(F, L3),
+ lists:usort(F, L2))),
L4 = [{1,b},{1,a}],
- ?line ok = ufunsort_check(1, lists:keymerge(1, L1, L4),
- lists:umerge(F, lists:usort(F, L1),
- lists:usort(F, L4))),
+ ok = ufunsort_check(1, lists:keymerge(1, L1, L4),
+ lists:umerge(F, lists:usort(F, L1),
+ lists:usort(F, L4))),
L5 = [{1,a},{1,b},{1,a},{2,a}],
- ?line ok = ufunsort_check(1, lists:keymerge(1, L5, []),
- lists:umerge(F, lists:usort(F, L5), [])),
+ ok = ufunsort_check(1, lists:keymerge(1, L5, []),
+ lists:umerge(F, lists:usort(F, L5), [])),
L6 = [{3,a}],
- ?line ok = ufunsort_check(1, lists:keymerge(1, L5, L6),
- lists:umerge(F, lists:usort(F, L5),
- lists:usort(F, L6))),
-
- ?line [{b,1},{c,1}] = lists:usort(F, [{c,1},{c,1},{b,1}]),
- ?line [{a,0},{b,2},{c,3},{d,4}] =
- lists:usort(F, [{d,4},{c,3},{b,2},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{c,1}] =
- lists:usort(F, [{c,1},{b,1},{b,1},{b,2},{b,2},{a,0}]),
- ?line [{a,0},{b,1},{c,1},{d,4}] =
- lists:usort(F, [{c,1},{b,1},{b,2},{a,0},{a,0},{d,4},{d,4}]),
+ ok = ufunsort_check(1, lists:keymerge(1, L5, L6),
+ lists:umerge(F, lists:usort(F, L5),
+ lists:usort(F, L6))),
+
+ [{b,1},{c,1}] = lists:usort(F, [{c,1},{c,1},{b,1}]),
+ [{a,0},{b,2},{c,3},{d,4}] =
+ lists:usort(F, [{d,4},{c,3},{b,2},{b,2},{a,0}]),
+ [{a,0},{b,1},{c,1}] =
+ lists:usort(F, [{c,1},{b,1},{b,1},{b,2},{b,2},{a,0}]),
+ [{a,0},{b,1},{c,1},{d,4}] =
+ lists:usort(F, [{c,1},{b,1},{b,2},{a,0},{a,0},{d,4},{d,4}]),
SFun = fun(L) -> fun(X) -> ufunsort_check(1, X, L) end end,
PL = [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f}],
Ps = perms([{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{2,b},{1,a}]),
- ?line lists:foreach(SFun(PL), Ps),
+ lists:foreach(SFun(PL), Ps),
ok.
%% usort/2 should be stable.
ufunsort_stable(Config) when is_list(Config) ->
- ?line ok = ufunsort_check(1, [{1,b},{1,c}], [{1,b}]),
- ?line ok = ufunsort_check(1, [{1,c},{1,b}], [{1,c}]),
- ?line ok = ufunsort_check(1,
- [{1,c},{1,b},{2,x},{3,p},{2,a}],
- [{1,c},{2,x},{3,p}]),
+ ok = ufunsort_check(1, [{1,b},{1,c}], [{1,b}]),
+ ok = ufunsort_check(1, [{1,c},{1,b}], [{1,c}]),
+ ok = ufunsort_check(1,
+ [{1,c},{1,b},{2,x},{3,p},{2,a}],
+ [{1,c},{2,x},{3,p}]),
- ?line ok = ufunsort_check_stability(bigfunlist(10)),
- ?line ok = ufunsort_check_stability(bigfunlist(100)),
- ?line ok = ufunsort_check_stability(bigfunlist(1000)),
- ?line case erlang:system_info(modified_timing_level) of
- undefined -> ok = ufunsort_check_stability(bigfunlist(10000));
- _ -> ok
- end,
+ ok = ufunsort_check_stability(bigfunlist(10)),
+ ok = ufunsort_check_stability(bigfunlist(100)),
+ ok = ufunsort_check_stability(bigfunlist(1000)),
+ case erlang:system_info(modified_timing_level) of
+ undefined -> ok = ufunsort_check_stability(bigfunlist(10000));
+ _ -> ok
+ end,
ok.
%% usort/2 should exit when given bad arguments.
ufunsort_error(Config) when is_list(Config) ->
- ?line {'EXIT', _} = (catch lists:usort(1, [{1,b} , {1,c}])),
- ?line {'EXIT', _} = (catch lists:usort(fun(X,Y) -> X =< Y end,
- [{1,b} | {1,c}])),
+ {'EXIT', _} = (catch lists:usort(1, [{1,b} , {1,c}])),
+ {'EXIT', _} = (catch lists:usort(fun(X,Y) -> X =< Y end,
+ [{1,b} | {1,c}])),
ok.
%% usort/2 on big randomized lists.
ufunsort_rand(Config) when is_list(Config) ->
- ?line ok = ufunsort_check3(1, biglist(10)),
- ?line ok = ufunsort_check3(1, biglist(100)),
- ?line ok = ufunsort_check3(1, biglist(1000)),
- ?line ok = ufunsort_check3(1, biglist(10000)),
+ ok = ufunsort_check3(1, biglist(10)),
+ ok = ufunsort_check3(1, biglist(100)),
+ ok = ufunsort_check3(1, biglist(1000)),
+ ok = ufunsort_check3(1, biglist(10000)),
- ?line ok = gen_ufunsort_check(1, ubiglist(100)),
- ?line ok = gen_ufunsort_check(1, ubiglist(1000)),
- ?line ok = gen_ufunsort_check(1, ubiglist(10000)),
+ ok = gen_ufunsort_check(1, ubiglist(100)),
+ ok = gen_ufunsort_check(1, ubiglist(1000)),
+ ok = gen_ufunsort_check(1, ubiglist(10000)),
ok.
%% Check that usort/2 is stable and correct relative sort/2.
@@ -1578,7 +1578,7 @@ ufunsort_check3(I, Input) ->
%%% Keysort a list, check that the returned list is what we expected,
%%% and that it is actually sorted.
ufunsort_check(I, Input, Expected) ->
- ?line Expected = ufunsort(I, Input),
+ Expected = ufunsort(I, Input),
ucheck_sorted(I, Input, Expected).
%% Do a keysort
@@ -1633,7 +1633,7 @@ ubiglist(0, L) ->
ubiglist(N, L) ->
E = urandom_tuple(11, 6),
ubiglist(N-1, [E|L]).
-
+
urandom_tuple(N, I) ->
R1 = randint(N),
R2 = randint(I),
@@ -1665,7 +1665,7 @@ bigfunlist(0, _P, L) ->
bigfunlist(N, P, L) ->
{E, NP} = random_funtuple(P, 11),
bigfunlist(N-1, NP, [E | L]).
-
+
random_funtuple(P, N) ->
R = randint(N),
F = make_fun(),
@@ -1676,7 +1676,7 @@ random_funtuple(P, N) ->
make_fun() ->
Pid = spawn(?MODULE, make_fun, [self()]),
receive {Pid, Fun} -> Fun end.
-
+
make_fun(Pid) ->
Pid ! {self(), fun make_fun/1}.
@@ -1786,7 +1786,7 @@ sloop(N, S) ->
end,
sloop(N, NS)
end.
-
+
display_state(S) ->
io:format("sort: ~p~n", [S#state.sort]),
io:format("usort: ~p~n", [S#state.usort]),
@@ -2057,24 +2057,24 @@ rkeymerge2_2(_I, T1, _E1, [], M, H1) ->
%% Test for infinite loop (OTP-2404).
seq_loop(Config) when is_list(Config) ->
- ?line _ = (catch lists:seq(1, 5, -1)),
+ _ = (catch lists:seq(1, 5, -1)),
ok.
%% Non-error cases for seq/2.
seq_2(Config) when is_list(Config) ->
- ?line [1,2,3] = lists:seq(1,3),
- ?line [1] = lists:seq(1,1),
- ?line Big = 748274827583793785928592859,
- ?line Big1 = Big+1,
- ?line Big2 = Big+2,
- ?line [Big, Big1, Big2] = lists:seq(Big, Big+2),
+ [1,2,3] = lists:seq(1,3),
+ [1] = lists:seq(1,1),
+ Big = 748274827583793785928592859,
+ Big1 = Big+1,
+ Big2 = Big+2,
+ [Big, Big1, Big2] = lists:seq(Big, Big+2),
ok.
%% Error cases for seq/2.
seq_2_e(Config) when is_list(Config) ->
- ?line seq_error([4, 2]),
- ?line seq_error([1, a]),
- ?line seq_error([1.0, 2.0]),
+ seq_error([4, 2]),
+ seq_error([1, a]),
+ seq_error([1.0, 2.0]),
ok.
seq_error(Args) ->
@@ -2082,37 +2082,37 @@ seq_error(Args) ->
%% Non-error cases for seq/3.
seq_3(Config) when is_list(Config) ->
- ?line [1,2,3] = lists:seq(1,3,1),
- ?line [1] = lists:seq(1,1,1),
- ?line Big = 748274827583793785928592859,
- ?line Big1 = Big+1,
- ?line Big2 = Big+2,
- ?line [Big, Big1, Big2] = lists:seq(Big, Big+2,1),
+ [1,2,3] = lists:seq(1,3,1),
+ [1] = lists:seq(1,1,1),
+ Big = 748274827583793785928592859,
+ Big1 = Big+1,
+ Big2 = Big+2,
+ [Big, Big1, Big2] = lists:seq(Big, Big+2,1),
- ?line [3,2,1] = lists:seq(3,1,-1),
- ?line [1] = lists:seq(1,1,-1),
+ [3,2,1] = lists:seq(3,1,-1),
+ [1] = lists:seq(1,1,-1),
- ?line [3,1] = lists:seq(3,1,-2),
- ?line [1] = lists:seq(1, 10, 10),
- ?line [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 19, 3),
- ?line [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 20, 3),
- ?line [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 21, 3),
+ [3,1] = lists:seq(3,1,-2),
+ [1] = lists:seq(1, 10, 10),
+ [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 19, 3),
+ [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 20, 3),
+ [1, 4, 7, 10, 13, 16, 19] = lists:seq(1, 21, 3),
- ?line [1] = lists:seq(1, 1, 0), %OTP-2613
+ [1] = lists:seq(1, 1, 0), %OTP-2613
ok.
%% Error cases for seq/3.
seq_3_e(Config) when is_list(Config) ->
- ?line seq_error([4, 2, 1]),
- ?line seq_error([3, 5, -1]),
- ?line seq_error([1, a, 1]),
- ?line seq_error([1.0, 2.0, 1]),
+ seq_error([4, 2, 1]),
+ seq_error([3, 5, -1]),
+ seq_error([1, a, 1]),
+ seq_error([1.0, 2.0, 1]),
- ?line seq_error([1, 3, 1.0]),
- ?line seq_error([1, 3, a]),
- ?line seq_error([1, 3, 0]),
+ seq_error([1, 3, 1.0]),
+ seq_error([1, 3, a]),
+ seq_error([1, 3, 0]),
- ?line seq_error([a, a, 0]),
+ seq_error([a, a, 0]),
ok.
%% OTP-7230. seq/1,2 returns the empty list.
@@ -2124,26 +2124,26 @@ otp_7230(Config) when is_list(Config) ->
L = lists:seq(From, To),
SL = lists:seq(StepFrom, StepTo),
- ?line [] =
- [{F, T, S} ||
- F <- L, T <- L, S <- SL,
- not check_seq(F, T, S, catch lists:seq(F, T, S))
- orelse
- S =:= 1 andalso not check_seq(F, T, S, catch lists:seq(F, T))
+ [] =
+ [{F, T, S} ||
+ F <- L, T <- L, S <- SL,
+ not check_seq(F, T, S, catch lists:seq(F, T, S))
+ orelse
+ S =:= 1 andalso not check_seq(F, T, S, catch lists:seq(F, T))
].
check_seq(From, To, 0, R) ->
- From =:= To andalso R =:= [From]
- orelse
- From =/= To andalso is_tuple(R) andalso element(1, R) =:= 'EXIT';
+ From =:= To andalso R =:= [From]
+ orelse
+ From =/= To andalso is_tuple(R) andalso element(1, R) =:= 'EXIT';
check_seq(From, To, Step, []) when Step =/= 0 ->
- 0 =:= property(From, To, Step)
- andalso
- (
- Step > 0 andalso To < From andalso From-To =< Step
- orelse
- Step < 0 andalso To > From andalso To-From =< -Step
- );
+ 0 =:= property(From, To, Step)
+ andalso
+ (
+ Step > 0 andalso To < From andalso From-To =< Step
+ orelse
+ Step < 0 andalso To > From andalso To-From =< -Step
+ );
check_seq(From, To, Step, R) when R =/= [], To < From, Step > 0 ->
is_tuple(R) andalso element(1, R) =:= 'EXIT';
check_seq(From, To, Step, R) when R =/= [], To > From, Step < 0 ->
@@ -2154,27 +2154,27 @@ check_seq(From, To, Step, L) when is_list(L), L =/= [], Step =/= 0 ->
Min = lists:min(L),
Max = lists:max(L),
- [] =:= [E || E <- L, not is_integer(E)]
- andalso
- %% The difference between two consecutive elements is Step:
- begin
- LS = [First-Step]++L,
- LR = L++[Last+Step],
- [Step] =:= lists:usort([B-A || {A,B} <- lists:zip(LS, LR)])
- end
- andalso
- %% The first element of L is From:
- From =:= First
- andalso
- %% No element outside the given interval:
- Min >= lists:min([From, To])
- andalso
- Max =< lists:max([From, To])
- andalso
- %% All elements are present:
- abs(To-Last) < abs(Step)
- andalso
- length(L) =:= property(From, To, Step);
+ [] =:= [E || E <- L, not is_integer(E)]
+ andalso
+ %% The difference between two consecutive elements is Step:
+ begin
+ LS = [First-Step]++L,
+ LR = L++[Last+Step],
+ [Step] =:= lists:usort([B-A || {A,B} <- lists:zip(LS, LR)])
+ end
+ andalso
+ %% The first element of L is From:
+ From =:= First
+ andalso
+ %% No element outside the given interval:
+ Min >= lists:min([From, To])
+ andalso
+ Max =< lists:max([From, To])
+ andalso
+ %% All elements are present:
+ abs(To-Last) < abs(Step)
+ andalso
+ length(L) =:= property(From, To, Step);
check_seq(_From, _To, _Step, _R) ->
false.
@@ -2184,18 +2184,18 @@ property(From, To, Step) ->
%%%------------------------------------------------------------
--define(sublist_error2(X,Y), ?line {'EXIT', _} = (catch lists:sublist(X,Y))).
--define(sublist_error3(X,Y,Z), ?line {'EXIT', _} = (catch lists:sublist(X,Y,Z))).
+-define(sublist_error2(X,Y), {'EXIT', _} = (catch lists:sublist(X,Y))).
+-define(sublist_error3(X,Y,Z), {'EXIT', _} = (catch lists:sublist(X,Y,Z))).
sublist_2(Config) when is_list(Config) ->
- ?line [] = lists:sublist([], 0),
- ?line [] = lists:sublist([], 1),
- ?line [] = lists:sublist([a], 0),
- ?line [a] = lists:sublist([a], 1),
- ?line [a] = lists:sublist([a], 2),
- ?line [a] = lists:sublist([a|b], 1),
+ [] = lists:sublist([], 0),
+ [] = lists:sublist([], 1),
+ [] = lists:sublist([a], 0),
+ [a] = lists:sublist([a], 1),
+ [a] = lists:sublist([a], 2),
+ [a] = lists:sublist([a|b], 1),
- ?line [a,b] = lists:sublist([a,b|c], 2),
+ [a,b] = lists:sublist([a,b|c], 2),
ok.
@@ -2212,28 +2212,28 @@ sublist_2_e(Config) when is_list(Config) ->
ok.
sublist_3(Config) when is_list(Config) ->
- ?line [] = lists:sublist([], 1, 0),
- ?line [] = lists:sublist([], 1, 1),
- ?line [] = lists:sublist([a], 1, 0),
- ?line [a] = lists:sublist([a], 1, 1),
- ?line [a] = lists:sublist([a], 1, 2),
- ?line [a] = lists:sublist([a|b], 1, 1),
-
- ?line [] = lists:sublist([], 1, 0),
- ?line [] = lists:sublist([], 1, 1),
- ?line [] = lists:sublist([a], 1, 0),
- ?line [a] = lists:sublist([a], 1, 1),
- ?line [a] = lists:sublist([a], 1, 2),
- ?line [] = lists:sublist([a], 2, 1),
- ?line [] = lists:sublist([a], 2, 2),
- ?line [] = lists:sublist([a], 2, 79),
- ?line [] = lists:sublist([a,b|c], 1, 0),
- ?line [] = lists:sublist([a,b|c], 2, 0),
- ?line [a] = lists:sublist([a,b|c], 1, 1),
- ?line [b] = lists:sublist([a,b|c], 2, 1),
- ?line [a,b] = lists:sublist([a,b|c], 1, 2),
-
- ?line [] = lists:sublist([a], 2, 0),
+ [] = lists:sublist([], 1, 0),
+ [] = lists:sublist([], 1, 1),
+ [] = lists:sublist([a], 1, 0),
+ [a] = lists:sublist([a], 1, 1),
+ [a] = lists:sublist([a], 1, 2),
+ [a] = lists:sublist([a|b], 1, 1),
+
+ [] = lists:sublist([], 1, 0),
+ [] = lists:sublist([], 1, 1),
+ [] = lists:sublist([a], 1, 0),
+ [a] = lists:sublist([a], 1, 1),
+ [a] = lists:sublist([a], 1, 2),
+ [] = lists:sublist([a], 2, 1),
+ [] = lists:sublist([a], 2, 2),
+ [] = lists:sublist([a], 2, 79),
+ [] = lists:sublist([a,b|c], 1, 0),
+ [] = lists:sublist([a,b|c], 2, 0),
+ [a] = lists:sublist([a,b|c], 1, 1),
+ [b] = lists:sublist([a,b|c], 2, 1),
+ [a,b] = lists:sublist([a,b|c], 1, 2),
+
+ [] = lists:sublist([a], 2, 0),
ok.
@@ -2271,8 +2271,8 @@ sublist_3_e(Config) when is_list(Config) ->
%%%------------------------------------------------------------
--define(flatten_error1(X), ?line {'EXIT', _} = (catch lists:flatten(X))).
--define(flatten_error2(X,Y), ?line {'EXIT', _} = (catch lists:flatten(X,Y))).
+-define(flatten_error1(X), {'EXIT', _} = (catch lists:flatten(X))).
+-define(flatten_error2(X,Y), {'EXIT', _} = (catch lists:flatten(X,Y))).
%% Test lists:flatten/1,2 and lists:flatlength/1.
flatten_1(Config) when is_list(Config) ->
@@ -2317,53 +2317,53 @@ flatten_2_e(Config) when is_list(Config) ->
%% Test lists:zip/2, lists:unzip/1.
zip_unzip(Config) when is_list(Config) ->
- ?line [] = lists:zip([], []),
- ?line [{a,b}] = lists:zip([a], [b]),
- ?line [{42.0,{kalle,nisse}},{a,b}] = lists:zip([42.0,a], [{kalle,nisse},b]),
+ [] = lists:zip([], []),
+ [{a,b}] = lists:zip([a], [b]),
+ [{42.0,{kalle,nisse}},{a,b}] = lists:zip([42.0,a], [{kalle,nisse},b]),
%% Longer lists.
- ?line SeqA = lists:seq(45, 200),
- ?line SeqB = [A*A || A <- SeqA],
- ?line AB = lists:zip(SeqA, SeqB),
- ?line SeqA = [A || {A,_} <- AB],
- ?line SeqB = [B || {_,B} <- AB],
- ?line {SeqA,SeqB} = lists:unzip(AB),
-
+ SeqA = lists:seq(45, 200),
+ SeqB = [A*A || A <- SeqA],
+ AB = lists:zip(SeqA, SeqB),
+ SeqA = [A || {A,_} <- AB],
+ SeqB = [B || {_,B} <- AB],
+ {SeqA,SeqB} = lists:unzip(AB),
+
%% Some more unzip/1.
- ?line {[],[]} = lists:unzip([]),
- ?line {[a],[b]} = lists:unzip([{a,b}]),
- ?line {[a,c],[b,d]} = lists:unzip([{a,b},{c,d}]),
+ {[],[]} = lists:unzip([]),
+ {[a],[b]} = lists:unzip([{a,b}]),
+ {[a,c],[b,d]} = lists:unzip([{a,b},{c,d}]),
%% Error cases.
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip([], [b])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip([a], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip([a], [b,c])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip([a], [b,c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip([], [b])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip([a], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip([a], [b,c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip([a], [b,c])),
ok.
%% Test lists:zip3/3, lists:unzip3/1.
zip_unzip3(Config) when is_list(Config) ->
- ?line [] = lists:zip3([], [], []),
- ?line [{a,b,c}] = lists:zip3([a], [b], [c]),
+ [] = lists:zip3([], [], []),
+ [{a,b,c}] = lists:zip3([a], [b], [c]),
%% Longer lists.
- ?line SeqA = lists:seq(45, 200),
- ?line SeqB = [2*A || A <- SeqA],
- ?line SeqC = [A*A || A <- SeqA],
- ?line ABC = lists:zip3(SeqA, SeqB, SeqC),
- ?line SeqA = [A || {A,_,_} <- ABC],
- ?line SeqB = [B || {_,B,_} <- ABC],
- ?line SeqC = [C || {_,_,C} <- ABC],
- ?line {SeqA,SeqB,SeqC} = lists:unzip3(ABC),
+ SeqA = lists:seq(45, 200),
+ SeqB = [2*A || A <- SeqA],
+ SeqC = [A*A || A <- SeqA],
+ ABC = lists:zip3(SeqA, SeqB, SeqC),
+ SeqA = [A || {A,_,_} <- ABC],
+ SeqB = [B || {_,B,_} <- ABC],
+ SeqC = [C || {_,_,C} <- ABC],
+ {SeqA,SeqB,SeqC} = lists:unzip3(ABC),
%% Some more unzip3/1.
- ?line {[],[],[]} = lists:unzip3([]),
- ?line {[a],[b],[c]} = lists:unzip3([{a,b,c}]),
+ {[],[],[]} = lists:unzip3([]),
+ {[a],[b],[c]} = lists:unzip3([{a,b,c}]),
%% Error cases.
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip3([], [], [c])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip3([], [b], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zip3([a], [], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip3([], [], [c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip3([], [b], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zip3([a], [], [])),
ok.
@@ -2371,61 +2371,61 @@ zip_unzip3(Config) when is_list(Config) ->
zipwith(Config) when is_list(Config) ->
Zip = fun(A, B) -> [A|B] end,
- ?line [] = lists:zipwith(Zip, [], []),
- ?line [[a|b]] = lists:zipwith(Zip, [a], [b]),
+ [] = lists:zipwith(Zip, [], []),
+ [[a|b]] = lists:zipwith(Zip, [a], [b]),
%% Longer lists.
- ?line SeqA = lists:seq(77, 300),
- ?line SeqB = [A*A || A <- SeqA],
- ?line AB = lists:zipwith(Zip, SeqA, SeqB),
- ?line SeqA = [A || [A|_] <- AB],
- ?line SeqB = [B || [_|B] <- AB],
-
+ SeqA = lists:seq(77, 300),
+ SeqB = [A*A || A <- SeqA],
+ AB = lists:zipwith(Zip, SeqA, SeqB),
+ SeqA = [A || [A|_] <- AB],
+ SeqB = [B || [_|B] <- AB],
+
%% Error cases.
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith(badfun, [], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [], [b])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [b,c])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [b,c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith(badfun, [], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [], [b])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [b,c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [b,c])),
ok.
%% Test lists:zipwith3/4.
zipwith3(Config) when is_list(Config) ->
Zip = fun(A, B, C) -> [A,B,C] end,
- ?line [] = lists:zipwith3(Zip, [], [], []),
- ?line [[a,b,c]] = lists:zipwith3(Zip, [a], [b], [c]),
+ [] = lists:zipwith3(Zip, [], [], []),
+ [[a,b,c]] = lists:zipwith3(Zip, [a], [b], [c]),
%% Longer lists.
- ?line SeqA = lists:seq(45, 200),
- ?line SeqB = [2*A || A <- SeqA],
- ?line SeqC = [A*A || A <- SeqA],
- ?line ABC = lists:zipwith3(Zip, SeqA, SeqB, SeqC),
- ?line SeqA = [A || [A,_,_] <- ABC],
- ?line SeqB = [B || [_,B,_] <- ABC],
- ?line SeqC = [C || [_,_,C] <- ABC],
+ SeqA = lists:seq(45, 200),
+ SeqB = [2*A || A <- SeqA],
+ SeqC = [A*A || A <- SeqA],
+ ABC = lists:zipwith3(Zip, SeqA, SeqB, SeqC),
+ SeqA = [A || [A,_,_] <- ABC],
+ SeqB = [B || [_,B,_] <- ABC],
+ SeqC = [C || [_,_,C] <- ABC],
%% Error cases.
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith3(badfun, [], [], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [], [], [c])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [], [b], [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [a], [], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith3(badfun, [], [], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [], [], [c])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [], [b], [])),
+ {'EXIT',{function_clause,_}} = (catch lists:zipwith3(Zip, [a], [], [])),
ok.
%% Test lists:filter/2, lists:partition/2.
filter_partition(Config) when is_list(Config) ->
F = fun(I) -> I rem 2 =:= 0 end,
- ?line filpart(F, [], []),
- ?line filpart(F, [1], []),
- ?line filpart(F, [1,3,17], []),
- ?line filpart(F, [1,2,3,17], [2]),
- ?line filpart(F, [6,8,1,2,3,17], [6,8,2]),
- ?line filpart(F, [6,8,1,2,42,3,17], [6,8,2,42]),
+ filpart(F, [], []),
+ filpart(F, [1], []),
+ filpart(F, [1,3,17], []),
+ filpart(F, [1,2,3,17], [2]),
+ filpart(F, [6,8,1,2,3,17], [6,8,2]),
+ filpart(F, [6,8,1,2,42,3,17], [6,8,2,42]),
%% Error cases.
- ?line {'EXIT',{function_clause,_}} = (catch lists:filter(badfun, [])),
- ?line {'EXIT',{function_clause,_}} = (catch lists:partition(badfun, [])),
+ {'EXIT',{function_clause,_}} = (catch lists:filter(badfun, [])),
+ {'EXIT',{function_clause,_}} = (catch lists:partition(badfun, [])),
ok.
filpart(F, All, Exp) ->
@@ -2443,68 +2443,68 @@ otp_5939(Config) when is_list(Config) ->
Fold = fun(_E, A) -> A end,
MapFold = fun(E, A) -> {E,A} end,
- ?line {'EXIT', _} = (catch lists:usort( [asd], [qwe])),
-
- ?line {'EXIT', _} = (catch lists:zipwith(func, [], [])),
- ?line [] = lists:zipwith(Fun2, [], []),
- ?line {'EXIT', _} = (catch lists:zipwith3(func, [], [], [])),
- ?line [] = lists:zipwith3(Fun3, [], [], []),
- ?line {'EXIT', _} = (catch lists:keymap(func, 1, [])),
- ?line {'EXIT', _} = (catch lists:keymap(Fun1, 0, [])),
- ?line [] = lists:keymap(Fun1, 1, []),
- ?line {'EXIT', _} = (catch lists:merge(func, [], [1])),
- ?line {'EXIT', _} = (catch lists:merge(func, [1], [])),
- ?line [] = lists:merge(Fun2, [], []),
- ?line {'EXIT', _} = (catch lists:rmerge(func, [], [1])),
- ?line {'EXIT', _} = (catch lists:rmerge(func, [1], [])),
- ?line [] = lists:rmerge(Fun2, [], []),
- ?line {'EXIT', _} = (catch lists:usort(func, [])),
- ?line {'EXIT', _} = (catch lists:usort(func, [a])),
- ?line {'EXIT', _} = (catch lists:usort(func, [a, b])),
- ?line [] = lists:usort(Fun2, []),
- ?line {'EXIT', _} = (catch lists:umerge(func, [], [1])),
- ?line {'EXIT', _} = (catch lists:merge(func, [1], [])),
- ?line [] = lists:umerge(Fun2, [], []),
- ?line {'EXIT', _} = (catch lists:rumerge(func, [], [1])),
- ?line {'EXIT', _} = (catch lists:rumerge(func, [1], [])),
- ?line [] = lists:rumerge(Fun2, [], []),
- ?line {'EXIT', _} = (catch lists:all(func, [])),
- ?line true = lists:all(Pred, []),
- ?line {'EXIT', _} = (catch lists:any(func, [])),
- ?line false = lists:any(Pred, []),
- ?line {'EXIT', _} = (catch lists:map(func, [])),
- ?line [] = lists:map(Fun1, []),
- ?line {'EXIT', _} = (catch lists:flatmap(func, [])),
- ?line [] = lists:flatmap(Fun1, []),
- ?line {'EXIT', _} = (catch lists:foldl(func, [], [])),
- ?line [] = lists:foldl(Fold, [], []),
- ?line {'EXIT', _} = (catch lists:foldr(func, [], [])),
- ?line [] = lists:foldr(Fold, [], []),
- ?line {'EXIT', _} = (catch lists:filter(func, [])),
- ?line [] = lists:filter(Pred, []),
- ?line {'EXIT', _} = (catch lists:partition(func, [])),
- ?line {[],[]} = lists:partition(Pred, []),
- ?line {'EXIT', _} = (catch lists:filtermap(func, [])),
- ?line [] = lists:filtermap(Fun1, []),
- ?line {'EXIT', _} = (catch lists:foreach(func, [])),
- ?line ok = lists:foreach(Fun1, []),
- ?line {'EXIT', _} = (catch lists:mapfoldl(func, [], [])),
- ?line {[],[]} = lists:mapfoldl(MapFold, [], []),
- ?line {'EXIT', _} = (catch lists:mapfoldr(func, [], [])),
- ?line {[],[]} = lists:mapfoldr(MapFold, [], []),
- ?line {'EXIT', _} = (catch lists:takewhile(func, [])),
- ?line [] = lists:takewhile(Pred, []),
- ?line {'EXIT', _} = (catch lists:dropwhile(func, [])),
- ?line [] = lists:dropwhile(Pred, []),
- ?line {'EXIT', _} = (catch lists:splitwith(func, [])),
- ?line {[],[]} = lists:splitwith(Pred, []),
+ {'EXIT', _} = (catch lists:usort( [asd], [qwe])),
+
+ {'EXIT', _} = (catch lists:zipwith(func, [], [])),
+ [] = lists:zipwith(Fun2, [], []),
+ {'EXIT', _} = (catch lists:zipwith3(func, [], [], [])),
+ [] = lists:zipwith3(Fun3, [], [], []),
+ {'EXIT', _} = (catch lists:keymap(func, 1, [])),
+ {'EXIT', _} = (catch lists:keymap(Fun1, 0, [])),
+ [] = lists:keymap(Fun1, 1, []),
+ {'EXIT', _} = (catch lists:merge(func, [], [1])),
+ {'EXIT', _} = (catch lists:merge(func, [1], [])),
+ [] = lists:merge(Fun2, [], []),
+ {'EXIT', _} = (catch lists:rmerge(func, [], [1])),
+ {'EXIT', _} = (catch lists:rmerge(func, [1], [])),
+ [] = lists:rmerge(Fun2, [], []),
+ {'EXIT', _} = (catch lists:usort(func, [])),
+ {'EXIT', _} = (catch lists:usort(func, [a])),
+ {'EXIT', _} = (catch lists:usort(func, [a, b])),
+ [] = lists:usort(Fun2, []),
+ {'EXIT', _} = (catch lists:umerge(func, [], [1])),
+ {'EXIT', _} = (catch lists:merge(func, [1], [])),
+ [] = lists:umerge(Fun2, [], []),
+ {'EXIT', _} = (catch lists:rumerge(func, [], [1])),
+ {'EXIT', _} = (catch lists:rumerge(func, [1], [])),
+ [] = lists:rumerge(Fun2, [], []),
+ {'EXIT', _} = (catch lists:all(func, [])),
+ true = lists:all(Pred, []),
+ {'EXIT', _} = (catch lists:any(func, [])),
+ false = lists:any(Pred, []),
+ {'EXIT', _} = (catch lists:map(func, [])),
+ [] = lists:map(Fun1, []),
+ {'EXIT', _} = (catch lists:flatmap(func, [])),
+ [] = lists:flatmap(Fun1, []),
+ {'EXIT', _} = (catch lists:foldl(func, [], [])),
+ [] = lists:foldl(Fold, [], []),
+ {'EXIT', _} = (catch lists:foldr(func, [], [])),
+ [] = lists:foldr(Fold, [], []),
+ {'EXIT', _} = (catch lists:filter(func, [])),
+ [] = lists:filter(Pred, []),
+ {'EXIT', _} = (catch lists:partition(func, [])),
+ {[],[]} = lists:partition(Pred, []),
+ {'EXIT', _} = (catch lists:filtermap(func, [])),
+ [] = lists:filtermap(Fun1, []),
+ {'EXIT', _} = (catch lists:foreach(func, [])),
+ ok = lists:foreach(Fun1, []),
+ {'EXIT', _} = (catch lists:mapfoldl(func, [], [])),
+ {[],[]} = lists:mapfoldl(MapFold, [], []),
+ {'EXIT', _} = (catch lists:mapfoldr(func, [], [])),
+ {[],[]} = lists:mapfoldr(MapFold, [], []),
+ {'EXIT', _} = (catch lists:takewhile(func, [])),
+ [] = lists:takewhile(Pred, []),
+ {'EXIT', _} = (catch lists:dropwhile(func, [])),
+ [] = lists:dropwhile(Pred, []),
+ {'EXIT', _} = (catch lists:splitwith(func, [])),
+ {[],[]} = lists:splitwith(Pred, []),
ok.
%% OTP-6023. lists:keyreplace/4, a typecheck.
otp_6023(Config) when is_list(Config) ->
- ?line {'EXIT', _} = (catch lists:keyreplace(a, 2, [{1,a}], b)),
- ?line [{2,b}] = lists:keyreplace(a, 2, [{1,a}], {2,b}),
+ {'EXIT', _} = (catch lists:keyreplace(a, 2, [{1,a}], b)),
+ [{2,b}] = lists:keyreplace(a, 2, [{1,a}], {2,b}),
ok.
@@ -2513,91 +2513,91 @@ otp_6606(Config) when is_list(Config) ->
I = 1,
F = float(1),
L1 = [{F,I},{F,F},{I,I},{I,F}],
- ?line L1 = lists:keysort(1, L1),
- ?line L1 = lists:sort(L1),
+ L1 = lists:keysort(1, L1),
+ L1 = lists:sort(L1),
L2 = [{I,I},{I,F},{F,I},{F,F}],
- ?line L2 = lists:keysort(1, L2),
- ?line L2 = lists:sort(L2),
+ L2 = lists:keysort(1, L2),
+ L2 = lists:sort(L2),
ok.
%% Test lists:suffix/2.
suffix(Config) when is_list(Config) ->
- ?line true = lists:suffix([], []),
- ?line true = lists:suffix([], [a]),
- ?line true = lists:suffix([], [a,b]),
- ?line true = lists:suffix([], [a,b,c]),
- ?line true = lists:suffix([a], lists:duplicate(200000, a)),
- ?line true = lists:suffix(lists:seq(1, 1024),
- lists:seq(2, 64000) ++ lists:seq(1, 1024)),
- ?line true = lists:suffix(lists:duplicate(20000, a),
- lists:duplicate(200000, a)),
- ?line true = lists:suffix([2.0,3.0], [1.0,2.0,3.0]),
+ true = lists:suffix([], []),
+ true = lists:suffix([], [a]),
+ true = lists:suffix([], [a,b]),
+ true = lists:suffix([], [a,b,c]),
+ true = lists:suffix([a], lists:duplicate(200000, a)),
+ true = lists:suffix(lists:seq(1, 1024),
+ lists:seq(2, 64000) ++ lists:seq(1, 1024)),
+ true = lists:suffix(lists:duplicate(20000, a),
+ lists:duplicate(200000, a)),
+ true = lists:suffix([2.0,3.0], [1.0,2.0,3.0]),
%% False cases.
- ?line false = lists:suffix([a], []),
- ?line false = lists:suffix([a,b,c], []),
- ?line false = lists:suffix([a,b,c], [b,c]),
- ?line false = lists:suffix([a,b,c], [a,b,c,a,b]),
- ?line false = lists:suffix(lists:duplicate(199999, a)++[b],
- lists:duplicate(200000, a)),
- ?line false = lists:suffix([2.0,3.0], [1,2,3]),
+ false = lists:suffix([a], []),
+ false = lists:suffix([a,b,c], []),
+ false = lists:suffix([a,b,c], [b,c]),
+ false = lists:suffix([a,b,c], [a,b,c,a,b]),
+ false = lists:suffix(lists:duplicate(199999, a)++[b],
+ lists:duplicate(200000, a)),
+ false = lists:suffix([2.0,3.0], [1,2,3]),
%% Error cases.
- ?line {'EXIT',_} = (catch lists:suffix({a,b,c}, [])),
- ?line {'EXIT',_} = (catch lists:suffix([], {a,b})),
- ?line {'EXIT',_} = (catch lists:suffix([a|b], [])),
- ?line {'EXIT',_} = (catch lists:suffix([a,b|c], [a|b])),
- ?line {'EXIT',_} = (catch lists:suffix([a|b], [a,b|c])),
- ?line {'EXIT',_} = (catch lists:suffix([a|b], [a|b])),
-
+ {'EXIT',_} = (catch lists:suffix({a,b,c}, [])),
+ {'EXIT',_} = (catch lists:suffix([], {a,b})),
+ {'EXIT',_} = (catch lists:suffix([a|b], [])),
+ {'EXIT',_} = (catch lists:suffix([a,b|c], [a|b])),
+ {'EXIT',_} = (catch lists:suffix([a|b], [a,b|c])),
+ {'EXIT',_} = (catch lists:suffix([a|b], [a|b])),
+
ok.
%% Test lists:subtract/2 and the '--' operator.
subtract(Config) when is_list(Config) ->
- ?line [] = sub([], []),
- ?line [] = sub([], [a]),
- ?line [] = sub([], lists:seq(1, 1024)),
- ?line sub_non_matching([a], []),
- ?line sub_non_matching([1,2], [make_ref()]),
- ?line sub_non_matching(lists:seq(1, 1024), [make_ref(),make_ref()]),
-
+ [] = sub([], []),
+ [] = sub([], [a]),
+ [] = sub([], lists:seq(1, 1024)),
+ sub_non_matching([a], []),
+ sub_non_matching([1,2], [make_ref()]),
+ sub_non_matching(lists:seq(1, 1024), [make_ref(),make_ref()]),
+
%% Matching subtracts.
- ?line [] = sub([a], [a]),
- ?line [a] = sub([a,b], [b]),
- ?line [a] = sub([a,b], [b,c]),
- ?line [a] = sub([a,b,c], [b,c]),
- ?line [a] = sub([a,b,c], [b,c]),
- ?line [d,a,a] = sub([a,b,c,d,a,a], [a,b,c]),
- ?line [d,x,a] = sub([a,b,c,d,a,x,a], [a,b,c,a]),
- ?line [1,2,3,4,5,6,7,8,9,9999,10000,20,21,22] =
+ [] = sub([a], [a]),
+ [a] = sub([a,b], [b]),
+ [a] = sub([a,b], [b,c]),
+ [a] = sub([a,b,c], [b,c]),
+ [a] = sub([a,b,c], [b,c]),
+ [d,a,a] = sub([a,b,c,d,a,a], [a,b,c]),
+ [d,x,a] = sub([a,b,c,d,a,x,a], [a,b,c,a]),
+ [1,2,3,4,5,6,7,8,9,9999,10000,20,21,22] =
sub(lists:seq(1, 10000)++[20,21,22], lists:seq(10, 9998)),
%% Floats/integers.
- ?line [42.0,42.0] = sub([42.0,42,42.0], [42,42,42]),
- ?line [1,2,3,4,43.0] = sub([1,2,3,4,5,42.0,43.0], [42.0,5]),
+ [42.0,42.0] = sub([42.0,42,42.0], [42,42,42]),
+ [1,2,3,4,43.0] = sub([1,2,3,4,5,42.0,43.0], [42.0,5]),
%% Crashing subtracts.
- ?line {'EXIT',_} = (catch sub([], [a|b])),
- ?line {'EXIT',_} = (catch sub([a], [a|b])),
- ?line {'EXIT',_} = (catch sub([a|b], [])),
- ?line {'EXIT',_} = (catch sub([a|b], [])),
- ?line {'EXIT',_} = (catch sub([a|b], [a])),
+ {'EXIT',_} = (catch sub([], [a|b])),
+ {'EXIT',_} = (catch sub([a], [a|b])),
+ {'EXIT',_} = (catch sub([a|b], [])),
+ {'EXIT',_} = (catch sub([a|b], [])),
+ {'EXIT',_} = (catch sub([a|b], [a])),
ok.
sub_non_matching(A, B) ->
A = sub(A, B).
-
+
sub(A, B) ->
Res = A -- B,
Res = lists:subtract(A, B).
%% Test lists:droplast/1
droplast(Config) when is_list(Config) ->
- ?line [] = lists:droplast([x]),
- ?line [x] = lists:droplast([x, y]),
- ?line {'EXIT', {function_clause, _}} = (catch lists:droplast([])),
- ?line {'EXIT', {function_clause, _}} = (catch lists:droplast(x)),
+ [] = lists:droplast([x]),
+ [x] = lists:droplast([x, y]),
+ {'EXIT', {function_clause, _}} = (catch lists:droplast([])),
+ {'EXIT', {function_clause, _}} = (catch lists:droplast(x)),
ok.
diff --git a/lib/stdlib/test/log_mf_h_SUITE.erl b/lib/stdlib/test/log_mf_h_SUITE.erl
index 8c5aa3d59b..6d45d5f0cd 100644
--- a/lib/stdlib/test/log_mf_h_SUITE.erl
+++ b/lib/stdlib/test/log_mf_h_SUITE.erl
@@ -53,17 +53,17 @@ end_per_group(_GroupName, Config) ->
%%-----------------------------------------------------------------
test(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_event:start_link(),
- ?line PrivDir = ?config(priv_dir, Config),
+ {ok, Pid} = gen_event:start_link(),
+ PrivDir = ?config(priv_dir, Config),
Log1 = PrivDir ++ "/log1",
- ?line ok = file:make_dir(Log1),
+ ok = file:make_dir(Log1),
Args1 = log_mf_h:init(Log1, 500, 3),
gen_event:add_handler(Pid, log_mf_h, Args1),
generate(Pid, 200),
{ok, Files} = file:list_dir(Log1),
- ?line true = lists:member("1", Files),
- ?line true = lists:member("index", Files),
- ?line false = lists:member("2", Files),
+ true = lists:member("1", Files),
+ true = lists:member("index", Files),
+ false = lists:member("2", Files),
generate(Pid, 2500),
%% The documentation doesn't guarantee that syncing one request
%% causes all previous ones to be finished too, but that seems to
@@ -71,26 +71,26 @@ test(Config) when is_list(Config) ->
%% look for them with 'list_dir'.
gen_event:sync_notify(Pid, "end"),
{ok, Files2} = file:list_dir(Log1),
- ?line true = lists:member("1", Files2),
- ?line true = lists:member("2", Files2),
- ?line true = lists:member("3", Files2),
- ?line false = lists:member("4", Files2),
- ?line true = lists:member("index", Files2),
- ?line {ok, #file_info{size=Size1,type=regular}} = file:read_file_info(Log1 ++ "/1"),
+ true = lists:member("1", Files2),
+ true = lists:member("2", Files2),
+ true = lists:member("3", Files2),
+ false = lists:member("4", Files2),
+ true = lists:member("index", Files2),
+ {ok, #file_info{size=Size1,type=regular}} = file:read_file_info(Log1 ++ "/1"),
if Size1 > 500 -> ct:fail({too_big, Size1});
true -> ok end,
- ?line {ok, #file_info{size=Size2,type=regular}} = file:read_file_info(Log1 ++ "/2"),
+ {ok, #file_info{size=Size2,type=regular}} = file:read_file_info(Log1 ++ "/2"),
if Size2 > 500 -> ct:fail({too_big, Size2});
true -> ok end,
- ?line {ok, #file_info{size=Size3,type=regular}} = file:read_file_info(Log1 ++ "/3"),
+ {ok, #file_info{size=Size3,type=regular}} = file:read_file_info(Log1 ++ "/3"),
if Size3 > 500 -> ct:fail({too_big, Size3});
true -> ok end,
gen_event:delete_handler(Pid, log_mf_h, []),
- ?line {ok, Index} = read_index_file(Log1),
+ {ok, Index} = read_index_file(Log1),
gen_event:add_handler(Pid, log_mf_h, Args1),
X = if Index == 3 -> 1; true -> Index + 1 end,
- ?line {ok, X} = read_index_file(Log1).
-
+ {ok, X} = read_index_file(Log1).
+
generate(Pid, Bytes) when Bytes > 32 ->
gen_event:notify(Pid, make_list(32, [])),
@@ -110,4 +110,3 @@ read_index_file(Dir) ->
end;
_ -> error
end.
-
diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl
index 4fd1e70b06..39dbc42546 100644
--- a/lib/stdlib/test/ms_transform_SUITE.erl
+++ b/lib/stdlib/test/ms_transform_SUITE.erl
@@ -82,86 +82,86 @@ end_per_group(_GroupName, Config) ->
%% Check that shadowed variables in fun head generate warning.
warnings(Config) when is_list(Config) ->
- ?line setup(Config),
+ setup(Config),
Prog = <<"A=5, "
- "ets:fun2ms(fun({A,B}) "
- " when is_integer(A) and (A+5 > B) -> "
- " A andalso B "
- " end)">>,
- ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
+ "ets:fun2ms(fun({A,B}) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " A andalso B "
+ " end)">>,
+ [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
compile_ww(Prog),
Prog2 = <<"C = 5,
ets:fun2ms(fun ({A,B} =
- C) when is_integer(A) and (A+5 > B) ->
+ C) when is_integer(A) and (A+5 > B) ->
{A andalso B,C}
end)">>,
[{_,[{3,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
- compile_ww(Prog2),
- Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>,
- Prog3 = <<"A = 3,
+ compile_ww(Prog2),
+ Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog3 = <<"A = 3,
C = 5,
- ets:fun2ms(fun (C
- = #a{a = A, b = B})
- when is_integer(A) and (A+5 > B) ->
- {A andalso B,C}
- end)">>,
+ ets:fun2ms(fun (C
+ = #a{a = A, b = B})
+ when is_integer(A) and (A+5 > B) ->
+ {A andalso B,C}
+ end)">>,
[{_,[{3,ms_transform,{?WARN_NUMBER_SHADOW,'C'}},
{4,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
- compile_ww(Rec3,Prog3),
- Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>,
- Prog4 = <<"A=3,C=5, "
- "F = fun(B) -> B*3 end,"
- "erlang:display(F(A)),"
- "ets:fun2ms(fun(#a{a = A, b = B} = C) "
- " when is_integer(A) and (A+5 > B) -> "
- " {A andalso B,C} "
- " end)">>,
- ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
- {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
- compile_ww(Rec4,Prog4),
- Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>,
- Prog5 = <<"A=3,C=5, "
- "F = fun(B) -> B*3 end,"
- "erlang:display(F(A)),"
- "B = ets:fun2ms(fun(#a{a = A, b = B} = C) "
- " when is_integer(A) and (A+5 > B) -> "
- " {A andalso B,C} "
- " end)">>,
- ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
- {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
- compile_ww(Rec5,Prog5),
- Prog6 = <<" X=bar, "
- " A = case X of"
- " foo ->"
- " foo;"
- " Y ->"
- " ets:fun2ms(fun(Y) ->" % This is a warning
- " 3*Y"
- " end)"
- " end,"
- " ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning
- " {3*Y,A}"
- " end)">>,
- ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
- compile_ww(Prog6),
- Prog7 = <<" X=bar, "
- " A = case X of"
- " foo ->"
- " Y = foo;"
- " Y ->"
- " bar"
- " end,"
- " ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn
- " {3*Y,A}"
- " end)">>,
- ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
- compile_ww(Prog7),
- ok.
+ compile_ww(Rec3,Prog3),
+ Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog4 = <<"A=3,C=5, "
+ "F = fun(B) -> B*3 end,"
+ "erlang:display(F(A)),"
+ "ets:fun2ms(fun(#a{a = A, b = B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
+ {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Rec4,Prog4),
+ Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog5 = <<"A=3,C=5, "
+ "F = fun(B) -> B*3 end,"
+ "erlang:display(F(A)),"
+ "B = ets:fun2ms(fun(#a{a = A, b = B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
+ {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Rec5,Prog5),
+ Prog6 = <<" X=bar, "
+ " A = case X of"
+ " foo ->"
+ " foo;"
+ " Y ->"
+ " ets:fun2ms(fun(Y) ->" % This is a warning
+ " 3*Y"
+ " end)"
+ " end,"
+ " ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning
+ " {3*Y,A}"
+ " end)">>,
+ [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
+ compile_ww(Prog6),
+ Prog7 = <<" X=bar, "
+ " A = case X of"
+ " foo ->"
+ " Y = foo;"
+ " Y ->"
+ " bar"
+ " end,"
+ " ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn
+ " {3*Y,A}"
+ " end)">>,
+ [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
+ compile_ww(Prog7),
+ ok.
%% Check that variables bound in other function clauses don't generate
%% warning.
no_warnings(Config) when is_list(Config) ->
- ?line setup(Config),
+ setup(Config),
Prog = <<"tmp(X) when X > 100 ->\n",
" Y=X,\n"
" Y;\n"
@@ -169,167 +169,167 @@ no_warnings(Config) when is_list(Config) ->
" ets:fun2ms(fun(Y) ->\n"
" {X, 3*Y}\n"
" end)">>,
- ?line [] = compile_no_ww(Prog),
+ [] = compile_no_ww(Prog),
Prog2 = <<"tmp(X) when X > 100 ->\n",
- " Y=X,\n"
- " Y;\n"
- "tmp(X) when X < 200 ->\n"
- " ok;\n"
- "tmp(X) ->\n"
- " ets:fun2ms(fun(Y) ->\n"
- " {X, 3*Y}\n"
- " end)">>,
- ?line [] = compile_no_ww(Prog2),
+ " Y=X,\n"
+ " Y;\n"
+ "tmp(X) when X < 200 ->\n"
+ " ok;\n"
+ "tmp(X) ->\n"
+ " ets:fun2ms(fun(Y) ->\n"
+ " {X, 3*Y}\n"
+ " end)">>,
+ [] = compile_no_ww(Prog2),
ok.
%% Test that andalso and orelse are allowed in guards.
andalso_orelse(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{{'$1','$2'},
- [{'and',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
- [{'andalso','$1','$2'}]}] =
+ setup(Config),
+ [{{'$1','$2'},
+ [{'and',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
+ [{'andalso','$1','$2'}]}] =
compile_and_run(<<"ets:fun2ms(fun({A,B}) "
- " when is_integer(A) and (A+5 > B) -> "
- " A andalso B "
- " end)">>),
- ?line [{{'$1','$2'},
- [{'or',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
- [{'orelse','$1','$2'}]}] =
+ " when is_integer(A) and (A+5 > B) -> "
+ " A andalso B "
+ " end)">>),
+ [{{'$1','$2'},
+ [{'or',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
+ [{'orelse','$1','$2'}]}] =
compile_and_run(<<"ets:fun2ms(fun({A,B}) "
- " when is_atom(A) or (A+5 > B) -> "
- " A orelse B "
- " end)">>),
- ?line [{{'$1','$2'},
- [{'andalso',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
- ['$1']}] =
+ " when is_atom(A) or (A+5 > B) -> "
+ " A orelse B "
+ " end)">>),
+ [{{'$1','$2'},
+ [{'andalso',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
+ ['$1']}] =
compile_and_run(
- <<"ets:fun2ms(fun({A,B}) when is_integer(A) andalso (A+5 > B) ->"
- " A "
- " end)">>),
- ?line [{{'$1','$2'},
- [{'orelse',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
- ['$1']}] =
+ <<"ets:fun2ms(fun({A,B}) when is_integer(A) andalso (A+5 > B) ->"
+ " A "
+ " end)">>),
+ [{{'$1','$2'},
+ [{'orelse',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
+ ['$1']}] =
compile_and_run(
- <<"ets:fun2ms(fun({A,B}) when is_atom(A) orelse (A+5 > B) -> "
- " A "
- " end)">>),
+ <<"ets:fun2ms(fun({A,B}) when is_atom(A) orelse (A+5 > B) -> "
+ " A "
+ " end)">>),
ok.
-
-
+
+
%% Test that bitsyntax works and does not work where appropriate.
bitsyntax(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{'_',[],
- [<<0,27,0,27>>]}] =
+ setup(Config),
+ [{'_',[],
+ [<<0,27,0,27>>]}] =
compile_and_run(<<"A = 27, "
"ets:fun2ms(fun(_) -> <<A:16,27:16>> end)">>),
- ?line [{{<<15,47>>,
- '$1',
- '$2'},
- [{'=:=','$1',
- <<0,27>>},
- {'=:=','$2',
- <<27,28,19>>}],
- [<<188,0,13>>]}] =
+ [{{<<15,47>>,
+ '$1',
+ '$2'},
+ [{'=:=','$1',
+ <<0,27>>},
+ {'=:=','$2',
+ <<27,28,19>>}],
+ [<<188,0,13>>]}] =
compile_and_run(<<"A = 27, "
"ets:fun2ms("
" fun({<<15,47>>,B,C}) "
" when B =:= <<A:16>>, C =:= <<27,28,19>> -> "
" <<A:4,12:4,13:16>> "
" end)">>),
- ?line expect_failure(
- <<>>,
- <<"ets:fun2ms(fun({<<15,47>>,B,C}) "
- " when B =:= <<16>>, C =:= <<27,28,19>> -> "
- " <<B:4,12:4,13:16>> "
- " end)">>),
- ?line expect_failure(
- <<>>,
- <<"ets:fun2ms(fun({<<A:15,47>>,B,C}) "
- " when B =:= <<16>>, C =:= <<27,28,19>> -> "
- " <<B:4,12:4,13:16>> "
- " end)">>),
+ expect_failure(
+ <<>>,
+ <<"ets:fun2ms(fun({<<15,47>>,B,C}) "
+ " when B =:= <<16>>, C =:= <<27,28,19>> -> "
+ " <<B:4,12:4,13:16>> "
+ " end)">>),
+ expect_failure(
+ <<>>,
+ <<"ets:fun2ms(fun({<<A:15,47>>,B,C}) "
+ " when B =:= <<16>>, C =:= <<27,28,19>> -> "
+ " <<B:4,12:4,13:16>> "
+ " end)">>),
ok.
%% Test that record defaults works.
record_defaults(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{{<<27>>,{a,5,'$1',hej,hej}},
- [],
- [{{a,hej,{'*','$1',2},flurp,flurp}}]}] =
+ setup(Config),
+ [{{<<27>>,{a,5,'$1',hej,hej}},
+ [],
+ [{{a,hej,{'*','$1',2},flurp,flurp}}]}] =
compile_and_run(<<"-record(a,{a,b,c,d=foppa}).">>,
<<"ets:fun2ms(fun({<<27>>,#a{a=5, b=B,_=hej}}) -> "
- "#a{a=hej,b=B*2,_=flurp} "
- "end)">>),
+ "#a{a=hej,b=B*2,_=flurp} "
+ "end)">>),
ok.
%% Test basic ets:fun2ms.
basic_ets(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{{a,b},[],[true]}] = compile_and_run(
- <<"ets:fun2ms(fun({a,b}) -> true end)">>),
- ?line [{{'$1',foo},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
+ setup(Config),
+ [{{a,b},[],[true]}] = compile_and_run(
+ <<"ets:fun2ms(fun({a,b}) -> true end)">>),
+ [{{'$1',foo},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
{{'$1','$1'},[{is_tuple,'$1'}],[{{{element,1,'$1'},'$*'}}]}] =
compile_and_run(<<"ets:fun2ms(fun({X,foo}) when is_list(X) -> ",
- "{hd(X),object()};",
- "({X,X}) when is_tuple(X) ->",
- "{element(1,X),bindings()}",
- "end)">>),
- ?line [{{'$1','$2'},[],[{{'$2','$1'}}]}] =
+ "{hd(X),object()};",
+ "({X,X}) when is_tuple(X) ->",
+ "{element(1,X),bindings()}",
+ "end)">>),
+ [{{'$1','$2'},[],[{{'$2','$1'}}]}] =
compile_and_run(<<"ets:fun2ms(fun({A,B}) -> {B,A} end)">>),
- ?line [{{'$1','$2'},[],[['$2','$1']]}] =
+ [{{'$1','$2'},[],[['$2','$1']]}] =
compile_and_run(<<"ets:fun2ms(fun({A,B}) -> [B,A] end)">>),
ok.
%% Tests basic ets:fun2ms.
basic_dbg(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{[a,b],[],[{message,banan},{return_trace}]}] =
+ setup(Config),
+ [{[a,b],[],[{message,banan},{return_trace}]}] =
compile_and_run(<<"dbg:fun2ms(fun([a,b]) -> message(banan), ",
- "return_trace() end)">>),
- ?line [{['$1','$2'],[],[{{'$2','$1'}}]}] =
+ "return_trace() end)">>),
+ [{['$1','$2'],[],[{{'$2','$1'}}]}] =
compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> {B,A} end)">>),
- ?line [{['$1','$2'],[],[['$2','$1']]}] =
+ [{['$1','$2'],[],[['$2','$1']]}] =
compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> [B,A] end)">>),
- ?line [{['$1','$2'],[],['$*']}] =
+ [{['$1','$2'],[],['$*']}] =
compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> bindings() end)">>),
- ?line [{['$1','$2'],[],['$_']}] =
+ [{['$1','$2'],[],['$_']}] =
compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> object() end)">>),
ok.
%% Test calling of ets/dbg:fun2ms from the shell.
from_shell(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line Fun = do_eval("fun({a,b}) -> true end"),
- ?line [{{a,b},[],[true]}] = apply(ets,fun2ms,[Fun]),
- ?line [{{a,b},[],[true]}] = do_eval("ets:fun2ms(fun({a,b}) -> true end)"),
- ?line Fun2 = do_eval("fun([a,b]) -> message(banan), return_trace() end"),
- ?line [{[a,b],[],[{message,banan},{return_trace}]}]
+ setup(Config),
+ Fun = do_eval("fun({a,b}) -> true end"),
+ [{{a,b},[],[true]}] = apply(ets,fun2ms,[Fun]),
+ [{{a,b},[],[true]}] = do_eval("ets:fun2ms(fun({a,b}) -> true end)"),
+ Fun2 = do_eval("fun([a,b]) -> message(banan), return_trace() end"),
+ [{[a,b],[],[{message,banan},{return_trace}]}]
= apply(dbg,fun2ms,[Fun2]),
- ?line [{[a,b],[],[{message,banan},{return_trace}]}] =
+ [{[a,b],[],[{message,banan},{return_trace}]}] =
do_eval(
"dbg:fun2ms(fun([a,b]) -> message(banan), return_trace() end)"),
ok.
%% Tests expansion of records in fun2ms.
records(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line RD = <<"-record(t, {"
- "t1 = [] :: list(),"
- "t2 = foo :: atom(),"
- "t3,"
- "t4"
- "}).">>,
- ?line [{{t,'$1','$2',foo,'_'},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
+ setup(Config),
+ RD = <<"-record(t, {"
+ "t1 = [] :: list(),"
+ "t2 = foo :: atom(),"
+ "t3,"
+ "t4"
+ "}).">>,
+ [{{t,'$1','$2',foo,'_'},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
{{t,'_','_','_','_'},[{'==',{element,2,'$_'},nisse}],[{{'$*'}}]}] =
compile_and_run(RD,<<
- "ets:fun2ms(fun(#t{t1 = X, t2 = Y, t3 = foo}) when is_list(X) ->
+ "ets:fun2ms(fun(#t{t1 = X, t2 = Y, t3 = foo}) when is_list(X) ->
{hd(X),object()};
- (#t{}) when (object())#t.t1 == nisse ->
- {bindings()}
- end)">>),
- ?line [{{t,'$1','$2','_',foo},
+ (#t{}) when (object())#t.t1 == nisse ->
+ {bindings()}
+ end)">>),
+ [{{t,'$1','$2','_',foo},
[{'==',{element,4,'$_'},7},{is_list,'$1'}],
[{{{hd,'$1'},'$_'}}]},
{'$1',[{is_record,'$1',t,5}],
@@ -347,7 +347,7 @@ records(Config) when is_list(Config) ->
}
end)"
>>),
- ?line [{[{t,'$1','$2',foo,'_'}],[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
+ [{[{t,'$1','$2',foo,'_'}],[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
{[{t,'_','_','_','_'}],[{'==',{element,2,{hd,'$_'}},nisse}],[{{'$*'}}]}]=
compile_and_run(RD,<<
"dbg:fun2ms(fun([#t{t1 = X, t2 = Y, t3 = foo}]) when is_list(X) ->
@@ -361,64 +361,64 @@ records(Config) when is_list(Config) ->
%% Test expansion of records in fun2ms, part 2.
record_index(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line RD = <<"-record(a,{a,b}).">>,
- ?line [{{2},[],[true]}] = compile_and_run(RD,
+ setup(Config),
+ RD = <<"-record(a,{a,b}).">>,
+ [{{2},[],[true]}] = compile_and_run(RD,
<<"ets:fun2ms(fun({#a.a}) -> true end)">>),
- ?line [{{2},[],[2]}] = compile_and_run(RD,
+ [{{2},[],[2]}] = compile_and_run(RD,
<<"ets:fun2ms(fun({#a.a}) -> #a.a end)">>),
- ?line [{{2,'$1'},[{'>','$1',2}],[2]}] = compile_and_run(RD,
+ [{{2,'$1'},[{'>','$1',2}],[2]}] = compile_and_run(RD,
<<"ets:fun2ms(fun({#a.a,A}) when A > #a.a -> #a.a end)">>),
ok.
%% Tests matching on top level in head to give alias for object().
top_match(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line RD = <<"-record(a,{a,b}).">>,
- ?line [{{a,3,'_'},[],['$_']}] =
+ setup(Config),
+ RD = <<"-record(a,{a,b}).">>,
+ [{{a,3,'_'},[],['$_']}] =
compile_and_run(RD,
<<"ets:fun2ms(fun(A = #a{a=3}) -> A end)">>),
- ?line [{{a,3,'_'},[],['$_']}] =
+ [{{a,3,'_'},[],['$_']}] =
compile_and_run(RD,
<<"ets:fun2ms(fun(#a{a=3} = A) -> A end)">>),
- ?line [{[a,b],[],['$_']}] =
+ [{[a,b],[],['$_']}] =
compile_and_run(RD,
<<"dbg:fun2ms(fun(A = [a,b]) -> A end)">>),
- ?line [{[a,b],[],['$_']}] =
+ [{[a,b],[],['$_']}] =
compile_and_run(RD,
<<"dbg:fun2ms(fun([a,b] = A) -> A end)">>),
- ?line expect_failure(RD,
+ expect_failure(RD,
<<"ets:fun2ms(fun({a,A = {_,b}}) -> A end)">>),
- ?line expect_failure(RD,
+ expect_failure(RD,
<<"dbg:fun2ms(fun([a,A = {_,b}]) -> A end)">>),
- ?line expect_failure(RD,
+ expect_failure(RD,
<<"ets:fun2ms(fun(A#a{a = 2}) -> A end)">>),
ok.
%% Tests that multi-defined fields in records give errors.
multipass(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line RD = <<"-record(a,{a,b}).">>,
- ?line expect_failure(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,a=3} end)">>),
- ?line expect_failure(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,a=3} end)">>),
- ?line expect_failure(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,a=3} ->",
+ setup(Config),
+ RD = <<"-record(a,{a,b}).">>,
+ expect_failure(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,a=3} end)">>),
+ expect_failure(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,a=3} end)">>),
+ expect_failure(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,a=3} ->",
" true end)">>),
- ?line expect_failure(RD,<<"ets:fun2ms(fun({A,B})when A =:= B#a{a=2,a=3}->",
+ expect_failure(RD,<<"ets:fun2ms(fun({A,B})when A =:= B#a{a=2,a=3}->",
"true end)">>),
- ?line expect_failure(RD,<<"ets:fun2ms(fun(#a{a=3,a=3}) -> true end)">>),
- ?line compile_and_run(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,b=3} end)">>),
- ?line compile_and_run(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,b=3} end)">>),
- ?line compile_and_run(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,b=3} ->",
+ expect_failure(RD,<<"ets:fun2ms(fun(#a{a=3,a=3}) -> true end)">>),
+ compile_and_run(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,b=3} end)">>),
+ compile_and_run(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,b=3} end)">>),
+ compile_and_run(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,b=3} ->",
" true end)">>),
- ?line compile_and_run(RD,<<"ets:fun2ms(fun({A,B})when A=:= B#a{a=2,b=3}->",
+ compile_and_run(RD,<<"ets:fun2ms(fun({A,B})when A=:= B#a{a=2,b=3}->",
"true end)">>),
- ?line compile_and_run(RD,<<"ets:fun2ms(fun(#a{a=3,b=3}) -> true end)">>),
+ compile_and_run(RD,<<"ets:fun2ms(fun(#a{a=3,b=3}) -> true end)">>),
ok.
%% Test that old type tests in guards are translated.
old_guards(Config) when is_list(Config) ->
- ?line setup(Config),
+ setup(Config),
Tests = [
{atom,is_atom},
{float,is_float},
@@ -431,7 +431,7 @@ old_guards(Config) when is_list(Config) ->
{tuple,is_tuple},
{binary,is_binary},
{function,is_function}],
- ?line lists:foreach(
+ lists:foreach(
fun({Old,New}) ->
Bin = list_to_binary([<<"ets:fun2ms(fun(X) when ">>,
atom_to_list(Old),
@@ -444,15 +444,15 @@ old_guards(Config) when is_list(Config) ->
end
end,
Tests),
- ?line RD = <<"-record(a,{a,b}).">>,
- ?line [{'$1',[{is_record,'$1',a,3}],[true]}] =
+ RD = <<"-record(a,{a,b}).">>,
+ [{'$1',[{is_record,'$1',a,3}],[true]}] =
compile_and_run(RD,
<<"ets:fun2ms(fun(X) when record(X,a) -> true end)">>),
- ?line expect_failure
+ expect_failure
(RD,
<<"ets:fun2ms(fun(X) when integer(X) and constant(X) -> "
"true end)">>),
- ?line [{'$1',[{is_integer,'$1'},
+ [{'$1',[{is_integer,'$1'},
{is_float,'$1'},
{is_atom,'$1'},
{is_list,'$1'},
@@ -476,7 +476,7 @@ old_guards(Config) when is_list(Config) ->
%% Test use of autoimported BIFs used like erlang:'+'(A,B) in guards
%% and body.
autoimported(Config) when is_list(Config) ->
- ?line setup(Config),
+ setup(Config),
Allowed = [
{abs,1},
{element,2},
@@ -530,8 +530,8 @@ autoimported(Config) when is_list(Config) ->
{'=:=',2,infix},
{'/=',2,infix},
{'=/=',2,infix}],
- ?line RD = <<"-record(a,{a,b}).">>,
- ?line lists:foreach(
+ RD = <<"-record(a,{a,b}).">>,
+ lists:foreach(
fun({A,0}) ->
L = atom_to_list(A),
Bin1 = list_to_binary(
@@ -648,64 +648,64 @@ autoimported(Config) when is_list(Config) ->
%% Test semicolon in guards of match_specs.
semicolon(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line Res01 = compile_and_run
+ setup(Config),
+ Res01 = compile_and_run
(<<"ets:fun2ms(fun(X) when is_integer(X); "
"is_float(X) -> true end)">>),
- ?line Res02 = compile_and_run
+ Res02 = compile_and_run
(<<"ets:fun2ms(fun(X) when is_integer(X) -> true; "
"(X) when is_float(X) -> true end)">>),
- ?line Res01 = Res02,
- ?line Res11 = compile_and_run
+ Res01 = Res02,
+ Res11 = compile_and_run
(<<"ets:fun2ms(fun(X) when is_integer(X); "
"is_float(X); atom(X) -> true end)">>),
- ?line Res12 = compile_and_run
+ Res12 = compile_and_run
(<<"ets:fun2ms(fun(X) when is_integer(X) -> true; "
"(X) when is_float(X) -> true; "
"(X) when is_atom(X) -> true end)">>),
- ?line Res11 = Res12,
+ Res11 = Res12,
ok.
%% OTP-5297. The function float/1.
float_1_function(Config) when is_list(Config) ->
- ?line setup(Config),
+ setup(Config),
RunMS = fun(L, MS) ->
ets:match_spec_run(L, ets:match_spec_compile(MS))
end,
- ?line MS1 = compile_and_run
+ MS1 = compile_and_run
(<<"ets:fun2ms(fun(X) -> float(X) end)">>),
- ?line [F1] = RunMS([3], MS1),
- ?line true = is_float(F1) and (F1 == 3),
+ [F1] = RunMS([3], MS1),
+ true = is_float(F1) and (F1 == 3),
- ?line MS1b = compile_and_run
+ MS1b = compile_and_run
(<<"dbg:fun2ms(fun(X) -> float(X) end)">>),
- ?line [F2] = RunMS([3], MS1b),
- ?line true = is_float(F2) and (F2 == 3),
+ [F2] = RunMS([3], MS1b),
+ true = is_float(F2) and (F2 == 3),
- ?line MS2 = compile_and_run
+ MS2 = compile_and_run
(<<"ets:fun2ms(fun(X) when is_pid(X) or float(X) -> true end)">>),
- ?line [] = RunMS([3.0], MS2),
+ [] = RunMS([3.0], MS2),
- ?line MS3 = compile_and_run
+ MS3 = compile_and_run
(<<"dbg:fun2ms(fun(X) when is_pid(X); float(X) -> true end)">>),
- ?line [true] = RunMS([3.0], MS3),
+ [true] = RunMS([3.0], MS3),
- ?line MS4 = compile_and_run
+ MS4 = compile_and_run
(<<"ets:fun2ms(fun(X) when erlang:float(X) > 1 -> big;"
" (_) -> small end)">>),
- ?line [small,big] = RunMS([1.0, 3.0], MS4),
+ [small,big] = RunMS([1.0, 3.0], MS4),
- ?line MS5 = compile_and_run
+ MS5 = compile_and_run
(<<"ets:fun2ms(fun(X) when float(X) > 1 -> big;"
" (_) -> small end)">>),
- ?line [small,big] = RunMS([1.0, 3.0], MS5),
+ [small,big] = RunMS([1.0, 3.0], MS5),
%% This is the test from autoimported/1.
- ?line [{'$1',[{is_float,'$1'}],[{float,'$1'}]}] =
+ [{'$1',[{is_float,'$1'}],[{float,'$1'}]}] =
compile_and_run
(<<"ets:fun2ms(fun(X) when float(X) -> float(X) end)">>),
- ?line [{'$1',[{float,'$1'}],[{float,'$1'}]}] =
+ [{'$1',[{float,'$1'}],[{float,'$1'}]}] =
compile_and_run
(<<"ets:fun2ms(fun(X) when erlang:'float'(X) -> "
"erlang:'float'(X) end)">>),
@@ -714,8 +714,8 @@ float_1_function(Config) when is_list(Config) ->
%% Test all 'action functions'.
action_function(Config) when is_list(Config) ->
- ?line setup(Config),
- ?line [{['$1','$2'],[],
+ setup(Config),
+ [{['$1','$2'],[],
[{set_seq_token,label,0},
{get_seq_token},
{message,'$1'},
@@ -728,7 +728,7 @@ action_function(Config) when is_list(Config) ->
"message(X), "
"return_trace(), "
"exception_trace() end)">>),
- ?line [{['$1','$2'],[],
+ [{['$1','$2'],[],
[{process_dump},
{enable_trace,send},
{enable_trace,'$2',send},
@@ -741,7 +741,7 @@ action_function(Config) when is_list(Config) ->
"enable_trace(Y, send), "
"disable_trace(procs), "
"disable_trace(Y, procs) end)">>),
- ?line [{['$1','$2'],
+ [{['$1','$2'],
[],
[{display,'$1'},
{caller},
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 4c85d4f18f..ebce74545a 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -217,7 +217,7 @@ sync_start_nolink(Config) when is_list(Config) ->
ct:fail(no_sync_start)
end,
ok.
-
+
sync_start_link(Config) when is_list(Config) ->
_Pid = spawn_link(?MODULE, sp3, [self()]),
receive
@@ -233,21 +233,21 @@ sync_start_link(Config) when is_list(Config) ->
after 1000 -> ct:fail(no_sync_start)
end,
ok.
-
+
spawn_opt(Config) when is_list(Config) ->
F = fun sp1/0,
{name,Fname} = erlang:fun_info(F, name),
FunMFArgs = {?MODULE,Fname,[]},
FunMFArity = {?MODULE,Fname,0},
- ?line Pid1 = proc_lib:spawn_opt(node(), F, [{priority,low}]),
- ?line Pid = proc_lib:spawn_opt(F, [{priority,low}]),
+ Pid1 = proc_lib:spawn_opt(node(), F, [{priority,low}]),
+ Pid = proc_lib:spawn_opt(F, [{priority,low}]),
ct:sleep(100),
- ?line FunMFArgs = proc_lib:initial_call(Pid),
- ?line FunMFArity = proc_lib:translate_initial_call(Pid),
- ?line Pid ! die,
- ?line FunMFArgs = proc_lib:initial_call(Pid1),
- ?line FunMFArity = proc_lib:translate_initial_call(Pid1),
- ?line Pid1 ! die,
+ FunMFArgs = proc_lib:initial_call(Pid),
+ FunMFArity = proc_lib:translate_initial_call(Pid),
+ Pid ! die,
+ FunMFArgs = proc_lib:initial_call(Pid1),
+ FunMFArity = proc_lib:translate_initial_call(Pid1),
+ Pid1 ! die,
ok.
@@ -283,38 +283,38 @@ hibernate(Config) when is_list(Config) ->
Ref = make_ref(),
Self = self(),
LoopData = {Ref,Self},
- ?line Pid = proc_lib:spawn_link(?MODULE, hib_loop, [LoopData]),
+ Pid = proc_lib:spawn_link(?MODULE, hib_loop, [LoopData]),
%% Just check that the child process can process and answer messages.
- ?line Pid ! {Self,loop_data},
+ Pid ! {Self,loop_data},
receive
{loop_data,LoopData} -> ok;
Unexpected0 ->
- ?line io:format("Unexpected: ~p\n", [Unexpected0]),
+ io:format("Unexpected: ~p\n", [Unexpected0]),
ct:fail(failed)
after 1000 ->
- ?line io:format("Timeout"),
+ io:format("Timeout"),
ct:fail(failed)
end,
%% Hibernate the process.
- ?line Pid ! hibernate,
+ Pid ! hibernate,
erlang:yield(),
io:format("~p\n", [process_info(Pid, heap_size)]),
%% Send a message to the process...
- ?line Pid ! {Self,loop_data},
+ Pid ! {Self,loop_data},
%% ... expect first a wake up message from the process...
receive
{awaken,LoopData} -> ok;
Unexpected1 ->
- ?line io:format("Unexpected: ~p\n", [Unexpected1]),
+ io:format("Unexpected: ~p\n", [Unexpected1]),
ct:fail(failed)
after 1000 ->
- ?line io:format("Timeout"),
+ io:format("Timeout"),
ct:fail(failed)
end,
@@ -322,18 +322,18 @@ hibernate(Config) when is_list(Config) ->
receive
{loop_data,LoopData} -> ok;
Unexpected2 ->
- ?line io:format("Unexpected: ~p\n", [Unexpected2]),
+ io:format("Unexpected: ~p\n", [Unexpected2]),
ct:fail(failed)
after 1000 ->
- ?line io:format("Timeout"),
+ io:format("Timeout"),
ct:fail(failed)
end,
%% Test that errors are handled correctly after wake up from hibernation...
- ?line process_flag(trap_exit, true),
- ?line error_logger:add_report_handler(?MODULE, self()),
- ?line Pid ! crash,
+ process_flag(trap_exit, true),
+ error_logger:add_report_handler(?MODULE, self()),
+ Pid ! crash,
%% We should receive two messages. Especially in the SMP emulator,
%% we can't be sure of the message order, so sort the messages before
@@ -341,10 +341,10 @@ hibernate(Config) when is_list(Config) ->
Messages = lists:sort(hib_receive_messages(2)),
io:format("~p", [Messages]),
- ?line [{'EXIT',Pid,i_crashed},{crash_report,Pid,[Report,[]]}] = Messages,
+ [{'EXIT',Pid,i_crashed},{crash_report,Pid,[Report,[]]}] = Messages,
%% Check that the initial_call has the expected format.
- ?line {value,{initial_call,{?MODULE,hib_loop,[_]}}} =
+ {value,{initial_call,{?MODULE,hib_loop,[_]}}} =
lists:keysearch(initial_call, 1, Report),
error_logger:delete_report_handler(?MODULE),
@@ -483,7 +483,7 @@ stop(_Config) ->
{'EXIT',noproc} = (catch proc_lib:stop({to_stop,Node})),
true = test_server:stop_node(Node),
-
+
%% Remote registered name, but non-existing node
{'EXIT',{{nodedown,Node},_}} = (catch proc_lib:stop({to_stop,Node})),
ok.
@@ -543,7 +543,7 @@ t_format_looper() ->
%%-----------------------------------------------------------------
init(Tester) ->
{ok, Tester}.
-
+
handle_event({error_report, _GL, {Pid, crash_report, Report}}, Tester) ->
io:format("~s\n", [proc_lib:format(Report)]),
Tester ! {crash_report, Pid, Report},
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 22504952d7..60737b20fa 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -80,7 +80,7 @@
backward/1, forward/1,
- eep37/1]).
+ eep37/1]).
%% Internal exports.
-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
@@ -157,25 +157,25 @@ end_per_group(_GroupName, Config) ->
badarg(Config) when is_list(Config) ->
Ts =
- [{badarg,
- <<"-import(qlc, [q/1, q/2]).
+ [{badarg,
+ <<"-import(qlc, [q/1, q/2]).
q(_, _, _) -> ok.
- badarg() ->
- qlc:q(foo),
- qlc:q(foo, cache_all),
- qlc:q(foo, cache_all, extra),
- q(bar),
- q(bar, cache_all),
- q(bar, cache_all, extra).
- ">>,
+badarg() ->
+ qlc:q(foo),
+ qlc:q(foo, cache_all),
+ qlc:q(foo, cache_all, extra),
+ q(bar),
+ q(bar, cache_all),
+ q(bar, cache_all, extra).
+">>,
[],
- {errors,[{5,?QLC,not_a_query_list_comprehension},
- {6,?QLC,not_a_query_list_comprehension},
- {8,?QLC,not_a_query_list_comprehension},
- {9,?QLC,not_a_query_list_comprehension}],
- []}}],
- ?line [] = compile(Config, Ts),
+{errors,[{5,?QLC,not_a_query_list_comprehension},
+ {6,?QLC,not_a_query_list_comprehension},
+ {8,?QLC,not_a_query_list_comprehension},
+ {9,?QLC,not_a_query_list_comprehension}],
+ []}}],
+ [] = compile(Config, Ts),
ok.
%% Nested qlc expressions.
@@ -218,7 +218,7 @@ nested_qlc(Config) when is_list(Config) ->
[warn_unused_vars],
{warnings,[{{6,39},erl_lint,{shadowed_var,'X',generate}}]}}
],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Unused variable with a name that should not be introduced.
@@ -233,7 +233,7 @@ unused_var(Config) when is_list(Config) ->
">>,
[warn_unused_vars],
{warnings,[{{2,33},erl_lint,{unused_var,'Y1'}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Ordinary LC expression.
@@ -245,7 +245,7 @@ lc(Config) when is_list(Config) ->
">>,
[],
{warnings,[{{2,30},erl_lint,{shadowed_var,'X',generate}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Fun with several clauses.
@@ -264,7 +264,7 @@ fun_clauses(Config) when is_list(Config) ->
{{3,41},erl_lint,{shadowed_var,'X',generate}},
{{4,22},erl_lint,{shadowed_var,'X','fun'}},
{{4,41},erl_lint,{shadowed_var,'X',generate}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Variable introduced in filter.
@@ -292,7 +292,7 @@ filter_var(Config) when is_list(Config) ->
">>,
[],
{errors,[{{2,25},erl_lint,{unsafe_var,'V',{'case',{3,19}}}}],[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
@@ -306,7 +306,7 @@ single(Config) when is_list(Config) ->
">>,
[warn_unused_vars],
{warnings,[{{2,30},erl_lint,{unused_var,'Y'}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Exported variable in list expression (rhs of generator).
@@ -326,7 +326,7 @@ exported_var(Config) when is_list(Config) ->
[warn_export_vars],
{warnings,[{{7,37},erl_lint,{exported_var,'Z',{'case',{3,36}}}},
{{7,44},erl_lint,{exported_var,'Z',{'case',{3,36}}}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Errors for generator variable used in list expression.
@@ -351,7 +351,7 @@ generator_vars(Config) when is_list(Config) ->
{{9,33},?QLC,{used_generator_variable,'Z'}},
{{9,40},?QLC,{used_generator_variable,'Z'}}],
[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Unreachable clauses also found when compiling.
@@ -426,7 +426,7 @@ nomatch(Config) when is_list(Config) ->
{warnings,[{3,v3_core,nomatch}]}}
],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
@@ -439,7 +439,7 @@ errors(Config) when is_list(Config) ->
">>,
[],
{errors,[{{2,33},erl_lint,{unbound_var,'A'}}],[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
%% Patterns.
@@ -464,7 +464,7 @@ pattern(Config) when is_list(Config) ->
end, [{<<\"hej\">>}])">>
],
- ?line run(Config, <<"-record(a, {k,v}).
+ run(Config, <<"-record(a, {k,v}).
-record(k, {t,v}).\n">>, Ts),
ok.
@@ -585,7 +585,7 @@ eval(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% cursor/2
@@ -697,7 +697,7 @@ cursor(Config) when is_list(Config) ->
ok = qlc:delete_cursor(C2)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% fold/4
@@ -790,7 +790,7 @@ fold(Config) when is_list(Config) ->
(catch qlc:fold(F, [], Q, [{unique_all,false}]))
">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Test the unique_all option of eval.
@@ -885,7 +885,7 @@ eval_unique(Config) when is_list(Config) ->
{sort,{sort,{list,_},[{unique,true}]},[]} = i(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Test the cache_all and unique_all options of eval.
@@ -1017,7 +1017,7 @@ eval_cache(Config) when is_list(Config) ->
[1] = qlc:e(H, unique_all)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Test the append function.
@@ -1138,90 +1138,90 @@ append(Config) when is_list(Config) ->
[a,b,1,2,1,2] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Simple call from evaluator.
evaluator(Config) when is_list(Config) ->
- ?line true = is_alive(),
+ true = is_alive(),
evaluator_2(Config, []),
- ?line {ok, Node} = start_node(qlc_SUITE_evaluator),
- ?line ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
+ {ok, Node} = start_node(qlc_SUITE_evaluator),
+ ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
test_server:stop_node(Node),
ok.
evaluator_2(Config, Apps) ->
- ?line lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
+ lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
FileName = filename:join(?privdir, "eval"),
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([X || X <- L]),
[1,2,3] = qlc:e(H).">>),
- ?line Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
- ?line ok = file:eval(FileName, Bs),
+ Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
+ ok = file:eval(FileName, Bs),
%% The error message is "handled" a bit too much...
%% (no trace of erl_lint left)
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([X || X <- L]), qlc:e(H).">>),
- ?line {error,_} = file:eval(FileName),
+ {error,_} = file:eval(FileName),
%% Ugly error message; badarg is caught by file.erl.
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([Z || {X,Y} <- [{a,2}], Z <- [Y]]), qlc:e(H).">>),
- ?line {error,_} = file:eval(FileName),
+ {error,_} = file:eval(FileName),
_ = file:delete(FileName),
ok.
start_node(Name) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
+ PA = filename:dirname(code:which(?MODULE)),
test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
%% string_to_handle/1,2.
string_to_handle(Config) when is_list(Config) ->
- ?line {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
+ {'EXIT',{badarg,_}} =
(catch qlc:string_to_handle("[X || X <- [a].", unique_all)),
- ?line R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
- ?line "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
- ?line {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
- ?line {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
- ?line R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
+ R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
+ "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
+ {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
+ {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
+ R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
qlc:string_to_handle("bad."),
- ?line "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
- ?line R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
+ "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
+ R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
qlc:string_to_handle("[X || begin Y = [1,2], true end, X <- Y]."),
- ?line "1: generated variable 'Y'" ++ _ =
+ "1: generated variable 'Y'" ++ _ =
lists:flatten(qlc:format_error(R4)),
- ?line {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
- ?line H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
- ?line [1,2] = qlc:e(H1),
- ?line H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
+ {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
+ H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
+ [1,2] = qlc:e(H1),
+ H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
"qlc:e(qlc:q([X || X <- [c,d,e]])))]."),
- ?line [a,b,c,d,e] = qlc:e(H2),
+ [a,b,c,d,e] = qlc:e(H2),
%% The generated fun has many arguments (erl_eval has a maximum of 20).
- ?line H3 = qlc:string_to_handle(
+ H3 = qlc:string_to_handle(
"[{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||"
" {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <- []]."),
- ?line [] = qlc:e(H3),
- ?line Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
- ?line H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
- ?line [1,2,3] = qlc:e(H4),
- ?line H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
- ?line [1,2] = qlc:e(H5),
-
- ?line Ets = ets:new(test, []),
- ?line true = ets:insert(Ets, [{1}]),
- ?line Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
- ?line Q = "[X || {X} <- ets:table(E)].",
- ?line [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
- ?line [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
- ?line [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
- ?line {'EXIT',{badarg,_}} =
+ [] = qlc:e(H3),
+ Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
+ H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
+ [1,2,3] = qlc:e(H4),
+ H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
+ [1,2] = qlc:e(H5),
+
+ Ets = ets:new(test, []),
+ true = ets:insert(Ets, [{1}]),
+ Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
+ Q = "[X || {X} <- ets:table(E)].",
+ [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
+ [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
+ [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
+ {'EXIT',{badarg,_}} =
(catch qlc:string_to_handle(Q, {max_lookup,-1}, Bs2)),
- ?line {'EXIT', {no_lookup_to_carry_out, _}} =
+ {'EXIT', {no_lookup_to_carry_out, _}} =
(catch qlc:e(qlc:string_to_handle(Q, {lookup,true}, Bs2))),
- ?line ets:delete(Ets),
+ ets:delete(Ets),
ok.
%% table
@@ -1426,7 +1426,7 @@ table(Config) when is_list(Config) ->
[1,2] = lookup_keys(Q)
end, [{1,1},{2,2}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
Ts2 = [
%% [T || P <- Table, F] turned into a match spec. Records needed.
@@ -1437,7 +1437,7 @@ table(Config) when is_list(Config) ->
[{a,1,2},{a,3,4}] = lists:sort(qlc:eval(QH)),
ets:delete(E)">>
],
- ?line run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
+ run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
ok.
@@ -1580,7 +1580,7 @@ process_dies(Config) when is_list(Config) ->
true = ets:delete(E), ok">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% The sort option.
@@ -1690,7 +1690,7 @@ sort(Config) when is_list(Config) ->
end
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% The sort option.
@@ -1812,7 +1812,7 @@ keysort(Config) when is_list(Config) ->
100003 = length(R)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -1824,7 +1824,7 @@ filesort(Config) when is_list(Config) ->
Q2 = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:keysort([1],Q,Opts)]),
[{{1},1},{{2},1},{{3},1},{{1},2},{{2},2},{{3},2}] = qlc:e(Q2)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -1986,7 +1986,7 @@ cache(Config) when is_list(Config) ->
[]} = i(H, cache_all)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% OTP-6038. The {cache,list} option.
@@ -2275,7 +2275,7 @@ cache_list(Config) when is_list(Config) ->
{'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, foo}))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Filters and match specs.
@@ -2400,7 +2400,7 @@ filter(Config) when is_list(Config) ->
[{2,b},{2,c},{3,b},{3,c}] = qlc:e(H)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% info/2.
@@ -2623,7 +2623,7 @@ info(Config) when is_list(Config) ->
[{4},{5},{6}] = qlc:e(F(3))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Nested QLC expressions. QLC expressions in filter and template.
@@ -2727,7 +2727,7 @@ nested_info(Config) when is_list(Config) ->
[{1,1},{1,1},{1,2},{1,2},{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -2936,7 +2936,7 @@ lookup1(Config) when is_list(Config) ->
[]}
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Lookup keys. Mostly test of filters.
@@ -3707,7 +3707,7 @@ lookup_rec(Config) when is_list(Config) ->
[_] = lookup_keys(Q)
end, [{keypos,2}], [#r{a=foo}])">>
],
- ?line run(Config, <<"-record(r, {a}).\n">>, Ts),
+ run(Config, <<"-record(r, {a}).\n">>, Ts),
ok.
%% Using indices for lookup.
@@ -3772,7 +3772,7 @@ indices(Config) when is_list(Config) ->
[{c,3,z,w}] = qlc:eval(QH)">>
],
- ?line run(Config, <<"-record(r, {a}).\n">>, Ts),
+ run(Config, <<"-record(r, {a}).\n">>, Ts),
ok.
%% Test the table/2 callback functions parent_fun and stop_fun.
@@ -3851,7 +3851,7 @@ pre_fun(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Lookup keys. With records.
@@ -3974,7 +3974,7 @@ skip_filters(Config) when is_list(Config) ->
end, [{0},{1},{2},{3},{4}])">>
],
- ?line run(Config, TsS),
+ run(Config, TsS),
Ts = [
<<"etsc(fun(E) ->
@@ -4252,7 +4252,7 @@ skip_filters(Config) when is_list(Config) ->
end, [{1},{2},{3}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -4298,7 +4298,7 @@ ets(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% dets:table/1,2.
@@ -4394,7 +4394,7 @@ dets(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
_ = file:delete(Fname),
ok.
@@ -4524,7 +4524,7 @@ join_option(Config) when is_list(Config) ->
ets:delete(E1)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% The 'cache' and 'unique' options of qlc/2 affects join.
CUTs = [
@@ -4572,7 +4572,7 @@ join_option(Config) when is_list(Config) ->
_],[{unique,true}]} = i(Q, Options),
[{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q, Options)">>
],
- ?line run(Config, CUTs),
+ run(Config, CUTs),
ok.
@@ -4613,7 +4613,7 @@ join_filter(Config) when is_list(Config) ->
end, [{a},{b},{c}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Lookup join.
@@ -4706,7 +4706,7 @@ join_lookup(Config) when is_list(Config) ->
ets:delete(E)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Merge join.
@@ -4981,7 +4981,7 @@ join_merge(Config) when is_list(Config) ->
[{2,a}] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% Small examples. Returning an error term.
ETs = [
@@ -5160,7 +5160,7 @@ join_merge(Config) when is_list(Config) ->
err = qlc:e(Q)">>
],
- ?line run(Config, ETs),
+ run(Config, ETs),
%% Mostly examples where temporary files are needed while merging.
FTs = [
@@ -5319,7 +5319,7 @@ join_merge(Config) when is_list(Config) ->
],
- ?line run(Config, FTs),
+ run(Config, FTs),
ok.
@@ -5603,7 +5603,7 @@ join_sort(Config) when is_list(Config) ->
end, [{1,2},{3,4}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% Join of more than two columns.
@@ -5634,7 +5634,7 @@ join_complex(Config) when is_list(Config) ->
{warnings,[{2,qlc,too_many_joins}]}}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
Ts2 = [{three,
<<"three() ->
@@ -5663,7 +5663,7 @@ join_complex(Config) when is_list(Config) ->
{[],["cannot handle more than one join efficiently"]}}
],
- ?line compile_format(Config, Ts2),
+ compile_format(Config, Ts2),
ok.
@@ -5676,7 +5676,7 @@ otp_5644(Config) when is_list(Config) ->
[_,_] = qlc:eval(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% OTP-5195. Allow traverse functions returning terms.
@@ -5757,7 +5757,7 @@ otp_5195(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
Ts2 = [<<"Q = qlc:q([{X,Y} || {X} <- [{1},{2},{3}],
begin
@@ -5766,7 +5766,7 @@ otp_5195(Config) when is_list(Config) ->
end,
X =:= Y]),
[{3,3}] = qlc:e(Q)">>],
- ?line run(Config, Ts2),
+ run(Config, Ts2),
ok.
@@ -5780,7 +5780,7 @@ otp_6038_bug(Config) when is_list(Config) ->
H2 = qlc:keysort(1, H1, [{unique,true}]),
[{1,a},{2,b}] = qlc:e(H2)">>],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% Sometimes the cache options did not empty the correct tables.
CTs = [
@@ -5809,7 +5809,7 @@ otp_6038_bug(Config) when is_list(Config) ->
L = [{X,Y} || X <- [1,2], Y <- L4],
true = R =:= L">>
],
- ?line run(Config, CTs),
+ run(Config, CTs),
ok.
@@ -5832,7 +5832,7 @@ otp_6359(Config) when is_list(Config) ->
ok">>]
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
%% OTP-6562. compressed = false (should be []) when sorting before join.
@@ -5854,7 +5854,7 @@ otp_6562(Config) when is_list(Config) ->
ets:delete(E1),
ets:delete(E2)">>
],
- ?line run(Config, Bug),
+ run(Config, Bug),
Bits = [
{otp_6562_1,
@@ -5866,11 +5866,11 @@ otp_6562(Config) when is_list(Config) ->
{errors,[{2,qlc,binary_generator}],
[]}}
],
- ?line [] = compile(Config, Bits),
+ [] = compile(Config, Bits),
- ?line R1 = {error,qlc,{1,qlc,binary_generator}}
+ R1 = {error,qlc,{1,qlc,binary_generator}}
= qlc:string_to_handle("[X || <<X:8>> <= <<\"hej\">>]."),
- ?line "1: cannot handle binary generators\n" =
+ "1: cannot handle binary generators\n" =
lists:flatten(qlc:format_error(R1)),
ok.
@@ -5887,7 +5887,7 @@ otp_6590(Config) when is_list(Config) ->
[id1] = qlc:e(Q)
end(v)">>],
- ?line run(Config, <<"-record(tab1, {id, tab2_id, value}).
+ run(Config, <<"-record(tab1, {id, tab2_id, value}).
-record(tab2, {id, value}).\n">>, Ts),
ok.
@@ -5947,7 +5947,7 @@ otp_6673(Config) when is_list(Config) ->
end,
[{1,x},{2,y},{3,z}])">>],
- ?line run(Config, Ts_PT),
+ run(Config, Ts_PT),
MS = ets:fun2ms(fun({X,_Y}=T) when X > 1 -> T end),
Ts_RT = [
@@ -5984,7 +5984,7 @@ otp_6673(Config) when is_list(Config) ->
end, [{x,1},{y,2},{z,3}])">>
],
- ?line run(Config, Ts_RT),
+ run(Config, Ts_RT),
ok.
@@ -6022,7 +6022,7 @@ otp_6964(Config) when is_list(Config) ->
_ = erlang:system_flag(backtrace_depth, D)
end,
qlc_SUITE:uninstall_error_logger()">>],
- ?line run(Config, T1),
+ run(Config, T1),
T2 = [
<<"%% File sorter.
@@ -6055,7 +6055,7 @@ otp_6964(Config) when is_list(Config) ->
{info, caching} = qlc_SUITE:read_error_logger(),
qlc_SUITE:uninstall_error_logger()">>],
- ?line run(Config, T2),
+ run(Config, T2),
T3 = [
<<"%% sort/keysort
@@ -6085,7 +6085,7 @@ otp_6964(Config) when is_list(Config) ->
qlc_SUITE:uninstall_error_logger(),
ets:delete(E1),
ets:delete(E2)">>],
- ?line run(Config, T3),
+ run(Config, T3),
T4 = [
<<"%% cache list
@@ -6116,7 +6116,7 @@ otp_6964(Config) when is_list(Config) ->
lists:flatten(qlc:format_error(ErrReply))
end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
I <- lists:seq(1, 10)])">>],
- ?line run(Config, T4),
+ run(Config, T4),
ok.
%% OTP-7238. info-option 'depth', &c.
@@ -6125,7 +6125,7 @@ otp_7238(Config) when is_list(Config) ->
T = otp_7238,
Fname = filename(T, Config),
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
%% A few more warnings.
T1 = [
@@ -6254,7 +6254,7 @@ otp_7238(Config) when is_list(Config) ->
[],
{warnings,[{2,sys_core_fold,no_clause_match}]}}
],
- ?line [] = compile(Config, T1),
+ [] = compile(Config, T1),
%% 'depth' is a new option used by info()
T2 = [
@@ -6480,7 +6480,7 @@ otp_7238(Config) when is_list(Config) ->
qlc:info(Q, [{format,abstract_code},{depth, 2}])">>
],
- ?line run(Config, T2),
+ run(Config, T2),
T3 = [
%% {nomatch_6,
@@ -6496,7 +6496,7 @@ otp_7238(Config) when is_list(Config) ->
%% [],
%% {[],["pattern cannot possibly match"]}}
],
- ?line compile_format(Config, T3),
+ compile_format(Config, T3),
%% *Very* simple test - just check that it doesn't crash.
Type = [{cres,
@@ -6504,7 +6504,7 @@ otp_7238(Config) when is_list(Config) ->
{'EXIT',{{badfun,_},_}} = (catch qlc:e(Q))">>,
[type_checker],
[]}],
- ?line run(Config, Type),
+ run(Config, Type),
ok.
@@ -6519,7 +6519,7 @@ otp_7114(Config) when is_list(Config) ->
[0,1,2,3,4,5] = qlc:e(qlc:sort(qlc:e(Q1)), unique_all),
ets:delete(T),
ok">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
%% OTP-7232. qlc:info() bug (pids, ports, refs, funs).
otp_7232(Config) when is_list(Config) ->
@@ -6549,7 +6549,7 @@ otp_7232(Config) when is_list(Config) ->
\"[<<8,1:1>>]\" = qlc:info(Q)">>
],
- ?line run(Config, Ts).
+ run(Config, Ts).
%% OTP-7552. Merge join bug.
otp_7552(Config) when is_list(Config) ->
@@ -6574,7 +6574,7 @@ otp_7552(Config) when is_list(Config) ->
Qn = F(nested_loop),
true = lists:sort(qlc:e(Qm, {max_list_size,20})) =:=
lists:sort(qlc:e(Qn))">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
%% OTP-7714. Merge join bug.
otp_7714(Config) when is_list(Config) ->
@@ -6591,7 +6591,7 @@ otp_7714(Config) when is_list(Config) ->
[{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)),
ets:delete(E1),
ets:delete(E2)">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
%% OTP-11758. Bug.
otp_11758(Config) when is_list(Config) ->
@@ -6607,7 +6607,7 @@ otp_11758(Config) when is_list(Config) ->
%% OTP-6674. match/comparison.
otp_6674(Config) when is_list(Config) ->
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
Ts = [%% lookup join
<<"E = ets:new(join, [ordered_set]),
@@ -7030,7 +7030,7 @@ otp_6674(Config) when is_list(Config) ->
],
- ?line run(Config, Ts).
+ run(Config, Ts).
%% Syntax error.
otp_12946(Config) when is_list(Config) ->
@@ -7045,7 +7045,7 @@ otp_12946(Config) when is_list(Config) ->
%% Examples from qlc(3).
manpage(Config) when is_list(Config) ->
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
Ts = [
<<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
@@ -7200,7 +7200,7 @@ manpage(Config) when is_list(Config) ->
ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))\",
L = qlc:info(QH)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
L = [1,2,3],
Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
@@ -7218,7 +7218,7 @@ manpage(Config) when is_list(Config) ->
true = qlc:info(QH1) =:= qlc:info(QH2),
true = ets:delete(Tab)">>]],
- ?line run(Config, ETs),
+ run(Config, ETs),
%% dets(3)
DTs = [
@@ -7231,16 +7231,16 @@ manpage(Config) when is_list(Config) ->
true = qlc:info(QH1) =:= qlc:info(QH2),
ok = dets:close(T)">>]],
- ?line run(Config, DTs),
+ run(Config, DTs),
ok.
compile_gb_table(Config) ->
GB_table_file = filename("gb_table.erl", Config),
- ?line ok = file:write_file(GB_table_file, gb_table()),
- ?line {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
- ?line code:purge(gb_table),
- ?line {module, gb_table} =
+ ok = file:write_file(GB_table_file, gb_table()),
+ {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
+ code:purge(gb_table),
+ {module, gb_table} =
code:load_abs(filename:rootname(GB_table_file)),
ok.
@@ -7363,7 +7363,7 @@ forward(Config) when is_list(Config) ->
{'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
eep37(Config) when is_list(Config) ->
@@ -8064,7 +8064,7 @@ read_error_logger() ->
{error, Pid, Tuple} ->
{error, Pid, Tuple}
after 1000 ->
- ?line io:format("No reply after 1 s\n", []),
+ io:format("No reply after 1 s\n", []),
ct:fail(failed)
end.
diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl
index 31d8ae297c..cd3f8e6e2f 100644
--- a/lib/stdlib/test/queue_SUITE.erl
+++ b/lib/stdlib/test/queue_SUITE.erl
@@ -57,39 +57,39 @@ end_per_group(_GroupName, Config) ->
do(Config) when is_list(Config) ->
- ?line L = [{in, 1},
- {in, 2},
- {out, {value, 1}},
- {in, 3},
- {out, {value, 2}},
- {out, {value, 3}},
- {out, empty}
- ],
-
- ?line E = queue:new(),
- ?line [] = queue:to_list(E),
- ?line Q = do_queue(E, L),
- ?line true = queue:is_empty(Q),
- ?line 0 = queue:len(Q),
+ L = [{in, 1},
+ {in, 2},
+ {out, {value, 1}},
+ {in, 3},
+ {out, {value, 2}},
+ {out, {value, 3}},
+ {out, empty}
+ ],
+
+ E = queue:new(),
+ [] = queue:to_list(E),
+ Q = do_queue(E, L),
+ true = queue:is_empty(Q),
+ 0 = queue:len(Q),
ok.
%% OTP-2701
to_list(Config) when is_list(Config) ->
- ?line E = queue:new(),
- ?line Q = do_queue(E, [{in, 1},
- {in, 2},
- {in, 3},
- {out, {value, 1}},
- {in, 4},
- {in, 5}]),
- ?line true = queue:is_queue(Q),
- ?line 4 = queue:len(Q),
- ?line case queue:to_list(Q) of
- [2,3,4,5] ->
- ok;
- Other1 ->
- ct:fail(Other1)
- end,
+ E = queue:new(),
+ Q = do_queue(E, [{in, 1},
+ {in, 2},
+ {in, 3},
+ {out, {value, 1}},
+ {in, 4},
+ {in, 5}]),
+ true = queue:is_queue(Q),
+ 4 = queue:len(Q),
+ case queue:to_list(Q) of
+ [2,3,4,5] ->
+ ok;
+ Other1 ->
+ ct:fail(Other1)
+ end,
ok.
do_queue(Q, []) ->
@@ -115,75 +115,75 @@ io_test(Config) when is_list(Config) ->
ok.
do_io_test(E) ->
- ?line [4,3,5] =
+ [4,3,5] =
io([snoc,snoc,head,head,head,cons,cons,snoc], E, 1),
- ?line [5,3,4] =
+ [5,3,4] =
io([cons,cons,daeh,daeh,daeh,snoc,snoc,cons], E, 1),
- ?line [4,3,5] =
+ [4,3,5] =
io([in,in,out,out,out,in_r,in_r,in], E, 1),
- ?line [5,3,4] =
+ [5,3,4] =
io([in_r,in_r,out_r,out_r,out_r,in,in,in_r], E, 1),
%%
- ?line [] =
+ [] =
io([snoc,snoc,head,snoc,snoc,head,head,snoc,head,head], E, 1),
- ?line [] =
+ [] =
io([cons,cons,daeh,cons,cons,daeh,daeh,cons,daeh,daeh], E, 1),
- ?line [] =
+ [] =
io([in,in,out,in,in,out,out,in,out,out], E, 1),
- ?line [] =
+ [] =
io([in_r,in_r,out_r,in_r,in_r,out_r,out_r,in_r,out_r,out_r],
E, 1),
%%
- ?line [5,6] =
+ [5,6] =
io([snoc,snoc,snoc,head,head,snoc,snoc,snoc,head,head], E, 1),
- ?line [6,5] =
+ [6,5] =
io([cons,cons,cons,daeh,daeh,cons,cons,cons,daeh,daeh], E, 1),
- ?line [5,6] =
+ [5,6] =
io([in,in,in,out,out,in,in,in,out,out], E, 1),
- ?line [6,5] =
+ [6,5] =
io([in_r,in_r,in_r,out_r,out_r,in_r,in_r,in_r,out_r,out_r],
E, 1),
%%
- ?line [5] =
+ [5] =
io([snoc,head,head,snoc,head,snoc,head,snoc,head,snoc], E, 1),
- ?line [5] =
+ [5] =
io([cons,daeh,daeh,cons,daeh,cons,daeh,cons,daeh,cons], E, 1),
- ?line [5] =
+ [5] =
io([in,out,out,in,out,in,out,in,out,in], E, 1),
- ?line [5] =
+ [5] =
io([in_r,out_r,out_r,in_r,out_r,in_r,out_r,in_r,out_r,in_r],
E, 1),
%%
- ?line [] =
+ [] =
io([snoc,head,snoc,snoc,head,head,snoc,snoc,snoc,head,head,head],
E, 1),
- ?line [] =
+ [] =
io([cons,daeh,cons,cons,daeh,daeh,cons,cons,cons,daeh,daeh,daeh],
- E, 1),
- ?line [] =
+ E, 1),
+ [] =
io([in,out,in,in,out,out,in,in,in,out,out,out],
E, 1),
- ?line [] =
+ [] =
io([in_r,out_r,in_r,in_r,out_r,out_r,in_r,in_r,in_r,out_r,out_r,out_r],
- E, 1),
+ E, 1),
%%
- ?line [3] = io([cons,cons,cons,snoc,daeh,daeh,daeh], E, 1),
- ?line [3] = io([snoc,snoc,snoc,cons,head,head,head], E, 1),
- ?line [3] = io([in,in,in,in_r,out,out,out], E, 1),
- ?line [3] = io([in_r,in_r,in_r,in,out_r,out_r,out_r], E, 1),
+ [3] = io([cons,cons,cons,snoc,daeh,daeh,daeh], E, 1),
+ [3] = io([snoc,snoc,snoc,cons,head,head,head], E, 1),
+ [3] = io([in,in,in,in_r,out,out,out], E, 1),
+ [3] = io([in_r,in_r,in_r,in,out_r,out_r,out_r], E, 1),
%%
- ?line Q2 = queue:join(queue:cons(1, E),queue:cons(2, E)),
- ?line Q1 = queue:reverse(Q2),
- ?line [1] = io([head], Q1, 3),
- ?line [1] = io([out], Q1, 3),
- ?line [1] = io([daeh], Q2, 3),
- ?line [1] = io([out_r], Q2, 3),
+ Q2 = queue:join(queue:cons(1, E),queue:cons(2, E)),
+ Q1 = queue:reverse(Q2),
+ [1] = io([head], Q1, 3),
+ [1] = io([out], Q1, 3),
+ [1] = io([daeh], Q2, 3),
+ [1] = io([out_r], Q2, 3),
%%
- ?line [2] =
+ [2] =
io([in,peek,peek_r,drop,in_r,peek,peek_r,in,peek,peek_r,drop_r], E, 1),
%% Malformed queues UGLY-GUTS-ALL-OVER-THE-PLACE
- ?line [2,1] = io([peek], {[1,2],[]}, 1),
- ?line [1,2] = io([peek_r], {[],[1,2]}, 1),
+ [2,1] = io([peek], {[1,2],[]}, 1),
+ [1,2] = io([peek_r], {[],[1,2]}, 1),
%%
ok.
@@ -287,92 +287,92 @@ op_test(Config) when is_list(Config) ->
ok.
do_op_test(F) ->
- ?line Len = 50,
- ?line Len2 = 2*Len,
- ?line L1 = lists:seq(1, Len),
- ?line L1r = lists:reverse(L1),
- ?line L2 = lists:seq(Len+1, Len2),
- ?line L2r = lists:reverse(L2),
- ?line L3 = L1++L2,
- ?line L3r = L2r++L1r,
- ?line Q0 = F(queue:new()),
- ?line [] = queue:to_list(Q0),
- ?line Q0 = F(queue:from_list([])),
- ?line Q1 = F(queue:from_list(L1)),
- ?line Q2 = F(queue:from_list(L2)),
- ?line Q3 = F(queue:from_list(L3)),
- ?line Len = queue:len(Q1),
- ?line Len = queue:len(Q2),
- ?line Len2 = queue:len(Q3),
- ?line L1 = queue:to_list(Q1),
- ?line L2 = queue:to_list(Q2),
- ?line L3 = queue:to_list(Q3),
- ?line Q3b = queue:join(Q0, queue:join(queue:join(Q1, Q2), Q0)),
- ?line L3 = queue:to_list(Q3b),
- ?line {Q0, Q3New1} = queue:split(0, Q3),
- ?line L3 = queue:to_list(Q3New1),
- ?line {Q3New2, Q0} = queue:split(Len2, Q3),
- ?line L3 = queue:to_list(Q3New2),
- ?line {Q1a, Q2a} = queue:split(Len, Q3),
- ?line L1 = queue:to_list(Q1a),
- ?line L2 = queue:to_list(Q2a),
- ?line {Q3c, Q3d} = queue:split(2, Q3),
- ?line L3 = queue:to_list(Q3c) ++ queue:to_list(Q3d),
- ?line {Q1b, Q2b} = queue:split(Len, Q3b),
- ?line L1 = queue:to_list(Q1b),
- ?line L2 = queue:to_list(Q2b),
- ?line Len = queue:len(Q1b),
- ?line Len = queue:len(Q2b),
- ?line Len2 = queue:len(Q3b),
- ?line Q1r = queue:reverse(Q1),
- ?line Q2r = queue:reverse(Q2),
- ?line Q1ar = queue:reverse(Q1a),
- ?line Q2ar = queue:reverse(Q2a),
- ?line Q1br = queue:reverse(Q1b),
- ?line Q2br = queue:reverse(Q2b),
- ?line Q3br = queue:reverse(Q3b),
- ?line L1r = queue:to_list(Q1r),
- ?line L1r = queue:to_list(Q1ar),
- ?line L1r = queue:to_list(Q1br),
- ?line L2r = queue:to_list(Q2r),
- ?line L2r = queue:to_list(Q2ar),
- ?line L2r = queue:to_list(Q2br),
- ?line L3r = queue:to_list(Q3br),
- ?line Len = queue:len(Q1br),
- ?line Len = queue:len(Q2br),
- ?line Len2 = queue:len(Q3br),
- ?line false = queue:member([], Q0),
- ?line false = queue:member(0, Q0),
- ?line false = queue:member(0, Q1),
- ?line false = queue:member([], Q1),
- ?line true = queue:member(1, Q1),
- ?line false = queue:member(1.0, Q1),
- ?line true = queue:member(Len, Q1),
+ Len = 50,
+ Len2 = 2*Len,
+ L1 = lists:seq(1, Len),
+ L1r = lists:reverse(L1),
+ L2 = lists:seq(Len+1, Len2),
+ L2r = lists:reverse(L2),
+ L3 = L1++L2,
+ L3r = L2r++L1r,
+ Q0 = F(queue:new()),
+ [] = queue:to_list(Q0),
+ Q0 = F(queue:from_list([])),
+ Q1 = F(queue:from_list(L1)),
+ Q2 = F(queue:from_list(L2)),
+ Q3 = F(queue:from_list(L3)),
+ Len = queue:len(Q1),
+ Len = queue:len(Q2),
+ Len2 = queue:len(Q3),
+ L1 = queue:to_list(Q1),
+ L2 = queue:to_list(Q2),
+ L3 = queue:to_list(Q3),
+ Q3b = queue:join(Q0, queue:join(queue:join(Q1, Q2), Q0)),
+ L3 = queue:to_list(Q3b),
+ {Q0, Q3New1} = queue:split(0, Q3),
+ L3 = queue:to_list(Q3New1),
+ {Q3New2, Q0} = queue:split(Len2, Q3),
+ L3 = queue:to_list(Q3New2),
+ {Q1a, Q2a} = queue:split(Len, Q3),
+ L1 = queue:to_list(Q1a),
+ L2 = queue:to_list(Q2a),
+ {Q3c, Q3d} = queue:split(2, Q3),
+ L3 = queue:to_list(Q3c) ++ queue:to_list(Q3d),
+ {Q1b, Q2b} = queue:split(Len, Q3b),
+ L1 = queue:to_list(Q1b),
+ L2 = queue:to_list(Q2b),
+ Len = queue:len(Q1b),
+ Len = queue:len(Q2b),
+ Len2 = queue:len(Q3b),
+ Q1r = queue:reverse(Q1),
+ Q2r = queue:reverse(Q2),
+ Q1ar = queue:reverse(Q1a),
+ Q2ar = queue:reverse(Q2a),
+ Q1br = queue:reverse(Q1b),
+ Q2br = queue:reverse(Q2b),
+ Q3br = queue:reverse(Q3b),
+ L1r = queue:to_list(Q1r),
+ L1r = queue:to_list(Q1ar),
+ L1r = queue:to_list(Q1br),
+ L2r = queue:to_list(Q2r),
+ L2r = queue:to_list(Q2ar),
+ L2r = queue:to_list(Q2br),
+ L3r = queue:to_list(Q3br),
+ Len = queue:len(Q1br),
+ Len = queue:len(Q2br),
+ Len2 = queue:len(Q3br),
+ false = queue:member([], Q0),
+ false = queue:member(0, Q0),
+ false = queue:member(0, Q1),
+ false = queue:member([], Q1),
+ true = queue:member(1, Q1),
+ false = queue:member(1.0, Q1),
+ true = queue:member(Len, Q1),
%%
%% Additional coverage.
- ?line {MyL1r,MyL2r} = lists:split(Len-2, L1r),
- ?line MyQ0r = queue:reverse(F(queue:from_list(L1))),
- ?line {MyQ1r,MyQ2r} = queue:split(Len-2, MyQ0r),
- ?line MyL1r = queue:to_list(MyQ1r),
- ?line MyL2r = queue:to_list(MyQ2r),
- ?line MyQ3r = queue:filter(
- fun (X) when X rem 4 >= 2 -> false;
- (X) when X rem 8 == 0 -> [float(X),{X}];
- (X) when X rem 2 >= 1 -> [{X}];
- (_) -> true
- end, MyQ1r),
- ?line MyL3r = lists:flatten(
- [if X rem 8 == 0 -> [float(X),{X}];
- X rem 2 >= 1 -> {X};
- true -> X
- end || X <- MyL1r,
- X rem 4 < 2]),
- ?line MyL3r = queue:to_list(MyQ3r),
- ?line MyQ4 = F(queue:from_list([11,22,33,44])),
- ?line [11,22] = queue:to_list(queue:filter(fun(X) when X < 27 -> true;
- (_) -> [] end, MyQ4)),
- ?line [33,44] = queue:to_list(queue:filter(fun(X) when X < 27 -> false;
- (X) -> [X] end, MyQ4)),
+ {MyL1r,MyL2r} = lists:split(Len-2, L1r),
+ MyQ0r = queue:reverse(F(queue:from_list(L1))),
+ {MyQ1r,MyQ2r} = queue:split(Len-2, MyQ0r),
+ MyL1r = queue:to_list(MyQ1r),
+ MyL2r = queue:to_list(MyQ2r),
+ MyQ3r = queue:filter(
+ fun (X) when X rem 4 >= 2 -> false;
+ (X) when X rem 8 == 0 -> [float(X),{X}];
+ (X) when X rem 2 >= 1 -> [{X}];
+ (_) -> true
+ end, MyQ1r),
+ MyL3r = lists:flatten(
+ [if X rem 8 == 0 -> [float(X),{X}];
+ X rem 2 >= 1 -> {X};
+ true -> X
+ end || X <- MyL1r,
+ X rem 4 < 2]),
+ MyL3r = queue:to_list(MyQ3r),
+ MyQ4 = F(queue:from_list([11,22,33,44])),
+ [11,22] = queue:to_list(queue:filter(fun(X) when X < 27 -> true;
+ (_) -> [] end, MyQ4)),
+ [33,44] = queue:to_list(queue:filter(fun(X) when X < 27 -> false;
+ (X) -> [X] end, MyQ4)),
%%
ok.
@@ -394,47 +394,47 @@ trycatch(M, F, Args) ->
end.
do_error(F, IQ) ->
- ?line io:format("Illegal Queue: ~p~n", [IQ]),
+ io:format("Illegal Queue: ~p~n", [IQ]),
%%
- ?line {error,badarg} = trycatch(in, [1, IQ]),
- ?line {error,badarg} = trycatch(out, [IQ]),
- ?line {error,badarg} = trycatch(in_r ,[1, IQ]),
- ?line {error,badarg} = trycatch(out_r ,[IQ]),
- ?line {error,badarg} = trycatch(to_list ,[IQ]),
+ {error,badarg} = trycatch(in, [1, IQ]),
+ {error,badarg} = trycatch(out, [IQ]),
+ {error,badarg} = trycatch(in_r ,[1, IQ]),
+ {error,badarg} = trycatch(out_r ,[IQ]),
+ {error,badarg} = trycatch(to_list ,[IQ]),
%%
- ?line {error,badarg} = trycatch(from_list, [no_list]),
- ?line {error,badarg} = trycatch(is_empty, [IQ]),
- ?line {error,badarg} = trycatch(len, [IQ]),
+ {error,badarg} = trycatch(from_list, [no_list]),
+ {error,badarg} = trycatch(is_empty, [IQ]),
+ {error,badarg} = trycatch(len, [IQ]),
%%
- ?line {error,badarg} = trycatch(cons, [1, IQ]),
- ?line {error,badarg} = trycatch(head, [IQ]),
- ?line {error,badarg} = trycatch(tail, [IQ]),
+ {error,badarg} = trycatch(cons, [1, IQ]),
+ {error,badarg} = trycatch(head, [IQ]),
+ {error,badarg} = trycatch(tail, [IQ]),
%%
- ?line {error,badarg} = trycatch(snoc, [IQ, 1]),
- ?line {error,badarg} = trycatch(last, [IQ]),
- ?line {error,badarg} = trycatch(daeh, [IQ]),
- ?line {error,badarg} = trycatch(liat, [IQ]),
- ?line {error,badarg} = trycatch(lait, [IQ]),
- ?line {error,badarg} = trycatch(init, [IQ]),
+ {error,badarg} = trycatch(snoc, [IQ, 1]),
+ {error,badarg} = trycatch(last, [IQ]),
+ {error,badarg} = trycatch(daeh, [IQ]),
+ {error,badarg} = trycatch(liat, [IQ]),
+ {error,badarg} = trycatch(lait, [IQ]),
+ {error,badarg} = trycatch(init, [IQ]),
%%
- ?line {error,badarg} = trycatch(reverse, [IQ]),
- ?line {error,badarg} = trycatch(join, [F(queue:new()), IQ]),
- ?line {error,badarg} = trycatch(join, [IQ, F(queue:new())]),
- ?line {error,badarg} = trycatch(split, [17, IQ]),
- ?line {error,badarg} = trycatch(head, [IQ]),
+ {error,badarg} = trycatch(reverse, [IQ]),
+ {error,badarg} = trycatch(join, [F(queue:new()), IQ]),
+ {error,badarg} = trycatch(join, [IQ, F(queue:new())]),
+ {error,badarg} = trycatch(split, [17, IQ]),
+ {error,badarg} = trycatch(head, [IQ]),
%%
- ?line Q0 = F(queue:new()),
- ?line {error,badarg} = trycatch(split, [1, Q0]),
- ?line {error,badarg} = trycatch(split, [2, queue:snoc(Q0, 1)]),
+ Q0 = F(queue:new()),
+ {error,badarg} = trycatch(split, [1, Q0]),
+ {error,badarg} = trycatch(split, [2, queue:snoc(Q0, 1)]),
%%
- ?line {value,false} = trycatch(is_queue, [IQ]),
- ?line {error,badarg} = trycatch(get, [IQ]),
- ?line {error,badarg} = trycatch(peek, [IQ]),
- ?line {error,badarg} = trycatch(peek_r, [IQ]),
- ?line {error,badarg} = trycatch(filter, [fun id/1, IQ]),
- ?line {error,badarg} = trycatch(filter, [no_fun, Q0]),
+ {value,false} = trycatch(is_queue, [IQ]),
+ {error,badarg} = trycatch(get, [IQ]),
+ {error,badarg} = trycatch(peek, [IQ]),
+ {error,badarg} = trycatch(peek_r, [IQ]),
+ {error,badarg} = trycatch(filter, [fun id/1, IQ]),
+ {error,badarg} = trycatch(filter, [no_fun, Q0]),
%%
- ?line {error,badarg} = trycatch(member, [1, IQ]),
+ {error,badarg} = trycatch(member, [1, IQ]),
ok.
id(X) ->
@@ -442,14 +442,14 @@ id(X) ->
%% Test queue errors.
oops(Config) when is_list(Config) ->
- ?line N = 3142,
- ?line Optab = optab(),
- ?line Seed0 = rand:seed(exsplus, {1,2,4}),
- ?line {Is,Seed} = random_list(N, tuple_size(Optab), Seed0, []),
- ?line io:format("~p ", [Is]),
- ?line QA = queue:new(),
- ?line QB = {[]},
- ?line emul([QA], [QB], Seed, [element(I, Optab) || I <- Is]).
+ N = 3142,
+ Optab = optab(),
+ Seed0 = rand:seed(exsplus, {1,2,4}),
+ {Is,Seed} = random_list(N, tuple_size(Optab), Seed0, []),
+ io:format("~p ", [Is]),
+ QA = queue:new(),
+ QB = {[]},
+ emul([QA], [QB], Seed, [element(I, Optab) || I <- Is]).
optab() ->
{{new,[], q, fun () -> {[]} end},
diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl
index d261b92514..34b350e132 100644
--- a/lib/stdlib/test/random_SUITE.erl
+++ b/lib/stdlib/test/random_SUITE.erl
@@ -58,48 +58,48 @@ end_per_group(_GroupName, Config) ->
%% 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.
%% 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.
%% 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;
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index bcf40063f1..7458aec13e 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -72,195 +72,195 @@ pcre(Config) when is_list(Config) ->
%% Test all documented compile options.
compile_options(Config) when is_list(Config) ->
- ?line ok = ctest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}),
- ?line ok = ctest("ABDabcdABCD","abcd",[anchored],true,nomatch),
- ?line ok = ctest("ABDabcdABCD",".*abcd",[anchored],true,{match,[{0,7}]}),
- ?line ok = ctest("ABCabcdABC","ABCD",[],true,nomatch),
- ?line ok = ctest("ABCabcdABC","ABCD",[caseless],true,{match,[{3,4}]}),
- ?line ok = ctest("abcdABC\n","ABC$",[],true,{match,[{4,3}]}),
- ?line ok = ctest("abcdABC\n","ABC$",[dollar_endonly],true,nomatch),
- ?line ok = ctest("abcdABC\n","ABC.",[],true,nomatch),
- ?line ok = ctest("abcdABC\n","ABC.",[dotall],true,{match,[{4,4}]}),
- ?line ok = ctest("abcdABCD","ABC .",[],true,nomatch),
- ?line ok = ctest("abcdABCD","ABC .",[extended],true,{match,[{4,4}]}),
- ?line ok = ctest("abcd\nABCD","ABC",[],true,{match,[{5,3}]}),
- ?line ok = ctest("abcd\nABCD","ABC",[firstline],true,nomatch),
- ?line ok = ctest("abcd\nABCD","^ABC",[],true,nomatch),
- ?line ok = ctest("abcd\nABCD","^ABC",[multiline],true,{match,[{5,3}]}),
- ?line ok = ctest("abcdABCD","(ABC)",[],true,{match,[{4,3},{4,3}]}),
- ?line ok = ctest("abcdABCD","(ABC)",[no_auto_capture],true,{match,[{4,3}]}),
- ?line ok = ctest(notused,"(?<FOO>ABC)|(?<FOO>DEF)",[],false,notused),
- ?line ok = ctest("abcdABCD","(?<FOO>ABC)|(?<FOO>DEF)",[dupnames],true,{match,[{4,3},{4,3}]}),
- ?line ok = ctest("abcdABCDabcABCD","abcd.*D",[],true,{match,[{0,15}]}),
- ?line ok = ctest("abcdABCDabcABCD","abcd.*D",[ungreedy],true,{match,[{0,8}]}),
- ?line ok = ctest("abcdABCabcABC\nD","abcd.*D",[],true,nomatch),
- ?line ok = ctest("abcdABCabcABC\nD","abcd.*D",[{newline,cr}],true,{match,[{0,15}]}),
- ?line ok = ctest("abcdABCabcABC\rD","abcd.*D",[],true,{match,[{0,15}]}),
- ?line ok = ctest("abcdABCabcABC\rD","abcd.*D",[{newline,lf}],true,{match,[{0,15}]}),
- ?line ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,lf}],true,nomatch),
- ?line ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,cr}],true,nomatch),
- ?line ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,crlf}],true,{match,[{7,4}]}),
-
- ?line ok = ctest("abcdABCabcd\r","abcd$",[{newline,crlf}],true,nomatch),
- ?line ok = ctest("abcdABCabcd\n","abcd$",[{newline,crlf}],true,nomatch),
- ?line ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
-
- ?line ok = ctest("abcdABCabcd\r","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
- ?line ok = ctest("abcdABCabcd\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+ ok = ctest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}),
+ ok = ctest("ABDabcdABCD","abcd",[anchored],true,nomatch),
+ ok = ctest("ABDabcdABCD",".*abcd",[anchored],true,{match,[{0,7}]}),
+ ok = ctest("ABCabcdABC","ABCD",[],true,nomatch),
+ ok = ctest("ABCabcdABC","ABCD",[caseless],true,{match,[{3,4}]}),
+ ok = ctest("abcdABC\n","ABC$",[],true,{match,[{4,3}]}),
+ ok = ctest("abcdABC\n","ABC$",[dollar_endonly],true,nomatch),
+ ok = ctest("abcdABC\n","ABC.",[],true,nomatch),
+ ok = ctest("abcdABC\n","ABC.",[dotall],true,{match,[{4,4}]}),
+ ok = ctest("abcdABCD","ABC .",[],true,nomatch),
+ ok = ctest("abcdABCD","ABC .",[extended],true,{match,[{4,4}]}),
+ ok = ctest("abcd\nABCD","ABC",[],true,{match,[{5,3}]}),
+ ok = ctest("abcd\nABCD","ABC",[firstline],true,nomatch),
+ ok = ctest("abcd\nABCD","^ABC",[],true,nomatch),
+ ok = ctest("abcd\nABCD","^ABC",[multiline],true,{match,[{5,3}]}),
+ ok = ctest("abcdABCD","(ABC)",[],true,{match,[{4,3},{4,3}]}),
+ ok = ctest("abcdABCD","(ABC)",[no_auto_capture],true,{match,[{4,3}]}),
+ ok = ctest(notused,"(?<FOO>ABC)|(?<FOO>DEF)",[],false,notused),
+ ok = ctest("abcdABCD","(?<FOO>ABC)|(?<FOO>DEF)",[dupnames],true,{match,[{4,3},{4,3}]}),
+ ok = ctest("abcdABCDabcABCD","abcd.*D",[],true,{match,[{0,15}]}),
+ ok = ctest("abcdABCDabcABCD","abcd.*D",[ungreedy],true,{match,[{0,8}]}),
+ ok = ctest("abcdABCabcABC\nD","abcd.*D",[],true,nomatch),
+ ok = ctest("abcdABCabcABC\nD","abcd.*D",[{newline,cr}],true,{match,[{0,15}]}),
+ ok = ctest("abcdABCabcABC\rD","abcd.*D",[],true,{match,[{0,15}]}),
+ ok = ctest("abcdABCabcABC\rD","abcd.*D",[{newline,lf}],true,{match,[{0,15}]}),
+ ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,lf}],true,nomatch),
+ ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,cr}],true,nomatch),
+ ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,crlf}],true,{match,[{7,4}]}),
+
+ ok = ctest("abcdABCabcd\r","abcd$",[{newline,crlf}],true,nomatch),
+ ok = ctest("abcdABCabcd\n","abcd$",[{newline,crlf}],true,nomatch),
+ ok = ctest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+
+ ok = ctest("abcdABCabcd\r","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+ ok = ctest("abcdABCabcd\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
ok.
%% Test all documented run specific options.
run_options(Config) when is_list(Config) ->
- ?line rtest("ABCabcdABC","abc",[],[],true),
- ?line rtest("ABCabcdABC","abc",[anchored],[],false),
+ rtest("ABCabcdABC","abc",[],[],true),
+ rtest("ABCabcdABC","abc",[anchored],[],false),
%% Anchored in run overrides unanchored in compilation
- ?line rtest("ABCabcdABC","abc",[],[anchored],false),
-
- ?line rtest("","a?b?",[],[],true),
- ?line rtest("","a?b?",[],[notempty],false),
-
- ?line rtest("abc","^a",[],[],true),
- ?line rtest("abc","^a",[],[notbol],false),
- ?line rtest("ab\nc","^a",[multiline],[],true),
- ?line rtest("ab\nc","^a",[multiline],[notbol],false),
- ?line rtest("ab\nc","^c",[multiline],[notbol],true),
-
- ?line rtest("abc","c$",[],[],true),
- ?line rtest("abc","c$",[],[noteol],false),
-
- ?line rtest("ab\nc","b$",[multiline],[],true),
- ?line rtest("ab\nc","c$",[multiline],[],true),
- ?line rtest("ab\nc","b$",[multiline],[noteol],true),
- ?line rtest("ab\nc","c$",[multiline],[noteol],false),
-
- ?line rtest("abc","ab",[],[{offset,0}],true),
- ?line rtest("abc","ab",[],[{offset,1}],false),
-
- ?line rtest("abcdABCabcABC\nD","abcd.*D",[],[],false),
- ?line rtest("abcdABCabcABC\nD","abcd.*D",[],[{newline,cr}],true),
- ?line rtest("abcdABCabcABC\rD","abcd.*D",[],[],true),
- ?line rtest("abcdABCabcABC\rD","abcd.*D",[{newline,cr}],[{newline,lf}],true),
- ?line rtest("abcdABCabcd\r\n","abcd$",[],[{newline,lf}],false),
- ?line rtest("abcdABCabcd\r\n","abcd$",[],[{newline,cr}],false),
- ?line rtest("abcdABCabcd\r\n","abcd$",[],[{newline,crlf}],true),
-
- ?line rtest("abcdABCabcd\r","abcd$",[],[{newline,crlf}],false),
- ?line rtest("abcdABCabcd\n","abcd$",[],[{newline,crlf}],false),
- ?line rtest("abcdABCabcd\r\n","abcd$",[],[{newline,anycrlf}],true),
-
- ?line rtest("abcdABCabcd\r","abcd$",[],[{newline,anycrlf}],true),
- ?line rtest("abcdABCabcd\n","abcd$",[],[{newline,anycrlf}],true),
-
- ?line {ok,MP} = re:compile(".*(abcd).*"),
- ?line {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[]),
- ?line {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all}]),
- ?line {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all,index}]),
- ?line {match,["ABCabcdABC","abcd"]} = re:run("ABCabcdABC",MP,[{capture,all,list}]),
- ?line {match,[<<"ABCabcdABC">>,<<"abcd">>]} = re:run("ABCabcdABC",MP,[{capture,all,binary}]),
- ?line {match,[{0,10}]} = re:run("ABCabcdABC",MP,[{capture,first}]),
- ?line {match,[{0,10}]} = re:run("ABCabcdABC",MP,[{capture,first,index}]), ?line {match,["ABCabcdABC"]} = re:run("ABCabcdABC",MP,[{capture,first,list}]),
- ?line {match,[<<"ABCabcdABC">>]} = re:run("ABCabcdABC",MP,[{capture,first,binary}]),
-
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all_but_first}]),
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,index}]),
- ?line {match,["abcd"]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,list}]),
- ?line {match,[<<"abcd">>]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,binary}]),
-
- ?line match = re:run("ABCabcdABC",MP,[{capture,none}]),
- ?line match = re:run("ABCabcdABC",MP,[{capture,none,index}]),
- ?line match = re:run("ABCabcdABC",MP,[{capture,none,list}]),
- ?line match = re:run("ABCabcdABC",MP,[{capture,none,binary}]),
-
- ?line {ok,MP2} = re:compile(".*(?<FOO>abcd).*"),
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,[1]}]),
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,['FOO']}]),
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"]}]),
- ?line {match,["abcd"]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"],list}]),
- ?line {match,[<<"abcd">>]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"],binary}]),
-
- ?line {match,[{-1,0}]} = re:run("ABCabcdABC",MP2,[{capture,[200]}]),
- ?line {match,[{-1,0}]} = re:run("ABCabcdABC",MP2,[{capture,['BAR']}]),
- ?line {match,[""]} = re:run("ABCabcdABC",MP2,[{capture,[200],list}]),
- ?line {match,[""]} = re:run("ABCabcdABC",MP2,[{capture,['BAR'],list}]),
- ?line {match,[<<>>]} = re:run("ABCabcdABC",MP2,[{capture,[200],binary}]),
- ?line {match,[<<>>]} = re:run("ABCabcdABC",MP2,[{capture,['BAR'],binary}]),
-
- ?line {ok, MP3} = re:compile(".*((?<FOO>abdd)|a(..d)).*"),
- ?line {match,[{0,10},{3,4},{-1,0},{4,3}]} = re:run("ABCabcdABC",MP3,[]),
- ?line {match,[{0,10},{3,4},{-1,0},{4,3}]} = re:run("ABCabcdABC",MP3,[{capture,all,index}]),
- ?line {match,[<<"ABCabcdABC">>,<<"abcd">>,<<>>,<<"bcd">>]} = re:run("ABCabcdABC",MP3,[{capture,all,binary}]),
- ?line {match,["ABCabcdABC","abcd",[],"bcd"]} = re:run("ABCabcdABC",MP3,[{capture,all,list}]),
+ rtest("ABCabcdABC","abc",[],[anchored],false),
+
+ rtest("","a?b?",[],[],true),
+ rtest("","a?b?",[],[notempty],false),
+
+ rtest("abc","^a",[],[],true),
+ rtest("abc","^a",[],[notbol],false),
+ rtest("ab\nc","^a",[multiline],[],true),
+ rtest("ab\nc","^a",[multiline],[notbol],false),
+ rtest("ab\nc","^c",[multiline],[notbol],true),
+
+ rtest("abc","c$",[],[],true),
+ rtest("abc","c$",[],[noteol],false),
+
+ rtest("ab\nc","b$",[multiline],[],true),
+ rtest("ab\nc","c$",[multiline],[],true),
+ rtest("ab\nc","b$",[multiline],[noteol],true),
+ rtest("ab\nc","c$",[multiline],[noteol],false),
+
+ rtest("abc","ab",[],[{offset,0}],true),
+ rtest("abc","ab",[],[{offset,1}],false),
+
+ rtest("abcdABCabcABC\nD","abcd.*D",[],[],false),
+ rtest("abcdABCabcABC\nD","abcd.*D",[],[{newline,cr}],true),
+ rtest("abcdABCabcABC\rD","abcd.*D",[],[],true),
+ rtest("abcdABCabcABC\rD","abcd.*D",[{newline,cr}],[{newline,lf}],true),
+ rtest("abcdABCabcd\r\n","abcd$",[],[{newline,lf}],false),
+ rtest("abcdABCabcd\r\n","abcd$",[],[{newline,cr}],false),
+ rtest("abcdABCabcd\r\n","abcd$",[],[{newline,crlf}],true),
+
+ rtest("abcdABCabcd\r","abcd$",[],[{newline,crlf}],false),
+ rtest("abcdABCabcd\n","abcd$",[],[{newline,crlf}],false),
+ rtest("abcdABCabcd\r\n","abcd$",[],[{newline,anycrlf}],true),
+
+ rtest("abcdABCabcd\r","abcd$",[],[{newline,anycrlf}],true),
+ rtest("abcdABCabcd\n","abcd$",[],[{newline,anycrlf}],true),
+
+ {ok,MP} = re:compile(".*(abcd).*"),
+ {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[]),
+ {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all}]),
+ {match,[{0,10},{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all,index}]),
+ {match,["ABCabcdABC","abcd"]} = re:run("ABCabcdABC",MP,[{capture,all,list}]),
+ {match,[<<"ABCabcdABC">>,<<"abcd">>]} = re:run("ABCabcdABC",MP,[{capture,all,binary}]),
+ {match,[{0,10}]} = re:run("ABCabcdABC",MP,[{capture,first}]),
+ {match,[{0,10}]} = re:run("ABCabcdABC",MP,[{capture,first,index}]), ?line {match,["ABCabcdABC"]} = re:run("ABCabcdABC",MP,[{capture,first,list}]),
+ {match,[<<"ABCabcdABC">>]} = re:run("ABCabcdABC",MP,[{capture,first,binary}]),
+
+ {match,[{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all_but_first}]),
+ {match,[{3,4}]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,index}]),
+ {match,["abcd"]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,list}]),
+ {match,[<<"abcd">>]} = re:run("ABCabcdABC",MP,[{capture,all_but_first,binary}]),
+
+ match = re:run("ABCabcdABC",MP,[{capture,none}]),
+ match = re:run("ABCabcdABC",MP,[{capture,none,index}]),
+ match = re:run("ABCabcdABC",MP,[{capture,none,list}]),
+ match = re:run("ABCabcdABC",MP,[{capture,none,binary}]),
+
+ {ok,MP2} = re:compile(".*(?<FOO>abcd).*"),
+ {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,[1]}]),
+ {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,['FOO']}]),
+ {match,[{3,4}]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"]}]),
+ {match,["abcd"]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"],list}]),
+ {match,[<<"abcd">>]} = re:run("ABCabcdABC",MP2,[{capture,["FOO"],binary}]),
+
+ {match,[{-1,0}]} = re:run("ABCabcdABC",MP2,[{capture,[200]}]),
+ {match,[{-1,0}]} = re:run("ABCabcdABC",MP2,[{capture,['BAR']}]),
+ {match,[""]} = re:run("ABCabcdABC",MP2,[{capture,[200],list}]),
+ {match,[""]} = re:run("ABCabcdABC",MP2,[{capture,['BAR'],list}]),
+ {match,[<<>>]} = re:run("ABCabcdABC",MP2,[{capture,[200],binary}]),
+ {match,[<<>>]} = re:run("ABCabcdABC",MP2,[{capture,['BAR'],binary}]),
+
+ {ok, MP3} = re:compile(".*((?<FOO>abdd)|a(..d)).*"),
+ {match,[{0,10},{3,4},{-1,0},{4,3}]} = re:run("ABCabcdABC",MP3,[]),
+ {match,[{0,10},{3,4},{-1,0},{4,3}]} = re:run("ABCabcdABC",MP3,[{capture,all,index}]),
+ {match,[<<"ABCabcdABC">>,<<"abcd">>,<<>>,<<"bcd">>]} = re:run("ABCabcdABC",MP3,[{capture,all,binary}]),
+ {match,["ABCabcdABC","abcd",[],"bcd"]} = re:run("ABCabcdABC",MP3,[{capture,all,list}]),
ok.
-
-
+
+
%% Test compile options given directly to run.
combined_options(Config) when is_list(Config) ->
- ?line ok = crtest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}),
- ?line ok = crtest("ABDabcdABCD","abcd",[anchored],true,nomatch),
- ?line ok = crtest("ABDabcdABCD",".*abcd",[anchored],true,{match,[{0,7}]}),
- ?line ok = crtest("ABCabcdABC","ABCD",[],true,nomatch),
- ?line ok = crtest("ABCabcdABC","ABCD",[caseless],true,{match,[{3,4}]}),
- ?line ok = crtest("abcdABC\n","ABC$",[],true,{match,[{4,3}]}),
- ?line ok = crtest("abcdABC\n","ABC$",[dollar_endonly],true,nomatch),
- ?line ok = crtest("abcdABC\n","ABC.",[],true,nomatch),
- ?line ok = crtest("abcdABC\n","ABC.",[dotall],true,{match,[{4,4}]}),
- ?line ok = crtest("abcdABCD","ABC .",[],true,nomatch),
- ?line ok = crtest("abcdABCD","ABC .",[extended],true,{match,[{4,4}]}),
- ?line ok = crtest("abcd\nABCD","ABC",[],true,{match,[{5,3}]}),
- ?line ok = crtest("abcd\nABCD","ABC",[firstline],true,nomatch),
- ?line ok = crtest("abcd\nABCD","^ABC",[],true,nomatch),
- ?line ok = crtest("abcd\nABCD","^ABC",[multiline],true,{match,[{5,3}]}),
- ?line ok = crtest("abcdABCD","(ABC)",[],true,{match,[{4,3},{4,3}]}),
- ?line ok = crtest("abcdABCD","(ABC)",[no_auto_capture],true,{match,[{4,3}]}),
- ?line ok = crtest(notused,"(?<FOO>ABC)|(?<FOO>DEF)",[],false,notused),
- ?line ok = crtest("abcdABCD","(?<FOO>ABC)|(?<FOO>DEF)",[dupnames],true,{match,[{4,3},{4,3}]}),
- ?line ok = crtest("abcdABCDabcABCD","abcd.*D",[],true,{match,[{0,15}]}),
- ?line ok = crtest("abcdABCDabcABCD","abcd.*D",[ungreedy],true,{match,[{0,8}]}),
- ?line ok = ctest("abcdABCabcABC\nD","abcd.*D",[],true,nomatch),
- ?line ok = crtest("abcdABCabcABC\nD","abcd.*D",[{newline,cr}],true,{match,[{0,15}]}),
- ?line ok = crtest("abcdABCabcABC\rD","abcd.*D",[],true,{match,[{0,15}]}),
- ?line ok = crtest("abcdABCabcABC\rD","abcd.*D",[{newline,lf}],true,{match,[{0,15}]}),
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,lf}],true,nomatch),
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,cr}],true,nomatch),
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,crlf}],true,{match,[{7,4}]}),
-
- ?line ok = crtest("abcdABCabcd\r","abcd$",[{newline,crlf}],true,nomatch),
- ?line ok = crtest("abcdABCabcd\n","abcd$",[{newline,crlf}],true,nomatch),
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
-
- ?line ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
- ?line ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
-
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
-
- ?line ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
-
- ?line ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
-
- ?line ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
-
- ?line ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
- ?line ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
-
+ ok = crtest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}),
+ ok = crtest("ABDabcdABCD","abcd",[anchored],true,nomatch),
+ ok = crtest("ABDabcdABCD",".*abcd",[anchored],true,{match,[{0,7}]}),
+ ok = crtest("ABCabcdABC","ABCD",[],true,nomatch),
+ ok = crtest("ABCabcdABC","ABCD",[caseless],true,{match,[{3,4}]}),
+ ok = crtest("abcdABC\n","ABC$",[],true,{match,[{4,3}]}),
+ ok = crtest("abcdABC\n","ABC$",[dollar_endonly],true,nomatch),
+ ok = crtest("abcdABC\n","ABC.",[],true,nomatch),
+ ok = crtest("abcdABC\n","ABC.",[dotall],true,{match,[{4,4}]}),
+ ok = crtest("abcdABCD","ABC .",[],true,nomatch),
+ ok = crtest("abcdABCD","ABC .",[extended],true,{match,[{4,4}]}),
+ ok = crtest("abcd\nABCD","ABC",[],true,{match,[{5,3}]}),
+ ok = crtest("abcd\nABCD","ABC",[firstline],true,nomatch),
+ ok = crtest("abcd\nABCD","^ABC",[],true,nomatch),
+ ok = crtest("abcd\nABCD","^ABC",[multiline],true,{match,[{5,3}]}),
+ ok = crtest("abcdABCD","(ABC)",[],true,{match,[{4,3},{4,3}]}),
+ ok = crtest("abcdABCD","(ABC)",[no_auto_capture],true,{match,[{4,3}]}),
+ ok = crtest(notused,"(?<FOO>ABC)|(?<FOO>DEF)",[],false,notused),
+ ok = crtest("abcdABCD","(?<FOO>ABC)|(?<FOO>DEF)",[dupnames],true,{match,[{4,3},{4,3}]}),
+ ok = crtest("abcdABCDabcABCD","abcd.*D",[],true,{match,[{0,15}]}),
+ ok = crtest("abcdABCDabcABCD","abcd.*D",[ungreedy],true,{match,[{0,8}]}),
+ ok = ctest("abcdABCabcABC\nD","abcd.*D",[],true,nomatch),
+ ok = crtest("abcdABCabcABC\nD","abcd.*D",[{newline,cr}],true,{match,[{0,15}]}),
+ ok = crtest("abcdABCabcABC\rD","abcd.*D",[],true,{match,[{0,15}]}),
+ ok = crtest("abcdABCabcABC\rD","abcd.*D",[{newline,lf}],true,{match,[{0,15}]}),
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,lf}],true,nomatch),
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,cr}],true,nomatch),
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,crlf}],true,{match,[{7,4}]}),
+
+ ok = crtest("abcdABCabcd\r","abcd$",[{newline,crlf}],true,nomatch),
+ ok = crtest("abcdABCabcd\n","abcd$",[{newline,crlf}],true,nomatch),
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+
+ ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+ ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}),
+
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
+
+ ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
+
+ ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf},{capture,all,list}],true,{match,["abcd"]}),
+
+ ok = crtest("abcdABCabcd\r\n","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
+
+ ok = crtest("abcdABCabcd\r","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
+ ok = crtest("abcdABCabcd\n","abcd$",[{newline,anycrlf},{capture,all,binary}],true,{match,[<<"abcd">>]}),
+
%% Check that unique run-options fail in compile only case:
- ?line {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},{capture,all,binary}])),
- ?line {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},{offset,3}])),
- ?line {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},notempty])),
- ?line {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},notbol])),
- ?line {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},noteol])),
-
-
- ?line {match,_} = re:run("abcdABCabcd\r\n","abcd$",[{newline,crlf}]),
- ?line nomatch = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf}]),
- ?line {match,_} = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf},multiline]),
- ?line nomatch = re:run("abcdABCabcd\r\nefgh","efgh$",[{newline,crlf},multiline,noteol]),
- ?line {match,_} = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf},multiline,noteol]),
- ?line {match,_} = re:run("abcdABCabcd\r\nefgh","^abcd",[{newline,crlf},multiline,noteol]),
- ?line nomatch = re:run("abcdABCabcd\r\nefgh","^abcd",[{newline,crlf},multiline,notbol]),
- ?line {match,_} = re:run("abcdABCabcd\r\nefgh","^efgh",[{newline,crlf},multiline,notbol]),
- ?line {match,_} = re:run("ABC\nD","[a-z]*",[{newline,crlf}]),
- ?line nomatch = re:run("ABC\nD","[a-z]*",[{newline,crlf},notempty]),
+ {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},{capture,all,binary}])),
+ {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},{offset,3}])),
+ {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},notempty])),
+ {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},notbol])),
+ {'EXIT',{badarg,_}} = (catch re:compile("abcd$",[{newline,anycrlf},noteol])),
+
+
+ {match,_} = re:run("abcdABCabcd\r\n","abcd$",[{newline,crlf}]),
+ nomatch = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf}]),
+ {match,_} = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf},multiline]),
+ nomatch = re:run("abcdABCabcd\r\nefgh","efgh$",[{newline,crlf},multiline,noteol]),
+ {match,_} = re:run("abcdABCabcd\r\nefgh","abcd$",[{newline,crlf},multiline,noteol]),
+ {match,_} = re:run("abcdABCabcd\r\nefgh","^abcd",[{newline,crlf},multiline,noteol]),
+ nomatch = re:run("abcdABCabcd\r\nefgh","^abcd",[{newline,crlf},multiline,notbol]),
+ {match,_} = re:run("abcdABCabcd\r\nefgh","^efgh",[{newline,crlf},multiline,notbol]),
+ {match,_} = re:run("ABC\nD","[a-z]*",[{newline,crlf}]),
+ nomatch = re:run("ABC\nD","[a-z]*",[{newline,crlf},notempty]),
ok.
%% Test replace with autogenerated erlang module.
@@ -270,36 +270,36 @@ replace_autogen(Config) when is_list(Config) ->
%% Test capture options together with global searching.
global_capture(Config) when is_list(Config) ->
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",".*(?<FOO>abcd).*",[{capture,[1]}]),
- ?line {match,[{10,4}]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[{capture,[1]}]),
- ?line {match,[[{10,4}]]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[global,{capture,[1]}]),
- ?line {match,[{3,4}]} = re:run("ABCabcdABC",".*(?<FOO>abcd).*",[{capture,['FOO']}]),
- ?line {match,[{10,4}]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[{capture,['FOO']}]),
- ?line {match,[[{10,4}]]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[global,{capture,['FOO']}]),
- ?line {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global]),
- ?line {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all}]),
- ?line {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all,index}]),
- ?line {match,[[{3,4}],[{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,first}]),
- ?line {match,[[{3,4}],[{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all_but_first}]),
- ?line {match,[[<<"bcd">>],[<<"bcd">>]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all_but_first,binary}]),
- ?line {match,[["bcd"],["bcd"]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all_but_first,list}]),
- ?line {match,[["abcd","bcd"],["abcd","bcd"]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,list}]),
- ?line {match,[[<<"abcd">>,<<"bcd">>],[<<"abcd">>,<<"bcd">>]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,binary}]),
- ?line {match,[[{3,4},{4,3}],[{10,4},{11,3}]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,index}]),
- ?line match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,index}]),
- ?line match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,binary}]),
- ?line match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,list}]),
- ?line {match,[[<<195,133,98,99,100>>,<<"bcd">>],[<<"abcd">>,<<"bcd">>]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,binary},unicode]),
- ?line {match,[["Åbcd","bcd"],["abcd","bcd"]]} = re:run(<<"ABC",8#303,8#205,"bcdABCabcdA">>,".(?<FOO>bcd)",[global,{capture,all,list},unicode]),
- ?line {match,[["Åbcd","bcd"],["abcd","bcd"]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,list},unicode]),
- ?line {match,[[{3,5},{5,3}],[{11,4},{12,3}]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,index},unicode]),
+ {match,[{3,4}]} = re:run("ABCabcdABC",".*(?<FOO>abcd).*",[{capture,[1]}]),
+ {match,[{10,4}]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[{capture,[1]}]),
+ {match,[[{10,4}]]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[global,{capture,[1]}]),
+ {match,[{3,4}]} = re:run("ABCabcdABC",".*(?<FOO>abcd).*",[{capture,['FOO']}]),
+ {match,[{10,4}]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[{capture,['FOO']}]),
+ {match,[[{10,4}]]} = re:run("ABCabcdABCabcdA",".*(?<FOO>abcd).*",[global,{capture,['FOO']}]),
+ {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global]),
+ {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all}]),
+ {match,[[{3,4},{3,4}],[{10,4},{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all,index}]),
+ {match,[[{3,4}],[{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,first}]),
+ {match,[[{3,4}],[{10,4}]]} = re:run("ABCabcdABCabcdA","(?<FOO>abcd)",[global,{capture,all_but_first}]),
+ {match,[[<<"bcd">>],[<<"bcd">>]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all_but_first,binary}]),
+ {match,[["bcd"],["bcd"]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all_but_first,list}]),
+ {match,[["abcd","bcd"],["abcd","bcd"]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,list}]),
+ {match,[[<<"abcd">>,<<"bcd">>],[<<"abcd">>,<<"bcd">>]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,binary}]),
+ {match,[[{3,4},{4,3}],[{10,4},{11,3}]]} = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,all,index}]),
+ match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,index}]),
+ match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,binary}]),
+ match = re:run("ABCabcdABCabcdA","a(?<FOO>bcd)",[global,{capture,none,list}]),
+ {match,[[<<195,133,98,99,100>>,<<"bcd">>],[<<"abcd">>,<<"bcd">>]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,binary},unicode]),
+ {match,[["Åbcd","bcd"],["abcd","bcd"]]} = re:run(<<"ABC",8#303,8#205,"bcdABCabcdA">>,".(?<FOO>bcd)",[global,{capture,all,list},unicode]),
+ {match,[["Åbcd","bcd"],["abcd","bcd"]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,list},unicode]),
+ {match,[[{3,5},{5,3}],[{11,4},{12,3}]]} = re:run("ABCÅbcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,index},unicode]),
ok.
%% Test replace with different input types.
replace_input_types(Config) when is_list(Config) ->
- ?line <<"abcd">> = re:replace("abcd","Z","X",[{return,binary},unicode]),
- ?line <<"abcd">> = re:replace("abcd","\x{400}","X",[{return,binary},unicode]),
- ?line <<"a",208,128,"cd">> = re:replace(<<"abcd">>,"b","\x{400}",[{return,binary},unicode]),
+ <<"abcd">> = re:replace("abcd","Z","X",[{return,binary},unicode]),
+ <<"abcd">> = re:replace("abcd","\x{400}","X",[{return,binary},unicode]),
+ <<"a",208,128,"cd">> = re:replace(<<"abcd">>,"b","\x{400}",[{return,binary},unicode]),
ok.
%% Test return options of replace together with global searching.
@@ -421,7 +421,7 @@ split_options(Config) when is_list(Config) ->
%% Parts 0 is equal to no parts specification (implicit strip)
ok = splittest("a b c d","( *)",[{parts,0},{return,list}],["a"," ","b"," ","c"," ","d"]),
ok.
-
+
join([]) -> [];
join([A]) -> [A];
join([H|T]) -> [H,<<":">>|join(T)].
@@ -429,12 +429,12 @@ join([H|T]) -> [H,<<":">>|join(T)].
%% Some special cases of split that are easy to get wrong.
split_specials(Config) when is_list(Config) ->
%% More or less just to remember these icky cases
- ?line <<"::abd:f">> =
+ <<"::abd:f">> =
iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[trim]))),
- ?line <<":abc2xyzabc3">> =
+ <<":abc2xyzabc3">> =
iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[trim]))),
ok.
-
+
%% Test that errors are handled correctly by the erlang code.
error_handling(_Config) ->
@@ -445,7 +445,7 @@ error_handling(_Config) ->
false ->
error_handling()
end.
-
+
error_handling() ->
%% This test checks the exception tuples manufactured in the erlang
%% code to hide the trapping from the user at least when it comes to errors
@@ -601,7 +601,7 @@ error_handling() ->
{?MODULE,error_handling,0,_} | _]}} =
(catch re:split("apa","(p",[banana])),
ok.
-
+
%% Fix as in http://vcs.pcre.org/viewvc?revision=360&view=revision
pcre_cve_2008_2371(Config) when is_list(Config) ->
%% Make sure it doesn't crash the emulator.
@@ -612,7 +612,7 @@ pcre_cve_2008_2371(Config) when is_list(Config) ->
%% http://vcs.pcre.org/viewvc/code/trunk/pcre_compile.c?r1=504&r2=505&view=patch
pcre_compile_workspace_overflow(Config) when is_list(Config) ->
N = 819,
- ?line {error,{"internal error: overran compiling workspace",799}} =
+ {error,{"internal error: overran compiling workspace",799}} =
re:compile([lists:duplicate(N, $(), lists:duplicate(N, $))]),
ok.
@@ -634,9 +634,9 @@ re_infinite_loop(Config) when is_list(Config) ->
%% Check for nasty bug where accented graphemes can make PCRE back
%% past beginning of subject.
re_backwards_accented(Config) when is_list(Config) ->
- ?line match = re:run(<<65,204,128,65,204,128,97,98,99>>,
- <<"\\X?abc">>,
- [unicode,{capture,none}]),
+ match = re:run(<<65,204,128,65,204,128,97,98,99>>,
+ <<"\\X?abc">>,
+ [unicode,{capture,none}]),
ok.
%% Check correct handling of dupnames option to re.
@@ -673,9 +673,9 @@ opt_dupnames(Config) when is_list(Config) ->
"(?<DN>Sat)(?:urday)?",
[dupnames, {capture, ['Skrap','DN','Skrap2'],index}]),
{match,[{-1,0},{0,3},{-1,0}]} = re:run("Wednesday","(?<Skrap>.)(?<DN>Mon|Fri|Sun)(?:day)?(?<Skrap2>.)|"
- "(?<DN>Tue)(?:sday)?|(?<DN>Wed)nesday|(?<DN>Thu)(?:rsday)?|"
- "(?<DN>Sat)(?:urday)?",
- [dupnames, {capture, ['Skrap','DN','Skrap2'],index}]),
+ "(?<DN>Tue)(?:sday)?|(?<DN>Wed)nesday|(?<DN>Thu)(?:rsday)?|"
+ "(?<DN>Sat)(?:urday)?",
+ [dupnames, {capture, ['Skrap','DN','Skrap2'],index}]),
nomatch = re:run("Wednsday","(?<Skrap>.)(?<DN>Mon|Fri|Sun)(?:day)?(?<Skrap2>.)|"
"(?<DN>Tue)(?:sday)?|(?<DN>Wed)nesday|(?<DN>Thu)(?:rsday)?|"
"(?<DN>Sat)(?:urday)?",
@@ -735,10 +735,10 @@ opt_all_names(Config) when is_list(Config) ->
"(?<DN>Sat)(?:urday)?",
[dupnames, {capture, all_names,index}]),
{match,[{0,3},{-1,0},{-1,0}]} = re:run("Wednesday","(?<Skrap>.)(?<DN>Mon|Fri|Sun)(?:day)?(?<Skrap2>.)|"
- "(?<DN>Tue)(?:sday)?|(?<DN>Wed)nesday|(?<DN>Thu)(?:rsday)?|"
- "(?<DN>Sat)(?:urday)?",
- [dupnames, {capture, all_names,index}]),
-
+ "(?<DN>Tue)(?:sday)?|(?<DN>Wed)nesday|(?<DN>Thu)(?:rsday)?|"
+ "(?<DN>Sat)(?:urday)?",
+ [dupnames, {capture, all_names,index}]),
+
_ = [ begin
{match,[{0,3}]} =
re:run(Day,
@@ -777,7 +777,7 @@ opt_all_names(Config) when is_list(Config) ->
{match,[[<<>>,<<>>,<<"C">>],
[<<>>,<<>>,<<"C">>],
[<<>>,<<>>,<<"C">>]]} = re:run("CCC","(?<A>A)|(?<B>B)|(?<C>C)",
- [global,{capture, all_names, binary}]),
+ [global,{capture, all_names, binary}]),
{match,[[<<"C">>,<<>>],
[<<>>,<<"B">>],
[<<"C">>,<<>>]]} = re:run("CBC","(?<A>A)|(?<B>B)|(?<A>C)",
@@ -837,7 +837,7 @@ opt_never_utf(Config) when is_list(Config) ->
opt_ucp(Config) when is_list(Config) ->
{match,[{0,1}]} = re:run([$a],"\\w",[unicode]),
{match,[{0,2}]} = re:run([229],"\\w",[unicode]), % Latin1 works without UCP, as we have a default
- %% Latin1 table
+ %% Latin1 table
nomatch = re:run([1024],"\\w",[unicode]), % Latin1 word characters only, 1024 is not latin1
{match,[{0,2}]} = re:run([1024],"\\w",[unicode,ucp]), % Any Unicode word character works with 'ucp'
ok.
@@ -849,12 +849,12 @@ match_limit(Config) when is_list(Config) ->
nomatch = re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit_recursion,10}]),
nomatch = re:run("aaaaaaaaaaaaaz","(a+)*zz",[report_errors]),
{error,match_limit} = re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit,3000},
- report_errors]),
+ report_errors]),
{error,match_limit_recursion} =
re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit_recursion,10},
report_errors]),
{error,match_limit} = re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit,3000},
- report_errors,global]),
+ report_errors,global]),
{error,match_limit_recursion} =
re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit_recursion,10},
report_errors,global]),
@@ -867,9 +867,9 @@ match_limit(Config) when is_list(Config) ->
"aaaaaaaaaaaaaz" = re:replace("aaaaaaaaaaaaaz","(a+)*zz","!",
[{match_limit,3000},{return,list}]),
{'EXIT', {badarg,_}} = (catch re:replace("aaaaaaaaaaaaaz","(a+)*zz","!",
- [{match_limit_recursion,-1},{return,list}])),
+ [{match_limit_recursion,-1},{return,list}])),
{'EXIT', {badarg,_}} = (catch re:replace("aaaaaaaaaaaaaz","(a+)*zz","!",
- [{match_limit,-1},{return,list}])),
+ [{match_limit,-1},{return,list}])),
{'EXIT', {badarg,_}} = (catch re:run("aaaaaaaaaaaaaz","(a+)*zz",
[{match_limit_recursion,-1},
report_errors,global])),
diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl
index 298026ad38..50a9ec9709 100644
--- a/lib/stdlib/test/select_SUITE.erl
+++ b/lib/stdlib/test/select_SUITE.erl
@@ -27,12 +27,12 @@
%% Define to run outside of test server
%%
%%-define(STANDALONE,1).
-
+
%%
%% Define for debug output
%%
%%-define(debug,1).
-
+
-ifdef(STANDALONE).
-define(config(A,B),config(A,B)).
-export([config/2]).
@@ -41,7 +41,7 @@
-endif.
-define(fmt(A,B), io:format(A, B)).
-
+
-ifdef(debug).
-ifdef(STANDALONE).
-define(line, erlang:display({?MODULE,?LINE}), ).
@@ -53,7 +53,7 @@
-endif.
-define(dbgformat(A,B),noop).
-endif.
-
+
-ifdef(STANDALONE).
config(priv_dir,_) ->
".".
@@ -121,15 +121,15 @@ create_tables(Config) ->
F1 = gen_dets_filename(Config,1),
(catch file:delete(F1)),
{ok,DetsPlain} = dets:open_file(testdets_1,
- [{file, F1}]),
+ [{file, F1}]),
F3 = gen_dets_filename(Config,3),
(catch file:delete(F3)),
{ok,DetsBag} = dets:open_file(testdets_3,
- [{file, F3},{type, bag}]),
+ [{file, F3},{type, bag}]),
F4 = gen_dets_filename(Config,4),
(catch file:delete(F4)),
{ok,DetsDBag} = dets:open_file(testdets_4,
- [{file, F4},{type, duplicate_bag}]),
+ [{file, F4},{type, duplicate_bag}]),
[{ets,Hash}, {ets,Tree}, {ets,Bag}, {ets,DBag},
{dets, DetsPlain}, {dets, DetsBag}, {dets, DetsDBag}].
@@ -182,7 +182,7 @@ build_tables(Config,Type) ->
L = create_tables(Config),
?dbgformat("Tables: ~p~n",[L]),
lists:foreach(fun(TD) ->
- fill_table(TD,table_size(TD),Type)
+ fill_table(TD,table_size(TD),Type)
end,
L),
L.
@@ -195,7 +195,7 @@ destroy_tables([{ets,Tab}|T]) ->
destroy_tables([{dets,Tab}|T]) ->
dets:close(Tab),
destroy_tables(T).
-
+
init_random(Config) ->
WriteDir = ReadDir = ?config(priv_dir,Config),
@@ -222,7 +222,7 @@ create_pb_key(N,list) ->
X = rand:uniform(N),
case rand:uniform(4) of
3 -> {[X, X+1, '_'], fun([Z,Z1,P1]) ->
- [Z,Z1,P1] =:= [X,X+1,P1] end};
+ [Z,Z1,P1] =:= [X,X+1,P1] end};
2 -> {[X, '_', '_'], fun([Z,P1,P2]) -> [Z,P1,P2] =:= [X,P1,P2] end};
1 -> {[X, X+1, '$1'], fun([Z,Z1,P1]) ->
[Z,Z1,P1] =:= [X,X+1,P1] end};
@@ -302,7 +302,7 @@ cmp_ms_to_fun({Mod,Tab}, MS, Fun1, Fun2, ChunkSize) ->
false ->
?fmt("Match_spec result differs from fun result:~n",[]),
?fmt("Parameters: ~p,~p,~p,~p~n",
- [{Mod,Tab}, MS, Fun1, Fun2]),
+ [{Mod,Tab}, MS, Fun1, Fun2]),
?fmt("Match_spec Result: ~p~n", [MSRes]),
?fmt("Fun Result: ~p~n", [FunRes]),
Info = (catch Mod:info(Tab)),
@@ -344,18 +344,18 @@ do_test(Config) ->
?fmt("multi_key done for type ~w~n",[Type]),
multi_mixed_key(Tabs,Type),
?fmt("multi_mixed_key done for type ~w~n",
- [Type]),
+ [Type]),
destroy_tables(Tabs)
end,
[tuple, list, complex]),
ok.
-
+
basic_key(Tabs,Type) ->
Fun = fun() ->
lists:map(fun(Tab) ->
- ?line Key =
+ Key =
create_random_key(num_els(Tab),Type),
- ?line MS =
+ MS =
[{{Key,'_','_','_','_'},[],['$_']}],
MF = fun({Key0,A,B,F,Bi},Acc) ->
case Key =:= Key0 of
@@ -366,18 +366,18 @@ basic_key(Tabs,Type) ->
Acc
end
end,
- ?line cmp_ms_to_fun(Tab,MS,MF,[])
+ cmp_ms_to_fun(Tab,MS,MF,[])
end,
Tabs)
end,
- ?line do_n(50,Fun),
+ do_n(50,Fun),
ok.
-
+
basic_pb_key(Tabs,Type) ->
InnerFun = fun(Tab) ->
- ?line {Key,KeyFun} =
+ {Key,KeyFun} =
create_pb_key(num_els(Tab),Type),
- ?line MS = [{{Key,'_','_','_','_'},[],['$_']}],
+ MS = [{{Key,'_','_','_','_'},[],['$_']}],
MF = fun({Key0,A,B,F,Bi},Acc) ->
case KeyFun(Key0) of
true ->
@@ -387,27 +387,27 @@ basic_pb_key(Tabs,Type) ->
Acc
end
end,
- ?line cmp_ms_to_fun(Tab,MS,MF,[])
+ cmp_ms_to_fun(Tab,MS,MF,[])
end,
- ?line {Etses, Detses} = split_by_type(Tabs),
-
- ?line FunEts = fun() ->
- ?line lists:foreach(InnerFun,
- Etses)
- end,
- ?line FunDets = fun() ->
- ?line lists:foreach(InnerFun,
- Detses)
- end,
- ?line do_n(table_factor(hd(Etses)) div 2,FunEts),
- ?line do_n(10,FunDets),
+ {Etses, Detses} = split_by_type(Tabs),
+
+ FunEts = fun() ->
+ lists:foreach(InnerFun,
+ Etses)
+ end,
+ FunDets = fun() ->
+ lists:foreach(InnerFun,
+ Detses)
+ end,
+ do_n(table_factor(hd(Etses)) div 2,FunEts),
+ do_n(10,FunDets),
ok.
-
+
double_pb_key(Tabs,Type) ->
InnerFun = fun(Tab) ->
- ?line {KeyA,KeyFunA} =
+ {KeyA,KeyFunA} =
create_pb_key(num_els(Tab),Type),
- ?line {KeyB,KeyFunB} =
+ {KeyB,KeyFunB} =
create_pb_key(num_els(Tab),Type),
MS = [{{KeyA,'_','_','_','_'},[],['$_']},
{{KeyB,'_','_','_','_'},[],['$_']}],
@@ -441,51 +441,51 @@ double_pb_key(Tabs,Type) ->
end
end
end,
- ?line cmp_ms_to_fun(Tab,MS,MF,[])
+ cmp_ms_to_fun(Tab,MS,MF,[])
end,
- ?line {Etses, Detses} = split_by_type(Tabs),
-
- ?line FunEts = fun() ->
- ?line lists:foreach(InnerFun,
- Etses)
- end,
- ?line FunDets = fun() ->
- ?line lists:foreach(InnerFun,
- Detses)
- end,
- ?line do_n(table_factor(hd(Etses)) div 2,FunEts),
- ?line do_n(10,FunDets),
+ {Etses, Detses} = split_by_type(Tabs),
+
+ FunEts = fun() ->
+ lists:foreach(InnerFun,
+ Etses)
+ end,
+ FunDets = fun() ->
+ lists:foreach(InnerFun,
+ Detses)
+ end,
+ do_n(table_factor(hd(Etses)) div 2,FunEts),
+ do_n(10,FunDets),
ok.
-
-
+
+
multi_key(Tabs,Type) ->
Fun = fun() ->
lists:map(fun(Tab) ->
- ?line KeyA =
+ KeyA =
create_random_key(num_els(Tab),Type),
- ?line KeyB =
+ KeyB =
create_random_key(num_els(Tab),Type),
- ?line KeyC =
+ KeyC =
create_random_key(num_els(Tab),Type),
- ?line KeyD =
+ KeyD =
create_random_key(num_els(Tab),Type),
- ?line KeyE =
+ KeyE =
create_random_key(num_els(Tab),Type),
- ?line KeyF =
+ KeyF =
create_random_key(num_els(Tab),Type),
- ?line KeyG =
+ KeyG =
create_random_key(num_els(Tab),Type),
- ?line KeyH =
+ KeyH =
create_random_key(num_els(Tab),Type),
- ?line KeyI =
+ KeyI =
create_random_key(num_els(Tab),Type),
- ?line KeyJ =
+ KeyJ =
create_random_key(num_els(Tab),Type),
- ?line KeyK =
+ KeyK =
create_random_key(num_els(Tab),Type),
- ?line KeyL =
+ KeyL =
create_random_key(num_els(Tab),Type),
-
+
MS = [{{KeyA,'$1','_','$2','_'},[],
[{{'$1','$2'}}]},
{{KeyB,'$1','_','$2','_'},[],
@@ -512,7 +512,7 @@ multi_key(Tabs,Type) ->
[{{'$1','$2'}}]}
],
?dbgformat("Tab: ~p, MS: ~p~n",
- [Tab,MS]),
+ [Tab,MS]),
MF = fun({Key0,A,_B,F,_Bi},Acc) ->
case Key0 of
KeyA ->
@@ -555,40 +555,40 @@ multi_key(Tabs,Type) ->
Acc
end
end,
- ?line cmp_ms_to_fun(Tab,MS,MF,[])
+ cmp_ms_to_fun(Tab,MS,MF,[])
end,
Tabs)
end,
- ?line do_n(33,Fun),
+ do_n(33,Fun),
ok.
-
+
multi_mixed_key(Tabs,Type) ->
InnerFun = fun(Tab) ->
- ?line KeyA =
+ KeyA =
create_random_key(num_els(Tab),Type),
- ?line KeyB =
+ KeyB =
create_random_key(num_els(Tab),Type),
- ?line KeyC =
+ KeyC =
create_random_key(num_els(Tab),Type),
- ?line KeyD =
+ KeyD =
create_random_key(num_els(Tab),Type),
- ?line {KeyE, FunE} =
+ {KeyE, FunE} =
create_pb_key(num_els(Tab),Type),
- ?line KeyF =
+ KeyF =
create_random_key(num_els(Tab),Type),
- ?line {KeyG, FunG} =
+ {KeyG, FunG} =
create_pb_key(num_els(Tab),Type),
- ?line KeyH =
+ KeyH =
create_random_key(num_els(Tab),Type),
- ?line KeyI =
+ KeyI =
create_random_key(num_els(Tab),Type),
- ?line {KeyJ, FunJ} =
+ {KeyJ, FunJ} =
create_pb_key(num_els(Tab),Type),
- ?line KeyK =
+ KeyK =
create_random_key(num_els(Tab),Type),
- ?line KeyL =
+ KeyL =
create_random_key(num_els(Tab),Type),
-
+
MS = [{{KeyA,'$1','_','$2','_'},[],
[{{'$1','$2'}}]},
{{KeyB,'$1','_','$2','_'},[],
@@ -657,34 +657,34 @@ multi_mixed_key(Tabs,Type) ->
end
end
end,
- ?line cmp_ms_to_fun(Tab,MS,MF,[]),
- ?line case Tab of
- {ets,_} ->
- ?line cmp_ms_to_fun(Tab,MS,MF,[],1),
- ?line cmp_ms_to_fun(Tab,MS,MF,[],10),
- ?line cmp_ms_to_fun(Tab,MS,MF,[],1000000),
- ?line cmp_ms_to_fun(Tab,MS,MF,[],-1),
- ?line cmp_ms_to_fun(Tab,MS,MF,[],-10),
- ?line cmp_ms_to_fun(Tab,MS,MF,[],-1000000);
- _ ->
- ok
- end
+ cmp_ms_to_fun(Tab,MS,MF,[]),
+ case Tab of
+ {ets,_} ->
+ cmp_ms_to_fun(Tab,MS,MF,[],1),
+ cmp_ms_to_fun(Tab,MS,MF,[],10),
+ cmp_ms_to_fun(Tab,MS,MF,[],1000000),
+ cmp_ms_to_fun(Tab,MS,MF,[],-1),
+ cmp_ms_to_fun(Tab,MS,MF,[],-10),
+ cmp_ms_to_fun(Tab,MS,MF,[],-1000000);
+ _ ->
+ ok
+ end
end,
- ?line {Etses, Detses} = split_by_type(Tabs),
-
- ?line FunEts = fun() ->
- ?line lists:foreach(InnerFun,
- Etses)
- end,
- ?line FunDets = fun() ->
- ?line lists:foreach(InnerFun,
- Detses)
- end,
- ?line do_n(table_factor(hd(Etses)) div 2,FunEts),
- ?line do_n(table_factor(hd(Detses)) div 2,FunDets),
+ {Etses, Detses} = split_by_type(Tabs),
+
+ FunEts = fun() ->
+ lists:foreach(InnerFun,
+ Etses)
+ end,
+ FunDets = fun() ->
+ lists:foreach(InnerFun,
+ Detses)
+ end,
+ do_n(table_factor(hd(Etses)) div 2,FunEts),
+ do_n(table_factor(hd(Detses)) div 2,FunDets),
ok.
-
-
+
+
split_by_type(List) ->
split_by_type(List,[],[]).
split_by_type([],AccEts,AccDets) ->
@@ -695,121 +695,119 @@ split_by_type([{ets,Tab}|T],AccEts,AccDets) ->
split_by_type(T,[{ets,Tab}|AccEts],AccDets).
whitebox() ->
- ?line ets:new(xxx,[named_table, ordered_set]),
- ?line ets:new(yyy,[named_table]),
- ?line E = fun(0,_)->ok;
- (N,F) ->
- ?line ets:insert(xxx,{N,N rem 10}),
- ?line ets:insert(yyy,{N,N rem 10}),
- F(N-1,F)
- end,
- ?line E(10000,E),
-
- ?line G = fun(F,C,A) ->
- ?line case ets:select(C) of
- {L,C2} ->
- ?line F(F,C2,A+length(L));
- '$end_of_table' ->
- ?line A
- end
- end,
- ?line H=fun({L,C}) ->
- ?line G(G,C,length(L))
- end,
-
- ?line 1 = H(ets:select(xxx,[{{'$1','$2'},[{'<','$1',2}],['$_']}],7)),
- ?line 10000 = H(ets:select(xxx,[{{'$1','$2'},[],['$_']}],1)),
- ?line 1 = H(ets:select(yyy,[{{'$1','$2'},[{'<','$1',2}],['$_']}],7)),
- ?line 10000 = H(ets:select(yyy,[{{'$1','$2'},[],['$_']}],1)),
-
- ?line {[{5,5}],_} = ets:select(xxx,[{{5,'$2'},[],['$_']}],1),
- ?line {[{5,5}],_} = ets:select(yyy,[{{5,'$2'},[],['$_']}],1),
-
- ?line I = fun(_,0) ->
- ok;
- (I,N) ->
- ?line 10000 =
- H(ets:select(xxx,[{{'$1','$2'},[],['$_']}],N)),
- I(I,N-1)
- end,
- ?line I(I,2000),
- ?line J = fun(F,C,A) ->
- ?line case ets:select(C) of
- {L,C2} ->
- ?line F(F,C2,lists:reverse(L)++A);
- '$end_of_table' ->
- ?line lists:reverse(A)
- end
- end,
- ?line K = fun({L,C}) ->
- ?line J(J,C,lists:reverse(L))
- end,
- ?line M = fun(_, _, 0) ->
- ok;
- (F, What, N) ->
- ?line What =
- K(ets:select(xxx,[{{'$1','$2'},[],['$_']}],N)),
- F(F, What, N-1)
- end,
- ?line N = fun(HM) ->
- ?line What = ets:select(xxx,[{{'$1','$2'},[],['$_']}]),
- ?line What = lists:sort(What),
- M(M, What, HM)
- end,
- ?line N(2000),
- ?line ets:delete(xxx),
- ?line ets:delete(yyy).
+ ets:new(xxx,[named_table, ordered_set]),
+ ets:new(yyy,[named_table]),
+ E = fun(0,_)->ok;
+ (N,F) ->
+ ets:insert(xxx,{N,N rem 10}),
+ ets:insert(yyy,{N,N rem 10}),
+ F(N-1,F)
+ end,
+ E(10000,E),
+
+ G = fun(F,C,A) ->
+ case ets:select(C) of
+ {L,C2} ->
+ F(F,C2,A+length(L));
+ '$end_of_table' ->
+ A
+ end
+ end,
+ H=fun({L,C}) ->
+ G(G,C,length(L))
+ end,
+
+ 1 = H(ets:select(xxx,[{{'$1','$2'},[{'<','$1',2}],['$_']}],7)),
+ 10000 = H(ets:select(xxx,[{{'$1','$2'},[],['$_']}],1)),
+ 1 = H(ets:select(yyy,[{{'$1','$2'},[{'<','$1',2}],['$_']}],7)),
+ 10000 = H(ets:select(yyy,[{{'$1','$2'},[],['$_']}],1)),
+
+ {[{5,5}],_} = ets:select(xxx,[{{5,'$2'},[],['$_']}],1),
+ {[{5,5}],_} = ets:select(yyy,[{{5,'$2'},[],['$_']}],1),
+
+ I = fun(_,0) ->
+ ok;
+ (I,N) ->
+ 10000 =
+ H(ets:select(xxx,[{{'$1','$2'},[],['$_']}],N)),
+ I(I,N-1)
+ end,
+ I(I,2000),
+ J = fun(F,C,A) ->
+ case ets:select(C) of
+ {L,C2} ->
+ F(F,C2,lists:reverse(L)++A);
+ '$end_of_table' ->
+ lists:reverse(A)
+ end
+ end,
+ K = fun({L,C}) ->
+ J(J,C,lists:reverse(L))
+ end,
+ M = fun(_, _, 0) ->
+ ok;
+ (F, What, N) ->
+ What =
+ K(ets:select(xxx,[{{'$1','$2'},[],['$_']}],N)),
+ F(F, What, N-1)
+ end,
+ N = fun(HM) ->
+ What = ets:select(xxx,[{{'$1','$2'},[],['$_']}]),
+ What = lists:sort(What),
+ M(M, What, HM)
+ end,
+ N(2000),
+ ets:delete(xxx),
+ ets:delete(yyy).
do_return_values() ->
- ?line T = ets:new(xxx,[ordered_set]),
- ?line U = ets:new(xxx,[]),
- ?line '$end_of_table' = ets:select(T,[{'_',[],['$_']}],1),
- ?line '$end_of_table' = ets:select(U,[{'_',[],['$_']}],1),
- ?line ets:insert(T,{ett,1}),
- ?line ets:insert(U,{ett,1}),
- ?line {[{ett,1}],C1} = ets:select(T,[{'_',[],['$_']}],1),
- ?line '$end_of_table' = ets:select(C1),
- ?line {[{ett,1}],C2} = ets:select(U,[{'_',[],['$_']}],1),
- ?line '$end_of_table' = ets:select(C2),
- ?line {[{ett,1}],C3} = ets:select(T,[{'_',[],['$_']}],2),
- ?line '$end_of_table' = ets:select(C3),
- ?line {[{ett,1}],C4} = ets:select(U,[{'_',[],['$_']}],2),
- ?line '$end_of_table' = ets:select(C4),
- ?line E = fun(0,_)->ok;
- (N,F) ->
- ?line ets:insert(T,{N,N rem 10}),
- ?line ets:insert(U,{N,N rem 10}),
- F(N-1,F)
- end,
- ?line E(10000,E),
- ?line '$end_of_table' = ets:select(T,[{{hej, hopp},[],['$_']}],1),
- ?line '$end_of_table' = ets:select(U,[{{hej,hopp},[],['$_']}],1),
- ?line {[{ett,1}],CC1} = ets:select(T,[{{'$1','_'},[{is_atom, '$1'}],
- ['$_']}],1),
- ?line '$end_of_table' = ets:select(CC1),
- ?line {[{ett,1}],CC2} = ets:select(U,[{{'$1','_'},[{is_atom, '$1'}],
- ['$_']}],1),
- ?line '$end_of_table' = ets:select(CC2),
- ?line {[{ett,1}],CC3} = ets:select(T,[{{'$1','_'},[{is_atom, '$1'}],
- ['$_']}],2),
- ?line '$end_of_table' = ets:select(CC3),
- ?line {[{ett,1}],CC4} = ets:select(U,[{{'$1','_'},[{is_atom, '$1'}],
- ['$_']}],2),
- ?line '$end_of_table' = ets:select(CC4),
- ?line ets:delete(T),
- ?line ets:delete(U),
- ?line V = ets:new(xxx,[{keypos, 4}]),
- ?line X = ets:new(xxx,[ordered_set, {keypos, 4}]),
- ?line ets:insert(V,{1,1,1,ett}),
- ?line ets:insert(X,{1,1,1,ett}),
- ?line '$end_of_table' = ets:select(V,[{{1,1,1},[],['$_']}],1),
- ?line '$end_of_table' = ets:select(X,[{{1,1,1},[],['$_']}],1),
- ?line ets:delete(V),
- ?line ets:delete(X),
+ T = ets:new(xxx,[ordered_set]),
+ U = ets:new(xxx,[]),
+ '$end_of_table' = ets:select(T,[{'_',[],['$_']}],1),
+ '$end_of_table' = ets:select(U,[{'_',[],['$_']}],1),
+ ets:insert(T,{ett,1}),
+ ets:insert(U,{ett,1}),
+ {[{ett,1}],C1} = ets:select(T,[{'_',[],['$_']}],1),
+ '$end_of_table' = ets:select(C1),
+ {[{ett,1}],C2} = ets:select(U,[{'_',[],['$_']}],1),
+ '$end_of_table' = ets:select(C2),
+ {[{ett,1}],C3} = ets:select(T,[{'_',[],['$_']}],2),
+ '$end_of_table' = ets:select(C3),
+ {[{ett,1}],C4} = ets:select(U,[{'_',[],['$_']}],2),
+ '$end_of_table' = ets:select(C4),
+ E = fun(0,_)->ok;
+ (N,F) ->
+ ets:insert(T,{N,N rem 10}),
+ ets:insert(U,{N,N rem 10}),
+ F(N-1,F)
+ end,
+ E(10000,E),
+ '$end_of_table' = ets:select(T,[{{hej, hopp},[],['$_']}],1),
+ '$end_of_table' = ets:select(U,[{{hej,hopp},[],['$_']}],1),
+ {[{ett,1}],CC1} = ets:select(T,[{{'$1','_'},[{is_atom, '$1'}],
+ ['$_']}],1),
+ '$end_of_table' = ets:select(CC1),
+ {[{ett,1}],CC2} = ets:select(U,[{{'$1','_'},[{is_atom, '$1'}],
+ ['$_']}],1),
+ '$end_of_table' = ets:select(CC2),
+ {[{ett,1}],CC3} = ets:select(T,[{{'$1','_'},[{is_atom, '$1'}],
+ ['$_']}],2),
+ '$end_of_table' = ets:select(CC3),
+ {[{ett,1}],CC4} = ets:select(U,[{{'$1','_'},[{is_atom, '$1'}],
+ ['$_']}],2),
+ '$end_of_table' = ets:select(CC4),
+ ets:delete(T),
+ ets:delete(U),
+ V = ets:new(xxx,[{keypos, 4}]),
+ X = ets:new(xxx,[ordered_set, {keypos, 4}]),
+ ets:insert(V,{1,1,1,ett}),
+ ets:insert(X,{1,1,1,ett}),
+ '$end_of_table' = ets:select(V,[{{1,1,1},[],['$_']}],1),
+ '$end_of_table' = ets:select(X,[{{1,1,1},[],['$_']}],1),
+ ets:delete(V),
+ ets:delete(X),
ok.
-
-
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index b5e21f0143..14b01a4109 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -55,16 +55,16 @@ config(priv_dir,_) ->
-include_lib("common_test/include/ct.hrl").
-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_Case, Config) ->
- ?line OrigPath = code:get_path(),
- ?line code:add_patha(?config(priv_dir,Config)),
+ OrigPath = code:get_path(),
+ code:add_patha(?config(priv_dir,Config)),
[{orig_path,OrigPath} | Config].
end_per_testcase(_Case, Config) ->
- ?line OrigPath = ?config(orig_path,Config),
- ?line code:set_path(OrigPath),
- ?line application:unset_env(stdlib, restricted_shell),
- ?line (catch code:purge(user_default)),
- ?line (catch code:delete(user_default)),
+ OrigPath = ?config(orig_path,Config),
+ code:set_path(OrigPath),
+ application:unset_env(stdlib, restricted_shell),
+ (catch code:purge(user_default)),
+ (catch code:delete(user_default)),
ok.
-endif.
@@ -111,93 +111,93 @@ end_per_group(_GroupName, Config) ->
%% Test that a restricted shell can be started from the normal shell.
start_restricted_from_shell(Config) when is_list(Config) ->
- ?line [{error,nofile}] = scan(<<"begin shell:start_restricted("
- "nonexisting_module) end.">>),
- ?line Test = filename:join(?config(priv_dir, Config),
- "test_restricted.erl"),
+ [{error,nofile}] = scan(<<"begin shell:start_restricted("
+ "nonexisting_module) end.">>),
+ Test = filename:join(?config(priv_dir, Config),
+ "test_restricted.erl"),
Contents = <<"-module(test_restricted).
-export([local_allowed/3, non_local_allowed/3]).
- local_allowed(m,[],State) ->
- {true,State};
- local_allowed(ugly,[],_State) ->
- non_conforming_reply;
- local_allowed(_,_,State) ->
- {false,State}.
-
- non_local_allowed({shell,stop_restricted},[],State) ->
- {true,State};
- non_local_allowed({erlang,'+'},[_],State) ->
- {true,State};
- non_local_allowed({erlang,'-'},[_,_],_State) ->
- non_conforming_reply;
- non_local_allowed({h, d}, [Arg], S) ->
- {{redirect, {erlang,hd}, [Arg]}, S};
- non_local_allowed(_,_,State) ->
- {false,State}.
- ">>,
- ?line ok = compile_file(Config, Test, Contents, []),
- ?line "exception exit: restricted shell starts now" =
- comm_err(<<"begin shell:start_restricted("
- "test_restricted) end.">>),
- ?line {ok, test_restricted} =
- application:get_env(stdlib, restricted_shell),
- ?line "Module" ++ _ = t({<<"begin m() end.">>, utf8}),
- ?line "exception exit: restricted shell does not allow c(foo)" =
- comm_err(<<"begin c(foo) end.">>),
- ?line "exception exit: restricted shell does not allow init:stop()" =
- comm_err(<<"begin init:stop() end.">>),
- ?line "exception exit: restricted shell does not allow init:stop()" =
- comm_err(<<"begin F = fun() -> init:stop() end, F() end.">>),
- ?line "exception error: an error occurred when evaluating an arithmetic expression" =
- comm_err(<<"begin +a end.">>),
- ?line "exception exit: restricted shell does not allow a + b" =
- comm_err(<<"begin a+b end.">>),
- ?line "exception exit: restricted shell does not allow - b" =
- comm_err(<<"begin -b end.">>),
- ?line "exception exit: restricted shell does not allow 1 + 2" =
- comm_err(<<"begin if atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow 1 + 2" =
- comm_err(<<"begin if is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow - 2" =
- comm_err(<<"begin if - 2 -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow - 2" =
- comm_err(<<"begin if (- 2 > 0) andalso true -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow - 2" =
- comm_err(<<"begin if (- 2 > 0) orelse true -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow 1 + 2" =
- comm_err(<<"begin if 1 + 2 > 0 -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow 1 + 2" =
- comm_err(<<"begin if erlang:is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow is_integer(1)" =
- comm_err(<<"begin if is_integer(1) -> 1; true -> 2 end end.">>),
- ?line "exception exit: restricted shell does not allow is_integer(1)" =
- comm_err(<<"begin if integer(1) -> 1; true -> 2 end end.">>),
- ?line "exception exit: "
- "restricted shell module returned bad value non_conforming_reply" =
- comm_err(<<"ugly().">>),
- ?line [one] = scan(<<"h:d([one,two]).">>),
- ?line "exception exit: "
- "restricted shell module returned bad value non_conforming_reply" =
- comm_err(<<"1 - 2.">>),
- ?line "exception exit: restricted shell stopped"=
- comm_err(<<"begin shell:stop_restricted() end.">>),
- ?line undefined =
- application:get_env(stdlib, restricted_shell),
- ok.
+local_allowed(m,[],State) ->
+ {true,State};
+local_allowed(ugly,[],_State) ->
+ non_conforming_reply;
+local_allowed(_,_,State) ->
+ {false,State}.
+
+non_local_allowed({shell,stop_restricted},[],State) ->
+ {true,State};
+non_local_allowed({erlang,'+'},[_],State) ->
+ {true,State};
+non_local_allowed({erlang,'-'},[_,_],_State) ->
+ non_conforming_reply;
+non_local_allowed({h, d}, [Arg], S) ->
+ {{redirect, {erlang,hd}, [Arg]}, S};
+non_local_allowed(_,_,State) ->
+ {false,State}.
+">>,
+ ok = compile_file(Config, Test, Contents, []),
+"exception exit: restricted shell starts now" =
+comm_err(<<"begin shell:start_restricted("
+ "test_restricted) end.">>),
+{ok, test_restricted} =
+application:get_env(stdlib, restricted_shell),
+"Module" ++ _ = t({<<"begin m() end.">>, utf8}),
+"exception exit: restricted shell does not allow c(foo)" =
+comm_err(<<"begin c(foo) end.">>),
+"exception exit: restricted shell does not allow init:stop()" =
+comm_err(<<"begin init:stop() end.">>),
+"exception exit: restricted shell does not allow init:stop()" =
+comm_err(<<"begin F = fun() -> init:stop() end, F() end.">>),
+"exception error: an error occurred when evaluating an arithmetic expression" =
+comm_err(<<"begin +a end.">>),
+"exception exit: restricted shell does not allow a + b" =
+comm_err(<<"begin a+b end.">>),
+"exception exit: restricted shell does not allow - b" =
+comm_err(<<"begin -b end.">>),
+"exception exit: restricted shell does not allow 1 + 2" =
+comm_err(<<"begin if atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow 1 + 2" =
+comm_err(<<"begin if is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow - 2" =
+comm_err(<<"begin if - 2 -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow - 2" =
+comm_err(<<"begin if (- 2 > 0) andalso true -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow - 2" =
+comm_err(<<"begin if (- 2 > 0) orelse true -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow 1 + 2" =
+comm_err(<<"begin if 1 + 2 > 0 -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow 1 + 2" =
+comm_err(<<"begin if erlang:is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow is_integer(1)" =
+comm_err(<<"begin if is_integer(1) -> 1; true -> 2 end end.">>),
+"exception exit: restricted shell does not allow is_integer(1)" =
+comm_err(<<"begin if integer(1) -> 1; true -> 2 end end.">>),
+"exception exit: "
+"restricted shell module returned bad value non_conforming_reply" =
+comm_err(<<"ugly().">>),
+[one] = scan(<<"h:d([one,two]).">>),
+"exception exit: "
+"restricted shell module returned bad value non_conforming_reply" =
+comm_err(<<"1 - 2.">>),
+"exception exit: restricted shell stopped"=
+comm_err(<<"begin shell:stop_restricted() end.">>),
+undefined =
+application:get_env(stdlib, restricted_shell),
+ok.
%% Check restricted shell when started from the command line.
start_restricted_on_command_line(Config) when is_list(Config) ->
- ?line {ok,Node} = start_node(shell_suite_helper_1,
- "-pa "++?config(priv_dir,Config)++
- " -stdlib restricted_shell foo"),
- ?line "Warning! Restricted shell module foo not found: nofile"++_ =
+ {ok,Node} = start_node(shell_suite_helper_1,
+ "-pa "++?config(priv_dir,Config)++
+ " -stdlib restricted_shell foo"),
+ "Warning! Restricted shell module foo not found: nofile"++_ =
t({Node, <<"begin m() end.">>}),
- ?line "exception exit: restricted shell does not allow m()" =
+ "exception exit: restricted shell does not allow m()" =
comm_err({Node, <<"begin m() end.">>}),
- ?line [ok] =
+ [ok] =
(catch scan({Node, <<"begin q() end.">>})),
- ?line test_server:stop_node(Node),
- ?line Test = filename:join(?config(priv_dir, Config),
+ test_server:stop_node(Node),
+ Test = filename:join(?config(priv_dir, Config),
"test_restricted2.erl"),
Contents = <<"-module(test_restricted2).
-export([local_allowed/3, non_local_allowed/3]).
@@ -213,34 +213,34 @@ start_restricted_on_command_line(Config) when is_list(Config) ->
non_local_allowed(_,_,State) ->
{false,State}.
">>,
- ?line ok = compile_file(Config, Test, Contents, []),
- ?line {ok,Node2} = start_node(shell_suite_helper_2,
+ ok = compile_file(Config, Test, Contents, []),
+ {ok,Node2} = start_node(shell_suite_helper_2,
"-pa "++?config(priv_dir,Config)++
" -stdlib restricted_shell test_restricted2"),
- ?line "Module" ++ _ = t({Node2,<<"begin m() end.">>, utf8}),
- ?line "exception exit: restricted shell does not allow c(foo)" =
+ "Module" ++ _ = t({Node2,<<"begin m() end.">>, utf8}),
+ "exception exit: restricted shell does not allow c(foo)" =
comm_err({Node2,<<"begin c(foo) end.">>}),
- ?line "exception exit: restricted shell does not allow init:stop()" =
+ "exception exit: restricted shell does not allow init:stop()" =
comm_err({Node2,<<"begin init:stop() end.">>}),
- ?line "exception exit: restricted shell does not allow init:stop()" =
+ "exception exit: restricted shell does not allow init:stop()" =
comm_err({Node2,<<"begin F = fun() -> init:stop() end, F() end.">>}),
- ?line [Node2] =
+ [Node2] =
scan({Node2, <<"begin erlang:node() end.">>}),
- ?line [Node2] =
+ [Node2] =
scan({Node2, <<"begin node() end.">>}),
- ?line "exception exit: restricted shell stopped"=
+ "exception exit: restricted shell stopped"=
comm_err({Node2,<<"begin shell:stop_restricted() end.">>}),
- ?line [ok] =
+ [ok] =
scan({Node2, <<"begin q() end.">>}),
- ?line test_server:stop_node(Node2),
+ test_server:stop_node(Node2),
ok.
%% Tests calling local shell functions with spectacular arguments in
%% restricted shell.
restricted_local(Config) when is_list(Config) ->
- ?line [{error,nofile}] = scan(<<"begin shell:start_restricted("
+ [{error,nofile}] = scan(<<"begin shell:start_restricted("
"nonexisting_module) end.">>),
- ?line Test = filename:join(?config(priv_dir, Config),
+ Test = filename:join(?config(priv_dir, Config),
"test_restricted_local.erl"),
Contents = <<"-module(test_restricted_local).
-export([local_allowed/3, non_local_allowed/3]).
@@ -260,8 +260,8 @@ restricted_local(Config) when is_list(Config) ->
non_local_allowed(_,_,State) ->
{false,State}.
">>,
- ?line ok = compile_file(Config, Test, Contents, []),
- ?line Test2 = filename:join(?config(priv_dir, Config),
+ ok = compile_file(Config, Test, Contents, []),
+ Test2 = filename:join(?config(priv_dir, Config),
"user_default.erl"),
Contents2 = <<"-module(user_default).
-export([funkis/1,apple/1]).
@@ -272,107 +272,107 @@ restricted_local(Config) when is_list(Config) ->
apple(_) ->
apple.
">>,
- ?line ok = compile_file(Config, Test2, Contents2, []),
- ?line "exception exit: restricted shell starts now" =
+ ok = compile_file(Config, Test2, Contents2, []),
+ "exception exit: restricted shell starts now" =
comm_err(<<"begin shell:start_restricted("
"test_restricted_local) end.">>),
- ?line {ok, test_restricted_local} =
+ {ok, test_restricted_local} =
application:get_env(stdlib, restricted_shell),
- ?line "exception exit: restricted shell does not allow foo(" ++ _ =
+ "exception exit: restricted shell does not allow foo(" ++ _ =
comm_err(<<"begin F=fun() -> hello end, foo(F) end.">>),
- ?line "exception error: undefined shell command banan/1" =
+ "exception error: undefined shell command banan/1" =
comm_err(<<"begin F=fun() -> hello end, banan(F) end.">>),
- ?line "{error,"++_ = t(<<"begin F=fun() -> hello end, c(F) end.">>),
- ?line "exception exit: restricted shell does not allow l(" ++ _ =
+ "{error,"++_ = t(<<"begin F=fun() -> hello end, c(F) end.">>),
+ "exception exit: restricted shell does not allow l(" ++ _ =
comm_err(<<"begin F=fun() -> hello end, l(F) end.">>),
- ?line "exception error: variable 'F' is unbound" =
+ "exception error: variable 'F' is unbound" =
comm_err(<<"begin F=fun() -> hello end, f(F), F end.">>),
- ?line [funkis] =
+ [funkis] =
scan(<<"begin F=fun() -> hello end, funkis(F) end.">>),
- ?line "exception exit: restricted shell does not allow apple(" ++ _ =
+ "exception exit: restricted shell does not allow apple(" ++ _ =
comm_err(<<"begin F=fun() -> hello end, apple(F) end.">>),
- ?line "exception exit: restricted shell stopped"=
+ "exception exit: restricted shell stopped"=
comm_err(<<"begin shell:stop_restricted() end.">>),
- ?line undefined =
+ undefined =
application:get_env(stdlib, restricted_shell),
- ?line (catch code:purge(user_default)),
- ?line true = (catch code:delete(user_default)),
+ (catch code:purge(user_default)),
+ true = (catch code:delete(user_default)),
ok.
%% f/0 and f/1.
forget(Config) when is_list(Config) ->
%% f/0
- ?line [ok] = scan(<<"begin f() end.">>),
- ?line "1: variable 'A' is unbound" =
+ [ok] = scan(<<"begin f() end.">>),
+ "1: variable 'A' is unbound" =
comm_err(<<"A = 3, f(), A.">>),
- ?line [ok] = scan(<<"A = 3, A = f(), A.">>),
+ [ok] = scan(<<"A = 3, A = f(), A.">>),
%% f/1
- ?line [ok] = scan(<<"begin f(A) end.">>),
- ?line "1: variable 'A' is unbound" =
+ [ok] = scan(<<"begin f(A) end.">>),
+ "1: variable 'A' is unbound" =
comm_err(<<"A = 3, f(A), A.">>),
- ?line [ok] = scan(<<"A = 3, A = f(A), A.">>),
- ?line "exception error: no function clause matching call to f/1" =
+ [ok] = scan(<<"A = 3, A = f(A), A.">>),
+ "exception error: no function clause matching call to f/1" =
comm_err(<<"f(a).">>),
ok.
%% Test of the record support. OTP-5063.
records(Config) when is_list(Config) ->
%% rd/2
- ?line [{attribute,_,record,{bar,_}},ok] =
+ [{attribute,_,record,{bar,_}},ok] =
scan(<<"rd(foo,{bar}),
rd(bar,{foo = (#foo{})#foo.bar}),
rl(bar).">>),
- ?line "variable 'R' is unbound" = % used to work (before OTP-5878, R11B)
+ "variable 'R' is unbound" = % used to work (before OTP-5878, R11B)
exit_string(<<"rd(foo,{bar}),
R = #foo{},
rd(bar,{foo = R#foo.bar}).">>),
- ?line "exception error: no function clause matching call to rd/2" =
+ "exception error: no function clause matching call to rd/2" =
comm_err(<<"rd({foo},{bar}).">>),
- ?line "bad record declaration" = exit_string(<<"A = bar, rd(foo,A).">>),
- ?line [foo] = scan(<<"begin rd(foo,{bar}) end.">>),
- ?line "1: record foo undefined" =
+ "bad record declaration" = exit_string(<<"A = bar, rd(foo,A).">>),
+ [foo] = scan(<<"begin rd(foo,{bar}) end.">>),
+ "1: record foo undefined" =
comm_err(<<"begin rd(foo,{bar}), #foo{} end.">>),
- ?line ['f o o'] = scan(<<"rd('f o o', {bar}).">>),
- ?line [foo] = scan(<<"rd(foo,{bar}), rd(foo,{foo = #foo{}}).">>),
+ ['f o o'] = scan(<<"rd('f o o', {bar}).">>),
+ [foo] = scan(<<"rd(foo,{bar}), rd(foo,{foo = #foo{}}).">>),
%% rf/0,1
- ?line [_, {attribute,_,record,{foo,_}},ok] =
+ [_, {attribute,_,record,{foo,_}},ok] =
scan(<<"rf('_'). rd(foo,{bar}),rl().">>),
- ?line "1: record foo undefined" =
+ "1: record foo undefined" =
comm_err(<<"rd(foo,{bar}), #foo{}, rf(foo), #foo{}.">>),
- ?line [ok,{foo,undefined}] =
+ [ok,{foo,undefined}] =
scan(<<"rd(foo,{bar}), A = #foo{}, rf(foo). A.">>),
- ?line [_] = scan(<<"begin rf() end.">>),
- ?line [ok] = scan(<<"begin rf(foo) end.">>),
+ [_] = scan(<<"begin rf() end.">>),
+ [ok] = scan(<<"begin rf(foo) end.">>),
%% rp/1
- ?line "#foo{bar = undefined}.\nok.\n" =
+ "#foo{bar = undefined}.\nok.\n" =
t(<<"rd(foo,{bar}), rp(#foo{}).">>),
- ?line [{foo,3,4,3},ok] = scan(<<"rd(foo,{a = 3, b}), rp({foo,3,4,3}).">>),
- ?line "#foo{a = 12}.\nok.\n" = t(<<"rd(foo,{a = 3}), rp({foo,12}).">>),
- ?line [{[{foo}],12},ok] = scan(<<"rd(foo,{a = 3}), rp({[{foo}],12}).">>),
+ [{foo,3,4,3},ok] = scan(<<"rd(foo,{a = 3, b}), rp({foo,3,4,3}).">>),
+ "#foo{a = 12}.\nok.\n" = t(<<"rd(foo,{a = 3}), rp({foo,12}).">>),
+ [{[{foo}],12},ok] = scan(<<"rd(foo,{a = 3}), rp({[{foo}],12}).">>),
%% rr/1,2,3
MS = ?MODULE_STRING,
RR1 = "rr(" ++ MS ++ "). #state{}.",
- ?line "[state]\n"
+ "[state]\n"
"#state{bin = undefined,reply = undefined,leader = undefined,\n"
" unic = latin1}.\n" =
t(RR1),
RR2 = "rr(" ++ MS ++ ",[state]). #state{}.",
- ?line "[state]\n"
+ "[state]\n"
"#state{bin = undefined,reply = undefined,leader = undefined,\n"
" unic = latin1}.\n" =
t(RR2),
RR3 = "rr(" ++ MS ++ ",'_'). #state{}.",
- ?line "[state]\n"
+ "[state]\n"
"#state{bin = undefined,reply = undefined,leader = undefined,\n"
" unic = latin1}.\n" =
t(RR3),
RR4 = "rr(" ++ MS ++ ", '_', {d,test1}).",
- ?line [[state]] = scan(RR4),
+ [[state]] = scan(RR4),
Test = filename:join(?config(priv_dir, Config), "test.erl"),
Contents = <<"-module(test).
@@ -387,7 +387,7 @@ records(Config) when is_list(Config) ->
-ifdef(test2).
-record(test2, {g}).
-endif.">>,
- ?line ok = file:write_file(Test, Contents),
+ ok = file:write_file(Test, Contents),
RR5 = "rr(\"" ++ Test ++ "\", '_', {d,test1}), rl([test1,test2]).",
A1 = erl_anno:new(1),
@@ -398,88 +398,88 @@ records(Config) when is_list(Config) ->
"\", '_', [{d,test1},{d,test2,17}]), rl([test1,test2]).",
[{attribute,A1,record,{test1,_}},{attribute,A1,record,{test2,_}},ok] =
scan(RR7),
- ?line PreReply = scan(<<"rr(prim_file).">>), % preloaded...
- ?line true = is_list(PreReply),
- ?line Dir = filename:join(?config(priv_dir, Config), "*.erl"),
- ?line RR8 = "rp(rr(\"" ++ Dir ++ "\")).",
- ?line [_,ok] = scan(RR8),
+ PreReply = scan(<<"rr(prim_file).">>), % preloaded...
+ true = is_list(PreReply),
+ Dir = filename:join(?config(priv_dir, Config), "*.erl"),
+ RR8 = "rp(rr(\"" ++ Dir ++ "\")).",
+ [_,ok] = scan(RR8),
file:delete(Test),
RR1000 = "begin rr(" ++ MS ++ ") end.",
- ?line [_] = scan(RR1000),
+ [_] = scan(RR1000),
RR1001 = "begin rr(" ++ MS ++ ", state) end.",
- ?line [_] = scan(RR1001),
+ [_] = scan(RR1001),
RR1002 = "begin rr(" ++ MS ++ ", state,{i,'.'}) end.",
- ?line [_] = scan(RR1002),
+ [_] = scan(RR1002),
- ?line [{error,nofile}] = scan(<<"rr(not_a_module).">>),
- ?line [{error,invalid_filename}] = scan(<<"rr({foo}).">>),
- ?line [[]] = scan(<<"rr(\"not_a_file\").">>),
+ [{error,nofile}] = scan(<<"rr(not_a_module).">>),
+ [{error,invalid_filename}] = scan(<<"rr({foo}).">>),
+ [[]] = scan(<<"rr(\"not_a_file\").">>),
%% using records
- ?line [2] = scan(<<"rd(foo,{bar}), record_info(size, foo).">>),
- ?line [true] = scan(<<"rd(foo,{bar}), is_record(#foo{}, foo).">>),
- ?line [true] = scan(<<"rd(foo,{bar}), erlang:is_record(#foo{}, foo).">>),
- ?line [true] = scan(<<"rd(foo,{bar}),
+ [2] = scan(<<"rd(foo,{bar}), record_info(size, foo).">>),
+ [true] = scan(<<"rd(foo,{bar}), is_record(#foo{}, foo).">>),
+ [true] = scan(<<"rd(foo,{bar}), erlang:is_record(#foo{}, foo).">>),
+ [true] = scan(<<"rd(foo,{bar}),
fun() when record(#foo{},foo) -> true end().">>),
- ?line [2] = scan(<<"rd(foo,{bar}), #foo.bar.">>),
- ?line "#foo{bar = 17}.\n" =
+ [2] = scan(<<"rd(foo,{bar}), #foo.bar.">>),
+ "#foo{bar = 17}.\n" =
t(<<"rd(foo,{bar}), A = #foo{}, A#foo{bar = 17}.">>),
%% test of is_record/2 in lc
- ?line "[#foo{bar = 3}].\n" =
+ "[#foo{bar = 3}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"is_record(X, foo)].">>),
- ?line "[x,[],{a,b}].\n" =
+ "[x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"not is_record(X, foo)].">>),
- ?line "[#foo{bar = 3}].\n" =
+ "[#foo{bar = 3}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin is_record(X, foo) end].">>),
- ?line "[x,[],{a,b}].\n" =
+ "[x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin not is_record(X, foo) end].">>),
- ?line "[#foo{bar = 3},x,[],{a,b}].\n" =
+ "[#foo{bar = 3},x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"is_record(X, foo) or not is_binary(X)].">>),
- ?line "[#foo{bar = 3},x,[],{a,b}].\n" =
+ "[#foo{bar = 3},x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"not is_record(X, foo) or not is_binary(X)].">>),
- ?line "[#foo{bar = 3}].\n" =
+ "[#foo{bar = 3}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"is_record(X, foo) or is_reference(X)].">>),
- ?line "[x,[],{a,b}].\n" =
+ "[x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"not is_record(X, foo) or is_reference(X)].">>),
- ?line "[#foo{bar = 3},x,[],{a,b}].\n" =
+ "[#foo{bar = 3},x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin is_record(X, foo) or not is_binary(X) end].">>),
- ?line "[#foo{bar = 3},x,[],{a,b}].\n" =
+ "[#foo{bar = 3},x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin not is_record(X, foo) or not is_binary(X) end].">>),
- ?line "[#foo{bar = 3}].\n" =
+ "[#foo{bar = 3}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin is_record(X, foo) or is_reference(X) end].">>),
- ?line "[x,[],{a,b}].\n" =
+ "[x,[],{a,b}].\n" =
t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
"begin not is_record(X, foo) or is_reference(X) end].">>),
- ?line [ok] =
+ [ok] =
scan(<<"rd(a,{}), is_record({a},a) andalso true, b().">>),
%% nested record defs
- ?line "#b{a = #a{}}.\n" = t(<<"rd(a,{}), rd(b, {a = #a{}}), #b{}.">>),
+ "#b{a = #a{}}.\n" = t(<<"rd(a,{}), rd(b, {a = #a{}}), #b{}.">>),
- ?line [ok,ok,ok] = scan(<<"rf('_'), rp(rp(rl(rf(rf(rf(rl())))))).">>),
+ [ok,ok,ok] = scan(<<"rf('_'), rp(rp(rl(rf(rf(rf(rl())))))).">>),
ok.
%% Known bugs.
known_bugs(Config) when is_list(Config) ->
%% erl_eval:merge_bindings/2 cannot handle _removal_ of bindings.
- ?line [3] = scan(<<"A = 3, length(begin f(A), [3] end), A.">>),
+ [3] = scan(<<"A = 3, length(begin f(A), [3] end), A.">>),
ok.
%% OTP-5226. Wildcards accepted when reading BEAM files using rr/1,2,3.
@@ -488,65 +488,65 @@ otp_5226(Config) when is_list(Config) ->
-record('_test1', {a,b}).">>,
Test2 = <<"-module(test2).
-record('_test2', {c,d}).">>,
- ?line File1 = filename("test1.erl", Config),
- ?line File2 = filename("test2.erl", Config),
- ?line Beam = filename("*.beam", Config),
- ?line ok = compile_file(Config, File1, Test1, [no_debug_info]),
- ?line ok = compile_file(Config, File2, Test2, [no_debug_info]),
- RR = "rr(\"" ++ Beam ++ "\").",
- ?line [Recs] = scan(RR),
- ?line true = lists:member('_test1', Recs),
- ?line true = lists:member('_test2', Recs),
- file:delete(filename("test1.beam", Config)),
- file:delete(filename("test2.beam", Config)),
- file:delete(File1),
- file:delete(File2),
- ok.
+ File1 = filename("test1.erl", Config),
+ File2 = filename("test2.erl", Config),
+ Beam = filename("*.beam", Config),
+ ok = compile_file(Config, File1, Test1, [no_debug_info]),
+ ok = compile_file(Config, File2, Test2, [no_debug_info]),
+ RR = "rr(\"" ++ Beam ++ "\").",
+ [Recs] = scan(RR),
+ true = lists:member('_test1', Recs),
+ true = lists:member('_test2', Recs),
+ file:delete(filename("test1.beam", Config)),
+ file:delete(filename("test2.beam", Config)),
+ file:delete(File1),
+ file:delete(File2),
+ ok.
%% OTP-5226. Test of eval_bits, mostly.
otp_5327(Config) when is_list(Config) ->
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"<<\"hej\":default>>.">>),
- ?line <<"abc">> =
+ <<"abc">> =
erl_parse:normalise({bin,1,[{bin_element,1,{string,1,"abc"},
- default,default}]}),
- ?line [<<"abc">>] = scan(<<"<<(<<\"abc\">>):3/binary>>.">>),
- ?line [<<"abc">>] = scan(<<"<<(<<\"abc\">>)/binary>>.">>),
- ?line "exception error: bad argument" =
+ default,default}]}),
+ [<<"abc">>] = scan(<<"<<(<<\"abc\">>):3/binary>>.">>),
+ [<<"abc">>] = scan(<<"<<(<<\"abc\">>)/binary>>.">>),
+ "exception error: bad argument" =
comm_err(<<"<<(<<\"abc\">>):4/binary>>.">>),
- ?line true = byte_size(hd(scan("<<3.14:64/float>>."))) =:= 8,
- ?line true = byte_size(hd(scan("<<3.14:32/float>>."))) =:= 4,
- ?line "exception error: bad argument" =
+ true = byte_size(hd(scan("<<3.14:64/float>>."))) =:= 8,
+ true = byte_size(hd(scan("<<3.14:32/float>>."))) =:= 4,
+ "exception error: bad argument" =
comm_err(<<"<<3.14:128/float>>.">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"<<10:default>>.">>),
- ?line [<<98,1:1>>] = scan(<<"<<3:3,5:6>>.">>),
- ?line {'EXIT',{badarg,_}} =
+ [<<98,1:1>>] = scan(<<"<<3:3,5:6>>.">>),
+ {'EXIT',{badarg,_}} =
(catch erl_parse:normalise({bin,1,[{bin_element,1,{integer,1,17},
{atom,1,all},
default}]})),
- ?line [<<-20/signed>>] = scan(<<"<<-20/signed>> = <<-20>>.">>),
- ?line [<<-300:16/signed>>] =
- scan(<<"<<-300:16/signed>> = <<-300:16>>.">>),
- ?line [<<-1000:24/signed>>] =
- scan(<<"<<-1000:24/signed>> = <<-1000:24>>.">>),
- ?line [<<-(1 bsl 29):32/signed>>] =
+ [<<-20/signed>>] = scan(<<"<<-20/signed>> = <<-20>>.">>),
+ [<<-300:16/signed>>] =
+ scan(<<"<<-300:16/signed>> = <<-300:16>>.">>),
+ [<<-1000:24/signed>>] =
+ scan(<<"<<-1000:24/signed>> = <<-1000:24>>.">>),
+ [<<-(1 bsl 29):32/signed>>] =
scan(<<"<<-(1 bsl 29):32/signed>> = <<-(1 bsl 29):32>>.">>),
- ?line "exception error: no match of right hand side value <<0,0,0>>" =
+ "exception error: no match of right hand side value <<0,0,0>>" =
comm_err(<<"<<B:3/unit:7-binary,_/binary>> = <<0:24>>.">>),
- ?line true = [<<103133:64/float>>] =:=
+ true = [<<103133:64/float>>] =:=
scan(<<"<<103133:64/float>> = <<103133:64/float>>.">>),
- ?line true = [<<103133.0:64/float>>] =:=
+ true = [<<103133.0:64/float>>] =:=
scan(<<"<<103133.0:64/float>> = <<103133:64/float>>.">>),
- ?line true = [<<103133:64/float>>] =:= scan(<<"<<103133:64/float>>.">>),
+ true = [<<103133:64/float>>] =:= scan(<<"<<103133:64/float>>.">>),
Int = 17,
- ?line true = [<<Int:64/float>>] =:= scan(<<"Int = 17, <<Int:64/float>>.">>),
- ?line "exception error: no match of right hand side value" ++ _ =
+ true = [<<Int:64/float>>] =:= scan(<<"Int = 17, <<Int:64/float>>.">>),
+ "exception error: no match of right hand side value" ++ _ =
comm_err(<<"<<103133:64/binary>> = <<103133:64/float>>.">>),
- ?line "exception error: interpreted function with arity 1 called with two arguments" =
+ "exception error: interpreted function with arity 1 called with two arguments" =
comm_err(<<"(fun(X) -> X end)(a,b).">>),
- ?line {'EXIT', {{illegal_pattern,_}, _}} =
+ {'EXIT', {{illegal_pattern,_}, _}} =
(catch evaluate("<<A:a>> = <<17:32>>.", [])),
C = <<"
<<A:4,B:4,C:4,D:4,E:4,F:4>> = <<\"hej\">>,
@@ -555,54 +555,54 @@ otp_5327(Config) when is_list(Config) ->
_ -> 2
end.
">>,
- ?line 1 = evaluate(C, []),
+ 1 = evaluate(C, []),
%% unbound_var would be nicer...
- ?line {'EXIT',{{illegal_pattern,_},_}} =
+ {'EXIT',{{illegal_pattern,_},_}} =
(catch evaluate(<<"<<A:B>> = <<17:32>>.">>, [])),
%% undefined_bittype is turned into badmatch:
- ?line {'EXIT',{{badmatch,<<17:32>>},_}} =
+ {'EXIT',{{badmatch,<<17:32>>},_}} =
(catch evaluate(<<"<<A/apa>> = <<17:32>>.">>, [])),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch evaluate(<<"<<17/binary-unit:8-unit:16>>.">>, [])),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch evaluate(<<"<<17:32/unsigned-signed>> = <<17:32>>.">>, [])),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch evaluate(<<"<<17:32/unsigned-signed>>.">>, [])),
- ?line <<17:32>> = evaluate(<<"<<17:32/signed-signed>>.">>, []),
- ?line {'EXIT',_} =
+ <<17:32>> = evaluate(<<"<<17:32/signed-signed>>.">>, []),
+ {'EXIT',_} =
(catch evaluate(<<"<<32/unit:8>>.">>, [])),
ok.
%% OTP-5435. sys_pre_expand not in the path.
otp_5435(Config) when is_list(Config) ->
- ?line true = <<103133:64/float>> =:=
+ true = <<103133:64/float>> =:=
evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []),
- ?line true = <<103133.0:64/float>> =:=
+ true = <<103133.0:64/float>> =:=
evaluate(<<"<<103133.0:64/float>> = <<103133:64/float>>.">>, []),
- ?line true = is_alive(),
- ?line {ok, Node} = start_node(shell_SUITE_otp_5435),
- ?line ok = rpc:call(Node, ?MODULE, otp_5435_2, []),
+ true = is_alive(),
+ {ok, Node} = start_node(shell_SUITE_otp_5435),
+ ok = rpc:call(Node, ?MODULE, otp_5435_2, []),
test_server:stop_node(Node),
ok.
-
+
start_node(Name) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
+ PA = filename:dirname(code:which(?MODULE)),
test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
otp_5435_2() ->
- ?line true = code:del_path(compiler),
+ true = code:del_path(compiler),
%% sys_pre_expand can no longer be found
%% OTP-5876. But erl_expand_records can!
- ?line [{attribute,_,record,{bar,_}},ok] =
+ [{attribute,_,record,{bar,_}},ok] =
scan(<<"rd(foo,{bar}),
rd(bar,{foo = (#foo{})#foo.bar}),
- rl(bar).">>),
+ rl(bar).">>),
ok.
%% OTP-5195. QLC, mostly.
otp_5195(Config) when is_list(Config) ->
%% QLC. It was easier to put these cases here than in qlc_SUITE.
- ?line "[#a{b = undefined}].\n" =
+ "[#a{b = undefined}].\n" =
t(<<"rd(a,{b}), qlc:e(qlc:q([X || X <- [#a{}],is_record(X, a)])).">>),
%% An experimental shell used to translate error tuples:
@@ -610,25 +610,25 @@ otp_5195(Config) when is_list(Config) ->
%% "list expression\".\n" =
%% t(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>),
%% Same as last one (if the shell does not translate error tuples):
- ?line [{error,qlc,{1,qlc,{used_generator_variable,'X'}}}] =
+ [{error,qlc,{1,qlc,{used_generator_variable,'X'}}}] =
scan(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>),
- ?line {error,qlc,{1,qlc,{used_generator_variable,'X'}}} =
+ {error,qlc,{1,qlc,{used_generator_variable,'X'}}} =
evaluate(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>, []),
Ugly = <<"qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],ugly()])])).">>,
- ?line "undefined shell command ugly/0" = error_string(Ugly),
- ?line {'EXIT',{undef,_}} = (catch evaluate(Ugly, [])),
+ "undefined shell command ugly/0" = error_string(Ugly),
+ {'EXIT',{undef,_}} = (catch evaluate(Ugly, [])),
V_1 = <<"qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],v(-1)])])).">>,
- ?line "- 1: command not found" = comm_err(V_1),
- ?line {'EXIT', {undef,_}} = (catch evaluate(V_1, [])),
+ "- 1: command not found" = comm_err(V_1),
+ {'EXIT', {undef,_}} = (catch evaluate(V_1, [])),
- ?line "1\n2\n3\n3.\n" =
+ "1\n2\n3\n3.\n" =
t(<<"1. 2. 3. 3 = fun(A) when A =:= 2 -> v(3) end(v(2)).">>),
- ?line List4 = t(<<"[a,list]. A = [1,2]. "
- "qlc:q([X || X <- qlc:append(A, v(1))]). "
- "[1,2,a,list] = qlc:e(v(-1)).">>),
- ?line "[1,2,a,list].\n" = string:substr(List4, string:len(List4)-13),
+ List4 = t(<<"[a,list]. A = [1,2]. "
+ "qlc:q([X || X <- qlc:append(A, v(1))]). "
+ "[1,2,a,list] = qlc:e(v(-1)).">>),
+ "[1,2,a,list].\n" = string:substr(List4, string:len(List4)-13),
ok.
@@ -636,159 +636,159 @@ otp_5195(Config) when is_list(Config) ->
otp_5915(Config) when is_list(Config) ->
C = <<"
rd(r, {a = 4,b}),
- rd(r1, {a,b}),
- rd(r2, {a = #r1{},b,c=length([1,2,3])}),
- rd(r3, {a = fun(_) -> #r1{} end(1), b}),
-
- foo = fun(A) when A#r1.a > A#r1.b -> foo end(#r1{b = 2}),
- 0 = fun(A) when A#r2.a -> 0 end(#r2{a = true}),
- 1 = fun(A) when (#r1{a = A})#r1.a > 2 -> 1 end(3),
- 2 = fun(N) when ((#r2{a = #r{a = 4}, b = length([a,b,c])})#r2.a)#r.a > N ->
- 2 end(2),
- 3 = fun(A) when (A#r2.a)#r1.a =:= 3 -> 3 end(#r2{a = #r1{a = 3}}),
- ok = fun() ->
- F = fun(A) when record(A#r.a, r1) -> 4;
- (A) when record(A#r1.a, r1) -> 5
- end,
- 5 = F(#r1{a = #r1{}}),
- 4 = F(#r{a = #r1{}}),
- ok
- end(),
- 3 = fun(A) when record(A#r1.a, r),
- (A#r1.a)#r.a > 3 -> 3
- end(#r1{a = #r{a = 4}}),
- 7 = fun(A) when record(A#r3.a, r1) -> 7 end(#r3{}),
- [#r1{a = 2,b = 1}] =
- fun() ->
- [A || A <- [#r1{a = 1, b = 3},
- #r2{a = 2,b = 1},
- #r1{a = 2, b = 1}],
- A#r1.a >
- A#r1.b]
- end(),
- {[_],b} =
- fun(L) ->
+ rd(r1, {a,b}),
+ rd(r2, {a = #r1{},b,c=length([1,2,3])}),
+ rd(r3, {a = fun(_) -> #r1{} end(1), b}),
+
+ foo = fun(A) when A#r1.a > A#r1.b -> foo end(#r1{b = 2}),
+ 0 = fun(A) when A#r2.a -> 0 end(#r2{a = true}),
+ 1 = fun(A) when (#r1{a = A})#r1.a > 2 -> 1 end(3),
+ 2 = fun(N) when ((#r2{a = #r{a = 4}, b = length([a,b,c])})#r2.a)#r.a > N ->
+ 2 end(2),
+ 3 = fun(A) when (A#r2.a)#r1.a =:= 3 -> 3 end(#r2{a = #r1{a = 3}}),
+ ok = fun() ->
+ F = fun(A) when record(A#r.a, r1) -> 4;
+ (A) when record(A#r1.a, r1) -> 5
+ end,
+ 5 = F(#r1{a = #r1{}}),
+ 4 = F(#r{a = #r1{}}),
+ ok
+ end(),
+ 3 = fun(A) when record(A#r1.a, r),
+ (A#r1.a)#r.a > 3 -> 3
+ end(#r1{a = #r{a = 4}}),
+ 7 = fun(A) when record(A#r3.a, r1) -> 7 end(#r3{}),
+ [#r1{a = 2,b = 1}] =
+ fun() ->
+ [A || A <- [#r1{a = 1, b = 3},
+ #r2{a = 2,b = 1},
+ #r1{a = 2, b = 1}],
+ A#r1.a >
+ A#r1.b]
+ end(),
+ {[_],b} =
+ fun(L) ->
%% A is checked only once:
- R1 = [{A,B} || A <- L, A#r1.a, B <- L, A#r1.b],
- A = #r2{a = true},
+ R1 = [{A,B} || A <- L, A#r1.a, B <- L, A#r1.b],
+ A = #r2{a = true},
%% A is checked again:
- B = if A#r1.a -> a; true -> b end,
- {R1,B}
- end([#r1{a = true, b = true}]),
-
- p = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
- (_) -> p
- end(#r1{a = 2}),
-
- o = fun(A) when (A#r1.a =:= 2) orelse (A#r2.a =:= 1) -> o;
- (_) -> p
- end(#r1{a = 2}),
-
- 3 = fun(A) when A#r1.a > 3,
- record(A, r1) -> 3
- end(#r1{a = 5}),
-
- ok = fun() ->
- F = fun(A) when (A#r2.a =:= 1) orelse (A#r2.a) -> 2;
- (A) when (A#r1.a =:= 1) orelse (A#r1.a) -> 1;
- (A) when (A#r2.a =:= 2) andalso (A#r2.b) -> 3
- end,
- 1 = F(#r1{a = 1}),
- 2 = F(#r2{a = true}),
- 3 = F(#r2{a = 2, b = true}),
- ok
- end(),
-
- b = fun(A) when false or not (A#r.a =:= 1) -> a;
- (_) -> b
- end(#r1{a = 1}),
- b = fun(A) when not (A#r.a =:= 1) or false -> a;
- (_) -> b
- end(#r1{a = 1}),
-
- ok = fun() ->
- F = fun(A) when not (A#r.a =:= 1) -> yes;
- (_) -> no
- end,
- no = F(#r1{a = 2}),
- yes = F(#r{a = 2}),
- no = F(#r{a = 1}),
- ok
- end(),
-
- a = fun(A) when record(A, r),
- A#r.a =:= 1,
- A#r.b =:= 2 ->a
- end(#r{a = 1, b = 2}),
- a = fun(A) when erlang:is_record(A, r),
- A#r.a =:= 1,
- A#r.b =:= 2 -> a
- end(#r{a = 1, b = 2}),
- a = fun(A) when is_record(A, r),
- A#r.a =:= 1,
- A#r.b =:= 2 -> a
- end(#r{a = 1, b = 2}),
-
- nop = fun(A) when (is_record(A, r1) and (A#r1.a > 3)) or (A#r2.a < 1) ->
- japp;
- (_) ->
- nop
- end(#r2{a = 0}),
- nop = fun(A) when (A#r1.a > 3) or (A#r2.a < 1) -> japp;
- (_) ->
- nop
- end(#r2{a = 0}),
-
- ok = fun() ->
- F = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
- (_) -> p
- end,
- p = F(#r2{a = 1}),
- p = F(#r1{a = 2}),
- ok
- end(),
-
- ok = fun() ->
- F = fun(A) when fail, A#r1.a; A#r1.a -> ab;
- (_) -> bu
- end,
- ab = F(#r1{a = true}),
- bu = F(#r2{a = true}),
- ok
- end(),
-
- both = fun(A) when A#r.a, A#r.b -> both
- end(#r{a = true, b = true}),
-
- ok = fun() ->
- F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
- or (B#r2.b) or (A#r1.b) -> true;
- (_, _) -> false
- end,
- true = F(#r1{a = false, b = false}, #r2{a = false, b = true}),
- false = F(#r1{a = true, b = true}, #r1{a = false, b = true}),
- ok
- end(),
-
- ok.">>,
+ B = if A#r1.a -> a; true -> b end,
+ {R1,B}
+ end([#r1{a = true, b = true}]),
+
+ p = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
+ (_) -> p
+ end(#r1{a = 2}),
+
+ o = fun(A) when (A#r1.a =:= 2) orelse (A#r2.a =:= 1) -> o;
+ (_) -> p
+ end(#r1{a = 2}),
+
+ 3 = fun(A) when A#r1.a > 3,
+ record(A, r1) -> 3
+ end(#r1{a = 5}),
+
+ ok = fun() ->
+ F = fun(A) when (A#r2.a =:= 1) orelse (A#r2.a) -> 2;
+ (A) when (A#r1.a =:= 1) orelse (A#r1.a) -> 1;
+ (A) when (A#r2.a =:= 2) andalso (A#r2.b) -> 3
+ end,
+ 1 = F(#r1{a = 1}),
+ 2 = F(#r2{a = true}),
+ 3 = F(#r2{a = 2, b = true}),
+ ok
+ end(),
+
+ b = fun(A) when false or not (A#r.a =:= 1) -> a;
+ (_) -> b
+ end(#r1{a = 1}),
+ b = fun(A) when not (A#r.a =:= 1) or false -> a;
+ (_) -> b
+ end(#r1{a = 1}),
+
+ ok = fun() ->
+ F = fun(A) when not (A#r.a =:= 1) -> yes;
+ (_) -> no
+ end,
+ no = F(#r1{a = 2}),
+ yes = F(#r{a = 2}),
+ no = F(#r{a = 1}),
+ ok
+ end(),
+
+ a = fun(A) when record(A, r),
+ A#r.a =:= 1,
+ A#r.b =:= 2 ->a
+ end(#r{a = 1, b = 2}),
+ a = fun(A) when erlang:is_record(A, r),
+ A#r.a =:= 1,
+ A#r.b =:= 2 -> a
+ end(#r{a = 1, b = 2}),
+ a = fun(A) when is_record(A, r),
+ A#r.a =:= 1,
+ A#r.b =:= 2 -> a
+ end(#r{a = 1, b = 2}),
+
+ nop = fun(A) when (is_record(A, r1) and (A#r1.a > 3)) or (A#r2.a < 1) ->
+ japp;
+ (_) ->
+ nop
+ end(#r2{a = 0}),
+ nop = fun(A) when (A#r1.a > 3) or (A#r2.a < 1) -> japp;
+ (_) ->
+ nop
+ end(#r2{a = 0}),
+
+ ok = fun() ->
+ F = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
+ (_) -> p
+ end,
+ p = F(#r2{a = 1}),
+ p = F(#r1{a = 2}),
+ ok
+ end(),
+
+ ok = fun() ->
+ F = fun(A) when fail, A#r1.a; A#r1.a -> ab;
+ (_) -> bu
+ end,
+ ab = F(#r1{a = true}),
+ bu = F(#r2{a = true}),
+ ok
+ end(),
+
+ both = fun(A) when A#r.a, A#r.b -> both
+ end(#r{a = true, b = true}),
+
+ ok = fun() ->
+ F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
+ or (B#r2.b) or (A#r1.b) -> true;
+ (_, _) -> false
+ end,
+ true = F(#r1{a = false, b = false}, #r2{a = false, b = true}),
+ false = F(#r1{a = true, b = true}, #r1{a = false, b = true}),
+ ok
+ end(),
+
+ ok.">>,
[ok] = scan(C),
- ok.
+ ok.
%% OTP-5916. erlang:is_record/3 allowed in guards.
otp_5916(Config) when is_list(Config) ->
C = <<"
rd(r1, {a,b}),
- rd(r2, {a,b}),
+ rd(r2, {a,b}),
- true = if erlang:is_record(#r1{},r1,3) -> true; true -> false end,
- false = if erlang:is_record(#r2{},r1,3) -> true; true -> false end,
+ true = if erlang:is_record(#r1{},r1,3) -> true; true -> false end,
+ false = if erlang:is_record(#r2{},r1,3) -> true; true -> false end,
- true = if is_record(#r1{},r1,3) -> true; true -> false end,
- false = if is_record(#r2{},r1,3) -> true; true -> false end,
+ true = if is_record(#r1{},r1,3) -> true; true -> false end,
+ false = if is_record(#r2{},r1,3) -> true; true -> false end,
- ok.">>,
+ ok.">>,
[ok] = scan(C),
- ok.
+ ok.
%% OTP-5327. Adopted from parts of emulator/test/bs_match_misc_SUITE.erl.
@@ -796,149 +796,149 @@ bs_match_misc_SUITE(Config) when is_list(Config) ->
C = <<"
F1 = fun() -> 3.1415 end,
- FOne = fun() -> 1.0 end,
-
- Fcmp = fun(F1, F2) when (F1 - F2) / F2 < 0.0000001 -> ok end,
-
- MakeSubBin = fun(Bin0) ->
- Sz = size(Bin0),
- Bin1 = <<37,Bin0/binary,38,39>>,
- <<_:8,Bin:Sz/binary,_:8,_:8>> = Bin1,
- Bin
- end,
-
- MatchFloat =
- fun(Bin0, Fsz, I) ->
- Bin = MakeSubBin(Bin0),
- Bsz = size(Bin) * 8,
- Tsz = Bsz - Fsz - I,
- <<_:I,F:Fsz/float,_:Tsz>> = Bin,
- F
- end,
-
- TFloat = fun() ->
- F = F1(),
- G = FOne(),
-
- G = MatchFloat(<<63,128,0,0>>, 32, 0),
- G = MatchFloat(<<63,240,0,0,0,0,0,0>>, 64, 0),
-
- Fcmp(F, MatchFloat(<<F:32/float>>, 32, 0)),
- Fcmp(F, MatchFloat(<<F:64/float>>, 64, 0)),
- Fcmp(F, MatchFloat(<<1:1,F:32/float,127:7>>, 32, 1)),
- Fcmp(F, MatchFloat(<<1:1,F:64/float,127:7>>, 64, 1)),
- Fcmp(F, MatchFloat(<<1:13,F:32/float,127:3>>, 32, 13)),
- Fcmp(F, MatchFloat(<<1:13,F:64/float,127:3>>, 64, 13))
- end,
- TFloat(),
-
- F2 = fun() -> 2.7133 end,
-
- MatchFloatLittle = fun(Bin0, Fsz, I) ->
- Bin = MakeSubBin(Bin0),
- Bsz = size(Bin) * 8,
- Tsz = Bsz - Fsz - I,
- <<_:I,F:Fsz/float-little,_:Tsz>> = Bin,
- F
- end,
-
- LittleFloat = fun() ->
- F = F2(),
- G = FOne(),
-
- G = MatchFloatLittle(<<0,0,0,0,0,0,240,63>>, 64, 0),
- G = MatchFloatLittle(<<0,0,128,63>>, 32, 0),
-
- Fcmp(F, MatchFloatLittle(<<F:32/float-little>>, 32, 0)),
- Fcmp(F, MatchFloatLittle(<<F:64/float-little>>, 64, 0)),
- Fcmp(F, MatchFloatLittle(<<1:1,F:32/float-little,127:7>>, 32, 1)),
- Fcmp(F, MatchFloatLittle(<<1:1,F:64/float-little,127:7>>, 64, 1)),
- Fcmp(F, MatchFloatLittle(<<1:13,F:32/float-little,127:3>>, 32, 13)),
- Fcmp(F, MatchFloatLittle(<<1:13,F:64/float-little,127:3>>, 64, 13))
- end,
- LittleFloat(),
-
- Sean1 = fun(<<B/binary>>) when size(B) < 4 -> small;
- (<<1, _B/binary>>) -> large
- end,
-
- Sean = fun() ->
- small = Sean1(<<>>),
- small = Sean1(<<1>>),
- small = Sean1(<<1,2>>),
- small = Sean1(<<1,2,3>>),
- large = Sean1(<<1,2,3,4>>),
-
- small = Sean1(<<4>>),
- small = Sean1(<<4,5>>),
- small = Sean1(<<4,5,6>>),
- {'EXIT',{function_clause,_}} = (catch Sean1(<<4,5,6,7>>))
- end,
- Sean(),
-
- NativeBig = fun() ->
- <<37.33:64/native-float>> = <<37.33:64/big-float>>,
- <<3974:16/native-integer>> = <<3974:16/big-integer>>
- end,
-
- NativeLittle = fun() ->
- <<37869.32343:64/native-float>> = <<37869.32343:64/little-float>>,
- <<7974:16/native-integer>> = <<7974:16/little-integer>>
- end,
-
- Native = fun() ->
- <<3.14:64/native-float>> = <<3.14:64/native-float>>,
- <<333:16/native>> = <<333:16/native>>,
- <<38658345:32/native>> = <<38658345:32/native>>,
- case <<1:16/native>> of
- <<0,1>> -> NativeBig();
- <<1,0>> -> NativeLittle()
- end
- end,
- Native(),
-
- Split = fun(<<N:16,B:N/binary,T/binary>>) -> {B,T} end,
-
- Split2 = fun(N, <<N:16,B:N/binary,T/binary>>) -> {B,T} end,
-
- Split_2 = fun(<<N0:8,N:N0,B:N/binary,T/binary>>) -> {B,T} end,
-
- Skip = fun(<<N:8,_:N/binary,T/binary>>) -> T end,
-
- SizeVar = fun() ->
- {<<45>>,<<>>} = Split(<<1:16,45>>),
- {<<45>>,<<46,47>>} = Split(<<1:16,45,46,47>>),
- {<<45,46>>,<<47>>} = Split(<<2:16,45,46,47>>),
-
- {<<45,46,47>>,<<48>>} = Split_2(<<16:8,3:16,45,46,47,48>>),
-
- {<<45,46>>,<<47>>} = Split2(2, <<2:16,45,46,47>>),
- {'EXIT',{function_clause,_}} =
- (catch Split2(42, <<2:16,45,46,47>>)),
-
- <<\"cdef\">> = Skip(<<2:8,\"abcdef\">>)
+ FOne = fun() -> 1.0 end,
+
+ Fcmp = fun(F1, F2) when (F1 - F2) / F2 < 0.0000001 -> ok end,
+
+ MakeSubBin = fun(Bin0) ->
+ Sz = size(Bin0),
+ Bin1 = <<37,Bin0/binary,38,39>>,
+ <<_:8,Bin:Sz/binary,_:8,_:8>> = Bin1,
+ Bin
+ end,
+
+ MatchFloat =
+ fun(Bin0, Fsz, I) ->
+ Bin = MakeSubBin(Bin0),
+ Bsz = size(Bin) * 8,
+ Tsz = Bsz - Fsz - I,
+ <<_:I,F:Fsz/float,_:Tsz>> = Bin,
+ F
+ end,
+
+ TFloat = fun() ->
+ F = F1(),
+ G = FOne(),
+
+ G = MatchFloat(<<63,128,0,0>>, 32, 0),
+ G = MatchFloat(<<63,240,0,0,0,0,0,0>>, 64, 0),
+
+ Fcmp(F, MatchFloat(<<F:32/float>>, 32, 0)),
+ Fcmp(F, MatchFloat(<<F:64/float>>, 64, 0)),
+ Fcmp(F, MatchFloat(<<1:1,F:32/float,127:7>>, 32, 1)),
+ Fcmp(F, MatchFloat(<<1:1,F:64/float,127:7>>, 64, 1)),
+ Fcmp(F, MatchFloat(<<1:13,F:32/float,127:3>>, 32, 13)),
+ Fcmp(F, MatchFloat(<<1:13,F:64/float,127:3>>, 64, 13))
+ end,
+ TFloat(),
+
+ F2 = fun() -> 2.7133 end,
+
+ MatchFloatLittle = fun(Bin0, Fsz, I) ->
+ Bin = MakeSubBin(Bin0),
+ Bsz = size(Bin) * 8,
+ Tsz = Bsz - Fsz - I,
+ <<_:I,F:Fsz/float-little,_:Tsz>> = Bin,
+ F
+ end,
+
+ LittleFloat = fun() ->
+ F = F2(),
+ G = FOne(),
+
+ G = MatchFloatLittle(<<0,0,0,0,0,0,240,63>>, 64, 0),
+ G = MatchFloatLittle(<<0,0,128,63>>, 32, 0),
+
+ Fcmp(F, MatchFloatLittle(<<F:32/float-little>>, 32, 0)),
+ Fcmp(F, MatchFloatLittle(<<F:64/float-little>>, 64, 0)),
+ Fcmp(F, MatchFloatLittle(<<1:1,F:32/float-little,127:7>>, 32, 1)),
+ Fcmp(F, MatchFloatLittle(<<1:1,F:64/float-little,127:7>>, 64, 1)),
+ Fcmp(F, MatchFloatLittle(<<1:13,F:32/float-little,127:3>>, 32, 13)),
+ Fcmp(F, MatchFloatLittle(<<1:13,F:64/float-little,127:3>>, 64, 13))
+ end,
+ LittleFloat(),
+
+ Sean1 = fun(<<B/binary>>) when size(B) < 4 -> small;
+ (<<1, _B/binary>>) -> large
+ end,
+
+ Sean = fun() ->
+ small = Sean1(<<>>),
+ small = Sean1(<<1>>),
+ small = Sean1(<<1,2>>),
+ small = Sean1(<<1,2,3>>),
+ large = Sean1(<<1,2,3,4>>),
+
+ small = Sean1(<<4>>),
+ small = Sean1(<<4,5>>),
+ small = Sean1(<<4,5,6>>),
+ {'EXIT',{function_clause,_}} = (catch Sean1(<<4,5,6,7>>))
+ end,
+ Sean(),
+
+ NativeBig = fun() ->
+ <<37.33:64/native-float>> = <<37.33:64/big-float>>,
+ <<3974:16/native-integer>> = <<3974:16/big-integer>>
+ end,
+
+ NativeLittle = fun() ->
+ <<37869.32343:64/native-float>> = <<37869.32343:64/little-float>>,
+ <<7974:16/native-integer>> = <<7974:16/little-integer>>
+ end,
+
+ Native = fun() ->
+ <<3.14:64/native-float>> = <<3.14:64/native-float>>,
+ <<333:16/native>> = <<333:16/native>>,
+ <<38658345:32/native>> = <<38658345:32/native>>,
+ case <<1:16/native>> of
+ <<0,1>> -> NativeBig();
+ <<1,0>> -> NativeLittle()
+ end
+ end,
+ Native(),
+
+ Split = fun(<<N:16,B:N/binary,T/binary>>) -> {B,T} end,
+
+ Split2 = fun(N, <<N:16,B:N/binary,T/binary>>) -> {B,T} end,
+
+ Split_2 = fun(<<N0:8,N:N0,B:N/binary,T/binary>>) -> {B,T} end,
+
+ Skip = fun(<<N:8,_:N/binary,T/binary>>) -> T end,
+
+ SizeVar = fun() ->
+ {<<45>>,<<>>} = Split(<<1:16,45>>),
+ {<<45>>,<<46,47>>} = Split(<<1:16,45,46,47>>),
+ {<<45,46>>,<<47>>} = Split(<<2:16,45,46,47>>),
+
+ {<<45,46,47>>,<<48>>} = Split_2(<<16:8,3:16,45,46,47,48>>),
+
+ {<<45,46>>,<<47>>} = Split2(2, <<2:16,45,46,47>>),
+ {'EXIT',{function_clause,_}} =
+ (catch Split2(42, <<2:16,45,46,47>>)),
+
+ <<\"cdef\">> = Skip(<<2:8,\"abcdef\">>)
end,
- SizeVar(),
-
- Wcheck = fun(<<A>>) when A==3-> ok1;
- (<<_,_:2/binary>>) -> ok2;
- (<<_>>) -> ok3;
- (Other) -> {error,Other}
- end,
-
- Wiger = fun() ->
- ok1 = Wcheck(<<3>>),
- ok2 = Wcheck(<<1,2,3>>),
- ok3 = Wcheck(<<4>>),
- {error,<<1,2,3,4>>} = Wcheck(<<1,2,3,4>>),
- {error,<<>>} = Wcheck(<<>>)
- end,
- Wiger(),
-
- ok.
- ">>,
+ SizeVar(),
+
+ Wcheck = fun(<<A>>) when A==3-> ok1;
+ (<<_,_:2/binary>>) -> ok2;
+ (<<_>>) -> ok3;
+ (Other) -> {error,Other}
+ end,
+
+ Wiger = fun() ->
+ ok1 = Wcheck(<<3>>),
+ ok2 = Wcheck(<<1,2,3>>),
+ ok3 = Wcheck(<<4>>),
+ {error,<<1,2,3,4>>} = Wcheck(<<1,2,3,4>>),
+ {error,<<>>} = Wcheck(<<>>)
+ end,
+ Wiger(),
+
+ ok.
+">>,
[ok] = scan(C),
- ok = evaluate(C, []).
+ok = evaluate(C, []).
%% This one is not run during night builds since it takes several minutes.
@@ -947,217 +947,217 @@ bs_match_int_SUITE(Config) when is_list(Config) ->
C = <<"
FunClause = fun({'EXIT',{function_clause,_}}) -> ok end,
- Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
-
- GetInt1 = fun(<<I:0>>) -> I;
- (<<I:8>>) -> I;
- (<<I:16>>) -> I;
- (<<I:24>>) -> I;
- (<<I:32>>) -> I
- end,
-
- GetInt2 = fun(Bin0, I, F) when size(Bin0) < 4 ->
- Bin = <<0,Bin0/binary>>,
- I = GetInt1(Bin),
- F(Bin, I, F);
- (_, I, _F) -> I
- end,
-
- GetInt = fun(Bin) ->
- I = GetInt1(Bin),
- GetInt2(Bin, I, GetInt2)
- end,
-
-
- Cmp128 = fun(<<I:128>>, I) -> equal;
- (_, _) -> not_equal
- end,
-
- Uint2 = fun([H|T], Acc, F) -> F(T, Acc bsl 8 bor H, F);
- ([], Acc, _F) -> Acc
- end,
-
- Uint = fun(L) -> Uint2(L, 0, Uint2) end,
-
- Integer = fun() ->
- 0 = GetInt(Mkbin([])),
- 0 = GetInt(Mkbin([0])),
- 42 = GetInt(Mkbin([42])),
- 255 = GetInt(Mkbin([255])),
- 256 = GetInt(Mkbin([1,0])),
- 257 = GetInt(Mkbin([1,1])),
- 258 = GetInt(Mkbin([1,2])),
- 258 = GetInt(Mkbin([1,2])),
- 65534 = GetInt(Mkbin([255,254])),
- 16776455 = GetInt(Mkbin([255,253,7])),
- 4245492555 = GetInt(Mkbin([253,13,19,75])),
- 4294967294 = GetInt(Mkbin([255,255,255,254])),
- 4294967295 = GetInt(Mkbin([255,255,255,255])),
- Eight = [200,1,19,128,222,42,97,111],
- Cmp128(Eight, Uint(Eight)),
- FunClause(catch GetInt(Mkbin(lists:seq(1,5))))
- end,
- Integer(),
-
- Sint = fun(Bin) ->
- case Bin of
- <<I:8/signed>> -> I;
- <<I:8/signed,_:3,_:5>> -> I;
- Other -> {no_match,Other}
- end
- end,
-
- SignedInteger = fun() ->
- {no_match,_} = Sint(Mkbin([])),
- {no_match,_} = Sint(Mkbin([1,2,3])),
- 127 = Sint(Mkbin([127])),
- -1 = Sint(Mkbin([255])),
- -128 = Sint(Mkbin([128])),
- 42 = Sint(Mkbin([42,255])),
- 127 = Sint(Mkbin([127,255]))
- end,
- SignedInteger(),
-
- Dynamic5 = fun(Bin, S1, S2, A, B) ->
- case Bin of
- <<A:S1,B:S2>> ->
+ Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
+
+ GetInt1 = fun(<<I:0>>) -> I;
+ (<<I:8>>) -> I;
+ (<<I:16>>) -> I;
+ (<<I:24>>) -> I;
+ (<<I:32>>) -> I
+ end,
+
+ GetInt2 = fun(Bin0, I, F) when size(Bin0) < 4 ->
+ Bin = <<0,Bin0/binary>>,
+ I = GetInt1(Bin),
+ F(Bin, I, F);
+ (_, I, _F) -> I
+ end,
+
+ GetInt = fun(Bin) ->
+ I = GetInt1(Bin),
+ GetInt2(Bin, I, GetInt2)
+ end,
+
+
+ Cmp128 = fun(<<I:128>>, I) -> equal;
+ (_, _) -> not_equal
+ end,
+
+ Uint2 = fun([H|T], Acc, F) -> F(T, Acc bsl 8 bor H, F);
+ ([], Acc, _F) -> Acc
+ end,
+
+ Uint = fun(L) -> Uint2(L, 0, Uint2) end,
+
+ Integer = fun() ->
+ 0 = GetInt(Mkbin([])),
+ 0 = GetInt(Mkbin([0])),
+ 42 = GetInt(Mkbin([42])),
+ 255 = GetInt(Mkbin([255])),
+ 256 = GetInt(Mkbin([1,0])),
+ 257 = GetInt(Mkbin([1,1])),
+ 258 = GetInt(Mkbin([1,2])),
+ 258 = GetInt(Mkbin([1,2])),
+ 65534 = GetInt(Mkbin([255,254])),
+ 16776455 = GetInt(Mkbin([255,253,7])),
+ 4245492555 = GetInt(Mkbin([253,13,19,75])),
+ 4294967294 = GetInt(Mkbin([255,255,255,254])),
+ 4294967295 = GetInt(Mkbin([255,255,255,255])),
+ Eight = [200,1,19,128,222,42,97,111],
+ Cmp128(Eight, Uint(Eight)),
+ FunClause(catch GetInt(Mkbin(lists:seq(1,5))))
+ end,
+ Integer(),
+
+ Sint = fun(Bin) ->
+ case Bin of
+ <<I:8/signed>> -> I;
+ <<I:8/signed,_:3,_:5>> -> I;
+ Other -> {no_match,Other}
+ end
+ end,
+
+ SignedInteger = fun() ->
+ {no_match,_} = Sint(Mkbin([])),
+ {no_match,_} = Sint(Mkbin([1,2,3])),
+ 127 = Sint(Mkbin([127])),
+ -1 = Sint(Mkbin([255])),
+ -128 = Sint(Mkbin([128])),
+ 42 = Sint(Mkbin([42,255])),
+ 127 = Sint(Mkbin([127,255]))
+ end,
+ SignedInteger(),
+
+ Dynamic5 = fun(Bin, S1, S2, A, B) ->
+ case Bin of
+ <<A:S1,B:S2>> ->
%% io:format(\"~p ~p ~p ~p~n\", [S1,S2,A,B]),
- ok;
- _Other -> erlang:error(badmatch, [Bin,S1,S2,A,B])
- end
- end,
-
- Dynamic2 = fun(Bin, S1, F) when S1 >= 0 ->
- S2 = size(Bin) * 8 - S1,
- Dynamic5(Bin, S1, S2, (1 bsl S1) - 1, (1 bsl S2) - 1),
- F(Bin, S1-1, F);
- (_, _, _) -> ok
- end,
-
- Dynamic = fun(Bin, S1) ->
- Dynamic2(Bin, S1, Dynamic2)
- end,
-
- Dynamic(Mkbin([255]), 8),
- Dynamic(Mkbin([255,255]), 16),
- Dynamic(Mkbin([255,255,255]), 24),
- Dynamic(Mkbin([255,255,255,255]), 32),
-
- BigToLittle4 =
- fun([B0,B1,B2,B3,B4,B5,B6,B7|T], N, Acc, F) when N >= 8 ->
- F(T, N-8, [B0,B1,B2,B3,B4,B5,B6,B7|Acc], F);
- (List, N, Acc, _F) -> lists:sublist(List, 1, N) ++ Acc
- end,
-
- BigToLittle =
- fun(List, N) -> BigToLittle4(List, N, [], BigToLittle4) end,
-
- ReversedSublist =
- fun(_List, 0, Acc, _F) -> Acc;
- ([H|T], N, Acc, F) -> F(T, N-1, [H|Acc], F)
- end,
-
- TwoComplementAndReverse =
- fun([H|T], Carry, Acc, F) ->
- Sum = 1-H+Carry,
- F(T, Sum div 2, [Sum rem 2|Acc], F);
- ([], Carry, Acc, _F) -> [Carry|Acc]
- end,
-
- MakeInt = fun(_List, 0, Acc, _F) -> Acc;
- ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
- end,
-
- MakeSignedInt =
- fun(_List, 0) -> 0;
- ([0|_]=List, N) -> MakeInt(List, N, 0, MakeInt);
- ([1|_]=List0, N) ->
- List1 = ReversedSublist(List0, N, [], ReversedSublist),
- List2 = TwoComplementAndReverse(List1, 1, [],
- TwoComplementAndReverse),
- -MakeInt(List2, length(List2), 0, MakeInt)
- end,
-
- BitsToList =
- fun([H|T], 0, F) -> F(T, 16#80, F);
- ([H|_]=List, Mask, F) ->
- [case H band Mask of
+ ok;
+ _Other -> erlang:error(badmatch, [Bin,S1,S2,A,B])
+ end
+ end,
+
+ Dynamic2 = fun(Bin, S1, F) when S1 >= 0 ->
+ S2 = size(Bin) * 8 - S1,
+ Dynamic5(Bin, S1, S2, (1 bsl S1) - 1, (1 bsl S2) - 1),
+ F(Bin, S1-1, F);
+ (_, _, _) -> ok
+ end,
+
+ Dynamic = fun(Bin, S1) ->
+ Dynamic2(Bin, S1, Dynamic2)
+ end,
+
+ Dynamic(Mkbin([255]), 8),
+ Dynamic(Mkbin([255,255]), 16),
+ Dynamic(Mkbin([255,255,255]), 24),
+ Dynamic(Mkbin([255,255,255,255]), 32),
+
+ BigToLittle4 =
+ fun([B0,B1,B2,B3,B4,B5,B6,B7|T], N, Acc, F) when N >= 8 ->
+ F(T, N-8, [B0,B1,B2,B3,B4,B5,B6,B7|Acc], F);
+ (List, N, Acc, _F) -> lists:sublist(List, 1, N) ++ Acc
+ end,
+
+ BigToLittle =
+ fun(List, N) -> BigToLittle4(List, N, [], BigToLittle4) end,
+
+ ReversedSublist =
+ fun(_List, 0, Acc, _F) -> Acc;
+ ([H|T], N, Acc, F) -> F(T, N-1, [H|Acc], F)
+ end,
+
+ TwoComplementAndReverse =
+ fun([H|T], Carry, Acc, F) ->
+ Sum = 1-H+Carry,
+ F(T, Sum div 2, [Sum rem 2|Acc], F);
+ ([], Carry, Acc, _F) -> [Carry|Acc]
+ end,
+
+ MakeInt = fun(_List, 0, Acc, _F) -> Acc;
+ ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
+ end,
+
+ MakeSignedInt =
+ fun(_List, 0) -> 0;
+ ([0|_]=List, N) -> MakeInt(List, N, 0, MakeInt);
+ ([1|_]=List0, N) ->
+ List1 = ReversedSublist(List0, N, [], ReversedSublist),
+ List2 = TwoComplementAndReverse(List1, 1, [],
+ TwoComplementAndReverse),
+ -MakeInt(List2, length(List2), 0, MakeInt)
+ end,
+
+ BitsToList =
+ fun([H|T], 0, F) -> F(T, 16#80, F);
+ ([H|_]=List, Mask, F) ->
+ [case H band Mask of
0 -> 0;
_ -> 1
- end | F(List, Mask bsr 1, F)];
- ([], _, _F) -> []
- end,
-
- MoreDynamic3 =
- fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
- Action(Bin, List, Bef, Aft-Bef),
- F(Action, Bin, List, Bef, Aft-1, F);
- (_, _, _, _, _, _) -> ok
- end,
-
- MoreDynamic2 =
- fun(Action, Bin, [_|T]=List, Bef, F) ->
- MoreDynamic3(Action, Bin, List, Bef, size(Bin)*8,
- MoreDynamic3),
- F(Action, Bin, T, Bef+1, F);
- (_, _, [], _, _F) -> ok
- end,
-
- MoreDynamic1 =
- fun(Action, Bin) ->
- BitList = BitsToList(binary_to_list(Bin),16#80,BitsToList),
- MoreDynamic2(Action, Bin, BitList, 0, MoreDynamic2)
- end,
-
- MoreDynamic = fun() ->
+ end | F(List, Mask bsr 1, F)];
+ ([], _, _F) -> []
+ end,
+
+ MoreDynamic3 =
+ fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
+ Action(Bin, List, Bef, Aft-Bef),
+ F(Action, Bin, List, Bef, Aft-1, F);
+ (_, _, _, _, _, _) -> ok
+ end,
+
+ MoreDynamic2 =
+ fun(Action, Bin, [_|T]=List, Bef, F) ->
+ MoreDynamic3(Action, Bin, List, Bef, size(Bin)*8,
+ MoreDynamic3),
+ F(Action, Bin, T, Bef+1, F);
+ (_, _, [], _, _F) -> ok
+ end,
+
+ MoreDynamic1 =
+ fun(Action, Bin) ->
+ BitList = BitsToList(binary_to_list(Bin),16#80,BitsToList),
+ MoreDynamic2(Action, Bin, BitList, 0, MoreDynamic2)
+ end,
+
+ MoreDynamic = fun() ->
%% Unsigned big-endian numbers.
- Unsigned = fun(Bin, List, SkipBef, N) ->
- SkipAft = 8*size(Bin) - N - SkipBef,
- <<_:SkipBef,Int:N,_:SkipAft>> = Bin,
- Int = MakeInt(List, N, 0, MakeInt)
- end,
- MoreDynamic1(Unsigned, erlang:md5(Mkbin([42]))),
+ Unsigned = fun(Bin, List, SkipBef, N) ->
+ SkipAft = 8*size(Bin) - N - SkipBef,
+ <<_:SkipBef,Int:N,_:SkipAft>> = Bin,
+ Int = MakeInt(List, N, 0, MakeInt)
+ end,
+ MoreDynamic1(Unsigned, erlang:md5(Mkbin([42]))),
%% Signed big-endian numbers.
- Signed = fun(Bin, List, SkipBef, N) ->
- SkipAft = 8*size(Bin) - N - SkipBef,
- <<_:SkipBef,Int:N/signed,_:SkipAft>> = Bin,
- case MakeSignedInt(List, N) of
- Int -> ok;
- Other ->
- io:format(\"Bin = ~p,\", [Bin]),
+ Signed = fun(Bin, List, SkipBef, N) ->
+ SkipAft = 8*size(Bin) - N - SkipBef,
+ <<_:SkipBef,Int:N/signed,_:SkipAft>> = Bin,
+ case MakeSignedInt(List, N) of
+ Int -> ok;
+ Other ->
+ io:format(\"Bin = ~p,\", [Bin]),
io:format(\"SkipBef = ~p, N = ~p\",
[SkipBef,N]),
- io:format(\"Expected ~p, got ~p\",
+ io:format(\"Expected ~p, got ~p\",
[Int,Other])
- end
- end,
- MoreDynamic1(Signed, erlang:md5(Mkbin([43]))),
+ end
+ end,
+ MoreDynamic1(Signed, erlang:md5(Mkbin([43]))),
%% Unsigned little-endian numbers.
- UnsLittle = fun(Bin, List, SkipBef, N) ->
- SkipAft = 8*size(Bin) - N - SkipBef,
- <<_:SkipBef,Int:N/little,_:SkipAft>> = Bin,
- Int = MakeInt(BigToLittle(List, N), N, 0,
- MakeInt)
- end,
- MoreDynamic1(UnsLittle, erlang:md5(Mkbin([44]))),
+ UnsLittle = fun(Bin, List, SkipBef, N) ->
+ SkipAft = 8*size(Bin) - N - SkipBef,
+ <<_:SkipBef,Int:N/little,_:SkipAft>> = Bin,
+ Int = MakeInt(BigToLittle(List, N), N, 0,
+ MakeInt)
+ end,
+ MoreDynamic1(UnsLittle, erlang:md5(Mkbin([44]))),
%% Signed little-endian numbers.
- SignLittle = fun(Bin, List, SkipBef, N) ->
- SkipAft = 8*size(Bin) - N - SkipBef,
- <<_:SkipBef,Int:N/signed-little,_:SkipAft>> = Bin,
- Little = BigToLittle(List, N),
- Int = MakeSignedInt(Little, N)
- end,
- MoreDynamic1(SignLittle, erlang:md5(Mkbin([45])))
- end,
- MoreDynamic(),
-
- ok.
- ">>,
+ SignLittle = fun(Bin, List, SkipBef, N) ->
+ SkipAft = 8*size(Bin) - N - SkipBef,
+ <<_:SkipBef,Int:N/signed-little,_:SkipAft>> = Bin,
+ Little = BigToLittle(List, N),
+ Int = MakeSignedInt(Little, N)
+ end,
+ MoreDynamic1(SignLittle, erlang:md5(Mkbin([45])))
+ end,
+ MoreDynamic(),
+
+ ok.
+">>,
[ok] = scan(C),
- ok = evaluate(C, []).
+ok = evaluate(C, []).
%% OTP-5327. Adopted from emulator/test/bs_match_tail_SUITE.erl.
bs_match_tail_SUITE(Config) when is_list(Config) ->
@@ -1167,13 +1167,13 @@ bs_match_tail_SUITE(Config) when is_list(Config) ->
GetTailUnused = fun(<<A:15,_/binary>>) -> A end,
GetDynTailUsed = fun(Bin, Sz) ->
- <<A:Sz,T/binary>> = Bin,
- {A,T}
+ <<A:Sz,T/binary>> = Bin,
+ {A,T}
end,
GetDynTailUnused = fun(Bin, Sz) ->
- <<A:Sz,_/binary>> = Bin,
- A
+ <<A:Sz,_/binary>> = Bin,
+ A
end,
Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
@@ -1183,12 +1183,12 @@ bs_match_tail_SUITE(Config) when is_list(Config) ->
TestZeroTail2 = fun(<<_A:4,_B:4>>) -> ok end,
ZeroTail = fun() ->
- 7 = (catch TestZeroTail(Mkbin([7]))),
- {'EXIT',{function_clause,_}} =
- (catch TestZeroTail(Mkbin([1,2]))),
- {'EXIT',{function_clause,_}} =
- (catch TestZeroTail2(Mkbin([1,2,3])))
- end,
+ 7 = (catch TestZeroTail(Mkbin([7]))),
+ {'EXIT',{function_clause,_}} =
+ (catch TestZeroTail(Mkbin([1,2]))),
+ {'EXIT',{function_clause,_}} =
+ (catch TestZeroTail2(Mkbin([1,2,3])))
+ end,
ZeroTail(),
AlGetTailUsed = fun(<<A:16,T/binary>>) -> {A,T} end,
@@ -1196,40 +1196,40 @@ bs_match_tail_SUITE(Config) when is_list(Config) ->
AlGetTailUnused = fun(<<A:16,_/binary>>) -> A end,
Aligned = fun() ->
- Tail1 = Mkbin([]),
- {258,Tail1} = AlGetTailUsed(Mkbin([1,2])),
- Tail2 = Mkbin(lists:seq(1, 127)),
- {35091,Tail2} = AlGetTailUsed(Mkbin([137,19|Tail2])),
-
- 64896 = AlGetTailUnused(Mkbin([253,128])),
- 64895 = AlGetTailUnused(Mkbin([253,127|lists:seq(42, 255)])),
-
- Tail3 = Mkbin(lists:seq(0, 19)),
- {0,Tail1} = GetDynTailUsed(Tail1, 0),
- {0,Tail3} = GetDynTailUsed(Mkbin([Tail3]), 0),
- {73,Tail3} = GetDynTailUsed(Mkbin([73|Tail3]), 8),
-
- 0 = GetDynTailUnused(Mkbin([]), 0),
- 233 = GetDynTailUnused(Mkbin([233]), 8),
- 23 = GetDynTailUnused(Mkbin([23,22,2]), 8)
- end,
+ Tail1 = Mkbin([]),
+ {258,Tail1} = AlGetTailUsed(Mkbin([1,2])),
+ Tail2 = Mkbin(lists:seq(1, 127)),
+ {35091,Tail2} = AlGetTailUsed(Mkbin([137,19|Tail2])),
+
+ 64896 = AlGetTailUnused(Mkbin([253,128])),
+ 64895 = AlGetTailUnused(Mkbin([253,127|lists:seq(42, 255)])),
+
+ Tail3 = Mkbin(lists:seq(0, 19)),
+ {0,Tail1} = GetDynTailUsed(Tail1, 0),
+ {0,Tail3} = GetDynTailUsed(Mkbin([Tail3]), 0),
+ {73,Tail3} = GetDynTailUsed(Mkbin([73|Tail3]), 8),
+
+ 0 = GetDynTailUnused(Mkbin([]), 0),
+ 233 = GetDynTailUnused(Mkbin([233]), 8),
+ 23 = GetDynTailUnused(Mkbin([23,22,2]), 8)
+ end,
Aligned(),
-
+
UnAligned = fun() ->
- {'EXIT',{function_clause,_}} =
- (catch GetTailUsed(Mkbin([42]))),
- {'EXIT',{{badmatch,_},_}} =
- (catch GetDynTailUsed(Mkbin([137]), 3)),
- {'EXIT',{function_clause,_}} =
- (catch GetTailUnused(Mkbin([42,33]))),
- {'EXIT',{{badmatch,_},_}} =
- (catch GetDynTailUnused(Mkbin([44]), 7))
- end,
+ {'EXIT',{function_clause,_}} =
+ (catch GetTailUsed(Mkbin([42]))),
+ {'EXIT',{{badmatch,_},_}} =
+ (catch GetDynTailUsed(Mkbin([137]), 3)),
+ {'EXIT',{function_clause,_}} =
+ (catch GetTailUnused(Mkbin([42,33]))),
+ {'EXIT',{{badmatch,_},_}} =
+ (catch GetDynTailUnused(Mkbin([44]), 7))
+ end,
UnAligned(),
ok.
- ">>,
+">>,
[ok] = scan(C),
- ok = evaluate(C, []).
+ok = evaluate(C, []).
%% OTP-5327. Adopted from emulator/test/bs_match_bin_SUITE.erl.
bs_match_bin_SUITE(Config) when is_list(Config) ->
@@ -1241,110 +1241,110 @@ bs_match_bin_SUITE(Config) when is_list(Config) ->
<<B1:Sz1/binary,B2:Sz2/binary>> = B,
B1 = list_to_binary(lists:sublist(L, 1, Pos)),
B2 = list_to_binary(lists:nthtail(Pos, L)),
- Fun(L, B, Pos-1, Fun);
- (L, B, _, _Fun) -> ok
- end,
- Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
- L = lists:seq(0, 57),
- B = Mkbin(L),
- ByteSplit(L, B, size(B), ByteSplit),
- Id = fun(I) -> I end,
- MakeUnalignedSubBinary =
- fun(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
- Bin
+ Fun(L, B, Pos-1, Fun);
+ (L, B, _, _Fun) -> ok
end,
- Unaligned = MakeUnalignedSubBinary(B),
- ByteSplit(L, Unaligned, size(Unaligned), ByteSplit),
- ok.
- ">>,
+ Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
+ L = lists:seq(0, 57),
+ B = Mkbin(L),
+ ByteSplit(L, B, size(B), ByteSplit),
+ Id = fun(I) -> I end,
+ MakeUnalignedSubBinary =
+ fun(Bin0) ->
+ Bin1 = <<0:3,Bin0/binary,31:5>>,
+ Sz = size(Bin0),
+ <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
+ Bin
+ end,
+ Unaligned = MakeUnalignedSubBinary(B),
+ ByteSplit(L, Unaligned, size(Unaligned), ByteSplit),
+ ok.
+">>,
[ok] = scan(ByteSplitBinary),
- ok = evaluate(ByteSplitBinary, []),
- BitSplitBinary =
- <<"Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
+ok = evaluate(ByteSplitBinary, []),
+BitSplitBinary =
+<<"Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
MakeInt =
- fun(List, 0, Acc, _F) -> Acc;
- ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
- end,
-
- MakeBinFromList =
- fun(List, 0, _F) -> Mkbin([]);
- (List, N, F) ->
- list_to_binary([MakeInt(List, 8, 0, MakeInt),
- F(lists:nthtail(8, List), N-8, F)])
- end,
-
- BitSplitBinary3 =
- fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
- Action(Bin, List, Bef, (Aft-Bef) div 8 * 8),
- F(Action, Bin, List, Bef, Aft-8, F);
- (_, _, _, _, _, _) -> ok
- end,
-
- BitSplitBinary2 =
- fun(Action, Bin, [_|T]=List, Bef, F) ->
- BitSplitBinary3(Action, Bin, List, Bef, size(Bin)*8,
- BitSplitBinary3),
- F(Action, Bin, T, Bef+1, F);
- (Action, Bin, [], Bef, F) -> ok
- end,
-
- BitsToList =
- fun([H|T], 0, F) -> F(T, 16#80, F);
- ([H|_]=List, Mask, F) ->
- [case H band Mask of
- 0 -> 0;
- _ -> 1
- end | F(List, Mask bsr 1, F)];
- ([], _, _F) -> []
- end,
-
- BitSplitBinary1 =
- fun(Action, Bin) ->
- BitList = BitsToList(binary_to_list(Bin), 16#80,
- BitsToList),
- BitSplitBinary2(Action, Bin, BitList, 0, BitSplitBinary2)
- end,
-
- Fun = fun(Bin, List, SkipBef, N) ->
- SkipAft = 8*size(Bin) - N - SkipBef,
- <<I1:SkipBef,OutBin:N/binary-unit:1,I2:SkipAft>> = Bin,
- OutBin = MakeBinFromList(List, N, MakeBinFromList)
- end,
-
- BitSplitBinary1(Fun, erlang:md5(<<1,2,3>>)),
- Id = fun(I) -> I end,
- MakeUnalignedSubBinary =
- fun(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
- Bin
- end,
- BitSplitBinary1(Fun, MakeUnalignedSubBinary(erlang:md5(<<1,2,3>>))),
- ok.
- ">>,
+ fun(List, 0, Acc, _F) -> Acc;
+ ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
+ end,
+
+ MakeBinFromList =
+ fun(List, 0, _F) -> Mkbin([]);
+ (List, N, F) ->
+ list_to_binary([MakeInt(List, 8, 0, MakeInt),
+ F(lists:nthtail(8, List), N-8, F)])
+ end,
+
+ BitSplitBinary3 =
+ fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
+ Action(Bin, List, Bef, (Aft-Bef) div 8 * 8),
+ F(Action, Bin, List, Bef, Aft-8, F);
+ (_, _, _, _, _, _) -> ok
+ end,
+
+ BitSplitBinary2 =
+ fun(Action, Bin, [_|T]=List, Bef, F) ->
+ BitSplitBinary3(Action, Bin, List, Bef, size(Bin)*8,
+ BitSplitBinary3),
+ F(Action, Bin, T, Bef+1, F);
+ (Action, Bin, [], Bef, F) -> ok
+ end,
+
+ BitsToList =
+ fun([H|T], 0, F) -> F(T, 16#80, F);
+ ([H|_]=List, Mask, F) ->
+ [case H band Mask of
+ 0 -> 0;
+ _ -> 1
+ end | F(List, Mask bsr 1, F)];
+ ([], _, _F) -> []
+ end,
+
+ BitSplitBinary1 =
+ fun(Action, Bin) ->
+ BitList = BitsToList(binary_to_list(Bin), 16#80,
+ BitsToList),
+ BitSplitBinary2(Action, Bin, BitList, 0, BitSplitBinary2)
+ end,
+
+ Fun = fun(Bin, List, SkipBef, N) ->
+ SkipAft = 8*size(Bin) - N - SkipBef,
+ <<I1:SkipBef,OutBin:N/binary-unit:1,I2:SkipAft>> = Bin,
+ OutBin = MakeBinFromList(List, N, MakeBinFromList)
+ end,
+
+ BitSplitBinary1(Fun, erlang:md5(<<1,2,3>>)),
+ Id = fun(I) -> I end,
+ MakeUnalignedSubBinary =
+ fun(Bin0) ->
+ Bin1 = <<0:3,Bin0/binary,31:5>>,
+ Sz = size(Bin0),
+ <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
+ Bin
+ end,
+ BitSplitBinary1(Fun, MakeUnalignedSubBinary(erlang:md5(<<1,2,3>>))),
+ ok.
+">>,
[ok] = scan(BitSplitBinary),
- ok = evaluate(BitSplitBinary, []).
+ok = evaluate(BitSplitBinary, []).
-define(FAIL(Expr), "{'EXIT',{badarg,_}} = (catch " ??Expr ")").
-define(COF(Int0),
"(fun(Int) ->
true = <<Int:32/float>> =:= <<(float(Int)):32/float>>,
- true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
- end)(Nonliteral(" ??Int0 ")),
- true = <<" ??Int0 ":32/float>> =:= <<(float("??Int0")):32/float>>,
- true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
+ true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
+ end)(Nonliteral(" ??Int0 ")),
+true = <<" ??Int0 ":32/float>> =:= <<(float("??Int0")):32/float>>,
+true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
-define(COF64(Int0),
"(fun(Int) ->
true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
- end)(Nonliteral(" ??Int0 ")),
- true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
+ end)(Nonliteral(" ??Int0 ")),
+true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
%% OTP-5327. Adopted from parts of emulator/test/bs_construct_SUITE.erl.
bs_construct_SUITE(Config) when is_list(Config) ->
@@ -1352,138 +1352,138 @@ bs_construct_SUITE(Config) when is_list(Config) ->
Testf_1 = fun(W, B) -> "
?FAIL(<<42:W>>) ","
- ?FAIL(<<3.14:W/float>>) ","
- ?FAIL(<<B:W/binary>>) "
+ ?FAIL(<<3.14:W/float>>) ","
+ ?FAIL(<<B:W/binary>>) "
end,
- TestF = fun() -> "
+ TestF = fun() -> "
?FAIL(<<3.14>>) ","
- ?FAIL(<<<<1,2>>>>) ","
+ ?FAIL(<<<<1,2>>>>) ","
- ?FAIL(<<2.71/binary>>) ","
- ?FAIL(<<24334/binary>>) ","
- ?FAIL(<<24334344294788947129487129487219847/binary>>) ","
+ ?FAIL(<<2.71/binary>>) ","
+ ?FAIL(<<24334/binary>>) ","
+ ?FAIL(<<24334344294788947129487129487219847/binary>>) ","
- ?FAIL(<<<<1,2,3>>/float>>) ",
+ ?FAIL(<<<<1,2,3>>/float>>) ",
%% Negative field widths.
Testf_1(-8, <<1,2,3,4,5>>),"
?FAIL(<<42:(-16)>>) ","
- ?FAIL(<<3.14:(-8)/float>>) ","
- ?FAIL(<<<<23,56,0,2>>:(-16)/binary>>) ","
- ?FAIL(<<<<23,56,0,2>>:(2.5)/binary>>) ","
- ?FAIL(<<<<23,56,0,2>>:(anka)>>) "
+ ?FAIL(<<3.14:(-8)/float>>) ","
+ ?FAIL(<<<<23,56,0,2>>:(-16)/binary>>) ","
+ ?FAIL(<<<<23,56,0,2>>:(2.5)/binary>>) ","
+ ?FAIL(<<<<23,56,0,2>>:(anka)>>) "
end,
- TestF(),
+ TestF(),
- NotUsed1 = fun(I, BinString) -> <<I:32,BinString/binary>>, ok end,
+ NotUsed1 = fun(I, BinString) -> <<I:32,BinString/binary>>, ok end,
- NotUsed2 = fun(I, Sz) -> <<I:Sz>>, ok end,
+ NotUsed2 = fun(I, Sz) -> <<I:Sz>>, ok end,
- NotUsed3 = fun(I) -><<I:(-8)>>, ok end,
+ NotUsed3 = fun(I) -><<I:(-8)>>, ok end,
- NotUsed = fun() ->
- ok = NotUsed1(3, <<\"dum\">>),
+ NotUsed = fun() ->
+ ok = NotUsed1(3, <<\"dum\">>),
{'EXIT',{badarg,_}} = (catch NotUsed1(3, \"dum\")), "
- ?FAIL(NotUsed2(444, -2)) ","
- ?FAIL(NotUsed2(444, anka)) ","
- ?FAIL(NotUsed3(444)) "
+ ?FAIL(NotUsed2(444, -2)) ","
+ ?FAIL(NotUsed2(444, anka)) ","
+ ?FAIL(NotUsed3(444)) "
end,
- NotUsed(),
-
- InGuard3 = fun(Bin, A, B) when <<A:13,B:3>> == Bin -> 1;
- (Bin, A, B) when <<A:16,B/binary>> == Bin -> 2;
- (Bin, A, B) when <<A:14,B/float,3:2>> == Bin -> 3;
- (Bin, A, B) when {a,b,<<A:14,B/float,3:2>>} == Bin ->
- cant_happen;
- (_, _, _) -> nope
- end,
-
- InGuard = fun() ->
- 1 = InGuard3(<<16#74ad:16>>, 16#e95, 5),
- 2 = InGuard3(<<16#3A,16#F7,\"hello\">>, 16#3AF7, <<\"hello\">>),
+ NotUsed(),
+
+ InGuard3 = fun(Bin, A, B) when <<A:13,B:3>> == Bin -> 1;
+ (Bin, A, B) when <<A:16,B/binary>> == Bin -> 2;
+ (Bin, A, B) when <<A:14,B/float,3:2>> == Bin -> 3;
+ (Bin, A, B) when {a,b,<<A:14,B/float,3:2>>} == Bin ->
+ cant_happen;
+ (_, _, _) -> nope
+ end,
+
+ InGuard = fun() ->
+ 1 = InGuard3(<<16#74ad:16>>, 16#e95, 5),
+ 2 = InGuard3(<<16#3A,16#F7,\"hello\">>, 16#3AF7, <<\"hello\">>),
3 = InGuard3(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415),
- nope = InGuard3(<<1>>, 42, b),
- nope = InGuard3(<<1>>, a, b),
- nope = InGuard3(<<1,2>>, 1, 1),
- nope = InGuard3(<<4,5>>, 1, 2.71),
- nope = InGuard3(<<4,5>>, 1, <<12,13>>)
- end,
- InGuard(),
+ nope = InGuard3(<<1>>, 42, b),
+ nope = InGuard3(<<1>>, a, b),
+ nope = InGuard3(<<1,2>>, 1, 1),
+ nope = InGuard3(<<4,5>>, 1, 2.71),
+ nope = InGuard3(<<4,5>>, 1, <<12,13>>)
+ end,
+ InGuard(),
- Nonliteral = fun(X) -> X end,
+ Nonliteral = fun(X) -> X end,
- CoerceToFloat = fun() -> "
+ CoerceToFloat = fun() -> "
?COF(0) ","
- ?COF(-1) ","
- ?COF(1) ","
- ?COF(42) ","
- ?COF(255) ","
- ?COF(-255) ","
- ?COF64(298748888888888888888888888883478264866528467367364766666666666666663) ","
- ?COF64(-367546729879999999999947826486652846736736476555566666663) "
+ ?COF(-1) ","
+ ?COF(1) ","
+ ?COF(42) ","
+ ?COF(255) ","
+ ?COF(-255) ","
+ ?COF64(298748888888888888888888888883478264866528467367364766666666666666663) ","
+ ?COF64(-367546729879999999999947826486652846736736476555566666663) "
end,
- CoerceToFloat(),
- ok.
- ">>,
+ CoerceToFloat(),
+ ok.
+">>,
[ok] = scan(C1),
- ok = evaluate(C1, []),
+ok = evaluate(C1, []),
- %% There is another one, lib/compiler/test/bs_construct_SUITE.erl...
- C2 = <<"
+%% There is another one, lib/compiler/test/bs_construct_SUITE.erl...
+C2 = <<"
I = fun(X) -> X end,
Fail = fun() ->
- I_minus_777 = I(-777),
- I_minus_2047 = I(-2047),
+ I_minus_777 = I(-777),
+ I_minus_2047 = I(-2047),
%% One negative field size, but the sum of field sizes will be 1 byte.
%% Make sure that we reject that properly.
- {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
- 57:I_minus_2047/unit:8>>),
+ {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
+ 57:I_minus_2047/unit:8>>),
%% Same thing, but use literals.
- {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
- 57:(-2047)/unit:8>>),
+ {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
+ 57:(-2047)/unit:8>>),
%% Bad alignment.
- I_one = I(1),
- <<1:1>> = <<2375:I_one>>,
- <<3:2>> = <<45:1,2375:I_one>>,
- <<14:4>> = <<45:1,2375:I_one,918:2>>,
- <<118:7>> = <<45:1,2375:I_one,918:5>>,
+ I_one = I(1),
+ <<1:1>> = <<2375:I_one>>,
+ <<3:2>> = <<45:1,2375:I_one>>,
+ <<14:4>> = <<45:1,2375:I_one,918:2>>,
+ <<118:7>> = <<45:1,2375:I_one,918:5>>,
%% Not numbers.
- {'EXIT',{badarg,_}} = (catch <<45:(I(not_a_number))>>),
- {'EXIT',{badarg,_}} = (catch <<13:8,45:(I(not_a_number))>>),
+ {'EXIT',{badarg,_}} = (catch <<45:(I(not_a_number))>>),
+ {'EXIT',{badarg,_}} = (catch <<13:8,45:(I(not_a_number))>>),
%% Unaligned sizes.
- BadSz = I(7),
- <<2:4>> = <<34:4>>,
- <<34:7>> = <<34:BadSz>>,
+ BadSz = I(7),
+ <<2:4>> = <<34:4>>,
+ <<34:7>> = <<34:BadSz>>,
- [] = [X || {X} <- [], X == <<3:BadSz>>],
- [] = [X || {X} <- [], X == <<3:4>>]
- end,
+ [] = [X || {X} <- [], X == <<3:BadSz>>],
+ [] = [X || {X} <- [], X == <<3:4>>]
+ end,
Fail(),
FloatBin1 = fun(F) ->
- {<<1,2,3>>,F+3.0}
- end,
+ {<<1,2,3>>,F+3.0}
+ end,
FloatBin = fun() ->
%% Some more coverage.
- {<<1,2,3>>,7.0} = FloatBin1(4)
- end,
+ {<<1,2,3>>,7.0} = FloatBin1(4)
+ end,
FloatBin(),
ok.
- ">>,
+">>,
[ok] = scan(C2),
- ok = evaluate(C2, []).
+ok = evaluate(C2, []).
evaluate(B, Vars) when is_binary(B) ->
evaluate(binary_to_list(B), Vars);
@@ -1500,40 +1500,40 @@ evaluate(Str, Vars) ->
%% Bit syntax examples from the Reference Manual. OTP-5237.
refman_bit_syntax(Config) when is_list(Config) ->
%% Reference Manual "Bit Syntax Expressions"
- ?line Bin1 = <<1,17,42>>,
- ?line true = [1,17,42] =:= binary_to_list(Bin1),
- ?line Bin2 = <<"abc">>,
- ?line true = "abc" =:= binary_to_list(Bin2),
- ?line Bin3 = <<1,17,42:16>>,
- ?line true = [1,17,0,42] =:= binary_to_list(Bin3),
- ?line <<_A,_B,C:16>> = <<1,17,42:16>>,
- ?line true = C =:= 42,
- ?line <<D:16,_E,F>> = <<1,17,42:16>>,
- ?line true = D =:= 273,
- ?line true = F =:= 42,
+ Bin1 = <<1,17,42>>,
+ true = [1,17,42] =:= binary_to_list(Bin1),
+ Bin2 = <<"abc">>,
+ true = "abc" =:= binary_to_list(Bin2),
+ Bin3 = <<1,17,42:16>>,
+ true = [1,17,0,42] =:= binary_to_list(Bin3),
+ <<_A,_B,C:16>> = <<1,17,42:16>>,
+ true = C =:= 42,
+ <<D:16,_E,F>> = <<1,17,42:16>>,
+ true = D =:= 273,
+ true = F =:= 42,
<<_G,H/binary>> = <<1,17,42:16>>,
- ?line true = H =:= <<17,0,42>>,
+ true = H =:= <<17,0,42>>,
- ?line [ok] =
+ [ok] =
scan(<<"Bin1 = <<1,17,42>>,
true = [1,17,42] =:= binary_to_list(Bin1),
- Bin2 = <<\"abc\">>,
+ Bin2 = <<\"abc\">>,
true = \"abc\" =:= binary_to_list(Bin2),
Bin3 = <<1,17,42:16>>,
- true =
- [1,17,0,42] =:= binary_to_list(Bin3),
- <<A,B,C:16>> = <<1,17,42:16>>,
- true = C =:= 42,
- <<D:16,E,F>> = <<1,17,42:16>>,
- true = D =:= 273,
- true = F =:= 42,
- <<G,H/binary>> = <<1,17,42:16>>,
- true = H =:= <<17,0,42>>,
- ok.">>),
+ true =
+ [1,17,0,42] =:= binary_to_list(Bin3),
+ <<A,B,C:16>> = <<1,17,42:16>>,
+ true = C =:= 42,
+ <<D:16,E,F>> = <<1,17,42:16>>,
+ true = D =:= 273,
+ true = F =:= 42,
+ <<G,H/binary>> = <<1,17,42:16>>,
+ true = H =:= <<17,0,42>>,
+ ok.">>),
%% Binary comprehensions.
- ?line <<2,4,6>> = << << (X*2) >> || <<X>> <= << 1,2,3 >> >>,
- ok.
+ <<2,4,6>> = << << (X*2) >> || <<X>> <= << 1,2,3 >> >>,
+ ok.
-define(IP_VERSION, 4).
@@ -1545,7 +1545,7 @@ progex_bit_syntax(Config) when is_list(Config) ->
true = [1, 17, 42] =:= binary_to_list(Bin11),
Bin12 = <<"abc">>,
true = [97, 98, 99] =:= binary_to_list(Bin12),
-
+
A = 1, B = 17, C = 42,
Bin2 = <<A, B, C:16>>,
true = [1, 17, 00, 42] =:= binary_to_list(Bin2),
@@ -1558,10 +1558,10 @@ progex_bit_syntax(Config) when is_list(Config) ->
DgramSize = byte_size(Dgram),
case Dgram of
<<?IP_VERSION:4, HLen:4, SrvcType:8, TotLen:16,
- ID:16, Flgs:3, FragOff:13,
- TTL:8, Proto:8, HdrChkSum:16,
- SrcIP:32, DestIP:32,
- RestDgram/binary>> when HLen>=5, 4*HLen=<DgramSize ->
+ ID:16, Flgs:3, FragOff:13,
+ TTL:8, Proto:8, HdrChkSum:16,
+ SrcIP:32, DestIP:32,
+ RestDgram/binary>> when HLen>=5, 4*HLen=<DgramSize ->
OptsLen = 4*(HLen - ?IP_MIN_HDR_LEN),
<<Opts:OptsLen/binary,Data/binary>> = RestDgram,
{SrvcType, TotLen, Flgs, FragOff, ID, HdrChkSum,
@@ -1598,57 +1598,57 @@ progex_bit_syntax(Config) when is_list(Config) ->
B2 = triples_to_bin2(BL),
true = Lst =:= binary_to_list(B2),
- ?line [ok] = scan(
- <<"Bin11 = <<1, 17, 42>>,
+ [ok] = scan(
+ <<"Bin11 = <<1, 17, 42>>,
true = [1, 17, 42] =:= binary_to_list(Bin11),
- Bin12 = <<\"abc\">>,
+ Bin12 = <<\"abc\">>,
true = [97, 98, 99] =:= binary_to_list(Bin12),
- A = 1, B = 17, C = 42,
- Bin2 = <<A, B, C:16>>,
- true = [1, 17, 00, 42] =:= binary_to_list(Bin2),
- <<D:16, E, F/binary>> = Bin2,
- true = D =:= 273,
- true = E =:= 00,
- true = [42] =:= binary_to_list(F),
-
- Fun4 = fun(Dgram) ->
- DgramSize = byte_size(Dgram),
- case Dgram of
- <<4:4, HLen:4, SrvcType:8, TotLen:16,
- ID:16, Flgs:3, FragOff:13,
- TTL:8, Proto:8, HdrChkSum:16,
- SrcIP:32, DestIP:32,
- RestDgram/binary>> when HLen>=5,
- 4*HLen=<DgramSize ->
- OptsLen = 4*(HLen - 5),
- <<Opts:OptsLen/binary,Data/binary>> = RestDgram,
- {SrvcType, TotLen, Flgs, FragOff, ID, HdrChkSum,
- Proto, TTL, SrcIP, DestIP, Data, Opts};
- _ ->
- not_ok
- end
- end,
- true = Fun4(<<>>) =:= not_ok,
- true = is_tuple(Fun4(list_to_binary
- ([<<4:4,5:4>>,list_to_binary(lists:seq(1,255))]))),
-
- X = 23432324, Y = 24324234,
- <<10:7>> = <<X:1, Y:6>>,
- Z = 234324324,
- XYZ = <<X:1, Y:6, Z:1>>,
- true = [20] =:= binary_to_list(XYZ),
- Hello1 = <<\"hello\">>,
+ A = 1, B = 17, C = 42,
+ Bin2 = <<A, B, C:16>>,
+ true = [1, 17, 00, 42] =:= binary_to_list(Bin2),
+ <<D:16, E, F/binary>> = Bin2,
+ true = D =:= 273,
+ true = E =:= 00,
+ true = [42] =:= binary_to_list(F),
+
+ Fun4 = fun(Dgram) ->
+ DgramSize = byte_size(Dgram),
+ case Dgram of
+ <<4:4, HLen:4, SrvcType:8, TotLen:16,
+ ID:16, Flgs:3, FragOff:13,
+ TTL:8, Proto:8, HdrChkSum:16,
+ SrcIP:32, DestIP:32,
+ RestDgram/binary>> when HLen>=5,
+ 4*HLen=<DgramSize ->
+ OptsLen = 4*(HLen - 5),
+ <<Opts:OptsLen/binary,Data/binary>> = RestDgram,
+ {SrvcType, TotLen, Flgs, FragOff, ID, HdrChkSum,
+ Proto, TTL, SrcIP, DestIP, Data, Opts};
+ _ ->
+ not_ok
+ end
+ end,
+ true = Fun4(<<>>) =:= not_ok,
+ true = is_tuple(Fun4(list_to_binary
+ ([<<4:4,5:4>>,list_to_binary(lists:seq(1,255))]))),
+
+ X = 23432324, Y = 24324234,
+ <<10:7>> = <<X:1, Y:6>>,
+ Z = 234324324,
+ XYZ = <<X:1, Y:6, Z:1>>,
+ true = [20] =:= binary_to_list(XYZ),
+ Hello1 = <<\"hello\">>,
Hello2 = <<$h,$e,$l,$l,$o>>,
- true = \"hello\" =:= binary_to_list(Hello1),
+ true = \"hello\" =:= binary_to_list(Hello1),
true = \"hello\" =:= binary_to_list(Hello2),
FunM1 = fun(<<X1:7/binary, Y1:1/binary>>) -> {X1,Y1} end,
- true = {<<\"1234567\">>,<<\"8\">>} =:= FunM1(<<\"12345678\">>),
+ true = {<<\"1234567\">>,<<\"8\">>} =:= FunM1(<<\"12345678\">>),
FunM2 = fun(<<_X1:7/binary-unit:7, _Y1:1/binary-unit:1>>) -> ok;
(_) -> not_ok end,
- true = not_ok =:= FunM2(<<\"1\">>),
+ true = not_ok =:= FunM2(<<\"1\">>),
ok.">>),
ok.
@@ -1672,552 +1672,552 @@ triples_to_bin2([], Acc) ->
%% Record examples from Programming Examples. OTP-5237.
progex_records(Config) when is_list(Config) ->
Test1 =
- <<"-module(recs).
+ <<"-module(recs).
-record(person, {name = \"\", phone = [], address}).
-record(name, {first = \"Robert\", last = \"Ericsson\"}).
-record(person2, {name = #name{}, phone}).
- -export([t/0]).
+-export([t/0]).
- t() ->
- _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
+t() ->
+ _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
\"Robert\" = _P1#person.name,
[0,8,2,3,4,3,1,2] = _P1#person.phone,
- undefined = _P1#person.address,
+ undefined = _P1#person.address,
- _P2 = #person{name = \"Jakob\", _ = '_'},
+ _P2 = #person{name = \"Jakob\", _ = '_'},
\"Jakob\" = _P2#person.name,
'_' = _P2#person.phone,
- '_' = _P2#person.address,
-
- P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
+ '_' = _P2#person.address,
+
+ P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
\"Joe\" = P#person.name,
[0,8,2,3,4,3,1,2] = P#person.phone,
- undefined = P#person.address,
+ undefined = P#person.address,
- P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
+ P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
P2 = P1#person{name=\"Robert\"},
\"Robert\" = P2#person.name,
[1,2,3] = P2#person.phone,
- \"A street\" = P2#person.address,
+ \"A street\" = P2#person.address,
a_person = foo(P1),
- {found, [1,2,3]} =
- find_phone([#person{name = a},
- #person{name = b, phone = [3,2,1]},
- #person{name = c, phone = [1,2,3]}],
- c),
+ {found, [1,2,3]} =
+ find_phone([#person{name = a},
+ #person{name = b, phone = [3,2,1]},
+ #person{name = c, phone = [1,2,3]}],
+ c),
- P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
+ P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
#person{name = Name} = P3,
- \"Joe\" = Name,
+ \"Joe\" = Name,
\"Robert\" = demo(),
ok.
- foo(P) when is_record(P, person) -> a_person;
- foo(_) -> not_a_person.
+foo(P) when is_record(P, person) -> a_person;
+foo(_) -> not_a_person.
- find_phone([#person{name=Name, phone=Phone} | _], Name) ->
- {found, Phone};
- find_phone([_| T], Name) ->
- find_phone(T, Name);
- find_phone([], _Name) ->
- not_found.
+find_phone([#person{name=Name, phone=Phone} | _], Name) ->
+ {found, Phone};
+find_phone([_| T], Name) ->
+ find_phone(T, Name);
+find_phone([], _Name) ->
+ not_found.
- demo() ->
- P = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
+demo() ->
+ P = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
phone=123},
- _First = (P#person2.name)#name.first.
- ">>,
- ?line ok = run_file(Config, recs, Test1),
+ _First = (P#person2.name)#name.first.
+">>,
+ ok = run_file(Config, recs, Test1),
- Test1_shell =
- <<"rd(person, {name = \"\", phone = [], address}),
+Test1_shell =
+<<"rd(person, {name = \"\", phone = [], address}),
rd(name, {first = \"Robert\", last = \"Ericsson\"}),
rd(person2, {name = #name{}, phone}),
- _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
+ _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
\"Robert\" = _P1#person.name,
[0,8,2,3,4,3,1,2] = _P1#person.phone,
- undefined = _P1#person.address,
+ undefined = _P1#person.address,
- _P2 = #person{name = \"Jakob\", _ = '_'},
+ _P2 = #person{name = \"Jakob\", _ = '_'},
\"Jakob\" = _P2#person.name,
'_' = _P2#person.phone,
- '_' = _P2#person.address,
+ '_' = _P2#person.address,
- P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
+ P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
\"Joe\" = P#person.name,
[0,8,2,3,4,3,1,2] = P#person.phone,
- undefined = P#person.address,
+ undefined = P#person.address,
- P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
+ P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
P2 = P1#person{name=\"Robert\"},
\"Robert\" = P2#person.name,
[1,2,3] = P2#person.phone,
- \"A street\" = P2#person.address,
+ \"A street\" = P2#person.address,
Foo = fun(P) when is_record(P, person) -> a_person;
(_) -> not_a_person
end,
- a_person = Foo(P1),
-
- Find = fun([#person{name=Name, phone=Phone} | _], Name, Fn) ->
- {found, Phone};
- ([_| T], Name, Fn) ->
- Fn(T, Name, Fn);
- ([], _Name, _Fn) ->
- not_found
- end,
-
- {found, [1,2,3]} = Find([#person{name = a},
- #person{name = b, phone = [3,2,1]},
- #person{name = c, phone = [1,2,3]}],
- c,
- Find),
-
- P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
+ a_person = Foo(P1),
+
+ Find = fun([#person{name=Name, phone=Phone} | _], Name, Fn) ->
+ {found, Phone};
+ ([_| T], Name, Fn) ->
+ Fn(T, Name, Fn);
+ ([], _Name, _Fn) ->
+ not_found
+ end,
+
+ {found, [1,2,3]} = Find([#person{name = a},
+ #person{name = b, phone = [3,2,1]},
+ #person{name = c, phone = [1,2,3]}],
+ c,
+ Find),
+
+ P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
#person{name = Name} = P3,
- \"Joe\" = Name,
+ \"Joe\" = Name,
Demo = fun() ->
- P17 = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
+ P17 = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
phone=123},
- _First = (P17#person2.name)#name.first
- end,
+ _First = (P17#person2.name)#name.first
+ end,
- \"Robert\" = Demo(),
+ \"Robert\" = Demo(),
ok.
- ">>,
- ?line [ok] = scan(Test1_shell),
+">>,
+ [ok] = scan(Test1_shell),
- Test2 =
- <<"-module(recs).
+Test2 =
+<<"-module(recs).
-record(person, {name, age, phone = [], dict = []}).
- -compile(export_all).
+-compile(export_all).
- t() -> ok.
+t() -> ok.
- make_hacker_without_phone(Name, Age) ->
- #person{name = Name, age = Age,
- dict = [{computer_knowledge, excellent},
- {drinks, coke}]}.
- print(#person{name = Name, age = Age,
- phone = Phone, dict = Dict}) ->
- io:format(\"Name: ~s, Age: ~w, Phone: ~w ~n\"
+make_hacker_without_phone(Name, Age) ->
+ #person{name = Name, age = Age,
+ dict = [{computer_knowledge, excellent},
+ {drinks, coke}]}.
+print(#person{name = Name, age = Age,
+ phone = Phone, dict = Dict}) ->
+ io:format(\"Name: ~s, Age: ~w, Phone: ~w ~n\"
\"Dictionary: ~w.~n\", [Name, Age, Phone, Dict]).
birthday(P) when record(P, person) ->
- P#person{age = P#person.age + 1}.
+ P#person{age = P#person.age + 1}.
- register_two_hackers() ->
- Hacker1 = make_hacker_without_phone(\"Joe\", 29),
+register_two_hackers() ->
+ Hacker1 = make_hacker_without_phone(\"Joe\", 29),
OldHacker = birthday(Hacker1),
%% The central_register_server should have
%% an interface function for this.
- central_register_server ! {register_person, Hacker1},
- central_register_server ! {register_person,
- OldHacker#person{name = \"Robert\",
+ central_register_server ! {register_person, Hacker1},
+ central_register_server ! {register_person,
+ OldHacker#person{name = \"Robert\",
phone = [0,8,3,2,4,5,3,1]}}.
- ">>,
- ?line ok = run_file(Config, recs, Test2),
- ok.
+">>,
+ ok = run_file(Config, recs, Test2),
+ok.
%% List comprehension examples from Programming Examples. OTP-5237.
progex_lc(Config) when is_list(Config) ->
Test1 =
- <<"-module(lc).
+ <<"-module(lc).
-export([t/0]).
- t() ->
- [a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
- [4,5,6] = [X || X <- [1,2,a,3,4,b,5,6], integer(X), X > 3],
- [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
- [{X, Y} || X <- [1,2,3], Y <- [a,b]],
-
- [1,2,3,4,5,6,7,8] = sort([4,5,1,8,3,6,7,2]),
- [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
- perms([b,u,g]),
- [] = pyth(11),
- [{3,4,5},{4,3,5}] = pyth(12),
- [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
- {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
- {16,12,20}] = pyth(50),
- [] = pyth1(11),
- [{3,4,5},{4,3,5}] = pyth1(12),
- [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
- {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
- {16,12,20}] = pyth1(50),
- [1,2,3,4,5] = append([[1,2,3],[4,5]]),
- [2,3,4] = map(fun(X) -> X + 1 end, [1,2,3]),
- [2,4] = filter(fun(X) -> X > 1 end, [0,2,4]),
- [1,2,3,7] = select(b,[{a,1},{b,2},{c,3},{b,7}]),
- [2,7] = select2(b,[{a,1},{b,2},{c,3},{b,7}]),
- ok.
+t() ->
+ [a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
+ [4,5,6] = [X || X <- [1,2,a,3,4,b,5,6], integer(X), X > 3],
+ [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
+ [{X, Y} || X <- [1,2,3], Y <- [a,b]],
+
+ [1,2,3,4,5,6,7,8] = sort([4,5,1,8,3,6,7,2]),
+ [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
+ perms([b,u,g]),
+ [] = pyth(11),
+ [{3,4,5},{4,3,5}] = pyth(12),
+ [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
+ {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
+ {16,12,20}] = pyth(50),
+ [] = pyth1(11),
+ [{3,4,5},{4,3,5}] = pyth1(12),
+ [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
+ {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
+ {16,12,20}] = pyth1(50),
+ [1,2,3,4,5] = append([[1,2,3],[4,5]]),
+ [2,3,4] = map(fun(X) -> X + 1 end, [1,2,3]),
+ [2,4] = filter(fun(X) -> X > 1 end, [0,2,4]),
+ [1,2,3,7] = select(b,[{a,1},{b,2},{c,3},{b,7}]),
+ [2,7] = select2(b,[{a,1},{b,2},{c,3},{b,7}]),
+ ok.
- sort([Pivot|T]) ->
- sort([ X || X <- T, X < Pivot]) ++
- [Pivot] ++
- sort([ X || X <- T, X >= Pivot]);
- sort([]) -> [].
-
- perms([]) -> [[]];
- perms(L) -> [[H|T] || H <- L, T <- perms(L--[H])].
-
- pyth(N) ->
- [ {A,B,C} ||
- A <- lists:seq(1,N),
- B <- lists:seq(1,N),
- C <- lists:seq(1,N),
- A+B+C =< N,
- A*A+B*B == C*C
- ].
-
- pyth1(N) ->
- [{A,B,C} ||
- A <- lists:seq(1,N),
- B <- lists:seq(1,N-A+1),
- C <- lists:seq(1,N-A-B+2),
- A+B+C =< N,
- A*A+B*B == C*C ].
-
- append(L) -> [X || L1 <- L, X <- L1].
- map(Fun, L) -> [Fun(X) || X <- L].
- filter(Pred, L) -> [X || X <- L, Pred(X)].
-
- select(X, L) -> [Y || {X, Y} <- L].
- select2(X, L) -> [Y || {X1, Y} <- L, X == X1].
- ">>,
- ?line ok = run_file(Config, lc, Test1),
-
- Test1_shell =
- <<"[a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
+sort([Pivot|T]) ->
+ sort([ X || X <- T, X < Pivot]) ++
+ [Pivot] ++
+ sort([ X || X <- T, X >= Pivot]);
+sort([]) -> [].
+
+perms([]) -> [[]];
+perms(L) -> [[H|T] || H <- L, T <- perms(L--[H])].
+
+pyth(N) ->
+ [ {A,B,C} ||
+ A <- lists:seq(1,N),
+ B <- lists:seq(1,N),
+ C <- lists:seq(1,N),
+ A+B+C =< N,
+ A*A+B*B == C*C
+ ].
+
+pyth1(N) ->
+ [{A,B,C} ||
+ A <- lists:seq(1,N),
+ B <- lists:seq(1,N-A+1),
+ C <- lists:seq(1,N-A-B+2),
+ A+B+C =< N,
+ A*A+B*B == C*C ].
+
+append(L) -> [X || L1 <- L, X <- L1].
+map(Fun, L) -> [Fun(X) || X <- L].
+filter(Pred, L) -> [X || X <- L, Pred(X)].
+
+select(X, L) -> [Y || {X, Y} <- L].
+select2(X, L) -> [Y || {X1, Y} <- L, X == X1].
+">>,
+ ok = run_file(Config, lc, Test1),
+
+Test1_shell =
+<<"[a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
[4,5,6] = [X || X <- [1,2,a,3,4,b,5,6], integer(X), X > 3],
- [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
- [{X, Y} || X <- [1,2,3], Y <- [a,b]],
-
- Sort = fun([Pivot|T], Fn) ->
- Fn([ X || X <- T, X < Pivot], Fn) ++
- [Pivot] ++
- Fn([ X || X <- T, X >= Pivot], Fn);
- ([], _Fn) -> []
- end,
-
- [1,2,3,4,5,6,7,8] = Sort([4,5,1,8,3,6,7,2], Sort),
- Perms = fun([], _Fn) -> [[]];
- (L, Fn) -> [[H|T] || H <- L, T <- Fn(L--[H], Fn)]
- end,
- [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
- Perms([b,u,g], Perms),
-
- Pyth = fun(N) ->
- [ {A,B,C} ||
- A <- lists:seq(1,N),
- B <- lists:seq(1,N),
- C <- lists:seq(1,N),
- A+B+C =< N,
- A*A+B*B == C*C
- ]
- end,
-
- [] = Pyth(11),
- [{3,4,5},{4,3,5}] = Pyth(12),
- %%[{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
- %% {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
- %% {16,12,20}] = Pyth(50),
-
- Pyth1 = fun(N) ->
- [{A,B,C} ||
- A <- lists:seq(1,N),
- B <- lists:seq(1,N-A+1),
- C <- lists:seq(1,N-A-B+2),
- A+B+C =< N,
- A*A+B*B == C*C ]
- end,
-
- [] = Pyth1(11),
- [{3,4,5},{4,3,5}] = Pyth1(12),
- [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
- {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
- {16,12,20}] = Pyth1(50),
-
- Append = fun(L) -> [X || L1 <- L, X <- L1] end,
- [1,2,3,4,5] = Append([[1,2,3],[4,5]]),
- Map = fun(Fun, L) -> [Fun(X) || X <- L] end,
- [2,3,4] = Map(fun(X) -> X + 1 end, [1,2,3]),
- Filter = fun(Pred, L) -> [X || X <- L, Pred(X)] end,
- [2,4] = Filter(fun(X) -> X > 1 end, [0,2,4]),
-
- Select = fun(X, L) -> [Y || {X, Y} <- L] end,
- [1,2,3,7] = Select(b,[{a,1},{b,2},{c,3},{b,7}]),
- Select2 = fun(X, L) -> [Y || {X1, Y} <- L, X == X1] end,
- [2,7] = Select2(b,[{a,1},{b,2},{c,3},{b,7}]),
- ok.
- ">>,
- ?line [ok] = scan(Test1_shell),
- ok.
+ [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
+ [{X, Y} || X <- [1,2,3], Y <- [a,b]],
+
+ Sort = fun([Pivot|T], Fn) ->
+ Fn([ X || X <- T, X < Pivot], Fn) ++
+ [Pivot] ++
+ Fn([ X || X <- T, X >= Pivot], Fn);
+ ([], _Fn) -> []
+ end,
+
+ [1,2,3,4,5,6,7,8] = Sort([4,5,1,8,3,6,7,2], Sort),
+ Perms = fun([], _Fn) -> [[]];
+ (L, Fn) -> [[H|T] || H <- L, T <- Fn(L--[H], Fn)]
+ end,
+ [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
+ Perms([b,u,g], Perms),
+
+ Pyth = fun(N) ->
+ [ {A,B,C} ||
+ A <- lists:seq(1,N),
+ B <- lists:seq(1,N),
+ C <- lists:seq(1,N),
+ A+B+C =< N,
+ A*A+B*B == C*C
+ ]
+ end,
+
+ [] = Pyth(11),
+ [{3,4,5},{4,3,5}] = Pyth(12),
+%%[{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
+%% {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
+%% {16,12,20}] = Pyth(50),
+
+ Pyth1 = fun(N) ->
+ [{A,B,C} ||
+ A <- lists:seq(1,N),
+ B <- lists:seq(1,N-A+1),
+ C <- lists:seq(1,N-A-B+2),
+ A+B+C =< N,
+ A*A+B*B == C*C ]
+ end,
+
+ [] = Pyth1(11),
+ [{3,4,5},{4,3,5}] = Pyth1(12),
+ [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
+ {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
+ {16,12,20}] = Pyth1(50),
+
+ Append = fun(L) -> [X || L1 <- L, X <- L1] end,
+ [1,2,3,4,5] = Append([[1,2,3],[4,5]]),
+ Map = fun(Fun, L) -> [Fun(X) || X <- L] end,
+ [2,3,4] = Map(fun(X) -> X + 1 end, [1,2,3]),
+ Filter = fun(Pred, L) -> [X || X <- L, Pred(X)] end,
+ [2,4] = Filter(fun(X) -> X > 1 end, [0,2,4]),
+
+ Select = fun(X, L) -> [Y || {X, Y} <- L] end,
+ [1,2,3,7] = Select(b,[{a,1},{b,2},{c,3},{b,7}]),
+ Select2 = fun(X, L) -> [Y || {X1, Y} <- L, X == X1] end,
+ [2,7] = Select2(b,[{a,1},{b,2},{c,3},{b,7}]),
+ ok.
+">>,
+ [ok] = scan(Test1_shell),
+ok.
%% Funs examples from Programming Examples. OTP-5237.
progex_funs(Config) when is_list(Config) ->
Test1 =
- <<"-module(funs).
+ <<"-module(funs).
-compile(export_all).
- double([H|T]) -> [2*H|double(T)];
- double([]) -> [].
+double([H|T]) -> [2*H|double(T)];
+double([]) -> [].
- add_one([H|T]) -> [H+1|add_one(T)];
- add_one([]) -> [].
+add_one([H|T]) -> [H+1|add_one(T)];
+add_one([]) -> [].
- map(F, [H|T]) -> [F(H)|map(F, T)];
- map(F, []) -> [].
+map(F, [H|T]) -> [F(H)|map(F, T)];
+map(F, []) -> [].
- double2(L) -> map(fun(X) -> 2*X end, L).
- add_one2(L) -> map(fun(X) -> 1 + X end, L).
+double2(L) -> map(fun(X) -> 2*X end, L).
+add_one2(L) -> map(fun(X) -> 1 + X end, L).
- print_list(Stream, [H|T]) ->
- io:format(Stream, \"~p~n\", [H]),
+print_list(Stream, [H|T]) ->
+ io:format(Stream, \"~p~n\", [H]),
print_list(Stream, T);
- print_list(Stream, []) ->
- true.
-
- broadcast(Msg, [Pid|Pids]) ->
- Pid ! Msg,
- broadcast(Msg, Pids);
- broadcast(_, []) ->
- true.
-
- foreach(F, [H|T]) ->
- F(H),
- foreach(F, T);
- foreach(F, []) ->
- ok.
+ print_list(Stream, []) ->
+ true.
+
+broadcast(Msg, [Pid|Pids]) ->
+ Pid ! Msg,
+ broadcast(Msg, Pids);
+broadcast(_, []) ->
+ true.
+
+foreach(F, [H|T]) ->
+ F(H),
+ foreach(F, T);
+foreach(F, []) ->
+ ok.
- print_list2(S, L) ->
- foreach(fun(H) -> io:format(S, \"~p~n\",[H]) end, L).
+print_list2(S, L) ->
+ foreach(fun(H) -> io:format(S, \"~p~n\",[H]) end, L).
broadcast2(M, L) -> foreach(fun(Pid) -> Pid ! M end, L).
- t1() -> map(fun(X) -> 2 * X end, [1,2,3,4,5]).
+t1() -> map(fun(X) -> 2 * X end, [1,2,3,4,5]).
- t2() -> map(fun double/1, [1,2,3,4,5]).
+t2() -> map(fun double/1, [1,2,3,4,5]).
- t3() -> map({?MODULE, double3}, [1,2,3,4,5]).
+t3() -> map({?MODULE, double3}, [1,2,3,4,5]).
- double3(X) -> X * 2.
+double3(X) -> X * 2.
- f(F, Args) when function(F) ->
- apply(F, Args);
- f(N, _) when integer(N) ->
- N.
+f(F, Args) when function(F) ->
+ apply(F, Args);
+f(N, _) when integer(N) ->
+ N.
- print_list3(File, List) ->
- {ok, Stream} = file:open(File, write),
- foreach(fun(X) -> io:format(Stream,\"~p~n\",[X]) end, List),
+print_list3(File, List) ->
+ {ok, Stream} = file:open(File, write),
+ foreach(fun(X) -> io:format(Stream,\"~p~n\",[X]) end, List),
file:close(Stream).
- print_list4(File, List) ->
- {ok, Stream} = file:open(File, write),
- foreach(fun(File) ->
- io:format(Stream,\"~p~n\",[File])
+print_list4(File, List) ->
+ {ok, Stream} = file:open(File, write),
+ foreach(fun(File) ->
+ io:format(Stream,\"~p~n\",[File])
end, List),
- file:close(Stream).
+ file:close(Stream).
+
+any(Pred, [H|T]) ->
+ case Pred(H) of
+ true -> true;
+ false -> any(Pred, T)
+ end;
+any(Pred, []) ->
+ false.
- any(Pred, [H|T]) ->
- case Pred(H) of
- true -> true;
- false -> any(Pred, T)
- end;
- any(Pred, []) ->
- false.
-
- all(Pred, [H|T]) ->
- case Pred(H) of
- true -> all(Pred, T);
- false -> false
- end;
- all(Pred, []) ->
- true.
-
- foldl(F, Accu, [Hd|Tail]) ->
- foldl(F, F(Hd, Accu), Tail);
- foldl(F, Accu, []) -> Accu.
-
- mapfoldl(F, Accu0, [Hd|Tail]) ->
- {R,Accu1} = F(Hd, Accu0),
- {Rs,Accu2} = mapfoldl(F, Accu1, Tail),
- {[R|Rs], Accu2};
- mapfoldl(F, Accu, []) -> {[], Accu}.
-
- filter(F, [H|T]) ->
- case F(H) of
- true -> [H|filter(F, T)];
- false -> filter(F, T)
- end;
- filter(F, []) -> [].
-
- diff(L1, L2) ->
- filter(fun(X) -> not lists:member(X, L2) end, L1).
-
- intersection(L1,L2) -> filter(fun(X) -> lists:member(X,L1) end, L2).
-
- takewhile(Pred, [H|T]) ->
- case Pred(H) of
- true -> [H|takewhile(Pred, T)];
- false -> []
- end;
- takewhile(Pred, []) ->
- [].
-
- dropwhile(Pred, [H|T]) ->
- case Pred(H) of
- true -> dropwhile(Pred, T);
- false -> [H|T]
- end;
- dropwhile(Pred, []) ->
- [].
-
- splitlist(Pred, L) ->
- splitlist(Pred, L, []).
-
- splitlist(Pred, [H|T], L) ->
- case Pred(H) of
- true -> splitlist(Pred, T, [H|L]);
- false -> {lists:reverse(L), [H|T]}
- end;
- splitlist(Pred, [], L) ->
- {lists:reverse(L), []}.
-
- first(Pred, [H|T]) ->
- case Pred(H) of
- true ->
- {true, H};
- false ->
- first(Pred, T)
- end;
- first(Pred, []) ->
- false.
-
- ints_from(N) ->
- fun() ->
- [N|ints_from(N+1)]
- end.
-
- pconst(X) ->
- fun (T) ->
- case T of
- [X|T1] -> {ok, {const, X}, T1};
- _ -> fail
- end
- end.
-
- pand(P1, P2) ->
- fun (T) ->
- case P1(T) of
- {ok, R1, T1} ->
- case P2(T1) of
- {ok, R2, T2} ->
- {ok, {'and', R1, R2}};
- fail ->
- fail
- end;
- fail ->
- fail
- end
- end.
-
- por(P1, P2) ->
- fun (T) ->
- case P1(T) of
- {ok, R, T1} ->
- {ok, {'or',1,R}, T1};
- fail ->
- case P2(T) of
- {ok, R1, T1} ->
- {ok, {'or',2,R1}, T1};
- fail ->
- fail
- end
- end
- end.
-
- grammar() ->
- pand(
- por(pconst(a), pconst(b)),
- por(pconst(c), pconst(d))).
-
- parse(List) ->
- (grammar())(List).
-
-
- t() ->
- [2,4,6,8] = double([1,2,3,4]),
- [2,3,4,5] = add_one([1,2,3,4]),
- [2,4,6,8] = double2([1,2,3,4]),
- [2,3,4,5] = add_one2([1,2,3,4]),
- XX = ints_from(1),
- [1 | _] = XX(),
- 1 = hd(XX()),
- Y = tl(XX()),
- 2 = hd(Y()),
-
- P1 = pconst(a),
- {ok,{const,a},[b,c]} = P1([a,b,c]),
- fail = P1([x,y,z]),
-
- {ok,{'and',{'or',1,{const,a}},{'or',1,{const,c}}}} =
- parse([a,c]),
- {ok,{'and',{'or',1,{const,a}},{'or',2,{const,d}}}} =
- parse([a,d]),
- {ok,{'and',{'or',2,{const,b}},{'or',1,{const,c}}}} =
- parse([b,c]),
- {ok,{'and',{'or',2,{const,b}},{'or',2,{const,d}}}} =
- parse([b,d]),
- fail = parse([a,b]),
- ok.
- ">>,
- ?line ok = run_file(Config, funs, Test1),
-
- Test2_shell =
- <<"Double = fun(X) -> 2 * X end,
+all(Pred, [H|T]) ->
+ case Pred(H) of
+ true -> all(Pred, T);
+ false -> false
+ end;
+all(Pred, []) ->
+ true.
+
+foldl(F, Accu, [Hd|Tail]) ->
+ foldl(F, F(Hd, Accu), Tail);
+foldl(F, Accu, []) -> Accu.
+
+mapfoldl(F, Accu0, [Hd|Tail]) ->
+ {R,Accu1} = F(Hd, Accu0),
+ {Rs,Accu2} = mapfoldl(F, Accu1, Tail),
+ {[R|Rs], Accu2};
+mapfoldl(F, Accu, []) -> {[], Accu}.
+
+filter(F, [H|T]) ->
+ case F(H) of
+ true -> [H|filter(F, T)];
+ false -> filter(F, T)
+ end;
+filter(F, []) -> [].
+
+diff(L1, L2) ->
+ filter(fun(X) -> not lists:member(X, L2) end, L1).
+
+intersection(L1,L2) -> filter(fun(X) -> lists:member(X,L1) end, L2).
+
+takewhile(Pred, [H|T]) ->
+ case Pred(H) of
+ true -> [H|takewhile(Pred, T)];
+ false -> []
+ end;
+takewhile(Pred, []) ->
+ [].
+
+dropwhile(Pred, [H|T]) ->
+ case Pred(H) of
+ true -> dropwhile(Pred, T);
+ false -> [H|T]
+ end;
+dropwhile(Pred, []) ->
+ [].
+
+splitlist(Pred, L) ->
+ splitlist(Pred, L, []).
+
+splitlist(Pred, [H|T], L) ->
+ case Pred(H) of
+ true -> splitlist(Pred, T, [H|L]);
+ false -> {lists:reverse(L), [H|T]}
+ end;
+splitlist(Pred, [], L) ->
+ {lists:reverse(L), []}.
+
+first(Pred, [H|T]) ->
+ case Pred(H) of
+ true ->
+ {true, H};
+ false ->
+ first(Pred, T)
+ end;
+first(Pred, []) ->
+ false.
+
+ints_from(N) ->
+ fun() ->
+ [N|ints_from(N+1)]
+ end.
+
+pconst(X) ->
+ fun (T) ->
+ case T of
+ [X|T1] -> {ok, {const, X}, T1};
+ _ -> fail
+ end
+ end.
+
+pand(P1, P2) ->
+ fun (T) ->
+ case P1(T) of
+ {ok, R1, T1} ->
+ case P2(T1) of
+ {ok, R2, T2} ->
+ {ok, {'and', R1, R2}};
+ fail ->
+ fail
+ end;
+ fail ->
+ fail
+ end
+ end.
+
+por(P1, P2) ->
+ fun (T) ->
+ case P1(T) of
+ {ok, R, T1} ->
+ {ok, {'or',1,R}, T1};
+ fail ->
+ case P2(T) of
+ {ok, R1, T1} ->
+ {ok, {'or',2,R1}, T1};
+ fail ->
+ fail
+ end
+ end
+ end.
+
+grammar() ->
+ pand(
+ por(pconst(a), pconst(b)),
+ por(pconst(c), pconst(d))).
+
+parse(List) ->
+ (grammar())(List).
+
+
+t() ->
+ [2,4,6,8] = double([1,2,3,4]),
+ [2,3,4,5] = add_one([1,2,3,4]),
+ [2,4,6,8] = double2([1,2,3,4]),
+ [2,3,4,5] = add_one2([1,2,3,4]),
+ XX = ints_from(1),
+ [1 | _] = XX(),
+ 1 = hd(XX()),
+ Y = tl(XX()),
+ 2 = hd(Y()),
+
+ P1 = pconst(a),
+ {ok,{const,a},[b,c]} = P1([a,b,c]),
+ fail = P1([x,y,z]),
+
+ {ok,{'and',{'or',1,{const,a}},{'or',1,{const,c}}}} =
+ parse([a,c]),
+ {ok,{'and',{'or',1,{const,a}},{'or',2,{const,d}}}} =
+ parse([a,d]),
+ {ok,{'and',{'or',2,{const,b}},{'or',1,{const,c}}}} =
+ parse([b,c]),
+ {ok,{'and',{'or',2,{const,b}},{'or',2,{const,d}}}} =
+ parse([b,d]),
+ fail = parse([a,b]),
+ ok.
+">>,
+ ok = run_file(Config, funs, Test1),
+
+Test2_shell =
+<<"Double = fun(X) -> 2 * X end,
[2,4,6,8,10] = lists:map(Double, [1,2,3,4,5]),
-
- Big = fun(X) -> if X > 10 -> true; true -> false end end,
- false = lists:any(Big, [1,2,3,4]),
- true = lists:any(Big, [1,2,3,12,5]),
- false = lists:all(Big, [1,2,3,4,12,6]),
- true = lists:all(Big, [12,13,14,15]),
- L = [\"I\",\"like\",\"Erlang\"],
+
+ Big = fun(X) -> if X > 10 -> true; true -> false end end,
+ false = lists:any(Big, [1,2,3,4]),
+ true = lists:any(Big, [1,2,3,12,5]),
+ false = lists:all(Big, [1,2,3,4,12,6]),
+ true = lists:all(Big, [12,13,14,15]),
+ L = [\"I\",\"like\",\"Erlang\"],
11 = lists:foldl(fun(X, Sum) -> length(X) + Sum end, 0, L),
- Upcase = fun(X) when $a =< X, X =< $z -> X + $A - $a;
- (X) -> X
- end,
- Upcase_word = fun(X) -> lists:map(Upcase, X) end,
- \"ERLANG\" = Upcase_word(\"Erlang\"),
+ Upcase = fun(X) when $a =< X, X =< $z -> X + $A - $a;
+ (X) -> X
+ end,
+ Upcase_word = fun(X) -> lists:map(Upcase, X) end,
+ \"ERLANG\" = Upcase_word(\"Erlang\"),
[\"I\",\"LIKE\",\"ERLANG\"] = lists:map(Upcase_word, L),
{[\"I\",\"LIKE\",\"ERLANG\"],11} =
lists:mapfoldl(fun(Word, Sum) ->
- {Upcase_word(Word), Sum + length(Word)}
+ {Upcase_word(Word), Sum + length(Word)}
end, 0, L),
- [500,12,45] = lists:filter(Big, [500,12,2,45,6,7]),
- [200,500,45] = lists:takewhile(Big, [200,500,45,5,3,45,6]),
- [5,3,45,6] = lists:dropwhile(Big, [200,500,45,5,3,45,6]),
- {[200,500,45],[5,3,45,6]} =
- lists:splitwith(Big, [200,500,45,5,3,45,6]),
+ [500,12,45] = lists:filter(Big, [500,12,2,45,6,7]),
+ [200,500,45] = lists:takewhile(Big, [200,500,45,5,3,45,6]),
+ [5,3,45,6] = lists:dropwhile(Big, [200,500,45,5,3,45,6]),
+ {[200,500,45],[5,3,45,6]} =
+ lists:splitwith(Big, [200,500,45,5,3,45,6]),
%% {true,45} = lists:first(Big, [1,2,45,6,123]),
%% false = lists:first(Big, [1,2,4,5]),
-
- Adder = fun(X) -> fun(Y) -> X + Y end end,
- Add6 = Adder(6),
- 16 = Add6(10),
- ok.
- ">>,
- ?line [ok] = scan(Test2_shell),
- ok.
+
+ Adder = fun(X) -> fun(Y) -> X + Y end end,
+ Add6 = Adder(6),
+ 16 = Add6(10),
+ ok.
+">>,
+ [ok] = scan(Test2_shell),
+ok.
%% OTP-5990. {erlang,is_record}.
otp_5990(Config) when is_list(Config) ->
- ?line [true] =
+ [true] =
scan(<<"rd('OrdSet', {orddata = {},ordtype = type}), "
"S = #'OrdSet'{ordtype = {}}, "
"if tuple(S#'OrdSet'.ordtype) -> true; true -> false end.">>),
@@ -2229,8 +2229,8 @@ otp_6166(Config) when is_list(Config) ->
Contents1 = <<"-module(test1).
-record(r5, {f}). -record(r3, {f = #r5{}}). "
"-record(r1, {f = #r3{}}). -record(r4, {f = #r1{}}). "
- "-record(r2, {f = #r4{}}).">>,
- ?line ok = file:write_file(Test1, Contents1),
+"-record(r2, {f = #r4{}}).">>,
+ ok = file:write_file(Test1, Contents1),
Test2 = filename:join(?config(priv_dir, Config), "test2.hrl"),
Contents2 = <<"-module(test2).
@@ -2239,7 +2239,7 @@ otp_6166(Config) when is_list(Config) ->
"-record(r2, {f = #r4{}}).
-record(r6, {f = #r5{}}). % r6 > r0
-record(r0, {f = #r5{}, g = #r5{}}). % r0 < r5">>,
- ?line ok = file:write_file(Test2, Contents2),
+ ok = file:write_file(Test2, Contents2),
RR12 = "[r1,r2,r3,r4,r5] = rr(\"" ++ Test1 ++ "\"),
[r0,r1,r2,r3,r4,r5,r6] = rr(\"" ++ Test2 ++ "\"),
@@ -2247,7 +2247,7 @@ otp_6166(Config) when is_list(Config) ->
true = is_record(R0, r0),
true = is_record(R6, r6),
ok. ",
- ?line [ok] = scan(RR12),
+ [ok] = scan(RR12),
file:delete(Test1),
file:delete(Test2),
@@ -2256,63 +2256,63 @@ otp_6166(Config) when is_list(Config) ->
%% OTP-6554. Formatted exits and error messages.
otp_6554(Config) when is_list(Config) ->
%% Should check the stacktrace as well...
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"math:sqrt(a).">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"fun(X, Y) -> X ++ Y end(a, b).">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"math:sqrt(lists:seq(1,40)).">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"math:sqrt(lists:seq(1,10)).">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"a ++ b.">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined},
aa ++ I.">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined},
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa ++ I.">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined},
I ++ I.">>),
- ?line "exception error: bad argument" =
+ "exception error: bad argument" =
comm_err(<<"fun(X) -> not X end(a).">>),
- ?line "exception error: bad argument: a" =
+ "exception error: bad argument: a" =
comm_err(<<"fun(A, B) -> A orelse B end(a, b).">>),
- ?line "exception error: an error occurred when evaluating an arithmetic expression" =
+ "exception error: an error occurred when evaluating an arithmetic expression" =
comm_err(<<"math:sqrt(2)/round(math:sqrt(0)).">>),
- ?line "exception error: interpreted function with arity 1 called with no arguments" =
+ "exception error: interpreted function with arity 1 called with no arguments" =
comm_err(<<"fun(V) -> V end().">>),
- ?line "exception error: interpreted function with arity 1 called with two arguments" =
+ "exception error: interpreted function with arity 1 called with two arguments" =
comm_err(<<"fun(V) -> V end(1,2).">>),
- ?line "exception error: interpreted function with arity 0 called with one argument" =
+ "exception error: interpreted function with arity 0 called with one argument" =
comm_err(<<"fun() -> v end(1).">>),
- ?line "exception error: interpreted function with arity 0 called with 4 arguments" =
+ "exception error: interpreted function with arity 0 called with 4 arguments" =
comm_err(<<"fun() -> v end(1,2,3,4).">>),
- ?line "exception error: math:sqrt/1 called with two arguments" =
+ "exception error: math:sqrt/1 called with two arguments" =
comm_err(<<"fun math:sqrt/1(1,2).">>),
- ?line "exception error: bad function 1." ++ _ =
+ "exception error: bad function 1." ++ _ =
comm_err(<<"(math:sqrt(2))().">>),
- ?line "exception error: bad function [1," ++ _ =
+ "exception error: bad function [1," ++ _ =
comm_err(<<"(lists:seq(1, 100))().">>),
- ?line "exception error: no match of right hand side value 1" ++ _ =
+ "exception error: no match of right hand side value 1" ++ _ =
comm_err(<<"a = math:sqrt(2).">>),
- ?line "exception error: no match of right hand side value" ++ _ =
+ "exception error: no match of right hand side value" ++ _ =
comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined,undefined,
undefined,undefined,undefined,undefined},
a = I.">>),
- ?line "exception error: no case clause matching 1" ++ _ =
+ "exception error: no case clause matching 1" ++ _ =
comm_err(<<"case math:sqrt(2) of a -> ok end.">>),
- ?line "exception error: no case clause matching [1," ++ _ =
+ "exception error: no case clause matching [1," ++ _ =
comm_err(<<"V = lists:seq(1, 20), case V of a -> ok end.">>),
- ?line "exception error: no function clause matching" =
+ "exception error: no function clause matching" =
comm_err(<<"fun(P) when is_pid(P) -> true end(a).">>),
case test_server:is_native(erl_eval) of
true ->
@@ -2334,68 +2334,68 @@ otp_6554(Config) when is_list(Config) ->
"lists:reverse(34) (lists.erl, line " ++ _ =
comm_err(<<"lists:reverse(34).">>)
end,
- ?line "exception error: function_clause" =
+ "exception error: function_clause" =
comm_err(<<"erlang:error(function_clause, 4).">>),
- ?line "exception error: no function clause matching" ++ _ =
+ "exception error: no function clause matching" ++ _ =
comm_err(<<"fun(a, b, c, d) -> foo end"
" (lists:seq(1,17),"
" lists:seq(1, 18),"
" lists:seq(1, 40),"
" lists:seq(1, 5)).">>),
- ?line "exception error: no function clause matching" =
+ "exception error: no function clause matching" =
comm_err(<<"fun(P, q) when is_pid(P) -> true end(a, b).">>),
- ?line "exception error: no true branch found when evaluating an if expression" =
+ "exception error: no true branch found when evaluating an if expression" =
comm_err(<<"if length([a,b]) > 17 -> a end.">>),
- ?line "exception error: no such process or port" =
+ "exception error: no such process or port" =
comm_err(<<"Pid = spawn(fun() -> a end),"
"timer:sleep(1),"
"link(Pid).">>),
- ?line "exception error: a system limit has been reached" =
+ "exception error: a system limit has been reached" =
comm_err(<<"list_to_atom(lists:duplicate(300,$a)).">>),
- ?line "exception error: bad receive timeout value" =
+ "exception error: bad receive timeout value" =
comm_err(<<"receive after a -> foo end.">>),
- ?line "exception error: no try clause matching 1" ++ _ =
+ "exception error: no try clause matching 1" ++ _ =
comm_err(<<"try math:sqrt(2) of bar -> yes after 3 end.">>),
- ?line "exception error: no try clause matching [1" ++ _ =
+ "exception error: no try clause matching [1" ++ _ =
comm_err(<<"V = lists:seq(1, 20),"
"try V of bar -> yes after 3 end.">>),
- ?line "exception error: undefined function math:sqrt/2" =
+ "exception error: undefined function math:sqrt/2" =
comm_err(<<"math:sqrt(2, 2).">>),
- ?line "exception error: limit of number of arguments to interpreted function "
+ "exception error: limit of number of arguments to interpreted function "
"exceeded" =
comm_err(<<"fun(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U) ->"
" a end().">>),
- ?line "exception error: bad filter a" =
+ "exception error: bad filter a" =
comm_err(<<"[b || begin a end].">>),
- ?line "exception error: bad generator a" =
+ "exception error: bad generator a" =
comm_err(<<"[X || X <- a].">>),
- ?line "exception throw: undef" = comm_err(<<"throw(undef).">>),
- ?line "exception exit: undef" = comm_err(<<"exit(undef).">>),
+ "exception throw: undef" = comm_err(<<"throw(undef).">>),
+ "exception exit: undef" = comm_err(<<"exit(undef).">>),
- ?line "exception exit: foo" =
+ "exception exit: foo" =
comm_err(<<"catch spawn_link(fun() ->"
" timer:sleep(300), exit(foo) "
" end),"
"timer:sleep(500).">>),
- ?line [ok] = scan(
+ [ok] = scan(
<<"begin process_flag(trap_exit, true),"
" Pid = spawn_link(fun() ->"
" timer:sleep(300), exit(foo) "
" end),"
" timer:sleep(500),"
" receive {'EXIT', Pid, foo} -> ok end end.">>),
- ?line "exception exit: badarith" =
+ "exception exit: badarith" =
comm_err(<<"catch spawn_link(fun() ->"
" timer:sleep(300), 1/0 "
" end),"
"timer:sleep(500).">>),
- ?line "exception exit: {nocatch,foo}" =
+ "exception exit: {nocatch,foo}" =
comm_err(<<"catch spawn_link(fun() ->"
" timer:sleep(300), throw(foo) "
" end),"
"timer:sleep(500).">>),
- ?line [ok] = scan(
+ [ok] = scan(
<<"begin process_flag(trap_exit, true),"
" Pid = spawn_link(fun() ->"
" timer:sleep(300), throw(foo) "
@@ -2404,37 +2404,37 @@ otp_6554(Config) when is_list(Config) ->
" receive {'EXIT', Pid, {{nocatch,foo},_}} -> ok end "
"end.">>),
- ?line "exception error: an error occurred when evaluating an arithmetic expression" =
+ "exception error: an error occurred when evaluating an arithmetic expression" =
comm_err(<<"begin catch_exception(true), 1/0 end.">>),
- ?line "exception error: an error occurred when evaluating an arithmetic expression" =
+ "exception error: an error occurred when evaluating an arithmetic expression" =
comm_err(<<"begin catch_exception(false), 1/0 end.">>),
- ?line "exception error: no function clause matching call to catch_exception/1" =
+ "exception error: no function clause matching call to catch_exception/1" =
comm_err(<<"catch_exception(1).">>),
%% A bug was corrected (expansion of 'try'):
- ?line "2: command not found" =
+ "2: command not found" =
comm_err(<<"try 1 of 1 -> v(2) after 3 end.">>),
%% Cover a few lines:
- ?line "3: command not found" =
+ "3: command not found" =
comm_err(<<"receive foo -> foo after 0 -> v(3) end.">>),
- ?line "3: command not found" =
+ "3: command not found" =
comm_err(<<"receive foo -> foo after 0 -> e(3) end.">>),
- ?line "1 / 0: command not found" = comm_err(<<"v(1/0).">>),
- ?line "1\n1.\n" = t(<<"1. e(1).">>),
- ?line [ok] = scan(<<"h().">>),
- ?line "exception exit: normal" = comm_err(<<"exit(normal).">>),
- ?line [foo] = scan(<<"begin history(0), foo end.">>),
- ?line application:unset_env(stdlib, shell_history_length),
- ?line [true] = scan(<<"begin <<10:(1024*1024*10)>>,"
+ "1 / 0: command not found" = comm_err(<<"v(1/0).">>),
+ "1\n1.\n" = t(<<"1. e(1).">>),
+ [ok] = scan(<<"h().">>),
+ "exception exit: normal" = comm_err(<<"exit(normal).">>),
+ [foo] = scan(<<"begin history(0), foo end.">>),
+ application:unset_env(stdlib, shell_history_length),
+ [true] = scan(<<"begin <<10:(1024*1024*10)>>,"
"<<10:(1024*1024*10)>>, garbage_collect() end.">>),
- ?line "1: syntax error before: '.'" = comm_err("1-."),
- %% ?line comm_err(<<"exit().">>), % would hang
- ?line "exception error: no function clause matching call to history/1" =
+ "1: syntax error before: '.'" = comm_err("1-."),
+ %% comm_err(<<"exit().">>), % would hang
+ "exception error: no function clause matching call to history/1" =
comm_err(<<"history(foo).">>),
- ?line "exception error: no function clause matching call to results/1" =
+ "exception error: no function clause matching call to results/1" =
comm_err(<<"results(foo).">>),
- ?line Test = filename:join(?config(priv_dir, Config),
+ Test = filename:join(?config(priv_dir, Config),
"otp_6554.erl"),
Contents = <<"-module(otp_6554).
-export([local_allowed/3, non_local_allowed/3]).
@@ -2444,31 +2444,31 @@ otp_6554(Config) when is_list(Config) ->
non_local_allowed(_,_,State) ->
{true,State}.
">>,
- ?line ok = compile_file(Config, Test, Contents, []),
- ?line "exception exit: restricted shell starts now" =
+ ok = compile_file(Config, Test, Contents, []),
+ "exception exit: restricted shell starts now" =
comm_err(<<"begin shell:start_restricted(otp_6554) end.">>),
- ?line "-record(r,{}).\n1.\nok.\n" =
+ "-record(r,{}).\n1.\nok.\n" =
t(<<"f(), f(B), h(), b(), history(20), results(20),"
"rd(r, {}), rl(r), rf('_'), rl(), rf(),"
"rp(1), _ = rr({foo}), _ = rr({foo}, []),"
"rr({foo}, [], []), ok.">>),
- ?line "false.\n" = t(<<"catch_exception(true).">>),
- ?line "exception exit: restricted shell stopped"=
+ "false.\n" = t(<<"catch_exception(true).">>),
+ "exception exit: restricted shell stopped"=
comm_err(<<"begin shell:stop_restricted() end.">>),
- ?line "true.\n" = t(<<"catch_exception(false).">>),
+ "true.\n" = t(<<"catch_exception(false).">>),
- ?line "20\n1\n1\n1: results(2)\n2: 1\n-> 1\n3: v(2)\n-> 1.\nok.\n" =
+ "20\n1\n1\n1: results(2)\n2: 1\n-> 1\n3: v(2)\n-> 1.\nok.\n" =
t(<<"results(2). 1. v(2). h().">>),
- ?line application:unset_env(stdlib, shell_saved_results),
- ?line "1\nfoo\n17\nB = foo\nC = 17\nF = fun() ->\n foo"
+ application:unset_env(stdlib, shell_saved_results),
+ "1\nfoo\n17\nB = foo\nC = 17\nF = fun() ->\n foo"
"\n end.\nok.\n" =
t(<<"begin F = fun() -> foo end, 1 end. B = F(). C = 17. b().">>),
- ?line "3: command not found" = comm_err(<<"#{v(3) => v}.">>),
- ?line "3: command not found" = comm_err(<<"#{k => v(3)}.">>),
- ?line "3: command not found" = comm_err(<<"#{v(3) := v}.">>),
- ?line "3: command not found" = comm_err(<<"#{k := v(3)}.">>),
- ?line "3: command not found" = comm_err(<<"(v(3))#{}.">>),
+ "3: command not found" = comm_err(<<"#{v(3) => v}.">>),
+ "3: command not found" = comm_err(<<"#{k => v(3)}.">>),
+ "3: command not found" = comm_err(<<"#{v(3) := v}.">>),
+ "3: command not found" = comm_err(<<"#{k := v(3)}.">>),
+ "3: command not found" = comm_err(<<"(v(3))#{}.">>),
%% Tests I'd like to do: (you should try them manually)
%% "catch spawn_link(fun() -> timer:sleep(1000), exit(foo) end)."
%% "** exception error: foo" should be output after 1 second
@@ -2483,7 +2483,7 @@ otp_6554(Config) when is_list(Config) ->
%% OTP-7184. Propagate exit signals from dying evaluator process.
otp_7184(Config) when is_list(Config) ->
register(otp_7184, self()),
- ?line catch
+ catch
t(<<"P = self(),
spawn_link(fun() -> process_flag(trap_exit,true),
P ! up,
@@ -2495,7 +2495,7 @@ otp_7184(Config) when is_list(Config) ->
erlang:raise(throw, thrown, []).">>),
receive {otp_7184,{'EXIT',_,{{nocatch,thrown},[]}}} -> ok end,
- ?line catch
+ catch
t(<<"P = self(),
spawn_link(fun() -> process_flag(trap_exit,true),
P ! up,
@@ -2507,7 +2507,7 @@ otp_7184(Config) when is_list(Config) ->
erlang:raise(exit, fini, []).">>),
receive {otp_7184,{'EXIT',_,{fini,[]}}} -> ok end,
- ?line catch
+ catch
t(<<"P = self(),
spawn_link(fun() -> process_flag(trap_exit,true),
P ! up,
@@ -2522,12 +2522,12 @@ otp_7184(Config) when is_list(Config) ->
unregister(otp_7184),
%% v/1, a few missed cases
- ?line "17\n<<0,0,0,64>>.\nok.\n" =
+ "17\n<<0,0,0,64>>.\nok.\n" =
t(<<"17. "
"<<64:32>>. "
"<<64>> = << << X >> || << X >> <= v(2), X > v(1) >>, ok.">>),
- ?line "17\n<<0,17>>.\n" =t(<<"17. <<(v(1)):16>>.">>),
+ "17\n<<0,17>>.\n" =t(<<"17. <<(v(1)):16>>.">>),
ok.
@@ -2544,20 +2544,20 @@ otp_7232(Config) when is_list(Config) ->
%% OTP-8393. Prompt string.
otp_8393(Config) when is_list(Config) ->
- ?line _ = shell:prompt_func(default),
- ?line "Bad prompt function: '> '" =
+ _ = shell:prompt_func(default),
+ "Bad prompt function: '> '" =
prompt_err(<<"shell:prompt_func('> ').">>),
- ?line _ = shell:prompt_func(default),
- ?line "exception error: an error occurred when evaluating an arithmetic expression"++_ =
+ _ = shell:prompt_func(default),
+ "exception error: an error occurred when evaluating an arithmetic expression"++_ =
prompt_err(<<"shell:prompt_func({shell_SUITE,prompt4}).">>),
- ?line _ = shell:prompt_func(default),
- ?line "default.\n" =
+ _ = shell:prompt_func(default),
+ "default.\n" =
t(<<"shell:prompt_func({shell_SUITE,prompt2}).">>),
- ?line _ = shell:prompt_func(default),
- ?line "default\nl.\n" =
+ _ = shell:prompt_func(default),
+ "default\nl.\n" =
t(<<"shell:prompt_func({shell_SUITE,prompt3}). l.">>),
%%
@@ -2566,8 +2566,8 @@ otp_8393(Config) when is_list(Config) ->
%% That is instead tested in the io_proto_SUITE, which has
%% the right infrastructure in place for such tests. /PaN
%%
- ?line _ = shell:prompt_func(default),
- ?line "default\nl.\n" =
+ _ = shell:prompt_func(default),
+ "default\nl.\n" =
t(<<"shell:prompt_func({shell_SUITE,prompt5}). l.">>),
%% Restricted shell.
@@ -2585,30 +2585,30 @@ otp_8393(Config) when is_list(Config) ->
non_local_allowed(_,_,State) ->
{false,State}.
">>,
- ?line Test = filename:join(?config(priv_dir, Config),
+ Test = filename:join(?config(priv_dir, Config),
"test_restricted_shell.erl"),
- ?line ok = compile_file(Config, Test, Contents, []),
- ?line _ = shell:prompt_func(default),
- ?line "exception exit: restricted shell starts now" =
+ ok = compile_file(Config, Test, Contents, []),
+ _ = shell:prompt_func(default),
+ "exception exit: restricted shell starts now" =
comm_err(<<"begin shell:start_restricted("
"test_restricted_shell) end.">>),
- ?line "default.\n"++_ =
+ "default.\n"++_ =
t(<<"shell:prompt_func({shell_SUITE,prompt1}).">>),
- ?line "exception exit: restricted shell does not allow apple(" ++ _ =
+ "exception exit: restricted shell does not allow apple(" ++ _ =
comm_err(<<"apple(1).">>),
- ?line "{shell_SUITE,prompt1}.\n" =
+ "{shell_SUITE,prompt1}.\n" =
t(<<"shell:prompt_func(default).">>),
- ?line "exception exit: restricted shell stopped"=
+ "exception exit: restricted shell stopped"=
comm_err(<<"begin shell:stop_restricted() end.">>),
- ?line undefined =
+ undefined =
application:get_env(stdlib, restricted_shell),
- ?line NR = shell:results(20),
- ?line "default\n20.\n" =
+ NR = shell:results(20),
+ "default\n20.\n" =
t(<<"shell:prompt_func({shell_SUITE,prompt3}). results(0).">>),
- ?line _ = shell:prompt_func(default),
- ?line 0 = shell:results(NR),
+ _ = shell:prompt_func(default),
+ 0 = shell:results(NR),
ok.
prompt1(_L) ->
@@ -3017,9 +3017,9 @@ run_file(Config, Module, Test) ->
ok.
compile_file(Config, File, Test, Opts0) ->
- ?line Opts = [export_all,return,{outdir,?config(priv_dir, Config)}|Opts0],
- ?line ok = file:write_file(File, Test),
- ?line case compile:file(File, Opts) of
+ Opts = [export_all,return,{outdir,?config(priv_dir, Config)}|Opts0],
+ ok = file:write_file(File, Test),
+ case compile:file(File, Opts) of
{ok, _M, _Ws} -> ok;
_ -> error
end.
@@ -3030,7 +3030,7 @@ filename(Name, Config) ->
filename:join(?config(priv_dir, Config), Name).
start_node(Name, Xargs) ->
- ?line N = test_server:start_node(Name, slave, [{args, " " ++ Xargs}]),
+ N = test_server:start_node(Name, slave, [{args, " " ++ Xargs}]),
global:sync(),
N.
diff --git a/lib/stdlib/test/slave_SUITE.erl b/lib/stdlib/test/slave_SUITE.erl
index cb171d1dc6..dc14e4735a 100644
--- a/lib/stdlib/test/slave_SUITE.erl
+++ b/lib/stdlib/test/slave_SUITE.erl
@@ -55,24 +55,24 @@ end_per_group(_GroupName, Config) ->
t_start_link(Config) when is_list(Config) ->
%% Define useful variables.
- ?line Host = host(),
- ?line Slave1 = node_name(Host, slave1),
- ?line Slave2 = node_name(Host, slave2),
+ Host = host(),
+ Slave1 = node_name(Host, slave1),
+ Slave2 = node_name(Host, slave2),
%% Test slave:start_link() with one, two, and three arguments.
- ?line ThisNode = node(),
- ?line {error, {already_running, ThisNode}} = slave:start_link(Host),
- ?line {ok, Slave1} = slave:start_link(Host, slave1),
- ?line {ok, Slave2} = slave:start_link(Host, slave2, "-my_option 42"),
- ?line {ok, [["42"]]} = rpc:call(Slave2, init, get_argument, [my_option]),
+ ThisNode = node(),
+ {error, {already_running, ThisNode}} = slave:start_link(Host),
+ {ok, Slave1} = slave:start_link(Host, slave1),
+ {ok, Slave2} = slave:start_link(Host, slave2, "-my_option 42"),
+ {ok, [["42"]]} = rpc:call(Slave2, init, get_argument, [my_option]),
%% Kill the two slave nodes and verify that they are dead.
- ?line rpc:cast(Slave1, erlang, halt, []),
- ?line rpc:cast(Slave2, erlang, halt, []),
- ?line is_dead(Slave1),
- ?line is_dead(Slave2),
+ rpc:cast(Slave1, erlang, halt, []),
+ rpc:cast(Slave2, erlang, halt, []),
+ is_dead(Slave1),
+ is_dead(Slave2),
%% Start two slave nodes from another process and verify that
%% the slaves die when that process terminates.
@@ -84,16 +84,16 @@ t_start_link(Config) when is_list(Config) ->
Parent ! slaves_started,
receive never -> ok end
end),
- ?line receive slaves_started -> ok end,
- ?line process_flag(trap_exit, true),
- ?line wait_alive(Slave1),
- ?line wait_alive(Slave2),
- ?line exit(Pid, kill),
- ?line receive {'EXIT', Pid, killed} -> ok end,
+ receive slaves_started -> ok end,
+ process_flag(trap_exit, true),
+ wait_alive(Slave1),
+ wait_alive(Slave2),
+ exit(Pid, kill),
+ receive {'EXIT', Pid, killed} -> ok end,
ct:sleep(250),
- ?line is_dead(Slave1),
- ?line is_dead(Slave2),
-
+ is_dead(Slave1),
+ is_dead(Slave2),
+
ok.
%% Test that slave:start_link() works when the master exits.
@@ -101,18 +101,18 @@ t_start_link(Config) when is_list(Config) ->
start_link_nodedown(Config) when is_list(Config) ->
%% Define useful variables.
- ?line Host = host(),
- ?line Master = node_name(Host, my_master),
- ?line Slave = node_name(Host, my_slave),
+ Host = host(),
+ Master = node_name(Host, my_master),
+ Slave = node_name(Host, my_slave),
+
+ Pa = "-pa " ++ filename:dirname(code:which(?MODULE)),
+ {ok, Master} = slave:start_link(Host, my_master, Pa),
+ spawn(Master, ?MODULE, start_a_slave, [self(), Host, my_slave]),
+ {reply, {ok, _Node}} = receive Any -> Any end,
- ?line Pa = "-pa " ++ filename:dirname(code:which(?MODULE)),
- ?line {ok, Master} = slave:start_link(Host, my_master, Pa),
- ?line spawn(Master, ?MODULE, start_a_slave, [self(), Host, my_slave]),
- ?line {reply, {ok, _Node}} = receive Any -> Any end,
-
- ?line rpc:call(Master, erlang, halt, []),
- ?line receive after 200 -> ok end,
- ?line pang = net_adm:ping(Slave),
+ rpc:call(Master, erlang, halt, []),
+ receive after 200 -> ok end,
+ pang = net_adm:ping(Slave),
ok.
@@ -125,44 +125,44 @@ start_a_slave(ReplyTo, Host, Name) ->
t_start(Config) when is_list(Config) ->
%% Define useful variables.
- ?line Host = host(),
- ?line Slave1 = node_name(Host, slave1),
- ?line Slave2 = node_name(Host, slave2),
+ Host = host(),
+ Slave1 = node_name(Host, slave1),
+ Slave2 = node_name(Host, slave2),
%% By running all tests from this master node which is linked
%% to this test case, we ensure that all slaves are killed
%% if this test case fails. (If they are not, and therefore further
%% test cases fail, there is a bug in slave.)
- ?line {ok, Master} = slave:start_link(Host, master),
-
+ {ok, Master} = slave:start_link(Host, master),
+
%% Test slave:start() with one, two, and three arguments.
- ?line ThisNode = node(),
- ?line {error, {already_running, ThisNode}} = slave:start(Host),
- ?line {ok, Slave1} = rpc:call(Master, slave, start, [Host, slave1]),
- ?line {ok, Slave2} = rpc:call(Master, slave, start,
- [Host, slave2, "-my_option 42"]),
- ?line {ok, [["42"]]} = rpc:call(Slave2, init, get_argument, [my_option]),
+ ThisNode = node(),
+ {error, {already_running, ThisNode}} = slave:start(Host),
+ {ok, Slave1} = rpc:call(Master, slave, start, [Host, slave1]),
+ {ok, Slave2} = rpc:call(Master, slave, start,
+ [Host, slave2, "-my_option 42"]),
+ {ok, [["42"]]} = rpc:call(Slave2, init, get_argument, [my_option]),
%% Test that a slave terminates when its master node terminates.
- ?line ok = slave:stop(Slave2),
- ?line is_dead(Slave2),
- ?line {ok, Slave2} = rpc:call(Slave1, slave, start, [Host, slave2]),
- ?line is_alive(Slave2),
- ?line rpc:call(Slave1, erlang, halt, []), % Kill master.
+ ok = slave:stop(Slave2),
+ is_dead(Slave2),
+ {ok, Slave2} = rpc:call(Slave1, slave, start, [Host, slave2]),
+ is_alive(Slave2),
+ rpc:call(Slave1, erlang, halt, []), % Kill master.
receive after 1000 -> ok end, % Make sure slaves have noticed
% their dead master.
- ?line is_dead(Slave1),
- ?line is_dead(Slave2), % Slave should be dead, too.
+ is_dead(Slave1),
+ is_dead(Slave2), % Slave should be dead, too.
%% Kill all slaves and verify that they are dead.
- ?line ok = slave:stop(Slave1),
- ?line ok = slave:stop(Slave2),
- ?line is_dead(Slave1),
- ?line is_dead(Slave2),
+ ok = slave:stop(Slave1),
+ ok = slave:stop(Slave2),
+ is_dead(Slave1),
+ is_dead(Slave2),
ok.
@@ -170,26 +170,26 @@ t_start(Config) when is_list(Config) ->
%% in slave is 32 seconds).
errors(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Pa = filename:dirname(code:which(?MODULE)),
- ?line {ok, Master} = slave_start_link(host(), master,
- "-rsh no_rsh_program -pa "++Pa++
- " -env ERL_CRASH_DUMP erl_crash_dump.master"),
- ?line Pids = rpc:call(Master, ?MODULE, test_errors, [self()]),
- ?line wait_for_result(Pids),
+ process_flag(trap_exit, true),
+ Pa = filename:dirname(code:which(?MODULE)),
+ {ok, Master} = slave_start_link(host(), master,
+ "-rsh no_rsh_program -pa "++Pa++
+ " -env ERL_CRASH_DUMP erl_crash_dump.master"),
+ Pids = rpc:call(Master, ?MODULE, test_errors, [self()]),
+ wait_for_result(Pids),
ok.
wait_for_result([]) ->
ok;
wait_for_result(Pids) ->
- ?line receive
- {'EXIT', Pid, normal} ->
- io:format("Process ~p terminated", [Pid]),
- wait_for_result(lists:delete(Pid, Pids));
- {'EXIT', _, Reason} ->
- exit(Reason)
- end.
+ receive
+ {'EXIT', Pid, normal} ->
+ io:format("Process ~p terminated", [Pid]),
+ wait_for_result(lists:delete(Pid, Pids));
+ {'EXIT', _, Reason} ->
+ exit(Reason)
+ end.
show_process_info(Pid) ->
io:format("~p: ~p", [Pid, catch process_info(Pid, initial_call)]).
@@ -197,25 +197,25 @@ show_process_info(Pid) ->
test_errors(ResultTo) ->
%% Sigh! We use ordinary spawn instead of fun_spawn/1 to be able
%% identify the processes by their initial call.
- ?line P1 = spawn(?MODULE, timeout_test, [ResultTo]),
- ?line P2 = spawn(?MODULE, auth_test, [ResultTo]),
- ?line P3 = spawn(?MODULE, rsh_test, [ResultTo]),
+ P1 = spawn(?MODULE, timeout_test, [ResultTo]),
+ P2 = spawn(?MODULE, auth_test, [ResultTo]),
+ P3 = spawn(?MODULE, rsh_test, [ResultTo]),
Pids =[P1, P2, P3],
- ?line lists:foreach(fun show_process_info/1, Pids),
+ lists:foreach(fun show_process_info/1, Pids),
Pids.
timeout_test(ResultTo) ->
link(ResultTo),
- ?line {error, timeout} = slave:start(host(), slave1, "-boot no_boot_script").
+ {error, timeout} = slave:start(host(), slave1, "-boot no_boot_script").
auth_test(ResultTo) ->
link(ResultTo),
- ?line {error, timeout} = slave:start(host(), slave2,
- "-setcookie definitely_not_a_cookie").
+ {error, timeout} = slave:start(host(), slave2,
+ "-setcookie definitely_not_a_cookie").
rsh_test(ResultTo) ->
link(ResultTo),
- ?line {error, no_rsh} = slave:start(super, slave3).
+ {error, no_rsh} = slave:start(super, slave3).
%%% Utilities.
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index b96adf1d41..2277b2d6fb 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -35,28 +35,28 @@
init_per_group/2,end_per_group/2]).
-export([ from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
- a_function_1/1, family_1/1, projection/1,
- relation_to_family_1/1, domain_1/1, range_1/1, image/1,
- inverse_image/1, inverse_1/1, converse_1/1, no_elements_1/1,
- substitution/1, restriction/1, drestriction/1,
- strict_relation_1/1, extension/1, weak_relation_1/1,
- to_sets_1/1, specification/1, union_1/1, intersection_1/1,
- difference/1, symdiff/1, symmetric_partition/1,
- is_sofs_set_1/1, is_set_1/1, is_equal/1, is_subset/1,
- is_a_function_1/1, is_disjoint/1, join/1, canonical/1,
- composite_1/1, relative_product_1/1, relative_product_2/1,
- product_1/1, partition_1/1, partition_3/1,
- multiple_relative_product/1, digraph/1, constant_function/1,
- misc/1]).
+ a_function_1/1, family_1/1, projection/1,
+ relation_to_family_1/1, domain_1/1, range_1/1, image/1,
+ inverse_image/1, inverse_1/1, converse_1/1, no_elements_1/1,
+ substitution/1, restriction/1, drestriction/1,
+ strict_relation_1/1, extension/1, weak_relation_1/1,
+ to_sets_1/1, specification/1, union_1/1, intersection_1/1,
+ difference/1, symdiff/1, symmetric_partition/1,
+ is_sofs_set_1/1, is_set_1/1, is_equal/1, is_subset/1,
+ is_a_function_1/1, is_disjoint/1, join/1, canonical/1,
+ composite_1/1, relative_product_1/1, relative_product_2/1,
+ product_1/1, partition_1/1, partition_3/1,
+ multiple_relative_product/1, digraph/1, constant_function/1,
+ misc/1]).
-export([ family_specification/1,
- family_domain_1/1, family_range_1/1,
- family_to_relation_1/1,
- union_of_family_1/1, intersection_of_family_1/1,
- family_projection/1, family_difference/1,
- family_intersection_1/1, family_union_1/1,
- family_intersection_2/1, family_union_2/1,
- partition_family/1]).
+ family_domain_1/1, family_range_1/1,
+ family_to_relation_1/1,
+ union_of_family_1/1, intersection_of_family_1/1,
+ family_projection/1, family_difference/1,
+ family_intersection_1/1, family_union_1/1,
+ family_intersection_2/1, family_union_2/1,
+ partition_family/1]).
-import(sofs,
[a_function/1, a_function/2, constant_function/2,
@@ -143,372 +143,372 @@ end_per_testcase(_Case, _Config) ->
from_term_1(Conf) when is_list(Conf) ->
%% would go wrong: projection(1,from_term([{2,b},{1,a,b}])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([], {atom,'_',atom})),
- ?line {'EXIT', {badarg, _}} = (catch from_term([], [])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([], [atom,atom])),
-
- ?line [] = to_external(from_term([])),
- ?line eval(from_term([]), empty_set()),
- ?line [] = to_external(from_term([], ['_'])),
- ?line eval(from_term([], ['_']), empty_set()),
- ?line [[]] = to_external(from_term([[]])),
- ?line [[['_']]] = type(from_term([[],[[]]])),
- ?line [[],[[]]] = to_external(from_term([[],[[]]])),
- ?line [[['_']]] = type(from_term([[],[[]]])),
- ?line eval(from_term([a],['_']), set([a])),
- ?line [[],[a]] = to_external(from_term([[],[a]])),
- ?line [[],[{a}]] = to_external(from_term([[{a}],[]])),
- ?line [{[],[{a,b,[d]}]},{[{a,b}],[]}] =
+ {'EXIT', {badarg, _}} = (catch from_term([], {atom,'_',atom})),
+ {'EXIT', {badarg, _}} = (catch from_term([], [])),
+ {'EXIT', {badarg, _}} = (catch from_term([], [atom,atom])),
+
+ [] = to_external(from_term([])),
+ eval(from_term([]), empty_set()),
+ [] = to_external(from_term([], ['_'])),
+ eval(from_term([], ['_']), empty_set()),
+ [[]] = to_external(from_term([[]])),
+ [[['_']]] = type(from_term([[],[[]]])),
+ [[],[[]]] = to_external(from_term([[],[[]]])),
+ [[['_']]] = type(from_term([[],[[]]])),
+ eval(from_term([a],['_']), set([a])),
+ [[],[a]] = to_external(from_term([[],[a]])),
+ [[],[{a}]] = to_external(from_term([[{a}],[]])),
+ [{[],[{a,b,[d]}]},{[{a,b}],[]}] =
to_external(from_term([{[],[{a,b,[d]}]},{[{a,b}],[]}])),
- ?line [{[a,b],[c,d]}] = to_external(from_term([{[a,b],[c,d]}])),
- ?line [{{a,b},[a,b],{{a},{b}}}] =
+ [{[a,b],[c,d]}] = to_external(from_term([{[a,b],[c,d]}])),
+ [{{a,b},[a,b],{{a},{b}}}] =
to_external(from_term([{{a,b},[a,b],{{a},{b}}}])),
- ?line [{{a,{[a,b]},a}},{{z,{[y,z]},z}}] =
+ [{{a,{[a,b]},a}},{{z,{[y,z]},z}}] =
to_external(from_term([{{a,{[a,b,a]},a}},{{z,{[y,y,z]},z}}])),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch from_term([{m1,[{m1,f1,1},{m1,f2,2}]},{m2,[]},{m3,[a]}])),
- ?line MS1 = [{m1,[{m1,f1,1},{m1,f2,2}]},{m2,[]},{m3,[{m3,f3,3}]}],
- ?line eval(to_external(from_term(MS1)), MS1),
-
- ?line eval(to_external(from_term(a)), a),
- ?line eval(to_external(from_term({a})), {a}),
-
- ?line eval(to_external(from_term([[a],[{b,c}]],[[atomic]])),
- [[a],[{b,c}]]),
- ?line eval(type(from_term([[a],[{b,c}]],[[atomic]])),
- [[atomic]]),
-
- ?line {'EXIT', {badarg, _}} = (catch from_term([[],[],a])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([{[a,b],[c,{d}]}])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([[],[a],[{a}]])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([a,{a,b}])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([[a],[{b,c}]],[['_']])),
- ?line {'EXIT', {badarg, _}} = (catch from_term([a | {a,b}])),
- ?line {'EXIT', {badarg, _}} =
+ MS1 = [{m1,[{m1,f1,1},{m1,f2,2}]},{m2,[]},{m3,[{m3,f3,3}]}],
+ eval(to_external(from_term(MS1)), MS1),
+
+ eval(to_external(from_term(a)), a),
+ eval(to_external(from_term({a})), {a}),
+
+ eval(to_external(from_term([[a],[{b,c}]],[[atomic]])),
+ [[a],[{b,c}]]),
+ eval(type(from_term([[a],[{b,c}]],[[atomic]])),
+ [[atomic]]),
+
+ {'EXIT', {badarg, _}} = (catch from_term([[],[],a])),
+ {'EXIT', {badarg, _}} = (catch from_term([{[a,b],[c,{d}]}])),
+ {'EXIT', {badarg, _}} = (catch from_term([[],[a],[{a}]])),
+ {'EXIT', {badarg, _}} = (catch from_term([a,{a,b}])),
+ {'EXIT', {badarg, _}} = (catch from_term([[a],[{b,c}]],[['_']])),
+ {'EXIT', {badarg, _}} = (catch from_term([a | {a,b}])),
+ {'EXIT', {badarg, _}} =
(catch from_term([{{a},b,c},{d,e,f}],[{{atom},atom,atom}])),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch from_term([{a,{b,c}} | tail], [{atom,{atom,atom}}])),
- ?line {'EXIT', {badarg, _}} = (catch from_term({})),
- ?line {'EXIT', {badarg, _}} = (catch from_term([{}])),
+ {'EXIT', {badarg, _}} = (catch from_term({})),
+ {'EXIT', {badarg, _}} = (catch from_term([{}])),
- ?line [{foo,bar},[b,a]] =
+ [{foo,bar},[b,a]] =
to_external(from_term([[b,a],{foo,bar},[b,a]], [atom])),
- ?line [{[atom],{atom,atom}}] =
+ [{[atom],{atom,atom}}] =
type(from_term([{[], {a,b}},{[a,b],{e,f}}])),
- ?line [{[atom],{atom,atom}}] =
+ [{[atom],{atom,atom}}] =
type(from_term([{[], {a,b}},{[a,b],{e,f}}], [{[atom],{atom,atom}}])),
- ?line [[atom]] = type(from_term([[a],[{b,c}]],[[atom]])),
+ [[atom]] = type(from_term([[a],[{b,c}]],[[atom]])),
- ?line {atom, atom} = type(from_term({a,b}, {atom, atom})),
- ?line atom = type(from_term(a, atom)),
- ?line {'EXIT', {badarg, _}} = (catch from_term({a,b},{atom})),
- ?line [{{a},b,c},{{d},e,f}] =
+ {atom, atom} = type(from_term({a,b}, {atom, atom})),
+ atom = type(from_term(a, atom)),
+ {'EXIT', {badarg, _}} = (catch from_term({a,b},{atom})),
+ [{{a},b,c},{{d},e,f}] =
to_external(from_term([{{a},b,c},{{a},b,c},{{d},e,f}],
[{{atom},atom,atom}])),
%% from_external too...
- ?line e = to_external(from_external(e, atom)),
- ?line {e} = to_external(from_external({e}, {atom})),
- ?line [e] = to_external(from_external([e], [atom])),
+ e = to_external(from_external(e, atom)),
+ {e} = to_external(from_external({e}, {atom})),
+ [e] = to_external(from_external([e], [atom])),
%% and is_type...
- ?line true = is_type(['_']),
- ?line false = is_type('_'),
- ?line true = is_type([['_']]),
- ?line false = is_type({atom,[],atom}),
- ?line false = is_type({atom,'_',atom}),
- ?line true = is_type({atom,atomic,atom}),
- ?line true = is_type({atom,atom}),
- ?line true = is_type(atom),
- ?line true = is_type([atom]),
- ?line true = is_type(type),
+ true = is_type(['_']),
+ false = is_type('_'),
+ true = is_type([['_']]),
+ false = is_type({atom,[],atom}),
+ false = is_type({atom,'_',atom}),
+ true = is_type({atom,atomic,atom}),
+ true = is_type({atom,atom}),
+ true = is_type(atom),
+ true = is_type([atom]),
+ true = is_type(type),
ok.
set_1(Conf) when is_list(Conf) ->
%% set/1
- ?line {'EXIT', {badarg, _}} = (catch set(a)),
- ?line {'EXIT', {badarg, _}} = (catch set({a})),
- ?line eval(set([]), from_term([],[atom])),
- ?line eval(set([a,b,c]), from_term([a,b,c])),
- ?line eval(set([a,b,a,a,b]), from_term([a,b])),
- ?line eval(set([a,b,c,a,d,d,c,1]), from_term([1,a,b,c,d])),
- ?line eval(set([a,b,d,a,c]), from_term([a,b,c,d])),
- ?line eval(set([f,e,d,c,d]), from_term([c,d,e,f])),
- ?line eval(set([h,f,d,g,g,d,c]), from_term([c,d,f,g,h])),
- ?line eval(set([h,e,d,k,l]), from_term([d,e,h,k,l])),
- ?line eval(set([h,e,c,k,d]), from_term([c,d,e,h,k])),
+ {'EXIT', {badarg, _}} = (catch set(a)),
+ {'EXIT', {badarg, _}} = (catch set({a})),
+ eval(set([]), from_term([],[atom])),
+ eval(set([a,b,c]), from_term([a,b,c])),
+ eval(set([a,b,a,a,b]), from_term([a,b])),
+ eval(set([a,b,c,a,d,d,c,1]), from_term([1,a,b,c,d])),
+ eval(set([a,b,d,a,c]), from_term([a,b,c,d])),
+ eval(set([f,e,d,c,d]), from_term([c,d,e,f])),
+ eval(set([h,f,d,g,g,d,c]), from_term([c,d,f,g,h])),
+ eval(set([h,e,d,k,l]), from_term([d,e,h,k,l])),
+ eval(set([h,e,c,k,d]), from_term([c,d,e,h,k])),
%% set/2
- ?line {'EXIT', {badarg, _}} = (catch set(a, [a])),
- ?line {'EXIT', {badarg, _}} = (catch set({a}, [a])),
- ?line {'EXIT', {badarg, _}} = (catch set([a], {a})),
- ?line {'EXIT', {badarg, _}} = (catch set([a], a)),
- ?line {'EXIT', {badarg, _}} = (catch set([a], [a,b])),
- ?line {'EXIT', {badarg, _}} = (catch set([a | b],[foo])),
- ?line {'EXIT', {badarg, _}} = (catch set([a | b],['_'])),
- ?line {'EXIT', {badarg, _}} = (catch set([a | b],[[atom]])),
- ?line {'EXIT', {badarg, _}} = (catch set([{}],[{}])),
- ?line eval(set([a],['_']), from_term([a],['_'])),
- ?line eval(set([], ['_']), empty_set()),
- ?line eval(set([a,b,a,b],[foo]), from_term([a,b],[foo])),
+ {'EXIT', {badarg, _}} = (catch set(a, [a])),
+ {'EXIT', {badarg, _}} = (catch set({a}, [a])),
+ {'EXIT', {badarg, _}} = (catch set([a], {a})),
+ {'EXIT', {badarg, _}} = (catch set([a], a)),
+ {'EXIT', {badarg, _}} = (catch set([a], [a,b])),
+ {'EXIT', {badarg, _}} = (catch set([a | b],[foo])),
+ {'EXIT', {badarg, _}} = (catch set([a | b],['_'])),
+ {'EXIT', {badarg, _}} = (catch set([a | b],[[atom]])),
+ {'EXIT', {badarg, _}} = (catch set([{}],[{}])),
+ eval(set([a],['_']), from_term([a],['_'])),
+ eval(set([], ['_']), empty_set()),
+ eval(set([a,b,a,b],[foo]), from_term([a,b],[foo])),
ok.
from_sets_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
+ E = empty_set(),
%% unordered
- ?line eval(from_sets([]), E),
- ?line {'EXIT', {type_mismatch, _}} =
+ eval(from_sets([]), E),
+ {'EXIT', {type_mismatch, _}} =
(catch from_sets([from_term([{a,b}]),
E,
from_term([{a,b,c}])])),
- ?line eval(from_sets([from_term([{a,b}]), E]),
- from_term([[],[{a,b}]])),
+ eval(from_sets([from_term([{a,b}]), E]),
+ from_term([[],[{a,b}]])),
- ?line eval(from_sets([from_term({a,b},{atom,atom}),
- from_term({b,c},{atom,atom})]),
- relation([{a,b}, {b,c}])),
- ?line {'EXIT', {type_mismatch, _}} =
+ eval(from_sets([from_term({a,b},{atom,atom}),
+ from_term({b,c},{atom,atom})]),
+ relation([{a,b}, {b,c}])),
+ {'EXIT', {type_mismatch, _}} =
(catch from_sets([from_term({a,b},{atom,atom}),
from_term({a,b,c},{atom,atom,atom})])),
- ?line {'EXIT', {badarg, _}} = (catch from_sets(foo)),
- ?line eval(from_sets([E]), from_term([[]])),
- ?line eval(from_sets([E,E]), from_term([[]])),
- ?line eval(from_sets([E,set([a])]), from_term([[],[a]])),
- ?line {'EXIT', {badarg, _}} = (catch from_sets([E,{a}])),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {badarg, _}} = (catch from_sets(foo)),
+ eval(from_sets([E]), from_term([[]])),
+ eval(from_sets([E,E]), from_term([[]])),
+ eval(from_sets([E,set([a])]), from_term([[],[a]])),
+ {'EXIT', {badarg, _}} = (catch from_sets([E,{a}])),
+ {'EXIT', {type_mismatch, _}} =
(catch from_sets([E,from_term({a}),E])),
- ?line {'EXIT', {type_mismatch, _}} = (catch from_sets([from_term({a}),E])),
+ {'EXIT', {type_mismatch, _}} = (catch from_sets([from_term({a}),E])),
%% ordered
- ?line O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
- ?line eval(from_sets(O), from_term({a,{b},[c,d]}, {atom,{atom},[atom]})),
- ?line {'EXIT', {badarg, _}} = (catch from_sets([a,b])),
- ?line {'EXIT', {badarg, _}} = (catch from_sets({a,b})),
- ?line eval(from_sets({from_term({a}),E}), from_term({{a},[]})),
+ O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
+ eval(from_sets(O), from_term({a,{b},[c,d]}, {atom,{atom},[atom]})),
+ {'EXIT', {badarg, _}} = (catch from_sets([a,b])),
+ {'EXIT', {badarg, _}} = (catch from_sets({a,b})),
+ eval(from_sets({from_term({a}),E}), from_term({{a},[]})),
ok.
relation_1(Conf) when is_list(Conf) ->
%% relation/1
- ?line eval(relation([]), from_term([], [{atom,atom}])),
- ?line eval(from_term([{a}]), relation([{a}])),
- ?line {'EXIT', {badarg, _}} = (catch relation(a)),
- ?line {'EXIT', {badarg, _}} = (catch relation([{a} | a])),
- ?line {'EXIT', {badarg, _}} = (catch relation([{}])),
- ?line {'EXIT', {badarg, _}} = (catch relation([],0)),
- ?line {'EXIT', {badarg, _}} = (catch relation([{a}],a)),
+ eval(relation([]), from_term([], [{atom,atom}])),
+ eval(from_term([{a}]), relation([{a}])),
+ {'EXIT', {badarg, _}} = (catch relation(a)),
+ {'EXIT', {badarg, _}} = (catch relation([{a} | a])),
+ {'EXIT', {badarg, _}} = (catch relation([{}])),
+ {'EXIT', {badarg, _}} = (catch relation([],0)),
+ {'EXIT', {badarg, _}} = (catch relation([{a}],a)),
%% relation/2
- ?line eval(relation([{a},{b}], 1), from_term([{a},{b}])),
- ?line eval(relation([{1,a},{2,b},{1,a}], [{x,y}]),
- from_term([{1,a},{2,b}], [{x,y}])),
- ?line eval(relation([{[1,2],a},{[2,1],b},{[2,1],a}], [{[x],y}]),
- from_term([{[1,2],a},{[1,2],b}], [{[x],y}])),
- ?line {'EXIT', {badarg, _}} = (catch relation([{1,a},{2,b}], [{[x],y}])),
- ?line {'EXIT', {badarg, _}} = (catch relation([{1,a},{1,a,b}], [{x,y}])),
- ?line {'EXIT', {badarg, _}} = (catch relation([{a}], 2)),
- ?line {'EXIT', {badarg, _}} = (catch relation([{a},{b},{c,d}], 1)),
- ?line eval(relation([{{a},[{foo,bar}]}], ['_']),
- from_term([{{a},[{foo,bar}]}], ['_'])),
- ?line eval(relation([], ['_']), from_term([], ['_'])),
- ?line {'EXIT', {badarg, _}} = (catch relation([[a]],['_'])),
- ?line eval(relation([{[a,b,a]}], [{[atom]}]), from_term([{[a,b,a]}])),
- ?line eval(relation([{[a,b,a],[[d,e,d]]}], [{[atom],[[atom]]}]),
- from_term([{[a,b,a],[[d,e,d]]}])),
- ?line eval(relation([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}]),
- from_term([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}])),
+ eval(relation([{a},{b}], 1), from_term([{a},{b}])),
+ eval(relation([{1,a},{2,b},{1,a}], [{x,y}]),
+ from_term([{1,a},{2,b}], [{x,y}])),
+ eval(relation([{[1,2],a},{[2,1],b},{[2,1],a}], [{[x],y}]),
+ from_term([{[1,2],a},{[1,2],b}], [{[x],y}])),
+ {'EXIT', {badarg, _}} = (catch relation([{1,a},{2,b}], [{[x],y}])),
+ {'EXIT', {badarg, _}} = (catch relation([{1,a},{1,a,b}], [{x,y}])),
+ {'EXIT', {badarg, _}} = (catch relation([{a}], 2)),
+ {'EXIT', {badarg, _}} = (catch relation([{a},{b},{c,d}], 1)),
+ eval(relation([{{a},[{foo,bar}]}], ['_']),
+ from_term([{{a},[{foo,bar}]}], ['_'])),
+ eval(relation([], ['_']), from_term([], ['_'])),
+ {'EXIT', {badarg, _}} = (catch relation([[a]],['_'])),
+ eval(relation([{[a,b,a]}], [{[atom]}]), from_term([{[a,b,a]}])),
+ eval(relation([{[a,b,a],[[d,e,d]]}], [{[atom],[[atom]]}]),
+ from_term([{[a,b,a],[[d,e,d]]}])),
+ eval(relation([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}]),
+ from_term([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}])),
ok.
a_function_1(Conf) when is_list(Conf) ->
%% a_function/1
- ?line eval(a_function([]), from_term([], [{atom,atom}])),
- ?line eval(a_function([{a,b},{a,b},{b,c}]), from_term([{a,b},{b,c}])),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a}])),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}])),
- ?line {'EXIT', {badarg, _}} = (catch a_function(a)),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a])),
- ?line {'EXIT', {bad_function, _}} =
+ eval(a_function([]), from_term([], [{atom,atom}])),
+ eval(a_function([{a,b},{a,b},{b,c}]), from_term([{a,b},{b,c}])),
+ {'EXIT', {badarg, _}} = (catch a_function([{a}])),
+ {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}])),
+ {'EXIT', {badarg, _}} = (catch a_function(a)),
+ {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a])),
+ {'EXIT', {bad_function, _}} =
(catch a_function([{a,b},{b,c},{a,c}])),
F = 0.0, I = round(F),
if
F == I -> % term ordering
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch a_function([{I,a},{F,b}])),
- ?line {'EXIT', {bad_function, _}} =
- (catch a_function([{[I],a},{[F],b}],[{[a],b}]));
+ {'EXIT', {bad_function, _}} =
+ (catch a_function([{[I],a},{[F],b}],[{[a],b}]));
true ->
- ?line 2 = no_elements(a_function([{I,a},{F,b}])),
- ?line 2 = no_elements(a_function([{[I],a},{[F],b}],[{[a],b}]))
+ 2 = no_elements(a_function([{I,a},{F,b}])),
+ 2 = no_elements(a_function([{[I],a},{[F],b}],[{[a],b}]))
end,
%% a_function/2
FT = [{atom,atom}],
- ?line eval(a_function([], FT), from_term([], FT)),
- ?line eval(a_function([{a,b},{b,c},{b,c}], FT),
- from_term([{a,b},{b,c}], FT)),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a}])),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a,[b,c]}])),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a}], FT)),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}], FT)),
- ?line {'EXIT', {badarg, _}} = (catch a_function(a, FT)),
- ?line {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a], FT)),
- ?line eval(a_function([{{a},[{foo,bar}]}], ['_']),
- from_term([{{a},[{foo,bar}]}], ['_'])),
- ?line eval(a_function([], ['_']), from_term([], ['_'])),
- ?line {'EXIT', {badarg, _}} = (catch a_function([[a]],['_'])),
- ?line {'EXIT', {bad_function, _}} =
+ eval(a_function([], FT), from_term([], FT)),
+ eval(a_function([{a,b},{b,c},{b,c}], FT),
+ from_term([{a,b},{b,c}], FT)),
+ {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a}])),
+ {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a,[b,c]}])),
+ {'EXIT', {badarg, _}} = (catch a_function([{a}], FT)),
+ {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}], FT)),
+ {'EXIT', {badarg, _}} = (catch a_function(a, FT)),
+ {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a], FT)),
+ eval(a_function([{{a},[{foo,bar}]}], ['_']),
+ from_term([{{a},[{foo,bar}]}], ['_'])),
+ eval(a_function([], ['_']), from_term([], ['_'])),
+ {'EXIT', {badarg, _}} = (catch a_function([[a]],['_'])),
+ {'EXIT', {bad_function, _}} =
(catch a_function([{a,b},{b,c},{a,c}], FT)),
- ?line eval(a_function([{a,[a]},{a,[a,a]}], [{atom,[atom]}]),
- from_term([{a,[a]}])),
- ?line eval(a_function([{[b,a],c},{[a,b],c}], [{[atom],atom}]),
- from_term([{[a,b],c}])),
+ eval(a_function([{a,[a]},{a,[a,a]}], [{atom,[atom]}]),
+ from_term([{a,[a]}])),
+ eval(a_function([{[b,a],c},{[a,b],c}], [{[atom],atom}]),
+ from_term([{[a,b],c}])),
ok.
family_1(Conf) when is_list(Conf) ->
%% family/1
- ?line eval(family([]), from_term([],[{atom,[atom]}])),
- ?line {'EXIT', {badarg, _}} = (catch family(a)),
- ?line {'EXIT', {badarg, _}} = (catch family([a])),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,b}])),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,[]} | a])),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}])),
- ?line {'EXIT', {bad_function, _}} =
+ eval(family([]), from_term([],[{atom,[atom]}])),
+ {'EXIT', {badarg, _}} = (catch family(a)),
+ {'EXIT', {badarg, _}} = (catch family([a])),
+ {'EXIT', {badarg, _}} = (catch family([{a,b}])),
+ {'EXIT', {badarg, _}} = (catch family([{a,[]} | a])),
+ {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}])),
+ {'EXIT', {bad_function, _}} =
(catch family([{a,[a]},{a,[]}])),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch family([{a,[]},{b,[]},{a,[a]}])),
F = 0.0, I = round(F),
if
F == I -> % term ordering
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch family([{I,[a]},{F,[b]}])),
- ?line true = (1 =:= no_elements(family([{a,[I]},{a,[F]}])));
+ true = (1 =:= no_elements(family([{a,[I]},{a,[F]}])));
true ->
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch family([{a,[I]},{a,[F]}]))
end,
- ?line eval(family([{a,[]},{b,[b]},{a,[]}]), from_term([{a,[]},{b,[b]}])),
- ?line eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}])),
- [{a,[]},{b,[tjo,{hej,san}]}]),
- ?line eval(family([{a,[a]},{a,[a,a]}]), family([{a,[a]}])),
+ eval(family([{a,[]},{b,[b]},{a,[]}]), from_term([{a,[]},{b,[b]}])),
+ eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}])),
+ [{a,[]},{b,[tjo,{hej,san}]}]),
+ eval(family([{a,[a]},{a,[a,a]}]), family([{a,[a]}])),
%% family/2
FT = [{a,[a]}],
- ?line eval(family([], FT), from_term([],FT)),
- ?line {'EXIT', {badarg, _}} = (catch family(a,FT)),
- ?line {'EXIT', {badarg, _}} = (catch family([a],FT)),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,b}],FT)),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,[]} | a],FT)),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}], FT)),
- ?line {'EXIT', {bad_function, _}} =
+ eval(family([], FT), from_term([],FT)),
+ {'EXIT', {badarg, _}} = (catch family(a,FT)),
+ {'EXIT', {badarg, _}} = (catch family([a],FT)),
+ {'EXIT', {badarg, _}} = (catch family([{a,b}],FT)),
+ {'EXIT', {badarg, _}} = (catch family([{a,[]} | a],FT)),
+ {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}], FT)),
+ {'EXIT', {bad_function, _}} =
(catch family([{a,[a]},{a,[]}], FT)),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch family([{a,[]},{b,[]},{a,[a]}], FT)),
- ?line eval(family([{a,[]},{b,[b,b]},{a,[]}], FT),
- from_term([{a,[]},{b,[b]}], FT)),
- ?line eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}], FT)),
- [{a,[]},{b,[tjo,{hej,san}]}]),
-
- ?line eval(family([{{a},[{foo,bar}]}], ['_']),
- from_term([{{a},[{foo,bar}]}], ['_'])),
- ?line eval(family([], ['_']), from_term([], ['_'])),
- ?line {'EXIT', {badarg, _}} = (catch family([[a]],['_'])),
- ?line {'EXIT', {badarg, _}} = (catch family([{a,b}],['_'])),
- ?line {'EXIT', {badarg, _}} =
+ eval(family([{a,[]},{b,[b,b]},{a,[]}], FT),
+ from_term([{a,[]},{b,[b]}], FT)),
+ eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}], FT)),
+ [{a,[]},{b,[tjo,{hej,san}]}]),
+
+ eval(family([{{a},[{foo,bar}]}], ['_']),
+ from_term([{{a},[{foo,bar}]}], ['_'])),
+ eval(family([], ['_']), from_term([], ['_'])),
+ {'EXIT', {badarg, _}} = (catch family([[a]],['_'])),
+ {'EXIT', {badarg, _}} = (catch family([{a,b}],['_'])),
+ {'EXIT', {badarg, _}} =
(catch family([{a,[foo]}], [{atom,atom}])),
- ?line eval(family([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}]),
- from_term([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}])),
- ?line eval(family([{a,[a]},{a,[a,a]}],[{atom,[atom]}]),
- family([{a,[a]}])),
- ?line eval(family([{[a,b],[a]},{[b,a],[a,a]}],[{[atom],[atom]}]),
- from_term([{[a,b],[a]},{[b,a],[a,a]}])),
+ eval(family([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}]),
+ from_term([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}])),
+ eval(family([{a,[a]},{a,[a,a]}],[{atom,[atom]}]),
+ family([{a,[a]}])),
+ eval(family([{[a,b],[a]},{[b,a],[a,a]}],[{[atom],[atom]}]),
+ from_term([{[a,b],[a]},{[b,a],[a,a]}])),
ok.
projection(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
+ E = empty_set(),
+ ER = relation([]),
%% set of ordered sets
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
-
- ?line eval(projection(1, E), E),
- ?line eval(projection(1, ER), set([])),
- ?line eval(projection(1, relation([{a,1}])), set([a])),
- ?line eval(projection(1, S1), set([a,b,c])),
- ?line eval(projection(1, S2), set([a,b])),
- ?line eval(projection(2, S1), set([0,1,2,22])),
- ?line eval(projection(2, relation([{1,a},{2,a},{3,b}])), set([a,b])),
- ?line eval(projection(1, relation([{a},{b},{c}])), set([a,b,c])),
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
+
+ eval(projection(1, E), E),
+ eval(projection(1, ER), set([])),
+ eval(projection(1, relation([{a,1}])), set([a])),
+ eval(projection(1, S1), set([a,b,c])),
+ eval(projection(1, S2), set([a,b])),
+ eval(projection(2, S1), set([0,1,2,22])),
+ eval(projection(2, relation([{1,a},{2,a},{3,b}])), set([a,b])),
+ eval(projection(1, relation([{a},{b},{c}])), set([a,b,c])),
Fun1 = {external, fun({A,B,C}) -> {A,{B,C}} end},
- ?line eval(projection(Fun1, E), E),
+ eval(projection(Fun1, E), E),
%% No check here:
- ?line eval(projection(3, projection(Fun1, empty_set())), E),
- ?line E2 = relation([], 3),
- ?line eval(projection(Fun1, E2), from_term([], [{atom,{atom,atom}}])),
+ eval(projection(3, projection(Fun1, empty_set())), E),
+ E2 = relation([], 3),
+ eval(projection(Fun1, E2), from_term([], [{atom,{atom,atom}}])),
Fun2 = {external, fun({A,_B}) -> {A} end},
- ?line eval(projection(Fun2, ER), from_term([], [{atom}])),
- ?line eval(projection(Fun2, relation([{a,1}])), relation([{a}])),
- ?line eval(projection(Fun2, relation([{a,1},{b,3},{a,2}])),
- relation([{a},{b}])),
+ eval(projection(Fun2, ER), from_term([], [{atom}])),
+ eval(projection(Fun2, relation([{a,1}])), relation([{a}])),
+ eval(projection(Fun2, relation([{a,1},{b,3},{a,2}])),
+ relation([{a},{b}])),
Fun3 = {external, fun({A,_B,C}) -> {C,{A},C} end},
- ?line eval(projection(Fun3, relation([{a,1,x},{b,3,y},{a,2,z}])),
- from_term([{x,{a},x},{y,{b},y},{z,{a},z}])),
+ eval(projection(Fun3, relation([{a,1,x},{b,3,y},{a,2,z}])),
+ from_term([{x,{a},x},{y,{b},y},{z,{a},z}])),
Fun4 = {external, fun(A={B,_C,_D}) -> {B, A} end},
- ?line eval(projection(Fun4, relation([{a,1,x},{b,3,y},{a,2,z}])),
- from_term([{a,{a,1,x}},{b,{b,3,y}},{a,{a,2,z}}])),
+ eval(projection(Fun4, relation([{a,1,x},{b,3,y},{a,2,z}])),
+ from_term([{a,{a,1,x}},{b,{b,3,y}},{a,{a,2,z}}])),
- ?line eval(projection({external, fun({A,B,_C,D}) -> {A,B,A,D} end},
- relation([{1,1,1,2}, {1,1,3,1}])),
- relation([{1,1,1,1}, {1,1,1,2}])),
+ eval(projection({external, fun({A,B,_C,D}) -> {A,B,A,D} end},
+ relation([{1,1,1,2}, {1,1,3,1}])),
+ relation([{1,1,1,1}, {1,1,1,2}])),
- ?line {'EXIT', {badarg, _}} = (catch projection(1, set([]))),
- ?line {'EXIT', {function_clause, _}} =
+ {'EXIT', {badarg, _}} = (catch projection(1, set([]))),
+ {'EXIT', {function_clause, _}} =
(catch projection({external, fun({A}) -> A end}, S1)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch projection({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]))),
%% {} is not an ordered set
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch projection({external, fun(_) -> {} end}, ER)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch projection({external, fun(_) -> {{}} end}, ER)),
- ?line eval(projection({external, fun({T,_}) -> T end},
- relation([{{},a},{{},b}])),
- set([{}])),
- ?line eval(projection({external, fun({T}) -> T end}, relation([{{}}])),
- set([{}])),
-
- ?line eval(projection({external, fun(A) -> {A} end},
- relation([{1,a},{2,b}])),
- from_term([{{1,a}},{{2,b}}])),
- ?line eval(projection({external, fun({A,B}) -> {B,A} end},
- relation([{1,a},{2,b}])),
- relation([{a,1},{b,2}])),
- ?line eval(projection({external, fun(X=Y=A) -> {X,Y,A} end}, set([a,b,c])),
- relation([{a,a,a},{b,b,b},{c,c,c}])),
-
- ?line eval(projection({external, fun({A,{_},B}) -> {A,B} end},
- from_term([{a,{a},b},{a,{b},c}])),
- relation([{a,b},{a,c}])),
- ?line eval(projection({external, fun({A,_,B}) -> {A,B} end},
- relation([{a,{},b},{a,{},c}])),
- relation([{a,b},{a,c}])),
+ eval(projection({external, fun({T,_}) -> T end},
+ relation([{{},a},{{},b}])),
+ set([{}])),
+ eval(projection({external, fun({T}) -> T end}, relation([{{}}])),
+ set([{}])),
+
+ eval(projection({external, fun(A) -> {A} end},
+ relation([{1,a},{2,b}])),
+ from_term([{{1,a}},{{2,b}}])),
+ eval(projection({external, fun({A,B}) -> {B,A} end},
+ relation([{1,a},{2,b}])),
+ relation([{a,1},{b,2}])),
+ eval(projection({external, fun(X=Y=A) -> {X,Y,A} end}, set([a,b,c])),
+ relation([{a,a,a},{b,b,b},{c,c,c}])),
+
+ eval(projection({external, fun({A,{_},B}) -> {A,B} end},
+ from_term([{a,{a},b},{a,{b},c}])),
+ relation([{a,b},{a,c}])),
+ eval(projection({external, fun({A,_,B}) -> {A,B} end},
+ relation([{a,{},b},{a,{},c}])),
+ relation([{a,b},{a,c}])),
Fun5 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
- ?line eval(projection(Fun5, E), E),
- ?line eval(projection(Fun5, set([a,b])), from_term([{a,0},{b,0}])),
- ?line eval(projection(Fun5, relation([{a,1},{b,2}])),
- from_term([{{a,1},0},{{b,2},0}])),
- ?line eval(projection(Fun5, from_term([[a],[b]])),
- from_term([{[a],0},{[b],0}])),
+ eval(projection(Fun5, E), E),
+ eval(projection(Fun5, set([a,b])), from_term([{a,0},{b,0}])),
+ eval(projection(Fun5, relation([{a,1},{b,2}])),
+ from_term([{{a,1},0},{{b,2},0}])),
+ eval(projection(Fun5, from_term([[a],[b]])),
+ from_term([{[a],0},{[b],0}])),
F = 0.0, I = round(F),
- ?line FR = relation([{I},{F}]),
+ FR = relation([{I},{F}]),
if
F == I -> % term ordering
true = (no_elements(projection(1, FR)) =:= 1);
@@ -517,374 +517,374 @@ projection(Conf) when is_list(Conf) ->
end,
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch projection({external, fun(X) -> X end},
from_term([], [[atom]]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch projection({external, fun(X) -> X end}, from_term([[a]]))),
- ?line eval(projection(fun sofs:union/1,
- from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
- from_term([[1,2,3], [a,b,c]])),
- ?line eval(projection(fun(_) -> from_term([a]) end,
- from_term([[b]], [[a]])),
- from_term([[a]])),
- ?line eval(projection(fun(_) -> from_term([a]) end,
- from_term([[1,2],[3,4]])),
- from_term([[a]])),
+ eval(projection(fun sofs:union/1,
+ from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
+ from_term([[1,2,3], [a,b,c]])),
+ eval(projection(fun(_) -> from_term([a]) end,
+ from_term([[b]], [[a]])),
+ from_term([[a]])),
+ eval(projection(fun(_) -> from_term([a]) end,
+ from_term([[1,2],[3,4]])),
+ from_term([[a]])),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
- ?line eval(projection(Fun10, from_term([[1]])), from_term([{1,1}])),
- ?line eval(projection(fun(_) -> from_term({a}) end, from_term([[a]])),
- from_term([{a}])),
- ?line {'EXIT', {badarg, _}} =
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
+ eval(projection(Fun10, from_term([[1]])), from_term([{1,1}])),
+ eval(projection(fun(_) -> from_term({a}) end, from_term([[a]])),
+ from_term([{a}])),
+ {'EXIT', {badarg, _}} =
(catch projection(fun(_) -> {a} end, from_term([[a]]))),
ok.
substitution(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
+ E = empty_set(),
+ ER = relation([]),
%% set of ordered sets
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
- ?line eval(substitution(1, E), E),
+ eval(substitution(1, E), E),
%% No check here:
Fun0 = {external, fun({A,B,C}) -> {A,{B,C}} end},
- ?line eval(substitution(3, substitution(Fun0, empty_set())), E),
- ?line eval(substitution(1, ER), from_term([],[{{atom,atom},atom}])),
- ?line eval(substitution(1, relation([{a,1}])), from_term([{{a,1},a}])),
- ?line eval(substitution(1, S1),
- from_term([{{a,1},a},{{b,2},b},{{b,22},b},{{c,0},c}])),
- ?line eval(substitution(1, S2),
- from_term([{{a,1},a},{{a,2},a},{{a,3},a},{{b,4},b},
- {{b,5},b},{{b,6},b}])),
- ?line eval(substitution(2, S1),
- from_term([{{a,1},1},{{b,2},2},{{b,22},22},{{c,0},0}])),
-
+ eval(substitution(3, substitution(Fun0, empty_set())), E),
+ eval(substitution(1, ER), from_term([],[{{atom,atom},atom}])),
+ eval(substitution(1, relation([{a,1}])), from_term([{{a,1},a}])),
+ eval(substitution(1, S1),
+ from_term([{{a,1},a},{{b,2},b},{{b,22},b},{{c,0},c}])),
+ eval(substitution(1, S2),
+ from_term([{{a,1},a},{{a,2},a},{{a,3},a},{{b,4},b},
+ {{b,5},b},{{b,6},b}])),
+ eval(substitution(2, S1),
+ from_term([{{a,1},1},{{b,2},2},{{b,22},22},{{c,0},0}])),
+
Fun1 = fun({A,_B}) -> {A} end,
XFun1 = {external, Fun1},
- ?line eval(substitution(XFun1, E), E),
- ?line eval(substitution(Fun1, E), E),
- ?line eval(substitution(XFun1, ER), from_term([], [{{atom,atom},{atom}}])),
- ?line eval(substitution(XFun1, relation([{a,1}])),
- from_term([{{a,1},{a}}])),
- ?line eval(substitution(XFun1, relation([{a,1},{b,3},{a,2}])),
- from_term([{{a,1},{a}},{{a,2},{a}},{{b,3},{b}}])),
- ?line eval(substitution({external, fun({A,_B,C}) -> {C,A,C} end},
- relation([{a,1,x},{b,3,y},{a,2,z}])),
- from_term([{{a,1,x},{x,a,x}},{{a,2,z},{z,a,z}},
- {{b,3,y},{y,b,y}}])),
+ eval(substitution(XFun1, E), E),
+ eval(substitution(Fun1, E), E),
+ eval(substitution(XFun1, ER), from_term([], [{{atom,atom},{atom}}])),
+ eval(substitution(XFun1, relation([{a,1}])),
+ from_term([{{a,1},{a}}])),
+ eval(substitution(XFun1, relation([{a,1},{b,3},{a,2}])),
+ from_term([{{a,1},{a}},{{a,2},{a}},{{b,3},{b}}])),
+ eval(substitution({external, fun({A,_B,C}) -> {C,A,C} end},
+ relation([{a,1,x},{b,3,y},{a,2,z}])),
+ from_term([{{a,1,x},{x,a,x}},{{a,2,z},{z,a,z}},
+ {{b,3,y},{y,b,y}}])),
Fun2 = fun(S) -> {A,_B} = to_external(S), from_term({A}) end,
- ?line eval(substitution(Fun2, ER), E),
- ?line eval(substitution(Fun2, relation([{a,1}])),
- from_term([{{a,1},{a}}])),
+ eval(substitution(Fun2, ER), E),
+ eval(substitution(Fun2, relation([{a,1}])),
+ from_term([{{a,1},{a}}])),
Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
- ?line eval(substitution(Fun3, E), E),
- ?line eval(substitution(Fun3, set([a,b])),
- from_term([{a,{a,0}},{b,{b,0}}])),
- ?line eval(substitution(Fun3, relation([{a,1},{b,2}])),
- from_term([{{a,1},{{a,1},0}},{{b,2},{{b,2},0}}])),
- ?line eval(substitution(Fun3, from_term([[a],[b]])),
- from_term([{[a],{[a],0}},{[b],{[b],0}}])),
-
- ?line eval(substitution(fun(_) -> E end, from_term([[a],[b]])),
- from_term([{[a],[]},{[b],[]}])),
-
- ?line {'EXIT', {badarg, _}} = (catch substitution(1, set([]))),
- ?line eval(substitution(1, ER), from_term([], [{{atom,atom},atom}])),
- ?line {'EXIT', {function_clause, _}} =
+ eval(substitution(Fun3, E), E),
+ eval(substitution(Fun3, set([a,b])),
+ from_term([{a,{a,0}},{b,{b,0}}])),
+ eval(substitution(Fun3, relation([{a,1},{b,2}])),
+ from_term([{{a,1},{{a,1},0}},{{b,2},{{b,2},0}}])),
+ eval(substitution(Fun3, from_term([[a],[b]])),
+ from_term([{[a],{[a],0}},{[b],{[b],0}}])),
+
+ eval(substitution(fun(_) -> E end, from_term([[a],[b]])),
+ from_term([{[a],[]},{[b],[]}])),
+
+ {'EXIT', {badarg, _}} = (catch substitution(1, set([]))),
+ eval(substitution(1, ER), from_term([], [{{atom,atom},atom}])),
+ {'EXIT', {function_clause, _}} =
(catch substitution({external, fun({A,_}) -> A end}, set([]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch substitution({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]))),
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch substitution({external, fun(X) -> X end},
from_term([], [[atom]]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch substitution({external, fun(X) -> X end}, from_term([[a]]))),
- ?line eval(substitution(fun(X) -> X end, from_term([], [[atom]])), E),
- ?line eval(substitution(fun sofs:union/1,
- from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
- from_term([{[[1,2],[2,3]],[1,2,3]}, {[[a,b],[b,c]],[a,b,c]}])),
- ?line eval(substitution(fun(_) -> from_term([a]) end,
- from_term([[b]], [[a]])),
- from_term([{[b],[a]}], [{[a],[atom]}])),
- ?line eval(substitution(fun(_) -> from_term([a]) end,
- from_term([[1,2],[3,4]])),
- from_term([{[1,2],[a]},{[3,4],[a]}])),
+ eval(substitution(fun(X) -> X end, from_term([], [[atom]])), E),
+ eval(substitution(fun sofs:union/1,
+ from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
+ from_term([{[[1,2],[2,3]],[1,2,3]}, {[[a,b],[b,c]],[a,b,c]}])),
+ eval(substitution(fun(_) -> from_term([a]) end,
+ from_term([[b]], [[a]])),
+ from_term([{[b],[a]}], [{[a],[atom]}])),
+ eval(substitution(fun(_) -> from_term([a]) end,
+ from_term([[1,2],[3,4]])),
+ from_term([{[1,2],[a]},{[3,4],[a]}])),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
- ?line eval(substitution(Fun10, from_term([[1]])),
- from_term([{[1],{1,1}}])),
- ?line {'EXIT', {type_mismatch, _}} =
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
+ eval(substitution(Fun10, from_term([[1]])),
+ from_term([{[1],{1,1}}])),
+ {'EXIT', {type_mismatch, _}} =
(catch substitution(Fun10, from_term([[1],[2]]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch substitution(Fun10, from_term([[1],[0]]))),
- ?line eval(substitution(fun(_) -> from_term({a}) end, from_term([[a]])),
- from_term([{[a],{a}}])),
- ?line {'EXIT', {badarg, _}} =
+ eval(substitution(fun(_) -> from_term({a}) end, from_term([[a]])),
+ from_term([{[a],{a}}])),
+ {'EXIT', {badarg, _}} =
(catch substitution(fun(_) -> {a} end, from_term([[a]]))),
ok.
restriction(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
+ E = empty_set(),
+ ER = relation([], 2),
%% set of ordered sets
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line eval(restriction(S1, set([a,b])),
- relation([{a,1},{b,2},{b,22}])),
- ?line eval(restriction(2, S1, set([1,2])),
- relation([{a,1},{b,2}])),
- ?line eval(restriction(S1, set([a,b,c])), S1),
- ?line eval(restriction(1, S1, set([0,1,d,e])), ER),
- ?line eval(restriction(1, S1, E), ER),
- ?line eval(restriction({external, fun({_A,B,C}) -> {B,C} end},
- relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
- relation([{bb,2},{cc,3}])),
- relation([{b,bb,2},{c,cc,3}])),
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ eval(restriction(S1, set([a,b])),
+ relation([{a,1},{b,2},{b,22}])),
+ eval(restriction(2, S1, set([1,2])),
+ relation([{a,1},{b,2}])),
+ eval(restriction(S1, set([a,b,c])), S1),
+ eval(restriction(1, S1, set([0,1,d,e])), ER),
+ eval(restriction(1, S1, E), ER),
+ eval(restriction({external, fun({_A,B,C}) -> {B,C} end},
+ relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
+ relation([{bb,2},{cc,3}])),
+ relation([{b,bb,2},{c,cc,3}])),
R1 = relation([],[{a,b}]),
- ?line eval(restriction(2, R1,sofs:set([],[b])), R1),
+ eval(restriction(2, R1,sofs:set([],[b])), R1),
Id = fun(X) -> X end,
XId = {external, Id},
- ?line eval(restriction(XId, relation([{a,b}]), E), ER),
- ?line eval(restriction(XId, E, relation([{b,d}])), E),
+ eval(restriction(XId, relation([{a,b}]), E), ER),
+ eval(restriction(XId, E, relation([{b,d}])), E),
Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
- ?line eval(restriction(Fun1,
- relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
- relation([{bb,2},{cc,3}])),
- relation([{b,bb,2},{c,cc,3}])),
- ?line eval(restriction({external, fun({_,{A},B}) -> {A,B} end},
- from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
- from_term([{bb,2},{cc,3}])),
- from_term([{b,{bb},2},{c,{cc},3}])),
+ eval(restriction(Fun1,
+ relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
+ relation([{bb,2},{cc,3}])),
+ relation([{b,bb,2},{c,cc,3}])),
+ eval(restriction({external, fun({_,{A},B}) -> {A,B} end},
+ from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
+ from_term([{bb,2},{cc,3}])),
+ from_term([{b,{bb},2},{c,{cc},3}])),
S5 = relation([{1,a},{2,b},{3,c}]),
- ?line eval(restriction(2, S5, set([b,c])), relation([{2,b},{3,c}])),
+ eval(restriction(2, S5, set([b,c])), relation([{2,b},{3,c}])),
S4 = relation([{a,1},{b,2},{b,27},{c,0}]),
- ?line eval(restriction(2, S4, E), ER),
+ eval(restriction(2, S4, E), ER),
S6 = relation([{1,a},{2,c},{3,b}]),
- ?line eval(restriction(2, S6, set([d,e])), ER),
- ?line eval(restriction(2,
- relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
- set([c])),
- relation([{2,c}])),
- ?line eval(restriction(XId,
- relation([{1,a},{3,b},{4,c},{4,d}]),
- relation([{2,a},{2,c},{4,c}])),
- relation([{4,c}])),
- ?line eval(restriction(2, relation([{a,b}]), E), ER),
- ?line eval(restriction(2, E, relation([{b,d}])), E),
- ?line eval(restriction(2, relation([{b,d}]), E), ER),
- ?line eval(restriction(XId, E, set([a])), E),
- ?line eval(restriction(1, S1, E), ER),
- ?line {'EXIT', {badarg, _}} =
+ eval(restriction(2, S6, set([d,e])), ER),
+ eval(restriction(2,
+ relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
+ set([c])),
+ relation([{2,c}])),
+ eval(restriction(XId,
+ relation([{1,a},{3,b},{4,c},{4,d}]),
+ relation([{2,a},{2,c},{4,c}])),
+ relation([{4,c}])),
+ eval(restriction(2, relation([{a,b}]), E), ER),
+ eval(restriction(2, E, relation([{b,d}])), E),
+ eval(restriction(2, relation([{b,d}]), E), ER),
+ eval(restriction(XId, E, set([a])), E),
+ eval(restriction(1, S1, E), ER),
+ {'EXIT', {badarg, _}} =
(catch restriction(3, relation([{a,b}]), E)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch restriction(3, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch restriction(3, relation([{a,b}]), set([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch restriction(2, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch restriction({external, fun({A,_B}) -> A end},
relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch restriction({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]),
from_term([{1,0}]))),
- ?line eval(restriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
- relation([{a,d},{c,b}])),
- ?line {'EXIT', {function_clause, _}} =
+ eval(restriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
+ relation([{a,d},{c,b}])),
+ {'EXIT', {function_clause, _}} =
(catch restriction({external, fun({A,_B}) -> A end}, set([]), E)),
Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
- ?line eval(restriction(Fun3, set([1,2]), from_term([{1,0}])),
- from_term([1])),
+ eval(restriction(Fun3, set([1,2]), from_term([{1,0}])),
+ from_term([1])),
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch restriction({external, fun(X) -> X end},
from_term([], [[atom]]), set([a]))),
S2 = from_term([], [[atom]]),
- ?line eval(restriction(Id, S2, E), E),
+ eval(restriction(Id, S2, E), E),
S3 = from_term([[a],[b]], [[atom]]),
- ?line eval(restriction(Id, S3, E), E),
- ?line eval(restriction(Id, from_term([], [[atom]]), set([a])),
- from_term([], [[atom]])),
- ?line eval(restriction(fun sofs:union/1,
- from_term([[[a],[b]], [[b],[c]],
- [[], [a,b]], [[1],[2]]]),
- from_term([[a,b],[1,2,3],[b,c]])),
- from_term([[[],[a,b]], [[a],[b]],[[b],[c]]])),
- ?line eval(restriction(fun(_) -> from_term([a]) end,
- from_term([], [[atom]]),
- from_term([], [[a]])),
- from_term([], [[atom]])),
- ?line {'EXIT', {type_mismatch, _}} =
+ eval(restriction(Id, S3, E), E),
+ eval(restriction(Id, from_term([], [[atom]]), set([a])),
+ from_term([], [[atom]])),
+ eval(restriction(fun sofs:union/1,
+ from_term([[[a],[b]], [[b],[c]],
+ [[], [a,b]], [[1],[2]]]),
+ from_term([[a,b],[1,2,3],[b,c]])),
+ from_term([[[],[a,b]], [[a],[b]],[[b],[c]]])),
+ eval(restriction(fun(_) -> from_term([a]) end,
+ from_term([], [[atom]]),
+ from_term([], [[a]])),
+ from_term([], [[atom]])),
+ {'EXIT', {type_mismatch, _}} =
(catch restriction(fun(_) -> from_term([a]) end,
from_term([[1,2],[3,4]]),
from_term([], [atom]))),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
- ?line {'EXIT', {type_mismatch, _}} =
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
+ {'EXIT', {type_mismatch, _}} =
(catch restriction(Fun10, from_term([[1]]), from_term([], [[atom]]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch restriction(fun(_) -> from_term({a}) end,
from_term([[a]]),
from_term([], [atom]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch restriction(fun(_) -> {a} end,
from_term([[a]]),
from_term([], [atom]))),
ok.
drestriction(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
+ E = empty_set(),
+ ER = relation([], 2),
%% set of ordered sets
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line eval(drestriction(S1, set([a,b])), relation([{c,0}])),
- ?line eval(drestriction(2, S1, set([1,2])),
- relation([{b,22},{c,0}])),
- ?line eval(drestriction(S1, set([a,b,c])), ER),
- ?line eval(drestriction(2, ER, set([a,b])), ER),
- ?line eval(drestriction(1, S1, set([0,1,d,e])), S1),
- ?line eval(drestriction(1, S1, E), S1),
- ?line eval(drestriction({external, fun({_A,B,C}) -> {B,C} end},
- relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
- relation([{bb,2},{cc,3}])),
- relation([{a,aa,1}])),
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ eval(drestriction(S1, set([a,b])), relation([{c,0}])),
+ eval(drestriction(2, S1, set([1,2])),
+ relation([{b,22},{c,0}])),
+ eval(drestriction(S1, set([a,b,c])), ER),
+ eval(drestriction(2, ER, set([a,b])), ER),
+ eval(drestriction(1, S1, set([0,1,d,e])), S1),
+ eval(drestriction(1, S1, E), S1),
+ eval(drestriction({external, fun({_A,B,C}) -> {B,C} end},
+ relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
+ relation([{bb,2},{cc,3}])),
+ relation([{a,aa,1}])),
Id = fun(X) -> X end,
XId = {external, Id},
- ?line eval(drestriction(XId, relation([{a,b}]), E), relation([{a,b}])),
- ?line eval(drestriction(XId, E, relation([{b,d}])), E),
+ eval(drestriction(XId, relation([{a,b}]), E), relation([{a,b}])),
+ eval(drestriction(XId, E, relation([{b,d}])), E),
Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
- ?line eval(drestriction(Fun1,
- relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
- relation([{bb,2},{cc,3}])),
- relation([{a,aa,1}])),
- ?line eval(drestriction({external, fun({_,{A},B}) -> {A,B} end},
- from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
- from_term([{bb,2},{cc,3}])),
- from_term([{a,{aa},1}])),
+ eval(drestriction(Fun1,
+ relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
+ relation([{bb,2},{cc,3}])),
+ relation([{a,aa,1}])),
+ eval(drestriction({external, fun({_,{A},B}) -> {A,B} end},
+ from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
+ from_term([{bb,2},{cc,3}])),
+ from_term([{a,{aa},1}])),
S5 = relation([{1,a},{2,b},{3,c}]),
- ?line eval(drestriction(2, S5, set([b,c])), relation([{1,a}])),
+ eval(drestriction(2, S5, set([b,c])), relation([{1,a}])),
S4 = relation([{a,1},{b,2},{b,27},{c,0}]),
- ?line eval(drestriction(2, S4, set([])), S4),
+ eval(drestriction(2, S4, set([])), S4),
S6 = relation([{1,a},{2,c},{3,b}]),
- ?line eval(drestriction(2, S6, set([d,e])), S6),
- ?line eval(drestriction(2,
- relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
- set([c])),
- relation([{1,d},{3,b},{4,a},{5,e}])),
- ?line eval(drestriction(XId,
- relation([{1,a},{3,b},{4,c},{4,d}]),
- relation([{2,a},{2,c},{4,c}])),
- relation([{1,a},{3,b},{4,d}])),
- ?line eval(drestriction(2, relation([{a,b}]), E), relation([{a,b}])),
- ?line eval(drestriction(2, E, relation([{b,d}])), E),
- ?line eval(drestriction(2, relation([{b,d}]), E), relation([{b,d}])),
- ?line eval(drestriction(XId, E, set([a])), E),
- ?line eval(drestriction(1, S1, E), S1),
- ?line {'EXIT', {badarg, _}} =
+ eval(drestriction(2, S6, set([d,e])), S6),
+ eval(drestriction(2,
+ relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
+ set([c])),
+ relation([{1,d},{3,b},{4,a},{5,e}])),
+ eval(drestriction(XId,
+ relation([{1,a},{3,b},{4,c},{4,d}]),
+ relation([{2,a},{2,c},{4,c}])),
+ relation([{1,a},{3,b},{4,d}])),
+ eval(drestriction(2, relation([{a,b}]), E), relation([{a,b}])),
+ eval(drestriction(2, E, relation([{b,d}])), E),
+ eval(drestriction(2, relation([{b,d}]), E), relation([{b,d}])),
+ eval(drestriction(XId, E, set([a])), E),
+ eval(drestriction(1, S1, E), S1),
+ {'EXIT', {badarg, _}} =
(catch drestriction(3, relation([{a,b}]), E)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch drestriction(3, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch drestriction(3, relation([{a,b}]), set([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch drestriction(2, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch drestriction({external, fun({A,_B}) -> A end},
relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch drestriction({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]),
from_term([{1,0}]))),
- ?line eval(drestriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
- relation([{b,e},{d,c}])),
- ?line {'EXIT', {function_clause, _}} =
+ eval(drestriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
+ relation([{b,e},{d,c}])),
+ {'EXIT', {function_clause, _}} =
(catch drestriction({external, fun({A,_B}) -> A end}, set([]), E)),
Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
- ?line eval(drestriction(Fun3, set([1,2]), from_term([{1,0}])),
- from_term([2])),
+ eval(drestriction(Fun3, set([1,2]), from_term([{1,0}])),
+ from_term([2])),
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch drestriction({external, fun(X) -> X end},
from_term([], [[atom]]), set([a]))),
S2 = from_term([], [[atom]]),
- ?line eval(drestriction(Id, S2, E), S2),
+ eval(drestriction(Id, S2, E), S2),
S3 = from_term([[a],[b]], [[atom]]),
- ?line eval(drestriction(Id, S3, E), S3),
- ?line eval(drestriction(Id, from_term([], [[atom]]), set([a])),
- from_term([], [[atom]])),
- ?line eval(drestriction(fun sofs:union/1,
- from_term([[[a],[b]], [[b],[c]],
- [[], [a,b]], [[1],[2]]]),
- from_term([[a,b],[1,2,3],[b,c]])),
- from_term([[[1],[2]]])),
- ?line eval(drestriction(fun(_) -> from_term([a]) end,
- from_term([], [[atom]]),
- from_term([], [[a]])),
- from_term([], [[atom]])),
- ?line {'EXIT', {type_mismatch, _}} =
+ eval(drestriction(Id, S3, E), S3),
+ eval(drestriction(Id, from_term([], [[atom]]), set([a])),
+ from_term([], [[atom]])),
+ eval(drestriction(fun sofs:union/1,
+ from_term([[[a],[b]], [[b],[c]],
+ [[], [a,b]], [[1],[2]]]),
+ from_term([[a,b],[1,2,3],[b,c]])),
+ from_term([[[1],[2]]])),
+ eval(drestriction(fun(_) -> from_term([a]) end,
+ from_term([], [[atom]]),
+ from_term([], [[a]])),
+ from_term([], [[atom]])),
+ {'EXIT', {type_mismatch, _}} =
(catch drestriction(fun(_) -> from_term([a]) end,
from_term([[1,2],[3,4]]),
from_term([], [atom]))),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
- ?line {'EXIT', {type_mismatch, _}} =
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
+ {'EXIT', {type_mismatch, _}} =
(catch drestriction(Fun10, from_term([[1]]), from_term([], [[atom]]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch drestriction(fun(_) -> from_term({a}) end,
from_term([[a]]),
from_term([], [atom]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch drestriction(fun(_) -> {a} end,
from_term([[a]]),
from_term([], [atom]))),
ok.
strict_relation_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
- ?line eval(strict_relation(E), E),
- ?line eval(strict_relation(ER), ER),
- ?line eval(strict_relation(relation([{1,a},{a,a},{2,b}])),
- relation([{1,a},{2,b}])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([], 2),
+ eval(strict_relation(E), E),
+ eval(strict_relation(ER), ER),
+ eval(strict_relation(relation([{1,a},{a,a},{2,b}])),
+ relation([{1,a},{2,b}])),
+ {'EXIT', {badarg, _}} =
(catch strict_relation(relation([{1,2,3}]))),
F = 0.0, I = round(F),
- ?line FR = relation([{F,I}]),
+ FR = relation([{F,I}]),
if
F == I -> % term ordering
eval(strict_relation(FR), ER);
@@ -894,71 +894,71 @@ strict_relation_1(Conf) when is_list(Conf) ->
ok.
extension(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
- ?line EF = family([]),
- ?line C1 = from_term(3),
- ?line C2 = from_term([3]),
- ?line {'EXIT', {function_clause, _}} = (catch extension(foo, E, C1)),
- ?line {'EXIT', {function_clause, _}} = (catch extension(ER, foo, C1)),
- ?line {'EXIT', {{case_clause, _},_}} = (catch extension(ER, E, foo)),
- ?line {'EXIT', {type_mismatch, _}} = (catch extension(ER, E, E)),
- ?line {'EXIT', {badarg, _}} = (catch extension(C2, E, E)),
- ?line eval(E, extension(E, E, E)),
- ?line eval(EF, extension(EF, E, E)),
- ?line eval(family([{3,[]}]), extension(EF, set([3]), E)),
- ?line eval(ER, extension(ER, E, C1)),
- ?line eval(E, extension(E, ER, E)),
- ?line eval(from_term([],[{{atom,atom},type(ER)}]), extension(E, ER, ER)),
-
- ?line R1 = relation([{c,7},{c,9},{c,11},{d,17},{f,20}]),
- ?line S1 = set([a,c,d,e]),
- ?line eval(extension(R1, S1, C1), lextension(R1, S1, C1)),
-
- ?line S2 = set([1,2,3]),
- ?line eval(extension(ER, S2, C1), lextension(ER, S2, C1)),
-
- ?line R3 = relation([{4,a},{8,b}]),
- ?line S3 = set([1,2,3,4,5,6,7,8,9,10,11]),
- ?line eval(extension(R3, S3, C1), lextension(R3, S3, C1)),
-
- ?line R4 = relation([{2,b},{4,d},{6,f}]),
- ?line S4 = set([1,3,5,7]),
- ?line eval(extension(R4, S4, C1), lextension(R4, S4, C1)),
-
- ?line F1 = family([{a,[1]},{c,[2]}]),
- ?line S5 = set([a,b,c,d]),
- ?line eval(extension(F1, S5, C2), lextension(F1, S5, C2)),
+ E = empty_set(),
+ ER = relation([], 2),
+ EF = family([]),
+ C1 = from_term(3),
+ C2 = from_term([3]),
+ {'EXIT', {function_clause, _}} = (catch extension(foo, E, C1)),
+ {'EXIT', {function_clause, _}} = (catch extension(ER, foo, C1)),
+ {'EXIT', {{case_clause, _},_}} = (catch extension(ER, E, foo)),
+ {'EXIT', {type_mismatch, _}} = (catch extension(ER, E, E)),
+ {'EXIT', {badarg, _}} = (catch extension(C2, E, E)),
+ eval(E, extension(E, E, E)),
+ eval(EF, extension(EF, E, E)),
+ eval(family([{3,[]}]), extension(EF, set([3]), E)),
+ eval(ER, extension(ER, E, C1)),
+ eval(E, extension(E, ER, E)),
+ eval(from_term([],[{{atom,atom},type(ER)}]), extension(E, ER, ER)),
+
+ R1 = relation([{c,7},{c,9},{c,11},{d,17},{f,20}]),
+ S1 = set([a,c,d,e]),
+ eval(extension(R1, S1, C1), lextension(R1, S1, C1)),
+
+ S2 = set([1,2,3]),
+ eval(extension(ER, S2, C1), lextension(ER, S2, C1)),
+
+ R3 = relation([{4,a},{8,b}]),
+ S3 = set([1,2,3,4,5,6,7,8,9,10,11]),
+ eval(extension(R3, S3, C1), lextension(R3, S3, C1)),
+
+ R4 = relation([{2,b},{4,d},{6,f}]),
+ S4 = set([1,3,5,7]),
+ eval(extension(R4, S4, C1), lextension(R4, S4, C1)),
+
+ F1 = family([{a,[1]},{c,[2]}]),
+ S5 = set([a,b,c,d]),
+ eval(extension(F1, S5, C2), lextension(F1, S5, C2)),
ok.
lextension(R, S, C) ->
union(R, drestriction(1, constant_function(S, C), domain(R))).
weak_relation_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
- ?line eval(weak_relation(E), E),
- ?line eval(weak_relation(ER), ER),
- ?line eval(weak_relation(relation([{a,1},{a,2},{b,2},{c,c}])),
- relation([{1,1},{2,2},{a,1},{a,2},{a,a},{b,2},{b,b},{c,c}])),
- ?line eval(weak_relation(relation([{a,1},{a,a},{a,b}])),
- relation([{1,1},{a,1},{a,a},{a,b},{b,b}])),
- ?line eval(weak_relation(relation([{a,1},{a,b},{7,w}])),
- relation([{1,1},{7,7},{7,w},{a,1},{a,a},{a,b},{b,b},{w,w}])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([], 2),
+ eval(weak_relation(E), E),
+ eval(weak_relation(ER), ER),
+ eval(weak_relation(relation([{a,1},{a,2},{b,2},{c,c}])),
+ relation([{1,1},{2,2},{a,1},{a,2},{a,a},{b,2},{b,b},{c,c}])),
+ eval(weak_relation(relation([{a,1},{a,a},{a,b}])),
+ relation([{1,1},{a,1},{a,a},{a,b},{b,b}])),
+ eval(weak_relation(relation([{a,1},{a,b},{7,w}])),
+ relation([{1,1},{7,7},{7,w},{a,1},{a,a},{a,b},{b,b},{w,w}])),
+ {'EXIT', {badarg, _}} =
(catch weak_relation(from_term([{{a},a}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch weak_relation(from_term([{a,a}],[{d,r}]))),
- ?line {'EXIT', {badarg, _}} = (catch weak_relation(relation([{1,2,3}]))),
+ {'EXIT', {badarg, _}} = (catch weak_relation(relation([{1,2,3}]))),
F = 0.0, I = round(F),
if
F == I -> % term ordering
- ?line FR1 = relation([{F,I}]),
+ FR1 = relation([{F,I}]),
eval(weak_relation(FR1), FR1),
- ?line FR2 = relation([{F,2},{I,1}]),
+ FR2 = relation([{F,2},{I,1}]),
true = no_elements(weak_relation(FR2)) =:= 5,
- ?line FR3 = relation([{1,0},{1.0,1}]),
+ FR3 = relation([{1,0},{1.0,1}]),
true = no_elements(weak_relation(FR3)) =:= 3;
true ->
ok
@@ -966,261 +966,261 @@ weak_relation_1(Conf) when is_list(Conf) ->
ok.
to_sets_1(Conf) when is_list(Conf) ->
- ?line {'EXIT', {badarg, _}} = (catch to_sets(from_term(a))),
- ?line {'EXIT', {function_clause, _}} = (catch to_sets(a)),
+ {'EXIT', {badarg, _}} = (catch to_sets(from_term(a))),
+ {'EXIT', {function_clause, _}} = (catch to_sets(a)),
%% unordered
- ?line [] = to_sets(empty_set()),
- ?line eval(to_sets(from_term([a])), [from_term(a)]),
- ?line eval(to_sets(from_term([[]],[[atom]])), [set([])]),
+ [] = to_sets(empty_set()),
+ eval(to_sets(from_term([a])), [from_term(a)]),
+ eval(to_sets(from_term([[]],[[atom]])), [set([])]),
- ?line L = [from_term([a,b]),from_term([c,d])],
- ?line eval(to_sets(from_sets(L)), L),
+ L = [from_term([a,b]),from_term([c,d])],
+ eval(to_sets(from_sets(L)), L),
- ?line eval(to_sets(relation([{a,1},{b,2}])),
- [from_term({a,1},{atom,atom}), from_term({b,2},{atom,atom})]),
+ eval(to_sets(relation([{a,1},{b,2}])),
+ [from_term({a,1},{atom,atom}), from_term({b,2},{atom,atom})]),
%% ordered
- ?line O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
- ?line eval(to_sets(from_sets(O)), O),
+ O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
+ eval(to_sets(from_sets(O)), O),
ok.
specification(Conf) when is_list(Conf) ->
Fun = {external, fun(I) when is_integer(I) -> true; (_) -> false end},
- ?line [1,2,3] = to_external(specification(Fun, set([a,1,b,2,c,3]))),
+ [1,2,3] = to_external(specification(Fun, set([a,1,b,2,c,3]))),
Fun2 = fun(S) -> is_subset(S, set([1,3,5,7,9])) end,
S2 = from_term([[1],[2],[3],[4],[5],[6],[7]]),
- ?line eval(specification(Fun2, S2), from_term([[1],[3],[5],[7]])),
+ eval(specification(Fun2, S2), from_term([[1],[3],[5],[7]])),
Fun2x = fun([1]) -> true;
([3]) -> true;
(_) -> false
end,
- ?line eval(specification({external,Fun2x}, S2), from_term([[1],[3]])),
+ eval(specification({external,Fun2x}, S2), from_term([[1],[3]])),
Fun3 = fun(_) -> neither_true_nor_false end,
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch specification(Fun3, set([a]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch specification({external, Fun3}, set([a]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch specification(Fun3, from_term([[a]]))),
- ?line {'EXIT', {function_clause, _}} =
+ {'EXIT', {function_clause, _}} =
(catch specification(Fun, a)),
ok.
union_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
- ?line {'EXIT', {badarg, _}} = (catch union(ER)),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ ER = relation([], 2),
+ {'EXIT', {badarg, _}} = (catch union(ER)),
+ {'EXIT', {type_mismatch, _}} =
(catch union(relation([{a,b}]), relation([{a,b,c}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch union(from_term([{a,b}]), from_term([{c,[x]}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch union(from_term([{a,b}]), from_term([{c,d}], [{d,r}]))),
- ?line {'EXIT', {badarg, _}} = (catch union(set([a,b,c]))),
- ?line eval(union(E), E),
- ?line eval(union(from_term([[]],[[atom]])), set([])),
- ?line eval(union(from_term([[{a,b},{b,c}],[{b,c}]])),
- relation([{a,b},{b,c}])),
- ?line eval(union(from_term([[1,2,3],[2,3,4],[3,4,5]])),
- set([1,2,3,4,5])),
-
- ?line eval(union(from_term([{[a],[],c}]), from_term([{[],[],q}])),
- from_term([{[a],[],c},{[],[],q}])),
-
- ?line eval(union(E, E), E),
- ?line eval(union(set([a,b]), E), set([a,b])),
- ?line eval(union(E, set([a,b])), set([a,b])),
-
- ?line eval(union(from_term([[a,b]])), from_term([a,b])),
+ {'EXIT', {badarg, _}} = (catch union(set([a,b,c]))),
+ eval(union(E), E),
+ eval(union(from_term([[]],[[atom]])), set([])),
+ eval(union(from_term([[{a,b},{b,c}],[{b,c}]])),
+ relation([{a,b},{b,c}])),
+ eval(union(from_term([[1,2,3],[2,3,4],[3,4,5]])),
+ set([1,2,3,4,5])),
+
+ eval(union(from_term([{[a],[],c}]), from_term([{[],[],q}])),
+ from_term([{[a],[],c},{[],[],q}])),
+
+ eval(union(E, E), E),
+ eval(union(set([a,b]), E), set([a,b])),
+ eval(union(E, set([a,b])), set([a,b])),
+
+ eval(union(from_term([[a,b]])), from_term([a,b])),
ok.
intersection_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line {'EXIT', {badarg, _}} = (catch intersection(from_term([a,b]))),
- ?line {'EXIT', {badarg, _}} = (catch intersection(E)),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ {'EXIT', {badarg, _}} = (catch intersection(from_term([a,b]))),
+ {'EXIT', {badarg, _}} = (catch intersection(E)),
+ {'EXIT', {type_mismatch, _}} =
(catch intersection(relation([{a,b}]), relation([{a,b,c}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch intersection(relation([{a,b}]), from_term([{a,b}],[{d,r}]))),
- ?line eval(intersection(from_term([[a,b,c],[d,e,f],[g,h,i]])), set([])),
-
- ?line eval(intersection(E, E), E),
- ?line eval(intersection(set([a,b,c]),set([0,b,q])),
- set([b])),
- ?line eval(intersection(set([0,b,q]),set([a,b,c])),
- set([b])),
- ?line eval(intersection(set([a,b,c]),set([a,b,c])),
- set([a,b,c])),
- ?line eval(intersection(set([a,b,d]),set([c,d])),
- set([d])),
+ eval(intersection(from_term([[a,b,c],[d,e,f],[g,h,i]])), set([])),
+
+ eval(intersection(E, E), E),
+ eval(intersection(set([a,b,c]),set([0,b,q])),
+ set([b])),
+ eval(intersection(set([0,b,q]),set([a,b,c])),
+ set([b])),
+ eval(intersection(set([a,b,c]),set([a,b,c])),
+ set([a,b,c])),
+ eval(intersection(set([a,b,d]),set([c,d])),
+ set([d])),
ok.
difference(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ {'EXIT', {type_mismatch, _}} =
(catch difference(relation([{a,b}]), relation([{a,b,c}]))),
- ?line eval(difference(E, E), E),
- ?line {'EXIT', {type_mismatch, _}} =
+ eval(difference(E, E), E),
+ {'EXIT', {type_mismatch, _}} =
(catch difference(relation([{a,b}]), from_term([{a,c}],[{d,r}]))),
- ?line eval(difference(set([a,b,c,d,f]), set([a,d,e,g])),
- set([b,c,f])),
- ?line eval(difference(set([a,b,c]), set([d,e,f])),
- set([a,b,c])),
- ?line eval(difference(set([a,b,c]), set([a,b,c,d,e,f])),
- set([])),
- ?line eval(difference(set([e,f,g]), set([a,b,c,e])),
- set([f,g])),
- ?line eval(difference(set([a,b,d,e,f]), set([c])),
- set([a,b,d,e,f])),
+ eval(difference(set([a,b,c,d,f]), set([a,d,e,g])),
+ set([b,c,f])),
+ eval(difference(set([a,b,c]), set([d,e,f])),
+ set([a,b,c])),
+ eval(difference(set([a,b,c]), set([a,b,c,d,e,f])),
+ set([])),
+ eval(difference(set([e,f,g]), set([a,b,c,e])),
+ set([f,g])),
+ eval(difference(set([a,b,d,e,f]), set([c])),
+ set([a,b,d,e,f])),
ok.
symdiff(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ {'EXIT', {type_mismatch, _}} =
(catch symdiff(relation([{a,b}]), relation([{a,b,c}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch symdiff(relation([{a,b}]), from_term([{a,b}], [{d,r}]))),
- ?line eval(symdiff(E, E), E),
- ?line eval(symdiff(set([a,b,c,d,e,f]), set([0,1,a,c])),
- union(set([b,d,e,f]), set([0,1]))),
- ?line eval(symdiff(set([a,b,c]), set([q,v,w,x,y])),
- union(set([a,b,c]), set([q,v,w,x,y]))),
- ?line eval(symdiff(set([a,b,c,d,e,f]), set([a,b,c])),
- set([d,e,f])),
- ?line eval(symdiff(set([c,e,g,h,i]), set([b,d,f])),
- union(set([c,e,g,h,i]), set([b,d,f]))),
- ?line eval(symdiff(set([c,d,g,h,k,l]),
- set([a,b,e,f,i,j,m,n])),
- union(set([c,d,g,h,k,l]), set([a,b,e,f,i,j,m,n]))),
- ?line eval(symdiff(set([c,d,g,h,k,l]),
- set([d,e,h,i,l,m,n,o,p])),
- union(set([c,g,k]), set([e,i,m,n,o,p]))),
+ eval(symdiff(E, E), E),
+ eval(symdiff(set([a,b,c,d,e,f]), set([0,1,a,c])),
+ union(set([b,d,e,f]), set([0,1]))),
+ eval(symdiff(set([a,b,c]), set([q,v,w,x,y])),
+ union(set([a,b,c]), set([q,v,w,x,y]))),
+ eval(symdiff(set([a,b,c,d,e,f]), set([a,b,c])),
+ set([d,e,f])),
+ eval(symdiff(set([c,e,g,h,i]), set([b,d,f])),
+ union(set([c,e,g,h,i]), set([b,d,f]))),
+ eval(symdiff(set([c,d,g,h,k,l]),
+ set([a,b,e,f,i,j,m,n])),
+ union(set([c,d,g,h,k,l]), set([a,b,e,f,i,j,m,n]))),
+ eval(symdiff(set([c,d,g,h,k,l]),
+ set([d,e,h,i,l,m,n,o,p])),
+ union(set([c,g,k]), set([e,i,m,n,o,p]))),
ok.
symmetric_partition(Conf) when is_list(Conf) ->
- ?line E = set([]),
- ?line S1 = set([1,2,3,4]),
- ?line S2 = set([3,4,5,6]),
- ?line S3 = set([3,4]),
- ?line S4 = set([1,2,3,4,5,6]),
- ?line T1 = set([1,2]),
- ?line T2 = set([3,4]),
- ?line T3 = set([5,6]),
- ?line T4 = set([1,2,5,6]),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = set([]),
+ S1 = set([1,2,3,4]),
+ S2 = set([3,4,5,6]),
+ S3 = set([3,4]),
+ S4 = set([1,2,3,4,5,6]),
+ T1 = set([1,2]),
+ T2 = set([3,4]),
+ T3 = set([5,6]),
+ T4 = set([1,2,5,6]),
+ {'EXIT', {type_mismatch, _}} =
(catch symmetric_partition(relation([{a,b}]), relation([{a,b,c}]))),
- ?line {E, E, E} = symmetric_partition(E, E),
- ?line {'EXIT', {type_mismatch, _}} =
+ {E, E, E} = symmetric_partition(E, E),
+ {'EXIT', {type_mismatch, _}} =
(catch symmetric_partition(relation([{a,b}]),
from_term([{a,c}],[{d,r}]))),
- ?line {E, E, S1} = symmetric_partition(E, S1),
- ?line {S1, E, E} = symmetric_partition(S1, E),
- ?line {T1, T2, T3} = symmetric_partition(S1, S2),
- ?line {T3, T2, T1} = symmetric_partition(S2, S1),
- ?line {E, T2, T4} = symmetric_partition(S3, S4),
- ?line {T4, T2, E} = symmetric_partition(S4, S3),
-
- ?line S5 = set([1,3,5]),
- ?line S6 = set([2,4,6,7,8]),
- ?line {S5, E, S6} = symmetric_partition(S5, S6),
- ?line {S6, E, S5} = symmetric_partition(S6, S5),
- ?line EE = empty_set(),
- ?line {EE, EE, EE} = symmetric_partition(EE, EE),
+ {E, E, S1} = symmetric_partition(E, S1),
+ {S1, E, E} = symmetric_partition(S1, E),
+ {T1, T2, T3} = symmetric_partition(S1, S2),
+ {T3, T2, T1} = symmetric_partition(S2, S1),
+ {E, T2, T4} = symmetric_partition(S3, S4),
+ {T4, T2, E} = symmetric_partition(S4, S3),
+
+ S5 = set([1,3,5]),
+ S6 = set([2,4,6,7,8]),
+ {S5, E, S6} = symmetric_partition(S5, S6),
+ {S6, E, S5} = symmetric_partition(S6, S5),
+ EE = empty_set(),
+ {EE, EE, EE} = symmetric_partition(EE, EE),
ok.
is_sofs_set_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line true = is_sofs_set(E),
- ?line true = is_sofs_set(from_term([a])),
- ?line true = is_sofs_set(from_term({a})),
- ?line true = is_sofs_set(from_term(a)),
- ?line false = is_sofs_set(a),
+ E = empty_set(),
+ true = is_sofs_set(E),
+ true = is_sofs_set(from_term([a])),
+ true = is_sofs_set(from_term({a})),
+ true = is_sofs_set(from_term(a)),
+ false = is_sofs_set(a),
ok.
is_set_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line true = is_set(E),
- ?line true = is_set(from_term([a])),
- ?line false = is_set(from_term({a})),
- ?line false = is_set(from_term(a)),
- ?line {'EXIT', _} = (catch is_set(a)),
-
- ?line true = is_empty_set(E),
- ?line false = is_empty_set(from_term([a])),
- ?line false = is_empty_set(from_term({a})),
- ?line false = is_empty_set(from_term(a)),
- ?line {'EXIT', _} = (catch is_empty_set(a)),
+ E = empty_set(),
+ true = is_set(E),
+ true = is_set(from_term([a])),
+ false = is_set(from_term({a})),
+ false = is_set(from_term(a)),
+ {'EXIT', _} = (catch is_set(a)),
+
+ true = is_empty_set(E),
+ false = is_empty_set(from_term([a])),
+ false = is_empty_set(from_term({a})),
+ false = is_empty_set(from_term(a)),
+ {'EXIT', _} = (catch is_empty_set(a)),
ok.
is_equal(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line true = is_equal(E, E),
- ?line false = is_equal(from_term([a]), E),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ true = is_equal(E, E),
+ false = is_equal(from_term([a]), E),
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(intersection(set([a]), set([b])),
intersection(from_term([{a}]), from_term([{b}])))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(from_term([],[{[atom],atom,[atom]}]),
from_term([],[{[atom],{atom},[atom]}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(set([a]), from_term([a],[type]))),
- ?line E2 = from_sets({from_term(a,atom)}),
- ?line true = is_equal(E2, E2),
- ?line true = is_equal(from_term({a}, {atom}), E2),
- ?line false = is_equal(from_term([{[a],[],c}]),
- from_term([{[],[],q}])),
+ E2 = from_sets({from_term(a,atom)}),
+ true = is_equal(E2, E2),
+ true = is_equal(from_term({a}, {atom}), E2),
+ false = is_equal(from_term([{[a],[],c}]),
+ from_term([{[],[],q}])),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(E, E2)),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(E2, E)),
- ?line true = is_equal(from_term({[],a,[]},{[atom],atom,[atom]}),
- from_term({[],a,[]},{[atom],atom,[atom]})),
- ?line {'EXIT', {type_mismatch, _}} =
+ true = is_equal(from_term({[],a,[]},{[atom],atom,[atom]}),
+ from_term({[],a,[]},{[atom],atom,[atom]})),
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(from_term({[],a,[]},{[atom],atom,[atom]}),
from_term({[],{a},[]},{[atom],{atom},[atom]}))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_equal(from_term({a}), from_term({a},{type}))),
ok.
is_subset(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line true = is_subset(E, E),
- ?line true = is_subset(set([a,c,e]), set([a,b,c,d,e])),
- ?line false = is_subset(set([a,b]), E),
- ?line false = is_subset(set([d,e,f]), set([b,c,d,e])),
- ?line false = is_subset(set([a,b,c]), set([b,c])),
- ?line false = is_subset(set([b,c]), set([a,c])),
- ?line false = is_subset(set([d,e]), set([a,b])),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ true = is_subset(E, E),
+ true = is_subset(set([a,c,e]), set([a,b,c,d,e])),
+ false = is_subset(set([a,b]), E),
+ false = is_subset(set([d,e,f]), set([b,c,d,e])),
+ false = is_subset(set([a,b,c]), set([b,c])),
+ false = is_subset(set([b,c]), set([a,c])),
+ false = is_subset(set([d,e]), set([a,b])),
+ {'EXIT', {type_mismatch, _}} =
(catch is_subset(intersection(set([a]), set([b])),
intersection(from_term([{a}]), from_term([{b}])))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_subset(set([a]), from_term([a,b], [at]))),
ok.
is_a_function_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([], 2),
- ?line {'EXIT', {badarg, _}} = (catch is_a_function(set([a,b]))),
- ?line true = is_a_function(E),
- ?line true = is_a_function(ER),
- ?line true = is_a_function(relation([])),
- ?line true = is_a_function(relation([],2)),
- ?line true = is_a_function(relation([{a,b},{b,c}])),
- ?line false = is_a_function(relation([{a,b},{b,c},{b,d},{e,f}])),
- ?line IS = relation([{{a,b},c},{{a,b},d}]),
- ?line false = is_a_function(IS),
+ E = empty_set(),
+ ER = relation([], 2),
+ {'EXIT', {badarg, _}} = (catch is_a_function(set([a,b]))),
+ true = is_a_function(E),
+ true = is_a_function(ER),
+ true = is_a_function(relation([])),
+ true = is_a_function(relation([],2)),
+ true = is_a_function(relation([{a,b},{b,c}])),
+ false = is_a_function(relation([{a,b},{b,c},{b,d},{e,f}])),
+ IS = relation([{{a,b},c},{{a,b},d}]),
+ false = is_a_function(IS),
F = 0.0, I = round(F),
- ?line FR = relation([{I,F},{F,1}]),
+ FR = relation([{I,F},{F,1}]),
if
F == I -> % term ordering
false = is_a_function(FR);
@@ -1230,314 +1230,314 @@ is_a_function_1(Conf) when is_list(Conf) ->
ok.
is_disjoint(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ {'EXIT', {type_mismatch, _}} =
(catch is_disjoint(relation([{a,1}]), set([a,b]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch is_disjoint(set([a]), from_term([a],[mota]))),
- ?line true = is_disjoint(E, E),
- ?line false = is_disjoint(set([a,b,c]),set([b,c,d])),
- ?line false = is_disjoint(set([b,c,d]),set([a,b,c])),
- ?line true = is_disjoint(set([a,c,e]),set([b,d,f])),
+ true = is_disjoint(E, E),
+ false = is_disjoint(set([a,b,c]),set([b,c,d])),
+ false = is_disjoint(set([b,c,d]),set([a,b,c])),
+ true = is_disjoint(set([a,c,e]),set([b,d,f])),
ok.
join(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
-
- ?line {'EXIT', {badarg, _}} = (catch join(relation([{a,1}]), 3, E, 5)),
- ?line {'EXIT', {badarg, _}} = (catch join(E, 1, relation([{a,1}]), 3)),
- ?line {'EXIT', {badarg, _}} = (catch join(E, 1, from_term([a]), 1)),
-
- ?line eval(join(E, 1, E, 2), E),
- ?line eval(join(E, 1, from_term([{{a},b}]), 2), E),
- ?line eval(join(from_term([{{a},b}]), 2, E, 1), E),
- ?line eval(join(from_term([{{a},b,e}]), 2, from_term([{c,{d}}]), 1),
- from_term([], [{{atom},atom,atom,{atom}}])),
- ?line eval(join(relation([{a}]), 1, relation([{1,a},{2,a}]), 2),
- relation([{a,1},{a,2}])),
- ?line eval(join(relation([{a,b,c},{b,c,d}]), 2,
- relation([{1,b},{2,a},{3,c}]), 2),
- relation([{a,b,c,1},{b,c,d,3}])),
- ?line eval(join(relation([{1,a,aa},{1,b,bb},{1,c,cc},{2,a,aa},{2,b,bb}]),
- 1,
- relation([{1,c,cc},{1,d,dd},{1,e,ee},{2,c,cc},{2,d,dd}]),
- 1),
- relation([{1,a,aa,c,cc},{1,a,aa,d,dd},{1,a,aa,e,ee},{1,b,bb,c,cc},
- {1,b,bb,d,dd},{1,b,bb,e,ee},{1,c,cc,c,cc},{1,c,cc,d,dd},
- {1,c,cc,e,ee},{2,a,aa,c,cc},{2,a,aa,d,dd},{2,b,bb,c,cc},
- {2,b,bb,d,dd}])),
+ E = empty_set(),
+
+ {'EXIT', {badarg, _}} = (catch join(relation([{a,1}]), 3, E, 5)),
+ {'EXIT', {badarg, _}} = (catch join(E, 1, relation([{a,1}]), 3)),
+ {'EXIT', {badarg, _}} = (catch join(E, 1, from_term([a]), 1)),
+
+ eval(join(E, 1, E, 2), E),
+ eval(join(E, 1, from_term([{{a},b}]), 2), E),
+ eval(join(from_term([{{a},b}]), 2, E, 1), E),
+ eval(join(from_term([{{a},b,e}]), 2, from_term([{c,{d}}]), 1),
+ from_term([], [{{atom},atom,atom,{atom}}])),
+ eval(join(relation([{a}]), 1, relation([{1,a},{2,a}]), 2),
+ relation([{a,1},{a,2}])),
+ eval(join(relation([{a,b,c},{b,c,d}]), 2,
+ relation([{1,b},{2,a},{3,c}]), 2),
+ relation([{a,b,c,1},{b,c,d,3}])),
+ eval(join(relation([{1,a,aa},{1,b,bb},{1,c,cc},{2,a,aa},{2,b,bb}]),
+ 1,
+ relation([{1,c,cc},{1,d,dd},{1,e,ee},{2,c,cc},{2,d,dd}]),
+ 1),
+ relation([{1,a,aa,c,cc},{1,a,aa,d,dd},{1,a,aa,e,ee},{1,b,bb,c,cc},
+ {1,b,bb,d,dd},{1,b,bb,e,ee},{1,c,cc,c,cc},{1,c,cc,d,dd},
+ {1,c,cc,e,ee},{2,a,aa,c,cc},{2,a,aa,d,dd},{2,b,bb,c,cc},
+ {2,b,bb,d,dd}])),
R1 = relation([{a,b},{b,c}]),
R2 = relation([{b,1},{a,2},{c,3},{c,4}]),
- ?line eval(join(R1, 1, R2, 1), from_term([{a,b,2},{b,c,1}])),
- ?line eval(join(R1, 2, R2, 1), from_term([{a,b,1},{b,c,3},{b,c,4}])),
- ?line eval(join(R1, 1, converse(R2), 2),
- from_term([{a,b,2},{b,c,1}])),
- ?line eval(join(R1, 2, converse(R2), 2),
- from_term([{a,b,1},{b,c,3},{b,c,4}])),
+ eval(join(R1, 1, R2, 1), from_term([{a,b,2},{b,c,1}])),
+ eval(join(R1, 2, R2, 1), from_term([{a,b,1},{b,c,3},{b,c,4}])),
+ eval(join(R1, 1, converse(R2), 2),
+ from_term([{a,b,2},{b,c,1}])),
+ eval(join(R1, 2, converse(R2), 2),
+ from_term([{a,b,1},{b,c,3},{b,c,4}])),
ok.
canonical(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ {'EXIT', {badarg, _}} =
(catch canonical_relation(set([a,b]))),
- ?line eval(canonical_relation(E), E),
- ?line eval(canonical_relation(from_term([[]])), E),
- ?line eval(canonical_relation(from_term([[a,b,c]])),
- from_term([{a,[a,b,c]},{b,[a,b,c]},{c,[a,b,c]}])),
+ eval(canonical_relation(E), E),
+ eval(canonical_relation(from_term([[]])), E),
+ eval(canonical_relation(from_term([[a,b,c]])),
+ from_term([{a,[a,b,c]},{b,[a,b,c]},{c,[a,b,c]}])),
ok.
relation_to_family_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line eval(relation_to_family(E), E),
- ?line eval(relation_to_family(relation([])), EF),
- ?line eval(relation_to_family(relation([], 2)), EF),
- ?line R = relation([{b,1},{c,7},{c,9},{c,11}]),
- ?line F = family([{b,[1]},{c,[7,9,11]}]),
- ?line eval(relation_to_family(R), F),
- ?line eval(sofs:rel2fam(R), F),
- ?line {'EXIT', {badarg, _}} = (catch relation_to_family(set([a]))),
+ E = empty_set(),
+ EF = family([]),
+ eval(relation_to_family(E), E),
+ eval(relation_to_family(relation([])), EF),
+ eval(relation_to_family(relation([], 2)), EF),
+ R = relation([{b,1},{c,7},{c,9},{c,11}]),
+ F = family([{b,[1]},{c,[7,9,11]}]),
+ eval(relation_to_family(R), F),
+ eval(sofs:rel2fam(R), F),
+ {'EXIT', {badarg, _}} = (catch relation_to_family(set([a]))),
ok.
domain_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line {'EXIT', {badarg, _}} = (catch domain(relation([],3))),
- ?line eval(domain(E), E),
- ?line eval(domain(ER), set([])),
- ?line eval(domain(relation([{1,a},{1,b},{2,a},{2,b}])), set([1,2])),
- ?line eval(domain(relation([{a,1},{b,2},{c,3}])), set([a,b,c])),
- ?line eval(field(relation([{a,1},{b,2},{c,3}])),
- set([a,b,c,1,2,3])),
+ E = empty_set(),
+ ER = relation([]),
+ {'EXIT', {badarg, _}} = (catch domain(relation([],3))),
+ eval(domain(E), E),
+ eval(domain(ER), set([])),
+ eval(domain(relation([{1,a},{1,b},{2,a},{2,b}])), set([1,2])),
+ eval(domain(relation([{a,1},{b,2},{c,3}])), set([a,b,c])),
+ eval(field(relation([{a,1},{b,2},{c,3}])),
+ set([a,b,c,1,2,3])),
F = 0.0, I = round(F),
- ?line FR = relation([{I,a},{F,b}]),
+ FR = relation([{I,a},{F,b}]),
if
F == I -> % term ordering
- ?line true = (1 =:= no_elements(domain(FR)));
+ true = (1 =:= no_elements(domain(FR)));
true ->
- ?line true = (2 =:= no_elements(domain(FR)))
+ true = (2 =:= no_elements(domain(FR)))
end,
ok.
range_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line {'EXIT', {badarg, _}} = (catch range(relation([],3))),
- ?line eval(range(E), E),
- ?line eval(range(ER), set([])),
- ?line eval(range(relation([{1,a},{1,b},{2,a},{2,b}])), set([a,b])),
- ?line eval(range(relation([{a,1},{b,2},{c,3}])), set([1,2,3])),
+ E = empty_set(),
+ ER = relation([]),
+ {'EXIT', {badarg, _}} = (catch range(relation([],3))),
+ eval(range(E), E),
+ eval(range(ER), set([])),
+ eval(range(relation([{1,a},{1,b},{2,a},{2,b}])), set([a,b])),
+ eval(range(relation([{a,1},{b,2},{c,3}])), set([1,2,3])),
ok.
-
+
inverse_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line {'EXIT', {badarg, _}} = (catch inverse(relation([],3))),
- ?line {'EXIT', {bad_function, _}} =
+ E = empty_set(),
+ ER = relation([]),
+ {'EXIT', {badarg, _}} = (catch inverse(relation([],3))),
+ {'EXIT', {bad_function, _}} =
(catch inverse(relation([{1,a},{1,b}]))),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch inverse(relation([{1,a},{2,a}]))),
- ?line eval(inverse(E), E),
- ?line eval(inverse(ER), ER),
- ?line eval(inverse(relation([{a,1},{b,2},{c,3}])),
- relation([{1,a},{2,b},{3,c}])),
+ eval(inverse(E), E),
+ eval(inverse(ER), ER),
+ eval(inverse(relation([{a,1},{b,2},{c,3}])),
+ relation([{1,a},{2,b},{3,c}])),
F = 0.0, I = round(F),
- ?line FR = relation([{I,a},{F,b}]),
+ FR = relation([{I,a},{F,b}]),
if
F == I -> % term ordering
- ?line {'EXIT', {bad_function, _}} = (catch inverse(FR));
+ {'EXIT', {bad_function, _}} = (catch inverse(FR));
true ->
- ?line eval(inverse(FR), relation([{a,I},{b,F}]))
+ eval(inverse(FR), relation([{a,I},{b,F}]))
end,
ok.
-
+
converse_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line {'EXIT', {badarg, _}} = (catch converse(relation([],3))),
- ?line eval(converse(ER), ER),
- ?line eval(converse(E), E),
- ?line eval(converse(relation([{a,1},{b,2},{c,3}])),
- relation([{1,a},{2,b},{3,c}])),
- ?line eval(converse(relation([{1,a},{1,b}])),
- relation([{a,1},{b,1}])),
- ?line eval(converse(relation([{1,a},{2,a}])),
- relation([{a,1},{a,2}])),
+ E = empty_set(),
+ ER = relation([]),
+ {'EXIT', {badarg, _}} = (catch converse(relation([],3))),
+ eval(converse(ER), ER),
+ eval(converse(E), E),
+ eval(converse(relation([{a,1},{b,2},{c,3}])),
+ relation([{1,a},{2,b},{3,c}])),
+ eval(converse(relation([{1,a},{1,b}])),
+ relation([{a,1},{b,1}])),
+ eval(converse(relation([{1,a},{2,a}])),
+ relation([{a,1},{a,2}])),
ok.
-
+
no_elements_1(Conf) when is_list(Conf) ->
- ?line 0 = no_elements(empty_set()),
- ?line 0 = no_elements(set([])),
- ?line 1 = no_elements(from_term([a])),
- ?line 10 = no_elements(from_term(lists:seq(1,10))),
- ?line 3 = no_elements(from_term({a,b,c},{atom,atom,atom})),
- ?line {'EXIT', {badarg, _}} = (catch no_elements(from_term(a))),
- ?line {'EXIT', {function_clause, _}} = (catch no_elements(a)),
+ 0 = no_elements(empty_set()),
+ 0 = no_elements(set([])),
+ 1 = no_elements(from_term([a])),
+ 10 = no_elements(from_term(lists:seq(1,10))),
+ 3 = no_elements(from_term({a,b,c},{atom,atom,atom})),
+ {'EXIT', {badarg, _}} = (catch no_elements(from_term(a))),
+ {'EXIT', {function_clause, _}} = (catch no_elements(a)),
ok.
image(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line eval(image(E, E), E),
- ?line eval(image(ER, E), set([])),
- ?line eval(image(relation([{a,1},{b,2},{c,3},{f,6}]), set([a,b,c,d,f])),
- set([1,2,3,6])),
- ?line eval(image(relation([{a,1},{b,2},{c,3},{d,4},{r,17}]),
- set([b,c,q,r])),
- set([2,3,17])),
- ?line eval(image(from_term([{[a],{1}},{[b],{2}}]), from_term([[a]])),
- from_term([{1}])),
- ?line eval(image(relation([{1,a},{2,a},{3,a},{4,b},{2,b}]), set([1,2,4])),
- set([a,b])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([]),
+ eval(image(E, E), E),
+ eval(image(ER, E), set([])),
+ eval(image(relation([{a,1},{b,2},{c,3},{f,6}]), set([a,b,c,d,f])),
+ set([1,2,3,6])),
+ eval(image(relation([{a,1},{b,2},{c,3},{d,4},{r,17}]),
+ set([b,c,q,r])),
+ set([2,3,17])),
+ eval(image(from_term([{[a],{1}},{[b],{2}}]), from_term([[a]])),
+ from_term([{1}])),
+ eval(image(relation([{1,a},{2,a},{3,a},{4,b},{2,b}]), set([1,2,4])),
+ set([a,b])),
+ {'EXIT', {badarg, _}} =
(catch image(from_term([a,b]), E)),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch image(from_term([{[a],1}]), set([[a]]))),
ok.
inverse_image(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line eval(inverse_image(E, E), E),
- ?line eval(inverse_image(ER, E), set([])),
- ?line eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},{f,6}])),
- set([a,b,c,d,f])),
- set([1,2,3,6])),
- ?line eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},
- {d,4},{r,17}])),
- set([b,c,q,r])),
- set([2,3,17])),
- ?line eval(inverse_image(converse(from_term([{[a],{1}},{[b],{2}}])),
- from_term([[a]])),
- from_term([{1}])),
- ?line eval(inverse_image(converse(relation([{1,a},{2,a},
- {3,a},{4,b},{2,b}])),
- set([1,2,4])),
- set([a,b])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([]),
+ eval(inverse_image(E, E), E),
+ eval(inverse_image(ER, E), set([])),
+ eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},{f,6}])),
+ set([a,b,c,d,f])),
+ set([1,2,3,6])),
+ eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},
+ {d,4},{r,17}])),
+ set([b,c,q,r])),
+ set([2,3,17])),
+ eval(inverse_image(converse(from_term([{[a],{1}},{[b],{2}}])),
+ from_term([[a]])),
+ from_term([{1}])),
+ eval(inverse_image(converse(relation([{1,a},{2,a},
+ {3,a},{4,b},{2,b}])),
+ set([1,2,4])),
+ set([a,b])),
+ {'EXIT', {badarg, _}} =
(catch inverse_image(from_term([a,b]), E)),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch inverse_image(converse(from_term([{[a],1}])), set([[a]]))),
ok.
composite_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = a_function([]),
- ?line eval(composite(E, E), E),
- ?line eval(composite(E, a_function([{a,b}])), E),
- ?line eval(composite(relation([{a,b}]), E), E),
- ?line {'EXIT', {bad_function, _}} =
+ E = empty_set(),
+ EF = a_function([]),
+ eval(composite(E, E), E),
+ eval(composite(E, a_function([{a,b}])), E),
+ eval(composite(relation([{a,b}]), E), E),
+ {'EXIT', {bad_function, _}} =
(catch composite(EF, relation([{a,b},{a,c}]))),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch composite(a_function([{b,a}]), EF)),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
(catch composite(relation([{1,a},{2,b},{2,a}]),
a_function([{a,1},{b,3}]))),
- ?line {'EXIT', {bad_function, _}} =
- (catch composite(a_function([{1,a},{2,b}]), a_function([{b,3}]))),
- ?line eval(composite(EF, EF), EF),
- ?line eval(composite(a_function([{b,a}]), from_term([{a,{b,c}}])),
- from_term([{b,{b,c}}])),
- ?line eval(composite(a_function([{q,1},{z,2}]),
- a_function([{1,a},{2,a}])),
- a_function([{q,a},{z,a}])),
- ?line eval(composite(a_function([{a,0},{b,0},{c,1},{d,1},{e,2},{f,3}]),
- a_function([{0,p},{1,q},{2,r},{3,w},{4,aa}])),
- a_function([{c,q},{d,q},{f,w},{e,r},{a,p},{b,p}])),
- ?line eval(composite(a_function([{1,c}]),
- a_function([{a,1},{b,3},{c,4}])),
- a_function([{1,4}])),
- ?line {'EXIT', {bad_function, _}} =
+ {'EXIT', {bad_function, _}} =
+ (catch composite(a_function([{1,a},{2,b}]), a_function([{b,3}]))),
+ eval(composite(EF, EF), EF),
+ eval(composite(a_function([{b,a}]), from_term([{a,{b,c}}])),
+ from_term([{b,{b,c}}])),
+ eval(composite(a_function([{q,1},{z,2}]),
+ a_function([{1,a},{2,a}])),
+ a_function([{q,a},{z,a}])),
+ eval(composite(a_function([{a,0},{b,0},{c,1},{d,1},{e,2},{f,3}]),
+ a_function([{0,p},{1,q},{2,r},{3,w},{4,aa}])),
+ a_function([{c,q},{d,q},{f,w},{e,r},{a,p},{b,p}])),
+ eval(composite(a_function([{1,c}]),
+ a_function([{a,1},{b,3},{c,4}])),
+ a_function([{1,4}])),
+ {'EXIT', {bad_function, _}} =
(catch composite(a_function([{1,a},{2,b}]),
a_function([{a,1},{c,3}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch composite(from_term([a,b]), E)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch composite(E, from_term([a,b]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch composite(from_term([{a,b}]), from_term([{{a},b}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch composite(from_term([{a,b}]),
from_term([{b,c}], [{d,r}]))),
F = 0.0, I = round(F),
- ?line FR1 = relation([{1,c}]),
- ?line FR2 = relation([{I,1},{F,3},{c,4}]),
+ FR1 = relation([{1,c}]),
+ FR2 = relation([{I,1},{F,3},{c,4}]),
if
F == I -> % term ordering
- ?line {'EXIT', {bad_function, _}} = (catch composite(FR1, FR2));
+ {'EXIT', {bad_function, _}} = (catch composite(FR1, FR2));
true ->
- ?line eval(composite(FR1, FR2), a_function([{1,4}]))
+ eval(composite(FR1, FR2), a_function([{1,4}]))
end,
ok.
relative_product_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line eval(relative_product1(E, E), E),
- ?line eval(relative_product1(E, relation([{a,b}])), E),
- ?line eval(relative_product1(relation([{a,b}]), E), E),
- ?line eval(relative_product1(relation([{a,b}]), from_term([{a,{b,c}}])),
- from_term([{b,{b,c}}])),
- ?line eval(relative_product1(relation([{1,z},{1,q},{2,z}]),
- relation([{1,a},{1,b},{2,a}])),
- relation([{q,a},{q,b},{z,a},{z,b}])),
- ?line eval(relative_product1(relation([{0,a},{0,b},{1,c},
- {1,d},{2,e},{3,f}]),
- relation([{1,q},{3,w}])),
- relation([{c,q},{d,q},{f,w}])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([]),
+ eval(relative_product1(E, E), E),
+ eval(relative_product1(E, relation([{a,b}])), E),
+ eval(relative_product1(relation([{a,b}]), E), E),
+ eval(relative_product1(relation([{a,b}]), from_term([{a,{b,c}}])),
+ from_term([{b,{b,c}}])),
+ eval(relative_product1(relation([{1,z},{1,q},{2,z}]),
+ relation([{1,a},{1,b},{2,a}])),
+ relation([{q,a},{q,b},{z,a},{z,b}])),
+ eval(relative_product1(relation([{0,a},{0,b},{1,c},
+ {1,d},{2,e},{3,f}]),
+ relation([{1,q},{3,w}])),
+ relation([{c,q},{d,q},{f,w}])),
+ {'EXIT', {badarg, _}} =
(catch relative_product1(from_term([a,b]), ER)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch relative_product1(ER, from_term([a,b]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch relative_product1(from_term([{a,b}]), from_term([{{a},b}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch relative_product1(from_term([{a,b}]),
from_term([{b,c}], [{d,r}]))),
ok.
relative_product_2(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
+ E = empty_set(),
+ ER = relation([]),
- ?line {'EXIT', {badarg, _}} = (catch relative_product({from_term([a,b])})),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {badarg, _}} = (catch relative_product({from_term([a,b])})),
+ {'EXIT', {type_mismatch, _}} =
(catch relative_product({from_term([{a,b}]), from_term([{{a},b}])})),
- ?line {'EXIT', {badarg, _}} = (catch relative_product({})),
- ?line true = is_equal(relative_product({ER}),
- from_term([], [{atom,{atom}}])),
- ?line eval(relative_product({relation([{a,b},{c,a}]),
- relation([{a,1},{a,2}]),
- relation([{a,aa},{c,1}])}),
- from_term([{a,{b,1,aa}},{a,{b,2,aa}}])),
- ?line eval(relative_product({relation([{a,b}])}, E), E),
- ?line eval(relative_product({E}, relation([{a,b}])), E),
- ?line eval(relative_product({E,from_term([], [{{atom,atom,atom},atom}])}),
- E),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} = (catch relative_product({})),
+ true = is_equal(relative_product({ER}),
+ from_term([], [{atom,{atom}}])),
+ eval(relative_product({relation([{a,b},{c,a}]),
+ relation([{a,1},{a,2}]),
+ relation([{a,aa},{c,1}])}),
+ from_term([{a,{b,1,aa}},{a,{b,2,aa}}])),
+ eval(relative_product({relation([{a,b}])}, E), E),
+ eval(relative_product({E}, relation([{a,b}])), E),
+ eval(relative_product({E,from_term([], [{{atom,atom,atom},atom}])}),
+ E),
+ {'EXIT', {badarg, _}} =
(catch relative_product({from_term([a,b])}, E)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch relative_product({relation([])}, set([]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch relative_product({from_term([{a,b}]),
from_term([{{a},b}])}, ER)),
- ?line {'EXIT', {badarg, _}} = (catch relative_product({}, ER)),
- ?line relprod2({relation([{a,b}])}, from_term([],[{{atom},atom}]), ER),
- ?line relprod2({relation([{a,b}]),relation([{a,1}])},
- from_term([{{b,1},{tjo,hej,sa}}]),
- from_term([{a,{tjo,hej,sa}}])),
- ?line relprod2({relation([{a,b}]), ER}, from_term([{{a,b},b}]), ER),
- ?line relprod2({relation([{a,b},{c,a}]),
- relation([{a,1},{a,2}])},
- from_term([{{b,1},b1},{{b,2},b2}]),
- relation([{a,b1},{a,b2}])),
- ?line eval(relative_product({relation([{a,b}]), ER}),
- from_term([],[{atom,{atom,atom}}])),
- ?line eval(relative_product({from_term([{{a,[a,b]},[a]}]),
- from_term([{{a,[a,b]},[[a,b]]}])}),
- from_term([{{a,[a,b]},{[a],[[a,b]]}}])),
+ {'EXIT', {badarg, _}} = (catch relative_product({}, ER)),
+ relprod2({relation([{a,b}])}, from_term([],[{{atom},atom}]), ER),
+ relprod2({relation([{a,b}]),relation([{a,1}])},
+ from_term([{{b,1},{tjo,hej,sa}}]),
+ from_term([{a,{tjo,hej,sa}}])),
+ relprod2({relation([{a,b}]), ER}, from_term([{{a,b},b}]), ER),
+ relprod2({relation([{a,b},{c,a}]),
+ relation([{a,1},{a,2}])},
+ from_term([{{b,1},b1},{{b,2},b2}]),
+ relation([{a,b1},{a,b2}])),
+ eval(relative_product({relation([{a,b}]), ER}),
+ from_term([],[{atom,{atom,atom}}])),
+ eval(relative_product({from_term([{{a,[a,b]},[a]}]),
+ from_term([{{a,[a,b]},[[a,b]]}])}),
+ from_term([{{a,[a,b]},{[a],[[a,b]]}}])),
ok.
relprod2(A1T, A2, R) ->
@@ -1546,212 +1546,212 @@ relprod2(A1T, A2, R) ->
eval(relative_product(tuple_to_list(A1T), A2), R).
product_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line eval(product(E, E), E),
- ?line eval(product(relation([]), E), E),
- ?line eval(product(E, relation([])), E),
- ?line eval(product(relation([{a,b}]),relation([{c,d}])),
- from_term([{{a,b},{c,d}}],[{{atom,atom},{atom,atom}}])),
-
- ?line eval(product({E, set([a,b,c])}), E),
- ?line eval(product({set([a,b,c]), E}), E),
- ?line eval(product({set([a,b,c]), E, E}), E),
- ?line eval(product({E,E}), E),
- ?line eval(product({set([a,b]),set([1,2])}),
- relation([{a,1},{a,2},{b,1},{b,2}])),
- ?line eval(product({from_term([a,b]), from_term([{a,b},{c,d}]),
- from_term([1])}),
- from_term([{a,{a,b},1},{a,{c,d},1},{b,{a,b},1},{b,{c,d},1}])),
- ?line {'EXIT', {badarg, _}} = (catch product({})),
- ?line {'EXIT', {badarg, _}} = (catch product({foo})),
- ?line eval(product({E}), E),
- ?line eval(product({E, E}), E),
- ?line eval(product(set([a,b]), set([1,2])),
- relation([{a,1},{a,2},{b,1},{b,2}])),
- ?line eval(product({relation([]), E}), E),
+ E = empty_set(),
+ eval(product(E, E), E),
+ eval(product(relation([]), E), E),
+ eval(product(E, relation([])), E),
+ eval(product(relation([{a,b}]),relation([{c,d}])),
+ from_term([{{a,b},{c,d}}],[{{atom,atom},{atom,atom}}])),
+
+ eval(product({E, set([a,b,c])}), E),
+ eval(product({set([a,b,c]), E}), E),
+ eval(product({set([a,b,c]), E, E}), E),
+ eval(product({E,E}), E),
+ eval(product({set([a,b]),set([1,2])}),
+ relation([{a,1},{a,2},{b,1},{b,2}])),
+ eval(product({from_term([a,b]), from_term([{a,b},{c,d}]),
+ from_term([1])}),
+ from_term([{a,{a,b},1},{a,{c,d},1},{b,{a,b},1},{b,{c,d},1}])),
+ {'EXIT', {badarg, _}} = (catch product({})),
+ {'EXIT', {badarg, _}} = (catch product({foo})),
+ eval(product({E}), E),
+ eval(product({E, E}), E),
+ eval(product(set([a,b]), set([1,2])),
+ relation([{a,1},{a,2},{b,1},{b,2}])),
+ eval(product({relation([]), E}), E),
ok.
partition_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line Id = fun(A) -> A end,
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line eval(partition(1, E), E),
- ?line eval(partition(2, E), E),
- ?line eval(partition(1, ER), from_term([], [type(ER)])),
- ?line eval(partition(2, ER), from_term([], [type(ER)])),
- ?line eval(partition(1, relation([{1,a},{1,b},{2,c},{2,d}])),
- from_term([[{1,a},{1,b}],[{2,c},{2,d}]])),
- ?line eval(partition(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
- from_term([[{1,a},{2,a}],[{1,b},{2,b}],[{3,c}]])),
- ?line eval(partition(2, relation([{1,a}])), from_term([[{1,a}]])),
- ?line eval(partition(2, relation([{1,a},{2,b}])),
- from_term([[{1,a}],[{2,b}]])),
- ?line eval(partition(2, relation([{1,a},{2,a},{3,a}])),
- from_term([[{1,a},{2,a},{3,a}]])),
- ?line eval(partition(2, relation([{1,b},{2,a}])), % OTP-4516
- from_term([[{1,b}],[{2,a}]])),
- ?line eval(union(partition(Id, S1)), S1),
- ?line eval(partition({external, fun({A,{B,_}}) -> {A,B} end},
- from_term([{a,{b,c}},{b,{c,d}},{a,{b,f}}])),
- from_term([[{a,{b,c}},{a,{b,f}}],[{b,{c,d}}]])),
+ E = empty_set(),
+ ER = relation([]),
+ Id = fun(A) -> A end,
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ eval(partition(1, E), E),
+ eval(partition(2, E), E),
+ eval(partition(1, ER), from_term([], [type(ER)])),
+ eval(partition(2, ER), from_term([], [type(ER)])),
+ eval(partition(1, relation([{1,a},{1,b},{2,c},{2,d}])),
+ from_term([[{1,a},{1,b}],[{2,c},{2,d}]])),
+ eval(partition(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
+ from_term([[{1,a},{2,a}],[{1,b},{2,b}],[{3,c}]])),
+ eval(partition(2, relation([{1,a}])), from_term([[{1,a}]])),
+ eval(partition(2, relation([{1,a},{2,b}])),
+ from_term([[{1,a}],[{2,b}]])),
+ eval(partition(2, relation([{1,a},{2,a},{3,a}])),
+ from_term([[{1,a},{2,a},{3,a}]])),
+ eval(partition(2, relation([{1,b},{2,a}])), % OTP-4516
+ from_term([[{1,b}],[{2,a}]])),
+ eval(union(partition(Id, S1)), S1),
+ eval(partition({external, fun({A,{B,_}}) -> {A,B} end},
+ from_term([{a,{b,c}},{b,{c,d}},{a,{b,f}}])),
+ from_term([[{a,{b,c}},{a,{b,f}}],[{b,{c,d}}]])),
F = 0.0, I = round(F),
- ?line FR = relation([{I,a},{F,b}]),
+ FR = relation([{I,a},{F,b}]),
if
F == I -> % term ordering
- ?line eval(partition(1, FR), from_term([[{I,a},{F,b}]]));
+ eval(partition(1, FR), from_term([[{I,a},{F,b}]]));
true ->
- ?line eval(partition(1, FR), from_term([[{I,a}],[{F,b}]]))
+ eval(partition(1, FR), from_term([[{I,a}],[{F,b}]]))
end,
- ?line {'EXIT', {badarg, _}} = (catch partition(2, set([a]))),
- ?line {'EXIT', {badarg, _}} = (catch partition(1, set([a]))),
- ?line eval(partition(Id, set([a])), from_term([[a]])),
-
- ?line eval(partition(E), E),
- ?line P1 = from_term([[a,b,c],[d,e,f],[g,h]]),
- ?line P2 = from_term([[a,d],[b,c,e,f,q,v]]),
- ?line eval(partition(union(P1, P2)),
- from_term([[a],[b,c],[d],[e,f],[g,h],[q,v]])),
- ?line {'EXIT', {badarg, _}} = (catch partition(from_term([a]))),
+ {'EXIT', {badarg, _}} = (catch partition(2, set([a]))),
+ {'EXIT', {badarg, _}} = (catch partition(1, set([a]))),
+ eval(partition(Id, set([a])), from_term([[a]])),
+
+ eval(partition(E), E),
+ P1 = from_term([[a,b,c],[d,e,f],[g,h]]),
+ P2 = from_term([[a,d],[b,c,e,f,q,v]]),
+ eval(partition(union(P1, P2)),
+ from_term([[a],[b,c],[d],[e,f],[g,h],[q,v]])),
+ {'EXIT', {badarg, _}} = (catch partition(from_term([a]))),
ok.
partition_3(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
+ E = empty_set(),
+ ER = relation([]),
%% set of ordered sets
- ?line S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
- ?line eval(partition(1, S1, set([0,1,d,e])),
- lpartition(1, S1, set([0,1,d,e]))),
- ?line eval(partition(1, S1, E), lpartition(1, S1, E)),
- ?line eval(partition(2, ER, set([a,b])), lpartition(2, ER, set([a,b]))),
+ S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
+ eval(partition(1, S1, set([0,1,d,e])),
+ lpartition(1, S1, set([0,1,d,e]))),
+ eval(partition(1, S1, E), lpartition(1, S1, E)),
+ eval(partition(2, ER, set([a,b])), lpartition(2, ER, set([a,b]))),
XFun1 = {external, fun({_A,B,C}) -> {B,C} end},
R1a = relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
R1b = relation([{bb,2},{cc,3}]),
- ?line eval(partition(XFun1, R1a, R1b), lpartition(XFun1, R1a, R1b)),
+ eval(partition(XFun1, R1a, R1b), lpartition(XFun1, R1a, R1b)),
Id = fun(X) -> X end,
XId = {external, Id},
R2 = relation([{a,b}]),
- ?line eval(partition(XId, R2, E), lpartition(XId, R2, E)),
+ eval(partition(XId, R2, E), lpartition(XId, R2, E)),
R3 = relation([{b,d}]),
- ?line eval(partition(XId, E, R3), lpartition(XId, E, R3)),
+ eval(partition(XId, E, R3), lpartition(XId, E, R3)),
Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
R4a = relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
R4b = relation([{bb,2},{cc,3}]),
- ?line eval(partition(Fun1,R4a,R4b), lpartition(Fun1,R4a,R4b)),
+ eval(partition(Fun1,R4a,R4b), lpartition(Fun1,R4a,R4b)),
XFun2 = {external, fun({_,{A},B}) -> {A,B} end},
R5a = from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
R5b = from_term([{bb,2},{cc,3}]),
- ?line eval(partition(XFun2,R5a, R5b), lpartition(XFun2,R5a, R5b)),
+ eval(partition(XFun2,R5a, R5b), lpartition(XFun2,R5a, R5b)),
R6 = relation([{a,b}]),
- ?line eval(partition(2, R6, E), lpartition(2, R6, E)),
+ eval(partition(2, R6, E), lpartition(2, R6, E)),
R7 = relation([{b,d}]),
- ?line eval(partition(2, E, R7), lpartition(2, E, R7)),
+ eval(partition(2, E, R7), lpartition(2, E, R7)),
S2 = set([a]),
- ?line eval(partition(XId, E, S2), lpartition(XId, E, S2)),
- ?line eval(partition(XId, S1, E), lpartition(XId, S1, E)),
- ?line {'EXIT', {badarg, _}} =
+ eval(partition(XId, E, S2), lpartition(XId, E, S2)),
+ eval(partition(XId, S1, E), lpartition(XId, S1, E)),
+ {'EXIT', {badarg, _}} =
(catch partition(3, relation([{a,b}]), E)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition(3, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition(3, relation([{a,b}]), set([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch partition(2, relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch partition({external, fun({A,_B}) -> A end},
relation([{a,b}]), relation([{b,d}]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]),
from_term([{1,0}]))),
S18a = relation([{1,e},{2,b},{3,c},{4,b},{5,a},{6,0}]),
S18b = set([b,d,f]),
- ?line eval(partition({external,fun({_,X}) -> X end}, S18a, S18b),
- lpartition({external,fun({_,X}) -> X end}, S18a, S18b)),
+ eval(partition({external,fun({_,X}) -> X end}, S18a, S18b),
+ lpartition({external,fun({_,X}) -> X end}, S18a, S18b)),
S19a = sofs:relation([{3,a},{8,b}]),
S19b = set([2,6,7]),
- ?line eval(partition({external,fun({X,_}) -> X end}, S19a, S19b),
- lpartition({external,fun({X,_}) -> X end}, S19a, S19b)),
+ eval(partition({external,fun({X,_}) -> X end}, S19a, S19b),
+ lpartition({external,fun({X,_}) -> X end}, S19a, S19b)),
R8a = relation([{a,d},{b,e},{c,b},{d,c}]),
S8 = set([b,d]),
- ?line eval(partition(2, R8a, S8), lpartition(2, R8a, S8)),
+ eval(partition(2, R8a, S8), lpartition(2, R8a, S8)),
S16a = relation([{1,e},{2,b},{3,c},{4,b},{5,a},{6,0}]),
S16b = set([b,c,d]),
- ?line eval(partition(2, S16a, S16b), lpartition(2, S16a, S16b)),
+ eval(partition(2, S16a, S16b), lpartition(2, S16a, S16b)),
S17a = relation([{e,1},{b,2},{c,3},{b,4},{a,5},{0,6}]),
S17b = set([b,c,d]),
- ?line eval(partition(1, S17a, S17b), lpartition(1, S17a, S17b)),
+ eval(partition(1, S17a, S17b), lpartition(1, S17a, S17b)),
- ?line {'EXIT', {function_clause, _}} =
+ {'EXIT', {function_clause, _}} =
(catch partition({external, fun({A,_B}) -> A end}, set([]), E)),
Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
S9a = set([1,2]),
S9b = from_term([{1,0}]),
- ?line eval(partition(Fun3, S9a, S9b), lpartition(Fun3, S9a, S9b)),
+ eval(partition(Fun3, S9a, S9b), lpartition(Fun3, S9a, S9b)),
S14a = relation([{1,a},{2,b},{3,c},{0,0}]),
S14b = set([b,c]),
- ?line eval(partition(2, S14a, S14b), lpartition(2, S14a, S14b)),
+ eval(partition(2, S14a, S14b), lpartition(2, S14a, S14b)),
S15a = relation([{a,1},{b,2},{c,3},{0,0}]),
S15b = set([b,c]),
- ?line eval(partition(1, S15a, S15b), lpartition(1, S15a, S15b)),
+ eval(partition(1, S15a, S15b), lpartition(1, S15a, S15b)),
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition({external, fun(X) -> X end},
from_term([], [[atom]]), set([a]))),
S10 = from_term([], [[atom]]),
- ?line eval(partition(Id, S10, E), lpartition(Id, S10, E)),
+ eval(partition(Id, S10, E), lpartition(Id, S10, E)),
S10e = from_term([[a],[b]], [[atom]]),
- ?line eval(partition(Id, S10e, E), lpartition(Id, S10e, E)),
+ eval(partition(Id, S10e, E), lpartition(Id, S10e, E)),
S11a = from_term([], [[atom]]),
S11b = set([a]),
- ?line eval(partition(Id, S11a, S11b), lpartition(Id, S11a, S11b)),
+ eval(partition(Id, S11a, S11b), lpartition(Id, S11a, S11b)),
S12a = from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]),
S12b = from_term([[a,b],[1,2,3],[b,c]]),
- ?line eval(partition(fun sofs:union/1, S12a, S12b),
- lpartition(fun sofs:union/1, S12a, S12b)),
+ eval(partition(fun sofs:union/1, S12a, S12b),
+ lpartition(fun sofs:union/1, S12a, S12b)),
Fun13 = fun(_) -> from_term([a]) end,
S13a = from_term([], [[atom]]),
S13b = from_term([], [[a]]),
- ?line eval(partition(Fun13, S13a, S13b), lpartition(Fun13, S13a, S13b)),
+ eval(partition(Fun13, S13a, S13b), lpartition(Fun13, S13a, S13b)),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch partition(fun(_) -> from_term([a]) end,
from_term([[1,2],[3,4]]),
from_term([], [atom]))),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
- ?line {'EXIT', {type_mismatch, _}} =
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
+ {'EXIT', {type_mismatch, _}} =
(catch partition(Fun10, from_term([[1]]), from_term([], [[atom]]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch partition(fun(_) -> from_term({a}) end,
from_term([[a]]),
from_term([], [atom]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition(fun(_) -> {a} end,
from_term([[a]]),
from_term([], [atom]))),
@@ -1761,79 +1761,79 @@ lpartition(F, S1, S2) ->
{restriction(F, S1, S2), drestriction(F, S1, S2)}.
multiple_relative_product(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line T = relation([{a,1},{a,11},{b,2},{c,3},{c,33},{d,4}]),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ ER = relation([]),
+ T = relation([{a,1},{a,11},{b,2},{c,3},{c,33},{d,4}]),
+ {'EXIT', {badarg, _}} =
(catch multiple_relative_product({}, ER)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch multiple_relative_product({}, relation([{a,b}]))),
- ?line eval(multiple_relative_product({E,T,T}, relation([], 3)), E),
- ?line eval(multiple_relative_product({T,T,T}, E), E),
- ?line eval(multiple_relative_product({T,T,T}, relation([],3)),
- from_term([],[{{atom,atom,atom},{atom,atom,atom}}])),
- ?line eval(multiple_relative_product({T,T,T},
+ eval(multiple_relative_product({E,T,T}, relation([], 3)), E),
+ eval(multiple_relative_product({T,T,T}, E), E),
+ eval(multiple_relative_product({T,T,T}, relation([],3)),
+ from_term([],[{{atom,atom,atom},{atom,atom,atom}}])),
+ eval(multiple_relative_product({T,T,T},
relation([{a,b,c},{c,d,a}])),
- from_term([{{a,b,c},{1,2,3}}, {{a,b,c},{1,2,33}},
- {{a,b,c},{11,2,3}}, {{a,b,c},{11,2,33}},
- {{c,d,a},{3,4,1}}, {{c,d,a},{3,4,11}},
- {{c,d,a},{33,4,1}}, {{c,d,a},{33,4,11}}])),
- ?line {'EXIT', {type_mismatch, _}} =
+ from_term([{{a,b,c},{1,2,3}}, {{a,b,c},{1,2,33}},
+ {{a,b,c},{11,2,3}}, {{a,b,c},{11,2,33}},
+ {{c,d,a},{3,4,1}}, {{c,d,a},{3,4,11}},
+ {{c,d,a},{33,4,1}}, {{c,d,a},{33,4,11}}])),
+ {'EXIT', {type_mismatch, _}} =
(catch multiple_relative_product({T}, from_term([{{a}}]))),
ok.
digraph(Conf) when is_list(Conf) ->
- ?line T0 = ets:all(),
- ?line E = empty_set(),
- ?line R = relation([{a,b},{b,c},{c,d},{d,a}]),
- ?line F = relation_to_family(R),
+ T0 = ets:all(),
+ E = empty_set(),
+ R = relation([{a,b},{b,c},{c,d},{d,a}]),
+ F = relation_to_family(R),
Type = type(F),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch family_to_digraph(set([a]))),
digraph_fail(badarg, catch family_to_digraph(set([a]), [foo])),
digraph_fail(badarg, catch family_to_digraph(F, [foo])),
digraph_fail(cyclic, catch family_to_digraph(family([{a,[a]}]),[acyclic])),
- ?line G1 = family_to_digraph(E),
- ?line {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, foo)),
- ?line {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, atom)),
- ?line true = [] == to_external(digraph_to_family(G1)),
- ?line true = [] == to_external(digraph_to_family(G1, Type)),
- ?line true = digraph:delete(G1),
-
- ?line G1a = family_to_digraph(E, [protected]),
- ?line true = [] == to_external(digraph_to_family(G1a)),
- ?line true = [] == to_external(digraph_to_family(G1a, Type)),
- ?line true = digraph:delete(G1a),
-
- ?line G2 = family_to_digraph(F),
- ?line true = F == digraph_to_family(G2),
- ?line true = F == digraph_to_family(G2, type(F)),
- ?line true = digraph:delete(G2),
-
- ?line R2 = from_term([{{a},b},{{c},d}]),
- ?line F2 = relation_to_family(R2),
- ?line Type2 = type(F2),
- ?line G3 = family_to_digraph(F2, [protected]),
- ?line true = is_subset(F2, digraph_to_family(G3, Type2)),
- ?line true = digraph:delete(G3),
+ G1 = family_to_digraph(E),
+ {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, foo)),
+ {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, atom)),
+ true = [] == to_external(digraph_to_family(G1)),
+ true = [] == to_external(digraph_to_family(G1, Type)),
+ true = digraph:delete(G1),
+
+ G1a = family_to_digraph(E, [protected]),
+ true = [] == to_external(digraph_to_family(G1a)),
+ true = [] == to_external(digraph_to_family(G1a, Type)),
+ true = digraph:delete(G1a),
+
+ G2 = family_to_digraph(F),
+ true = F == digraph_to_family(G2),
+ true = F == digraph_to_family(G2, type(F)),
+ true = digraph:delete(G2),
+
+ R2 = from_term([{{a},b},{{c},d}]),
+ F2 = relation_to_family(R2),
+ Type2 = type(F2),
+ G3 = family_to_digraph(F2, [protected]),
+ true = is_subset(F2, digraph_to_family(G3, Type2)),
+ true = digraph:delete(G3),
Fl = 0.0, I = round(Fl),
if
Fl == I -> % term ordering
- ?line G4 = digraph:new(),
+ G4 = digraph:new(),
digraph:add_vertex(G4, Fl),
digraph:add_vertex(G4, I),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch digraph_to_family(G4, Type)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch digraph_to_family(G4)),
- ?line true = digraph:delete(G4);
+ true = digraph:delete(G4);
true -> ok
end,
-
- ?line true = T0 == ets:all(),
+
+ true = T0 == ets:all(),
ok.
digraph_fail(ExitReason, Fail) ->
@@ -1844,27 +1844,27 @@ digraph_fail(ExitReason, Fail) ->
end.
constant_function(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line C = from_term(3),
- ?line eval(constant_function(E, C), E),
- ?line eval(constant_function(set([a,b]), E), from_term([{a,[]},{b,[]}])),
- ?line eval(constant_function(set([a,b]), C), from_term([{a,3},{b,3}])),
- ?line {'EXIT', {badarg, _}} = (catch constant_function(C, C)),
- ?line {'EXIT', {badarg, _}} = (catch constant_function(set([]), foo)),
+ E = empty_set(),
+ C = from_term(3),
+ eval(constant_function(E, C), E),
+ eval(constant_function(set([a,b]), E), from_term([{a,[]},{b,[]}])),
+ eval(constant_function(set([a,b]), C), from_term([{a,3},{b,3}])),
+ {'EXIT', {badarg, _}} = (catch constant_function(C, C)),
+ {'EXIT', {badarg, _}} = (catch constant_function(set([]), foo)),
ok.
misc(Conf) when is_list(Conf) ->
%% find "relational" part of relation:
- ?line S = relation([{a,b},{b,c},{b,d},{c,d}]),
+ S = relation([{a,b},{b,c},{b,d},{c,d}]),
Id = fun(A) -> A end,
- ?line RR = relational_restriction(S),
- ?line eval(union(difference(partition(Id,S), partition(1,S))), RR),
- ?line eval(union(difference(partition(1,S), partition(Id,S))), RR),
+ RR = relational_restriction(S),
+ eval(union(difference(partition(Id,S), partition(1,S))), RR),
+ eval(union(difference(partition(1,S), partition(Id,S))), RR),
%% the "functional" part:
- ?line eval(union(intersection(partition(1,S), partition(Id,S))),
- difference(S, RR)),
- ?line {'EXIT', {undef, _}} =
+ eval(union(intersection(partition(1,S), partition(Id,S))),
+ difference(S, RR)),
+ {'EXIT', {undef, _}} =
(catch projection(fun external:foo/1, set([a,b,c]))),
ok.
@@ -1876,140 +1876,140 @@ relational_restriction(R) ->
family_specification(Conf) when is_list(Conf) ->
E = empty_set(),
%% internal
- ?line eval(family_specification(fun sofs:is_set/1, E), E),
- ?line {'EXIT', {badarg, _}} =
- (catch family_specification(fun sofs:is_set/1, set([]))),
- ?line F1 = from_term([{1,[1]}]),
- ?line eval(family_specification(fun sofs:is_set/1, F1), F1),
+ eval(family_specification(fun sofs:is_set/1, E), E),
+ {'EXIT', {badarg, _}} =
+ (catch family_specification(fun sofs:is_set/1, set([]))),
+ F1 = from_term([{1,[1]}]),
+ eval(family_specification(fun sofs:is_set/1, F1), F1),
Fun = fun(S) -> is_subset(S, set([0,1,2,3,4])) end,
- ?line F2 = family([{a,[1,2]},{b,[3,4,5]}]),
- ?line eval(family_specification(Fun, F2), family([{a,[1,2]}])),
- ?line F3 = from_term([{a,[]},{b,[]}]),
- ?line eval(family_specification(fun sofs:is_set/1, F3), F3),
+ F2 = family([{a,[1,2]},{b,[3,4,5]}]),
+ eval(family_specification(Fun, F2), family([{a,[1,2]}])),
+ F3 = from_term([{a,[]},{b,[]}]),
+ eval(family_specification(fun sofs:is_set/1, F3), F3),
Fun2 = fun(_) -> throw(fippla) end,
- ?line fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
+ fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
Fun3 = fun(_) -> neither_true_nor_false end,
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch family_specification(Fun3, F3)),
%% external
IsList = {external, fun(L) when is_list(L) -> true; (_) -> false end},
- ?line eval(family_specification(IsList, E), E),
- ?line eval(family_specification(IsList, F1), F1),
+ eval(family_specification(IsList, E), E),
+ eval(family_specification(IsList, F1), F1),
MF = {external, fun(L) -> lists:member(3, L) end},
- ?line eval(family_specification(MF, F2), family([{b,[3,4,5]}])),
- ?line fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
- ?line {'EXIT', {badarg, _}} =
+ eval(family_specification(MF, F2), family([{b,[3,4,5]}])),
+ fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
+ {'EXIT', {badarg, _}} =
(catch family_specification({external, Fun3}, F3)),
ok.
family_domain_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
- ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
- ?line eval(family_domain(E), E),
- ?line eval(family_domain(ER), EF),
- ?line FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
- ?line eval(family_domain(FR), from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}])),
- ?line eval(family_field(E), E),
- ?line eval(family_field(FR),
- from_term([{a,[a,b,c,1,2,3]},{b,[]},{c,[d,e,4,5]}])),
- ?line eval(family_domain(from_term([{{a},[{{1,[]},c}]}])),
- from_term([{{a},[{1,[]}]}])),
- ?line eval(family_domain(from_term([{{a},[{{1,[a]},c}]}])),
- from_term([{{a},[{1,[a]}]}])),
- ?line eval(family_domain(from_term([{{a},[]}])),
- from_term([{{a},[]}])),
- ?line eval(family_domain(from_term([], type(FR))),
- from_term([], [{atom,[atom]}])),
- ?line {'EXIT', {badarg, _}} = (catch family_domain(set([a]))),
- ?line {'EXIT', {badarg, _}} = (catch family_field(set([a]))),
- ?line {'EXIT', {badarg, _}} = (catch family_domain(set([{a,[b]}]))),
+ E = empty_set(),
+ ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
+ EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
+ eval(family_domain(E), E),
+ eval(family_domain(ER), EF),
+ FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
+ eval(family_domain(FR), from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}])),
+ eval(family_field(E), E),
+ eval(family_field(FR),
+ from_term([{a,[a,b,c,1,2,3]},{b,[]},{c,[d,e,4,5]}])),
+ eval(family_domain(from_term([{{a},[{{1,[]},c}]}])),
+ from_term([{{a},[{1,[]}]}])),
+ eval(family_domain(from_term([{{a},[{{1,[a]},c}]}])),
+ from_term([{{a},[{1,[a]}]}])),
+ eval(family_domain(from_term([{{a},[]}])),
+ from_term([{{a},[]}])),
+ eval(family_domain(from_term([], type(FR))),
+ from_term([], [{atom,[atom]}])),
+ {'EXIT', {badarg, _}} = (catch family_domain(set([a]))),
+ {'EXIT', {badarg, _}} = (catch family_field(set([a]))),
+ {'EXIT', {badarg, _}} = (catch family_domain(set([{a,[b]}]))),
ok.
family_range_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
- ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
- ?line eval(family_range(E), E),
- ?line eval(family_range(ER), EF),
- ?line FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
- ?line eval(family_range(FR), from_term([{a,[a,b,c]},{b,[]},{c,[d,e]}])),
- ?line eval(family_range(from_term([{{a},[{c,{1,[a]}}]}])),
- from_term([{{a},[{1,[a]}]}])),
- ?line eval(family_range(from_term([{{a},[{c,{1,[]}}]}])),
- from_term([{{a},[{1,[]}]}])),
- ?line eval(family_range(from_term([{{a},[]}])),
- from_term([{{a},[]}])),
- ?line eval(family_range(from_term([], type(FR))),
- from_term([], [{atom,[atom]}])),
- ?line {'EXIT', {badarg, _}} = (catch family_range(set([a]))),
- ?line {'EXIT', {badarg, _}} = (catch family_range(set([{a,[b]}]))),
+ E = empty_set(),
+ ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
+ EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
+ eval(family_range(E), E),
+ eval(family_range(ER), EF),
+ FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
+ eval(family_range(FR), from_term([{a,[a,b,c]},{b,[]},{c,[d,e]}])),
+ eval(family_range(from_term([{{a},[{c,{1,[a]}}]}])),
+ from_term([{{a},[{1,[a]}]}])),
+ eval(family_range(from_term([{{a},[{c,{1,[]}}]}])),
+ from_term([{{a},[{1,[]}]}])),
+ eval(family_range(from_term([{{a},[]}])),
+ from_term([{{a},[]}])),
+ eval(family_range(from_term([], type(FR))),
+ from_term([], [{atom,[atom]}])),
+ {'EXIT', {badarg, _}} = (catch family_range(set([a]))),
+ {'EXIT', {badarg, _}} = (catch family_range(set([{a,[b]}]))),
ok.
family_to_relation_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line ER = relation([]),
- ?line EF = family([]),
- ?line eval(family_to_relation(E), E),
- ?line eval(family_to_relation(EF), ER),
- ?line eval(sofs:fam2rel(EF), ER),
- ?line F = family([{a,[]},{b,[1]},{c,[7,9,11]}]),
- ?line eval(family_to_relation(F), relation([{b,1},{c,7},{c,9},{c,11}])),
- ?line {'EXIT', {badarg, _}} = (catch family_to_relation(set([a]))),
+ E = empty_set(),
+ ER = relation([]),
+ EF = family([]),
+ eval(family_to_relation(E), E),
+ eval(family_to_relation(EF), ER),
+ eval(sofs:fam2rel(EF), ER),
+ F = family([{a,[]},{b,[1]},{c,[7,9,11]}]),
+ eval(family_to_relation(F), relation([{b,1},{c,7},{c,9},{c,11}])),
+ {'EXIT', {badarg, _}} = (catch family_to_relation(set([a]))),
ok.
union_of_family_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
- ?line eval(union_of_family(E), E),
- ?line eval(union_of_family(EF), set([])),
- ?line eval(union_of_family(family([])), set([])),
- ?line FR = from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}]),
- ?line eval(union_of_family(FR), set([1,2,3,4,5])),
- ?line eval(union_of_family(sofs:family([{a,[1,2]},{b,[1,2]}])),
- set([1,2])),
- ?line {'EXIT', {badarg, _}} = (catch union_of_family(set([a]))),
+ E = empty_set(),
+ EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
+ eval(union_of_family(E), E),
+ eval(union_of_family(EF), set([])),
+ eval(union_of_family(family([])), set([])),
+ FR = from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}]),
+ eval(union_of_family(FR), set([1,2,3,4,5])),
+ eval(union_of_family(sofs:family([{a,[1,2]},{b,[1,2]}])),
+ set([1,2])),
+ {'EXIT', {badarg, _}} = (catch union_of_family(set([a]))),
ok.
intersection_of_family_1(Conf) when is_list(Conf) ->
- ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
- ?line eval(intersection_of_family(EF), set([])),
- ?line FR = from_term([{a,[1,2,3]},{b,[2,3]},{c,[3,4,5]}]),
- ?line eval(intersection_of_family(FR), set([3])),
- ?line {'EXIT', {badarg, _}} =
+ EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
+ eval(intersection_of_family(EF), set([])),
+ FR = from_term([{a,[1,2,3]},{b,[2,3]},{c,[3,4,5]}]),
+ eval(intersection_of_family(FR), set([3])),
+ {'EXIT', {badarg, _}} =
(catch intersection_of_family(family([]))),
- ?line EE = from_term([], [[atom]]),
- ?line {'EXIT', {badarg, _}} = (catch intersection_of_family(EE)),
- ?line {'EXIT', {badarg, _}} = (catch intersection_of_family(set([a]))),
+ EE = from_term([], [[atom]]),
+ {'EXIT', {badarg, _}} = (catch intersection_of_family(EE)),
+ {'EXIT', {badarg, _}} = (catch intersection_of_family(set([a]))),
ok.
family_projection(Conf) when is_list(Conf) ->
SSType = [{atom,[[atom]]}],
SRType = [{atom,[{atom,atom}]}],
- ?line E = empty_set(),
-
- ?line eval(family_projection(fun(X) -> X end, family([])), E),
- ?line L1 = [{a,[]}],
- ?line eval(family_projection(fun sofs:union/1, E), E),
- ?line eval(family_projection(fun sofs:union/1, from_term(L1, SSType)),
- family(L1)),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+
+ eval(family_projection(fun(X) -> X end, family([])), E),
+ L1 = [{a,[]}],
+ eval(family_projection(fun sofs:union/1, E), E),
+ eval(family_projection(fun sofs:union/1, from_term(L1, SSType)),
+ family(L1)),
+ {'EXIT', {badarg, _}} =
(catch family_projection(fun sofs:union/1, set([]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch family_projection(fun sofs:union/1, from_term([{1,[1]}]))),
- ?line F2 = from_term([{a,[[1],[2]]},{b,[[3,4],[5]]}], SSType),
- ?line eval(family_projection(fun sofs:union/1, F2),
- family_union(F2)),
+ F2 = from_term([{a,[[1],[2]]},{b,[[3,4],[5]]}], SSType),
+ eval(family_projection(fun sofs:union/1, F2),
+ family_union(F2)),
- ?line F3 = from_term([{1,[{a,b},{b,c},{c,d}]},{3,[]},{5,[{3,5}]}],
- SRType),
- ?line eval(family_projection(fun sofs:domain/1, F3), family_domain(F3)),
- ?line eval(family_projection(fun sofs:range/1, F3), family_range(F3)),
+ F3 = from_term([{1,[{a,b},{b,c},{c,d}]},{3,[]},{5,[{3,5}]}],
+ SRType),
+ eval(family_projection(fun sofs:domain/1, F3), family_domain(F3)),
+ eval(family_projection(fun sofs:range/1, F3), family_range(F3)),
- ?line eval(family_projection(fun(_) -> E end, family([{a,[b,c]}])),
- from_term([{a,[]}])),
+ eval(family_projection(fun(_) -> E end, family([{a,[b,c]}])),
+ from_term([{a,[]}])),
Fun1 = fun(S) ->
case to_external(S) of
@@ -2017,252 +2017,252 @@ family_projection(Conf) when is_list(Conf) ->
_ -> S
end
end,
- ?line eval(family_projection(Fun1, family([{a,[1]}])),
- from_term([{a,{1,1}}])),
+ eval(family_projection(Fun1, family([{a,[1]}])),
+ from_term([{a,{1,1}}])),
Fun2 = fun(_) -> throw(fippla) end,
- ?line fippla =
+ fippla =
(catch family_projection(Fun2, family([{a,[1]}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch family_projection(Fun1, from_term([{1,[1]},{2,[2]}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch family_projection(Fun1, from_term([{1,[1]},{0,[0]}]))),
- ?line eval(family_projection(fun(_) -> E end, from_term([{a,[]}])),
- from_term([{a,[]}])),
+ eval(family_projection(fun(_) -> E end, from_term([{a,[]}])),
+ from_term([{a,[]}])),
F4 = from_term([{a,[{1,2,3}]},{b,[{4,5,6}]},{c,[]},{m3,[]}]),
Z = from_term(0),
- ?line eval(family_projection(fun(S) -> local_adjoin(S, Z) end, F4),
- from_term([{a,[{{1,2,3},0}]},{b,[{{4,5,6},0}]},{c,[]},{m3,[]}])),
- ?line {'EXIT', {badarg, _}} =
+ eval(family_projection(fun(S) -> local_adjoin(S, Z) end, F4),
+ from_term([{a,[{{1,2,3},0}]},{b,[{{4,5,6},0}]},{c,[]},{m3,[]}])),
+ {'EXIT', {badarg, _}} =
(catch family_projection({external, fun(X) -> X end},
from_term([{1,[1]}]))),
%% ordered set element
- ?line eval(family_projection(fun(_) -> from_term(a, atom) end,
- from_term([{1,[a]}])),
- from_term([{1,a}])),
+ eval(family_projection(fun(_) -> from_term(a, atom) end,
+ from_term([{1,[a]}])),
+ from_term([{1,a}])),
ok.
family_difference(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line F9 = from_term([{b,[b,c]}]),
- ?line F10 = from_term([{a,[b,c]}]),
- ?line eval(family_difference(E, E), E),
- ?line eval(family_difference(E, F10), from_term([], type(F10))),
- ?line eval(family_difference(F10, E), F10),
- ?line eval(family_difference(F9, F10), F9),
- ?line eval(family_difference(F10, F10), family([{a,[]}])),
- ?line F20 = from_term([{a,[1,2,3]},{b,[1,2,3]},{c,[1,2,3]}]),
- ?line F21 = from_term([{b,[1,2,3]},{c,[1,2,3]}]),
- ?line eval(family_difference(F20, from_term([{a,[2]}])),
- from_term([{a,[1,3]},{b,[1,2,3]},{c,[1,2,3]}])),
- ?line eval(family_difference(F20, from_term([{0,[2]},{q,[1,2]}])), F20),
- ?line eval(family_difference(F20, F21),
- from_term([{a,[1,2,3]},{b,[]},{c,[]}])),
-
- ?line eval(family_difference(from_term([{e,[f,g]}]), family([])),
- from_term([{e,[f,g]}])),
- ?line eval(family_difference(from_term([{e,[f,g]}]), EF),
- from_term([{e,[f,g]}])),
- ?line eval(family_difference(from_term([{a,[a,b,c,d]},{c,[b,c]}]),
- from_term([{a,[b,c]},{b,[d]},{d,[e,f]}])),
- from_term([{a,[a,d]},{c,[b,c]}])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ EF = family([]),
+ F9 = from_term([{b,[b,c]}]),
+ F10 = from_term([{a,[b,c]}]),
+ eval(family_difference(E, E), E),
+ eval(family_difference(E, F10), from_term([], type(F10))),
+ eval(family_difference(F10, E), F10),
+ eval(family_difference(F9, F10), F9),
+ eval(family_difference(F10, F10), family([{a,[]}])),
+ F20 = from_term([{a,[1,2,3]},{b,[1,2,3]},{c,[1,2,3]}]),
+ F21 = from_term([{b,[1,2,3]},{c,[1,2,3]}]),
+ eval(family_difference(F20, from_term([{a,[2]}])),
+ from_term([{a,[1,3]},{b,[1,2,3]},{c,[1,2,3]}])),
+ eval(family_difference(F20, from_term([{0,[2]},{q,[1,2]}])), F20),
+ eval(family_difference(F20, F21),
+ from_term([{a,[1,2,3]},{b,[]},{c,[]}])),
+
+ eval(family_difference(from_term([{e,[f,g]}]), family([])),
+ from_term([{e,[f,g]}])),
+ eval(family_difference(from_term([{e,[f,g]}]), EF),
+ from_term([{e,[f,g]}])),
+ eval(family_difference(from_term([{a,[a,b,c,d]},{c,[b,c]}]),
+ from_term([{a,[b,c]},{b,[d]},{d,[e,f]}])),
+ from_term([{a,[a,d]},{c,[b,c]}])),
+ {'EXIT', {badarg, _}} =
(catch family_difference(set([]), set([]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch family_difference(from_term([{a,[b,c]}]),
from_term([{e,[{f}]}]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch family_difference(from_term([{a,[b]}]),
from_term([{c,[d]}], [{i,[s]}]))),
ok.
family_intersection_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line ES = from_term([], [{atom,[[atom]]}]),
- ?line eval(family_intersection(E), E),
- ?line {'EXIT', {badarg, _}} = (catch family_intersection(EF)),
- ?line eval(family_intersection(ES), EF),
- ?line {'EXIT', {badarg, _}} = (catch family_intersection(set([]))),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ EF = family([]),
+ ES = from_term([], [{atom,[[atom]]}]),
+ eval(family_intersection(E), E),
+ {'EXIT', {badarg, _}} = (catch family_intersection(EF)),
+ eval(family_intersection(ES), EF),
+ {'EXIT', {badarg, _}} = (catch family_intersection(set([]))),
+ {'EXIT', {badarg, _}} =
(catch family_intersection(from_term([{a,[1,2]}]))),
- ?line F1 = from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}]),
- ?line {'EXIT', {badarg, _}} = (catch family_intersection(F1)),
- ?line F2 = from_term([{b,[[1],[2],[2,3]]},{a,[]},{c,[[4]]}]),
- ?line {'EXIT', {badarg, _}} = (catch family_intersection(F2)),
- ?line F3 = from_term([{a,[[1,2,3],[2],[2,3]]},{c,[[4,5,6],[5,6,7]]}]),
- ?line eval(family_intersection(F3), family([{a,[2]},{c,[5,6]}])),
+ F1 = from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}]),
+ {'EXIT', {badarg, _}} = (catch family_intersection(F1)),
+ F2 = from_term([{b,[[1],[2],[2,3]]},{a,[]},{c,[[4]]}]),
+ {'EXIT', {badarg, _}} = (catch family_intersection(F2)),
+ F3 = from_term([{a,[[1,2,3],[2],[2,3]]},{c,[[4,5,6],[5,6,7]]}]),
+ eval(family_intersection(F3), family([{a,[2]},{c,[5,6]}])),
ok.
family_intersection_2(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
- ?line F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
- ?line F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
- {q,[1]}]),
-
- ?line eval(family_intersection(E, E), E),
- ?line eval(family_intersection(EF, EF), EF),
- ?line eval(family_intersection(F1, F2),
- from_term([{c,[7]},{d,[10,11]}])),
- ?line eval(family_intersection(F1, F3), F1),
- ?line eval(family_intersection(F2, F3), F2),
-
- ?line eval(family_intersection(EF, from_term([{e,[f,g]}])), EF),
- ?line eval(family_intersection(E, from_term([{e,[f,g]}])), EF),
- ?line eval(family_intersection(from_term([{e,[f,g]}]), EF), EF),
- ?line eval(family_intersection(from_term([{e,[f,g]}]), E), EF),
- ?line {'EXIT', {type_mismatch, _}} =
+ E = empty_set(),
+ EF = family([]),
+ F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
+ F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
+ F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
+ {q,[1]}]),
+
+ eval(family_intersection(E, E), E),
+ eval(family_intersection(EF, EF), EF),
+ eval(family_intersection(F1, F2),
+ from_term([{c,[7]},{d,[10,11]}])),
+ eval(family_intersection(F1, F3), F1),
+ eval(family_intersection(F2, F3), F2),
+
+ eval(family_intersection(EF, from_term([{e,[f,g]}])), EF),
+ eval(family_intersection(E, from_term([{e,[f,g]}])), EF),
+ eval(family_intersection(from_term([{e,[f,g]}]), EF), EF),
+ eval(family_intersection(from_term([{e,[f,g]}]), E), EF),
+ {'EXIT', {type_mismatch, _}} =
(catch family_intersection(from_term([{a,[b,c]}]),
from_term([{e,[{f}]}]))),
- ?line F11 = family([{a,[1,2,3]},{b,[0,2,4]},{c,[0,3,6,9]}]),
- ?line eval(union_of_family(F11), set([0,1,2,3,4,6,9])),
- ?line F12 = from_term([{a,[1,2,3,4]},{b,[0,2,4]},{c,[2,3,4,5]}]),
- ?line eval(intersection_of_family(F12), set([2,4])),
+ F11 = family([{a,[1,2,3]},{b,[0,2,4]},{c,[0,3,6,9]}]),
+ eval(union_of_family(F11), set([0,1,2,3,4,6,9])),
+ F12 = from_term([{a,[1,2,3,4]},{b,[0,2,4]},{c,[2,3,4,5]}]),
+ eval(intersection_of_family(F12), set([2,4])),
ok.
family_union_1(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line ES = from_term([], [{atom,[[atom]]}]),
- ?line eval(family_union(E), E),
- ?line eval(family_union(ES), EF),
- ?line {'EXIT', {badarg, _}} = (catch family_union(set([]))),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ EF = family([]),
+ ES = from_term([], [{atom,[[atom]]}]),
+ eval(family_union(E), E),
+ eval(family_union(ES), EF),
+ {'EXIT', {badarg, _}} = (catch family_union(set([]))),
+ {'EXIT', {badarg, _}} =
(catch family_union(from_term([{a,[1,2]}]))),
- ?line eval(family_union(from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}])),
- family([{a,[1,2,3]},{b,[]},{c,[4]}])),
+ eval(family_union(from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}])),
+ family([{a,[1,2,3]},{b,[]},{c,[4]}])),
ok.
family_union_2(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
- ?line EF = family([]),
- ?line F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
- ?line F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
- ?line F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
- {q,[1]}]),
-
- ?line eval(family_union(E, E), E),
- ?line eval(family_union(F1, E), F1),
- ?line eval(family_union(E, F2), F2),
- ?line eval(family_union(F1, F2), F3),
- ?line eval(family_union(F2, F1), F3),
-
- ?line eval(family_union(E, from_term([{e,[f,g]}])),
- from_term([{e,[f,g]}])),
- ?line eval(family_union(EF, from_term([{e,[f,g]}])),
- from_term([{e,[f,g]}])),
- ?line eval(family_union(from_term([{e,[f,g]}]), E),
- from_term([{e,[f,g]}])),
- ?line {'EXIT', {badarg, _}} =
+ E = empty_set(),
+ EF = family([]),
+ F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
+ F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
+ F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
+ {q,[1]}]),
+
+ eval(family_union(E, E), E),
+ eval(family_union(F1, E), F1),
+ eval(family_union(E, F2), F2),
+ eval(family_union(F1, F2), F3),
+ eval(family_union(F2, F1), F3),
+
+ eval(family_union(E, from_term([{e,[f,g]}])),
+ from_term([{e,[f,g]}])),
+ eval(family_union(EF, from_term([{e,[f,g]}])),
+ from_term([{e,[f,g]}])),
+ eval(family_union(from_term([{e,[f,g]}]), E),
+ from_term([{e,[f,g]}])),
+ {'EXIT', {badarg, _}} =
(catch family_union(set([]),set([]))),
- ?line {'EXIT', {type_mismatch, _}} =
+ {'EXIT', {type_mismatch, _}} =
(catch family_union(from_term([{a,[b,c]}]),
from_term([{e,[{f}]}]))),
ok.
partition_family(Conf) when is_list(Conf) ->
- ?line E = empty_set(),
+ E = empty_set(),
%% set of ordered sets
- ?line ER = relation([]),
- ?line EF = from_term([], [{atom,[{atom,atom}]}]),
-
- ?line eval(partition_family(1, E), E),
- ?line eval(partition_family(2, E), E),
- ?line eval(partition_family(fun sofs:union/1, E), E),
- ?line eval(partition_family(1, ER), EF),
- ?line eval(partition_family(2, ER), EF),
- ?line {'EXIT', {badarg, _}} = (catch partition_family(1, set([]))),
- ?line {'EXIT', {badarg, _}} = (catch partition_family(2, set([]))),
- ?line {'EXIT', {function_clause, _}} =
+ ER = relation([]),
+ EF = from_term([], [{atom,[{atom,atom}]}]),
+
+ eval(partition_family(1, E), E),
+ eval(partition_family(2, E), E),
+ eval(partition_family(fun sofs:union/1, E), E),
+ eval(partition_family(1, ER), EF),
+ eval(partition_family(2, ER), EF),
+ {'EXIT', {badarg, _}} = (catch partition_family(1, set([]))),
+ {'EXIT', {badarg, _}} = (catch partition_family(2, set([]))),
+ {'EXIT', {function_clause, _}} =
(catch partition_family(fun({_A,B}) -> {B} end, from_term([{1}]))),
- ?line eval(partition_family(1, relation([{1,a},{1,b},{2,c},{2,d}])),
- from_term([{1,[{1,a},{1,b}]},{2,[{2,c},{2,d}]}])),
- ?line eval(partition_family(1, relation([{1,a},{2,b}])),
- from_term([{1,[{1,a}]},{2,[{2,b}]}])),
- ?line eval(partition_family(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
- from_term([{a,[{1,a},{2,a}]},{b,[{1,b},{2,b}]},{c,[{3,c}]}])),
- ?line eval(partition_family(2, relation([{1,a}])),
- from_term([{a,[{1,a}]}])),
- ?line eval(partition_family(2, relation([{1,a},{2,a},{3,a}])),
- from_term([{a,[{1,a},{2,a},{3,a}]}])),
- ?line eval(partition_family(2, relation([{1,a},{2,b}])),
- from_term([{a,[{1,a}]},{b,[{2,b}]}])),
- ?line F13 = from_term([{a,b,c},{a,b,d},{b,b,c},{a,c,c},{a,c,d},{b,c,c}]),
- ?line eval(partition_family(2, F13),
- from_term([{b,[{a,b,c},{a,b,d},{b,b,c}]},
- {c,[{a,c,c},{a,c,d},{b,c,c}]}])),
+ eval(partition_family(1, relation([{1,a},{1,b},{2,c},{2,d}])),
+ from_term([{1,[{1,a},{1,b}]},{2,[{2,c},{2,d}]}])),
+ eval(partition_family(1, relation([{1,a},{2,b}])),
+ from_term([{1,[{1,a}]},{2,[{2,b}]}])),
+ eval(partition_family(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
+ from_term([{a,[{1,a},{2,a}]},{b,[{1,b},{2,b}]},{c,[{3,c}]}])),
+ eval(partition_family(2, relation([{1,a}])),
+ from_term([{a,[{1,a}]}])),
+ eval(partition_family(2, relation([{1,a},{2,a},{3,a}])),
+ from_term([{a,[{1,a},{2,a},{3,a}]}])),
+ eval(partition_family(2, relation([{1,a},{2,b}])),
+ from_term([{a,[{1,a}]},{b,[{2,b}]}])),
+ F13 = from_term([{a,b,c},{a,b,d},{b,b,c},{a,c,c},{a,c,d},{b,c,c}]),
+ eval(partition_family(2, F13),
+ from_term([{b,[{a,b,c},{a,b,d},{b,b,c}]},
+ {c,[{a,c,c},{a,c,d},{b,c,c}]}])),
Fun1 = {external, fun({A,_B}) -> {A} end},
- ?line eval(partition_family(Fun1, relation([{a,1},{a,2},{b,3}])),
- from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
+ eval(partition_family(Fun1, relation([{a,1},{a,2},{b,3}])),
+ from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
Fun2 = fun(S) -> {A,_B} = to_external(S), from_term({A}) end,
- ?line eval(partition_family(Fun2, relation([{a,1},{a,2},{b,3}])),
- from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
+ eval(partition_family(Fun2, relation([{a,1},{a,2},{b,3}])),
+ from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition_family({external, fun({A,_}) -> {A,0} end},
from_term([{1,a}]))),
- ?line [{{atom,atom},[{atom,atom,atom,atom}]}] =
+ [{{atom,atom},[{atom,atom,atom,atom}]}] =
type(partition_family({external, fun({A,_B,C,_D}) -> {C,A} end},
relation([],4))),
Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
- ?line eval(partition_family(Fun3, E), E),
- ?line eval(partition_family(Fun3, set([a,b])),
- from_term([{{a,0},[a]}, {{b,0},[b]}])),
- ?line eval(partition_family(Fun3, relation([{a,1},{b,2}])),
- from_term([{{{a,1},0},[{a,1}]},{{{b,2},0},[{b,2}]}])),
- ?line eval(partition_family(Fun3, from_term([[a],[b]])),
- from_term([{{[a],0},[[a]]}, {{[b],0},[[b]]}])),
- ?line partition_family({external, fun(X) -> X end}, E),
+ eval(partition_family(Fun3, E), E),
+ eval(partition_family(Fun3, set([a,b])),
+ from_term([{{a,0},[a]}, {{b,0},[b]}])),
+ eval(partition_family(Fun3, relation([{a,1},{b,2}])),
+ from_term([{{{a,1},0},[{a,1}]},{{{b,2},0},[{b,2}]}])),
+ eval(partition_family(Fun3, from_term([[a],[b]])),
+ from_term([{{[a],0},[[a]]}, {{[b],0},[[b]]}])),
+ partition_family({external, fun(X) -> X end}, E),
F = 0.0, I = round(F),
- ?line FR = relation([{I,a},{F,b}]),
+ FR = relation([{I,a},{F,b}]),
if
F == I -> % term ordering
- ?line true = (1 =:= no_elements(partition_family(1, FR)));
+ true = (1 =:= no_elements(partition_family(1, FR)));
true ->
- ?line eval(partition_family(1, FR),
- from_term([{I,[{I,a}]},{F,[{F,b}]}]))
+ eval(partition_family(1, FR),
+ from_term([{I,[{I,a}]},{F,[{F,b}]}]))
end,
%% set of sets
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition_family({external, fun(X) -> X end},
from_term([], [[atom]]))),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch partition_family({external, fun(X) -> X end},
from_term([[a]]))),
- ?line eval(partition_family(fun sofs:union/1,
- from_term([[[1],[1,2]], [[1,2]]])),
- from_term([{[1,2], [[[1],[1,2]],[[1,2]]]}])),
- ?line eval(partition_family(fun(X) -> X end,
- from_term([[1],[1,2],[1,2,3]])),
- from_term([{[1],[[1]]},{[1,2],[[1,2]]},{[1,2,3],[[1,2,3]]}])),
-
- ?line eval(partition_family(fun(_) -> from_term([a]) end,
- from_term([], [[atom]])),
- E),
+ eval(partition_family(fun sofs:union/1,
+ from_term([[[1],[1,2]], [[1,2]]])),
+ from_term([{[1,2], [[[1],[1,2]],[[1,2]]]}])),
+ eval(partition_family(fun(X) -> X end,
+ from_term([[1],[1,2],[1,2,3]])),
+ from_term([{[1],[[1]]},{[1,2],[[1,2]]},{[1,2,3],[[1,2,3]]}])),
+
+ eval(partition_family(fun(_) -> from_term([a]) end,
+ from_term([], [[atom]])),
+ E),
Fun10 = fun(S) ->
- %% Cheating a lot...
- case to_external(S) of
- [1] -> from_term({1,1});
- _ -> S
- end
- end,
+ %% Cheating a lot...
+ case to_external(S) of
+ [1] -> from_term({1,1});
+ _ -> S
+ end
+ end,
- ?line eval(partition_family(Fun10, from_term([[1]])),
- from_term([{{1,1},[[1]]}])),
- ?line eval(partition_family(fun(_) -> from_term({a}) end,
- from_term([[a]])),
- from_term([{{a},[[a]]}])),
- ?line {'EXIT', {badarg, _}} =
- (catch partition_family(fun(_) -> {a} end, from_term([[a]]))),
+ eval(partition_family(Fun10, from_term([[1]])),
+ from_term([{{1,1},[[1]]}])),
+ eval(partition_family(fun(_) -> from_term({a}) end,
+ from_term([[a]])),
+ from_term([{{a},[[a]]}])),
+ {'EXIT', {badarg, _}} =
+ (catch partition_family(fun(_) -> {a} end, from_term([[a]]))),
ok.
%% Not meant to be efficient...
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl
index 30c46a5bb4..b5d221732e 100644
--- a/lib/stdlib/test/string_SUITE.erl
+++ b/lib/stdlib/test/string_SUITE.erl
@@ -73,115 +73,115 @@ end_per_testcase(_Case, _Config) ->
%%
len(Config) when is_list(Config) ->
- ?line 0 = string:len(""),
- ?line L = tuple_size(list_to_tuple(atom_to_list(?MODULE))),
- ?line L = string:len(atom_to_list(?MODULE)),
+ 0 = string:len(""),
+ L = tuple_size(list_to_tuple(atom_to_list(?MODULE))),
+ L = string:len(atom_to_list(?MODULE)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:len({})),
+ {'EXIT',_} = (catch string:len({})),
ok.
equal(Config) when is_list(Config) ->
- ?line true = string:equal("", ""),
- ?line false = string:equal("", " "),
- ?line true = string:equal("laban", "laban"),
- ?line false = string:equal("skvimp", "skvump"),
+ true = string:equal("", ""),
+ false = string:equal("", " "),
+ true = string:equal("laban", "laban"),
+ false = string:equal("skvimp", "skvump"),
%% invalid arg type
- ?line true = string:equal(2, 2), % not good, should crash
+ true = string:equal(2, 2), % not good, should crash
ok.
concat(Config) when is_list(Config) ->
- ?line "erlang rules" = string:concat("erlang ", "rules"),
- ?line "" = string:concat("", ""),
- ?line "x" = string:concat("x", ""),
- ?line "y" = string:concat("", "y"),
+ "erlang rules" = string:concat("erlang ", "rules"),
+ "" = string:concat("", ""),
+ "x" = string:concat("x", ""),
+ "y" = string:concat("", "y"),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:concat(hello, please)),
+ {'EXIT',_} = (catch string:concat(hello, please)),
ok.
chr_rchr(Config) when is_list(Config) ->
{_,_,X} = erlang:timestamp(),
- ?line 0 = string:chr("", (X rem (255-32)) + 32),
- ?line 0 = string:rchr("", (X rem (255-32)) + 32),
- ?line 1 = string:chr("x", $x),
- ?line 1 = string:rchr("x", $x),
- ?line 1 = string:chr("xx", $x),
- ?line 2 = string:rchr("xx", $x),
- ?line 3 = string:chr("xyzyx", $z),
- ?line 3 = string:rchr("xyzyx", $z),
+ 0 = string:chr("", (X rem (255-32)) + 32),
+ 0 = string:rchr("", (X rem (255-32)) + 32),
+ 1 = string:chr("x", $x),
+ 1 = string:rchr("x", $x),
+ 1 = string:chr("xx", $x),
+ 2 = string:rchr("xx", $x),
+ 3 = string:chr("xyzyx", $z),
+ 3 = string:rchr("xyzyx", $z),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chr(hello, $h)),
+ {'EXIT',_} = (catch string:chr(hello, $h)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chr("hello", h)),
+ {'EXIT',_} = (catch string:chr("hello", h)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:rchr(hello, $h)),
+ {'EXIT',_} = (catch string:rchr(hello, $h)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:rchr("hello", h)),
+ {'EXIT',_} = (catch string:rchr("hello", h)),
ok.
str_rstr(Config) when is_list(Config) ->
{_,_,X} = erlang:timestamp(),
- ?line 0 = string:str("", [(X rem (255-32)) + 32]),
- ?line 0 = string:rstr("", [(X rem (255-32)) + 32]),
- ?line 1 = string:str("x", "x"),
- ?line 1 = string:rstr("x", "x"),
- ?line 0 = string:str("hello", ""),
- ?line 0 = string:rstr("hello", ""),
- ?line 1 = string:str("xxxx", "xx"),
- ?line 3 = string:rstr("xxxx", "xx"),
- ?line 3 = string:str("xy z yx", " z"),
- ?line 3 = string:rstr("xy z yx", " z"),
+ 0 = string:str("", [(X rem (255-32)) + 32]),
+ 0 = string:rstr("", [(X rem (255-32)) + 32]),
+ 1 = string:str("x", "x"),
+ 1 = string:rstr("x", "x"),
+ 0 = string:str("hello", ""),
+ 0 = string:rstr("hello", ""),
+ 1 = string:str("xxxx", "xx"),
+ 3 = string:rstr("xxxx", "xx"),
+ 3 = string:str("xy z yx", " z"),
+ 3 = string:rstr("xy z yx", " z"),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:str(hello, "he")),
+ {'EXIT',_} = (catch string:str(hello, "he")),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:str("hello", he)),
+ {'EXIT',_} = (catch string:str("hello", he)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:rstr(hello, "he")),
+ {'EXIT',_} = (catch string:rstr(hello, "he")),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:rstr("hello", he)),
+ {'EXIT',_} = (catch string:rstr("hello", he)),
ok.
span_cspan(Config) when is_list(Config) ->
- ?line 0 = string:span("", "1"),
- ?line 0 = string:span("1", ""),
- ?line 0 = string:cspan("", "1"),
- ?line 1 = string:cspan("1", ""),
- ?line 1 = string:span("1 ", "1"),
- ?line 5 = string:span(" 1 ", "12 "),
- ?line 6 = string:span("1231234", "123"),
- ?line 0 = string:cspan("1 ", "1"),
- ?line 1 = string:cspan("3 ", "12 "),
- ?line 6 = string:cspan("1231234", "4"),
+ 0 = string:span("", "1"),
+ 0 = string:span("1", ""),
+ 0 = string:cspan("", "1"),
+ 1 = string:cspan("1", ""),
+ 1 = string:span("1 ", "1"),
+ 5 = string:span(" 1 ", "12 "),
+ 6 = string:span("1231234", "123"),
+ 0 = string:cspan("1 ", "1"),
+ 1 = string:cspan("3 ", "12 "),
+ 6 = string:cspan("1231234", "4"),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:span(1234, "1")),
+ {'EXIT',_} = (catch string:span(1234, "1")),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:span(1234, "1")),
+ {'EXIT',_} = (catch string:span(1234, "1")),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:cspan("1234", 1)),
+ {'EXIT',_} = (catch string:cspan("1234", 1)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:cspan("1234", 4)),
+ {'EXIT',_} = (catch string:cspan("1234", 4)),
ok.
substr(Config) when is_list(Config) ->
- ?line {'EXIT',_} = (catch string:substr("", 0)),
- ?line [] = string:substr("", 1),
- ?line {'EXIT',_} = (catch string:substr("", 2)),
- ?line [] = string:substr("1", 2),
- ?line {'EXIT',_} = (catch string:substr("", 0, 1)),
- ?line [] = string:substr("", 1, 1),
- ?line [] = string:substr("", 1, 2),
- ?line {'EXIT',_} = (catch string:substr("", 2, 2)),
- ?line "1234" = string:substr("1234", 1),
- ?line "1234" = string:substr("1234", 1, 4),
- ?line "1234" = string:substr("1234", 1, 5),
- ?line "23" = string:substr("1234", 2, 2),
- ?line "4" = string:substr("1234", 4),
- ?line "" = string:substr("1234", 4, 0),
- ?line "4" = string:substr("1234", 4, 1),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:substr(1234, 1)),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:substr("1234", "1")),
+ {'EXIT',_} = (catch string:substr("", 0)),
+ [] = string:substr("", 1),
+ {'EXIT',_} = (catch string:substr("", 2)),
+ [] = string:substr("1", 2),
+ {'EXIT',_} = (catch string:substr("", 0, 1)),
+ [] = string:substr("", 1, 1),
+ [] = string:substr("", 1, 2),
+ {'EXIT',_} = (catch string:substr("", 2, 2)),
+ "1234" = string:substr("1234", 1),
+ "1234" = string:substr("1234", 1, 4),
+ "1234" = string:substr("1234", 1, 5),
+ "23" = string:substr("1234", 2, 2),
+ "4" = string:substr("1234", 4),
+ "" = string:substr("1234", 4, 0),
+ "4" = string:substr("1234", 4, 1),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:substr(1234, 1)),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:substr("1234", "1")),
ok.
tokens(Config) when is_list(Config) ->
@@ -219,216 +219,216 @@ replace_sep(C, Seps, New) ->
end.
chars(Config) when is_list(Config) ->
- ?line [] = string:chars($., 0),
- ?line [] = string:chars($., 0, []),
- ?line 10 = length(string:chars(32, 10, [])),
- ?line "aaargh" = string:chars($a, 3, "rgh"),
+ [] = string:chars($., 0),
+ [] = string:chars($., 0, []),
+ 10 = length(string:chars(32, 10, [])),
+ "aaargh" = string:chars($a, 3, "rgh"),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chars($x, [])),
+ {'EXIT',_} = (catch string:chars($x, [])),
ok.
copies(Config) when is_list(Config) ->
- ?line "" = string:copies("", 10),
- ?line "" = string:copies(".", 0),
- ?line "." = string:copies(".", 1),
- ?line 30 = length(string:copies("123", 10)),
+ "" = string:copies("", 10),
+ "" = string:copies(".", 0),
+ "." = string:copies(".", 1),
+ 30 = length(string:copies("123", 10)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:copies("hej", -1)),
- ?line {'EXIT',_} = (catch string:copies("hej", 2.0)),
+ {'EXIT',_} = (catch string:copies("hej", -1)),
+ {'EXIT',_} = (catch string:copies("hej", 2.0)),
ok.
words(Config) when is_list(Config) ->
- ?line 1 = string:words(""),
- ?line 1 = string:words("", $,),
- ?line 1 = string:words("hello"),
- ?line 1 = string:words("hello", $,),
- ?line 1 = string:words("...", $.),
- ?line 2 = string:words("2.35", $.),
- ?line 100 = string:words(string:copies(". ", 100)),
+ 1 = string:words(""),
+ 1 = string:words("", $,),
+ 1 = string:words("hello"),
+ 1 = string:words("hello", $,),
+ 1 = string:words("...", $.),
+ 2 = string:words("2.35", $.),
+ 100 = string:words(string:copies(". ", 100)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chars(hej, 1)),
+ {'EXIT',_} = (catch string:chars(hej, 1)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chars("hej", 1, " ")),
+ {'EXIT',_} = (catch string:chars("hej", 1, " ")),
ok.
strip(Config) when is_list(Config) ->
- ?line "" = string:strip(""),
- ?line "" = string:strip("", both),
- ?line "" = string:strip("", both, $.),
- ?line "hej" = string:strip(" hej "),
- ?line "hej " = string:strip(" hej ", left),
- ?line " hej" = string:strip(" hej ", right),
- ?line " hej " = string:strip(" hej ", right, $.),
- ?line "hej hopp" = string:strip(" hej hopp ", both),
+ "" = string:strip(""),
+ "" = string:strip("", both),
+ "" = string:strip("", both, $.),
+ "hej" = string:strip(" hej "),
+ "hej " = string:strip(" hej ", left),
+ " hej" = string:strip(" hej ", right),
+ " hej " = string:strip(" hej ", right, $.),
+ "hej hopp" = string:strip(" hej hopp ", both),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:strip(hej)),
+ {'EXIT',_} = (catch string:strip(hej)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:strip(" hej", up)),
+ {'EXIT',_} = (catch string:strip(" hej", up)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:strip(" hej", left, " ")), % not good
+ {'EXIT',_} = (catch string:strip(" hej", left, " ")), % not good
ok.
sub_word(Config) when is_list(Config) ->
- ?line "" = string:sub_word("", 1),
- ?line "" = string:sub_word("", 1, $,),
- ?line {'EXIT',_} = (catch string:sub_word("1 2 3", 0)),
- ?line "" = string:sub_word("1 2 3", 4),
- ?line "llo th" = string:sub_word("but hello there", 2, $e),
+ "" = string:sub_word("", 1),
+ "" = string:sub_word("", 1, $,),
+ {'EXIT',_} = (catch string:sub_word("1 2 3", 0)),
+ "" = string:sub_word("1 2 3", 4),
+ "llo th" = string:sub_word("but hello there", 2, $e),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:sub_word('hello there', 1)),
+ {'EXIT',_} = (catch string:sub_word('hello there', 1)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:sub_word("hello there", 1, "e")),
+ {'EXIT',_} = (catch string:sub_word("hello there", 1, "e")),
ok.
left_right(Config) when is_list(Config) ->
- ?line "" = string:left("", 0),
- ?line "" = string:left("hej", 0),
- ?line "" = string:left("hej", 0, $.),
- ?line "" = string:right("", 0),
- ?line "" = string:right("hej", 0),
- ?line "" = string:right("hej", 0, $.),
- ?line "123 " = string:left("123 ", 5),
- ?line " 123" = string:right(" 123", 5),
- ?line "123!!" = string:left("123!", 5, $!),
- ?line "==123" = string:right("=123", 5, $=),
- ?line "1" = string:left("123", 1, $.),
- ?line "3" = string:right("123", 1, $.),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:left(hello, 5)),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:right(hello, 5)),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:left("hello", 5, ".")),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:right("hello", 5, ".")),
+ "" = string:left("", 0),
+ "" = string:left("hej", 0),
+ "" = string:left("hej", 0, $.),
+ "" = string:right("", 0),
+ "" = string:right("hej", 0),
+ "" = string:right("hej", 0, $.),
+ "123 " = string:left("123 ", 5),
+ " 123" = string:right(" 123", 5),
+ "123!!" = string:left("123!", 5, $!),
+ "==123" = string:right("=123", 5, $=),
+ "1" = string:left("123", 1, $.),
+ "3" = string:right("123", 1, $.),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:left(hello, 5)),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:right(hello, 5)),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:left("hello", 5, ".")),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:right("hello", 5, ".")),
ok.
sub_string(Config) when is_list(Config) ->
- ?line {'EXIT',_} = (catch string:sub_string("", 0)),
- ?line [] = string:sub_string("", 1),
- ?line {'EXIT',_} = (catch string:sub_string("", 2)),
- ?line [] = string:sub_string("1", 2),
- ?line {'EXIT',_} = (catch string:sub_string("", 0, 1)),
- ?line [] = string:sub_string("", 1, 1),
- ?line [] = string:sub_string("", 1, 2),
- ?line {'EXIT',_} = (catch string:sub_string("", 2, 2)),
- ?line "1234" = string:sub_string("1234", 1),
- ?line "1234" = string:sub_string("1234", 1, 4),
- ?line "1234" = string:sub_string("1234", 1, 5),
- ?line "23" = string:sub_string("1234", 2, 3),
- ?line "4" = string:sub_string("1234", 4),
- ?line "4" = string:sub_string("1234", 4, 4),
- ?line "4" = string:sub_string("1234", 4, 5),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:sub_string(1234, 1)),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:sub_string("1234", "1")),
+ {'EXIT',_} = (catch string:sub_string("", 0)),
+ [] = string:sub_string("", 1),
+ {'EXIT',_} = (catch string:sub_string("", 2)),
+ [] = string:sub_string("1", 2),
+ {'EXIT',_} = (catch string:sub_string("", 0, 1)),
+ [] = string:sub_string("", 1, 1),
+ [] = string:sub_string("", 1, 2),
+ {'EXIT',_} = (catch string:sub_string("", 2, 2)),
+ "1234" = string:sub_string("1234", 1),
+ "1234" = string:sub_string("1234", 1, 4),
+ "1234" = string:sub_string("1234", 1, 5),
+ "23" = string:sub_string("1234", 2, 3),
+ "4" = string:sub_string("1234", 4),
+ "4" = string:sub_string("1234", 4, 4),
+ "4" = string:sub_string("1234", 4, 5),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:sub_string(1234, 1)),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:sub_string("1234", "1")),
ok.
centre(Config) when is_list(Config) ->
- ?line "" = string:centre("", 0),
- ?line "" = string:centre("1", 0),
- ?line "" = string:centre("", 0, $-),
- ?line "" = string:centre("1", 0, $-),
- ?line "gd" = string:centre("agda", 2),
- ?line "agda " = string:centre("agda", 5),
- ?line " agda " = string:centre("agda", 6),
- ?line "agda." = string:centre("agda", 5, $.),
- ?line "--agda--" = string:centre("agda", 8, $-),
- ?line "agda" = string:centre("agda", 4),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:centre(hello, 10)),
+ "" = string:centre("", 0),
+ "" = string:centre("1", 0),
+ "" = string:centre("", 0, $-),
+ "" = string:centre("1", 0, $-),
+ "gd" = string:centre("agda", 2),
+ "agda " = string:centre("agda", 5),
+ " agda " = string:centre("agda", 6),
+ "agda." = string:centre("agda", 5, $.),
+ "--agda--" = string:centre("agda", 8, $-),
+ "agda" = string:centre("agda", 4),
+ %% invalid arg type
+ {'EXIT',_} = (catch string:centre(hello, 10)),
ok.
to_integer(Config) when is_list(Config) ->
- ?line {1,""} = test_to_integer("1"),
- ?line {1,""} = test_to_integer("+1"),
- ?line {-1,""} = test_to_integer("-1"),
- ?line {1,"="} = test_to_integer("1="),
- ?line {7,"F"} = test_to_integer("7F"),
- ?line {709,""} = test_to_integer("709"),
- ?line {709,"*2"} = test_to_integer("709*2"),
- ?line {0,"xAB"} = test_to_integer("0xAB"),
- ?line {16,"#FF"} = test_to_integer("16#FF"),
- ?line {error,no_integer} = test_to_integer(""),
- ?line {error,no_integer} = test_to_integer("!1"),
- ?line {error,no_integer} = test_to_integer("F1"),
- ?line {error,not_a_list} = test_to_integer('23'),
- ?line {3,[[]]} = test_to_integer([$3,[]]),
- ?line {3,[hello]} = test_to_integer([$3,hello]),
+ {1,""} = test_to_integer("1"),
+ {1,""} = test_to_integer("+1"),
+ {-1,""} = test_to_integer("-1"),
+ {1,"="} = test_to_integer("1="),
+ {7,"F"} = test_to_integer("7F"),
+ {709,""} = test_to_integer("709"),
+ {709,"*2"} = test_to_integer("709*2"),
+ {0,"xAB"} = test_to_integer("0xAB"),
+ {16,"#FF"} = test_to_integer("16#FF"),
+ {error,no_integer} = test_to_integer(""),
+ {error,no_integer} = test_to_integer("!1"),
+ {error,no_integer} = test_to_integer("F1"),
+ {error,not_a_list} = test_to_integer('23'),
+ {3,[[]]} = test_to_integer([$3,[]]),
+ {3,[hello]} = test_to_integer([$3,hello]),
ok.
test_to_integer(Str) ->
io:format("Checking ~p~n", [Str]),
case string:to_integer(Str) of
{error,_Reason} = Bad ->
- ?line {'EXIT',_} = (catch list_to_integer(Str)),
+ {'EXIT',_} = (catch list_to_integer(Str)),
Bad;
{F,_Rest} = Res ->
- ?line _ = integer_to_list(F),
+ _ = integer_to_list(F),
Res
end.
to_float(Config) when is_list(Config) ->
- ?line {1.2,""} = test_to_float("1.2"),
- ?line {1.2,""} = test_to_float("1,2"),
- ?line {120.0,""} = test_to_float("1.2e2"),
- ?line {120.0,""} = test_to_float("+1,2e2"),
- ?line {-120.0,""} = test_to_float("-1.2e2"),
- ?line {-120.0,""} = test_to_float("-1,2e+2"),
- ?line {-1.2e-2,""} = test_to_float("-1.2e-2"),
- ?line {1.2,"="} = test_to_float("1.2="),
- ?line {7.9,"e"} = test_to_float("7.9e"),
- ?line {7.9,"ee"} = test_to_float("7.9ee"),
- ?line {7.9,"e+"} = test_to_float("7.9e+"),
- ?line {7.9,"e-"} = test_to_float("7.9e-"),
- ?line {7.9,"e++"} = test_to_float("7.9e++"),
- ?line {7.9,"e--"} = test_to_float("7.9e--"),
- ?line {7.9,"e+e"} = test_to_float("7.9e+e"),
- ?line {7.9,"e-e"} = test_to_float("7.9e-e"),
- ?line {7.9,"e+."} = test_to_float("7.9e+."),
- ?line {7.9,"e-."} = test_to_float("7.9e-."),
- ?line {7.9,"e+,"} = test_to_float("7.9e+,"),
- ?line {7.9,"e-,"} = test_to_float("7.9e-,"),
- ?line {error,no_float} = test_to_float(""),
- ?line {error,no_float} = test_to_float("e1,0"),
- ?line {error,no_float} = test_to_float("1;0"),
- ?line {error,no_float} = test_to_float("1"),
- ?line {error,no_float} = test_to_float("1e"),
- ?line {error,no_float} = test_to_float("2."),
- ?line {error,not_a_list} = test_to_float('2.3'),
- ?line {2.3,[[]]} = test_to_float([$2,$.,$3,[]]),
- ?line {2.3,[hello]} = test_to_float([$2,$.,$3,hello]),
+ {1.2,""} = test_to_float("1.2"),
+ {1.2,""} = test_to_float("1,2"),
+ {120.0,""} = test_to_float("1.2e2"),
+ {120.0,""} = test_to_float("+1,2e2"),
+ {-120.0,""} = test_to_float("-1.2e2"),
+ {-120.0,""} = test_to_float("-1,2e+2"),
+ {-1.2e-2,""} = test_to_float("-1.2e-2"),
+ {1.2,"="} = test_to_float("1.2="),
+ {7.9,"e"} = test_to_float("7.9e"),
+ {7.9,"ee"} = test_to_float("7.9ee"),
+ {7.9,"e+"} = test_to_float("7.9e+"),
+ {7.9,"e-"} = test_to_float("7.9e-"),
+ {7.9,"e++"} = test_to_float("7.9e++"),
+ {7.9,"e--"} = test_to_float("7.9e--"),
+ {7.9,"e+e"} = test_to_float("7.9e+e"),
+ {7.9,"e-e"} = test_to_float("7.9e-e"),
+ {7.9,"e+."} = test_to_float("7.9e+."),
+ {7.9,"e-."} = test_to_float("7.9e-."),
+ {7.9,"e+,"} = test_to_float("7.9e+,"),
+ {7.9,"e-,"} = test_to_float("7.9e-,"),
+ {error,no_float} = test_to_float(""),
+ {error,no_float} = test_to_float("e1,0"),
+ {error,no_float} = test_to_float("1;0"),
+ {error,no_float} = test_to_float("1"),
+ {error,no_float} = test_to_float("1e"),
+ {error,no_float} = test_to_float("2."),
+ {error,not_a_list} = test_to_float('2.3'),
+ {2.3,[[]]} = test_to_float([$2,$.,$3,[]]),
+ {2.3,[hello]} = test_to_float([$2,$.,$3,hello]),
ok.
test_to_float(Str) ->
io:format("Checking ~p~n", [Str]),
case string:to_float(Str) of
{error,_Reason} = Bad ->
- ?line {'EXIT',_} = (catch list_to_float(Str)),
+ {'EXIT',_} = (catch list_to_float(Str)),
Bad;
{F,_Rest} = Res ->
- ?line _ = float_to_list(F),
+ _ = float_to_list(F),
Res
end.
-
+
to_upper_to_lower(Config) when is_list(Config) ->
- ?line "1234ABCDEFÅÄÖ=" = string:to_upper("1234abcdefåäö="),
- ?line "éèíúùòóåäöabc()" = string:to_lower("ÉÈÍÚÙÒÓÅÄÖabc()"),
- ?line All = lists:seq(0, 255),
+ "1234ABCDEFÅÄÖ=" = string:to_upper("1234abcdefåäö="),
+ "éèíúùòóåäöabc()" = string:to_lower("ÉÈÍÚÙÒÓÅÄÖabc()"),
+ All = lists:seq(0, 255),
- ?line UC = string:to_upper(All),
- ?line 256 = length(UC),
- ?line all_upper_latin1(UC, 0),
+ UC = string:to_upper(All),
+ 256 = length(UC),
+ all_upper_latin1(UC, 0),
- ?line LC = string:to_lower(All),
- ?line all_lower_latin1(LC, 0),
+ LC = string:to_lower(All),
+ all_lower_latin1(LC, 0),
- ?line LC = string:to_lower(string:to_upper(LC)),
- ?line LC = string:to_lower(string:to_upper(UC)),
- ?line UC = string:to_upper(string:to_lower(LC)),
- ?line UC = string:to_upper(string:to_lower(UC)),
+ LC = string:to_lower(string:to_upper(LC)),
+ LC = string:to_lower(string:to_upper(UC)),
+ UC = string:to_upper(string:to_lower(LC)),
+ UC = string:to_upper(string:to_lower(UC)),
ok.
all_upper_latin1([C|T], C) when 0 =< C, C < $a;
@@ -456,10 +456,10 @@ all_lower_latin1([H|T], C) when $A =< C, C =< $Z;
all_lower_latin1([], 256) -> ok.
join(Config) when is_list(Config) ->
- ?line "erlang rules" = string:join(["erlang", "rules"], " "),
- ?line "a,-,b,-,c" = string:join(["a", "b", "c"], ",-,"),
- ?line "1234" = string:join(["1", "2", "3", "4"], ""),
- ?line [] = string:join([], ""), % OTP-7231
+ "erlang rules" = string:join(["erlang", "rules"], " "),
+ "a,-,b,-,c" = string:join(["a", "b", "c"], ",-,"),
+ "1234" = string:join(["1", "2", "3", "4"], ""),
+ [] = string:join([], ""), % OTP-7231
%% invalid arg type
- ?line {'EXIT',_} = (catch string:join([apa], "")),
+ {'EXIT',_} = (catch string:join([apa], "")),
ok.
diff --git a/lib/stdlib/test/supervisor_bridge_SUITE.erl b/lib/stdlib/test/supervisor_bridge_SUITE.erl
index 09e353847a..029cb3fd7f 100644
--- a/lib/stdlib/test/supervisor_bridge_SUITE.erl
+++ b/lib/stdlib/test/supervisor_bridge_SUITE.erl
@@ -58,8 +58,8 @@ end_per_group(_GroupName, Config) ->
starting(Config) when is_list(Config) ->
process_flag(trap_exit,true),
- ?line ignore = start(1),
- ?line {error,testing} = start(2),
+ ignore = start(1),
+ {error,testing} = start(2),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -74,8 +74,8 @@ mini_die(Config) when is_list(Config) ->
miniappl(N) ->
process_flag(trap_exit,true),
- ?line {ok,Server} = start(3),
- ?line Client = spawn_link(?MODULE,client,[N]),
+ {ok,Server} = start(3),
+ Client = spawn_link(?MODULE,client,[N]),
ct:timetrap({seconds,2}),
miniappl_loop(Client, Server).
@@ -86,15 +86,15 @@ miniappl_loop(Client,Server) ->
io:format("Client ~p, Server ~p\n",[Client,Server]),
receive
{'EXIT',Client,_} ->
- ?line miniappl_loop([],Server);
+ miniappl_loop([],Server);
{'EXIT',Server,killed} -> %% terminate
- ?line miniappl_loop(Client,[]);
+ miniappl_loop(Client,[]);
{'EXIT',Server,died} -> %% die
- ?line miniappl_loop(Client,[]);
+ miniappl_loop(Client,[]);
{dying,_Reason} ->
- ?line miniappl_loop(Client, Server);
+ miniappl_loop(Client, Server);
Other ->
- ?line exit({failed,Other})
+ exit({failed,Other})
end.
%%%%%%%%%%%%%%%%%%%%
@@ -173,11 +173,11 @@ terminate(_Reason, _State) ->
badstart(Config) when is_list(Config) ->
%% Various bad arguments.
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch supervisor_bridge:start_link({xxx,?bridge_name},?MODULE,1)),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch supervisor_bridge:start_link({local,"foo"},?MODULE,1)),
- ?line {'EXIT',_} =
+ {'EXIT',_} =
(catch supervisor_bridge:start_link(?bridge_name,?MODULE,1)),
receive
Msg ->
@@ -188,18 +188,18 @@ badstart(Config) when is_list(Config) ->
%% Already started.
- ?line process_flag(trap_exit, true),
- ?line {ok,Pid} =
+ process_flag(trap_exit, true),
+ {ok,Pid} =
supervisor_bridge:start_link({local,?bridge_name},?MODULE,3),
- ?line {error,{already_started,Pid}} =
+ {error,{already_started,Pid}} =
supervisor_bridge:start_link({local,?bridge_name},?MODULE,3),
- ?line public_kill(),
+ public_kill(),
%% We used to wait 1 ms before retrieving the message queue,
%% but that might not always be enough if the machine is overloaded.
- ?line receive
- {'EXIT', Pid, killed} -> ok
- end,
+ receive
+ {'EXIT', Pid, killed} -> ok
+ end,
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -214,15 +214,15 @@ simple_global_supervisor(Config) when is_list(Config) ->
supervisor:start_link({local,bridge9212}, ?MODULE, {4,InitResult}),
BN_1 = global:whereis_name(?bridge_name),
- ?line exit(BN_1, kill),
+ exit(BN_1, kill),
timer:sleep(200),
BN_2 = global:whereis_name(?bridge_name),
- ?line true = is_pid(BN_2),
- ?line true = BN_1 =/= BN_2,
+ true = is_pid(BN_2),
+ true = BN_1 =/= BN_2,
- ?line process_flag(trap_exit, true),
+ process_flag(trap_exit, true),
exit(Sup, kill),
- ?line receive {'EXIT', Sup, killed} -> ok end,
+ receive {'EXIT', Sup, killed} -> ok end,
ok.
server9212() ->
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index e80c86562d..3f87c21b3e 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_SUITE.erl
@@ -108,24 +108,24 @@ trace(Config) when is_list(Config) ->
ok.
suspend(Config) when is_list(Config) ->
- ?line {ok,_Server} = start(),
- ?line sys:suspend(?server,1000),
- ?line {'EXIT',_} = (catch public_call(48)),
- ?line {status,_,_,[_,suspended,_,_,_]} = sys:get_status(?server),
- ?line sys:suspend(?server,1000), %% doing it twice is no error
- ?line {'EXIT',_} = (catch public_call(48)),
- ?line sys:resume(?server),
- ?line {status,_,_,[_,running,_,_,_]} = sys:get_status(?server),
- ?line {ok,-48} = (catch public_call(48)),
- ?line sys:resume(?server), %% doing it twice is no error
- ?line {ok,-48} = (catch public_call(48)),
- ?line stop(),
+ {ok,_Server} = start(),
+ sys:suspend(?server,1000),
+ {'EXIT',_} = (catch public_call(48)),
+ {status,_,_,[_,suspended,_,_,_]} = sys:get_status(?server),
+ sys:suspend(?server,1000), %% doing it twice is no error
+ {'EXIT',_} = (catch public_call(48)),
+ sys:resume(?server),
+ {status,_,_,[_,running,_,_,_]} = sys:get_status(?server),
+ {ok,-48} = (catch public_call(48)),
+ sys:resume(?server), %% doing it twice is no error
+ {ok,-48} = (catch public_call(48)),
+ stop(),
ok.
install(Config) when is_list(Config) ->
- ?line {ok,_Server} = start(),
- ?line Master = self(),
- ?line SpyFun =
+ {ok,_Server} = start(),
+ Master = self(),
+ SpyFun =
fun(func_state,Event,ProcState) ->
case Event of
{in,{'$gen_call',_From,{req,Arg}}} ->
@@ -135,18 +135,18 @@ install(Config) when is_list(Config) ->
io:format("Trigged other=~p\n",[Other])
end
end,
- ?line sys:install(?server,{SpyFun,func_state}),
- ?line {ok,-1} = (catch public_call(1)),
- ?line sys:no_debug(?server),
- ?line {ok,-2} = (catch public_call(2)),
- ?line sys:install(?server,{SpyFun,func_state}),
- ?line sys:install(?server,{SpyFun,func_state}),
- ?line {ok,-3} = (catch public_call(3)),
- ?line sys:remove(?server,SpyFun),
- ?line {ok,-4} = (catch public_call(4)),
+ sys:install(?server,{SpyFun,func_state}),
+ {ok,-1} = (catch public_call(1)),
+ sys:no_debug(?server),
+ {ok,-2} = (catch public_call(2)),
+ sys:install(?server,{SpyFun,func_state}),
+ sys:install(?server,{SpyFun,func_state}),
+ {ok,-3} = (catch public_call(3)),
+ sys:remove(?server,SpyFun),
+ {ok,-4} = (catch public_call(4)),
[{spy_got,{request,1},sys_SUITE_server},
{spy_got,{request,3},sys_SUITE_server}] = get_messages(),
- ?line stop(),
+ stop(),
ok.
get_messages() ->
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 2584f9c01f..28f42c6b37 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -63,47 +63,47 @@ borderline(Config) when is_list(Config) ->
%% Therefore, strip off the current working directory from the front
%% of the private directory path.
- ?line {ok, Cwd} = file:get_cwd(),
- ?line RootDir = ?config(priv_dir, Config),
- ?line TempDir = remove_prefix(Cwd++"/", filename:join(RootDir, "borderline")),
- ?line ok = file:make_dir(TempDir),
+ {ok, Cwd} = file:get_cwd(),
+ RootDir = ?config(priv_dir, Config),
+ TempDir = remove_prefix(Cwd++"/", filename:join(RootDir, "borderline")),
+ ok = file:make_dir(TempDir),
- ?line Record = 512,
- ?line Block = 20 * Record,
+ Record = 512,
+ Block = 20 * Record,
- ?line lists:foreach(fun(Size) -> borderline_test(Size, TempDir) end,
- [0, 1, 10, 13, 127, 333, Record-1, Record, Record+1,
- Block-2*Record-1, Block-2*Record, Block-2*Record+1,
- Block-Record-1, Block-Record, Block-Record+1,
- Block-1, Block, Block+1,
- Block+Record-1, Block+Record, Block+Record+1]),
+ lists:foreach(fun(Size) -> borderline_test(Size, TempDir) end,
+ [0, 1, 10, 13, 127, 333, Record-1, Record, Record+1,
+ Block-2*Record-1, Block-2*Record, Block-2*Record+1,
+ Block-Record-1, Block-Record, Block-Record+1,
+ Block-1, Block, Block+1,
+ Block+Record-1, Block+Record, Block+Record+1]),
%% Clean up.
- ?line delete_files([TempDir]),
+ delete_files([TempDir]),
ok.
borderline_test(Size, TempDir) ->
- ?line Archive = filename:join(TempDir, "ar_"++integer_to_list(Size)++".tar"),
- ?line Name = filename:join(TempDir, "file_"++integer_to_list(Size)),
- ?line io:format("Testing size ~p", [Size]),
+ Archive = filename:join(TempDir, "ar_"++integer_to_list(Size)++".tar"),
+ Name = filename:join(TempDir, "file_"++integer_to_list(Size)),
+ io:format("Testing size ~p", [Size]),
%% Create a file and archive it.
X0 = erlang:monotonic_time(),
- ?line file:write_file(Name, random_byte_list(X0, Size)),
- ?line ok = erl_tar:create(Archive, [Name]),
- ?line ok = file:delete(Name),
+ file:write_file(Name, random_byte_list(X0, Size)),
+ ok = erl_tar:create(Archive, [Name]),
+ ok = file:delete(Name),
%% Verify listing and extracting.
- ?line {ok, [Name]} = erl_tar:table(Archive),
- ?line ok = erl_tar:extract(Archive, [verbose]),
+ {ok, [Name]} = erl_tar:table(Archive),
+ ok = erl_tar:extract(Archive, [verbose]),
%% Verify contents of extracted file.
- ?line {ok, Bin} = file:read_file(Name),
- ?line true = match_byte_list(X0, binary_to_list(Bin)),
+ {ok, Bin} = file:read_file(Name),
+ true = match_byte_list(X0, binary_to_list(Bin)),
%% Verify that Unix tar can read it.
- ?line tar_tf(Archive, Name),
+ tar_tf(Archive, Name),
ok.
@@ -116,20 +116,20 @@ tar_tf(Archive, Name) ->
end.
tar_tf1(Archive, Name) ->
- ?line Expect = Name ++ "\n",
- ?line cmd_expect("tar tf " ++ Archive, Expect).
+ Expect = Name ++ "\n",
+ cmd_expect("tar tf " ++ Archive, Expect).
%% We can't use os:cmd/1, because Unix 'tar tf Name' on Solaris never
%% terminates when given an archive of a size it doesn't like.
cmd_expect(Cmd, Expect) ->
- ?line Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]),
- ?line get_data(Port, Expect).
+ Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]),
+ get_data(Port, Expect).
get_data(Port, Expect) ->
receive
{Port, {data, Bytes}} ->
- ?line get_data(Port, match_output(Bytes, Expect, Port));
+ get_data(Port, match_output(Bytes, Expect, Port));
{Port, eof} ->
Port ! {self(), close},
receive
@@ -142,21 +142,21 @@ get_data(Port, Expect) ->
after 1 -> % force context switch
ok
end,
- ?line match_output(eof, Expect, Port)
+ match_output(eof, Expect, Port)
end.
match_output([C|Output], [C|Expect], Port) ->
- ?line match_output(Output, Expect, Port);
+ match_output(Output, Expect, Port);
match_output([_|_], [_|_], Port) ->
- ?line kill_port_and_fail(Port, badmatch);
+ kill_port_and_fail(Port, badmatch);
match_output([X|Output], [], Port) ->
- ?line kill_port_and_fail(Port, {too_much_data, [X|Output]});
+ kill_port_and_fail(Port, {too_much_data, [X|Output]});
match_output([], Expect, _Port) ->
Expect;
match_output(eof, [], _Port) ->
[];
match_output(eof, _Expect, Port) ->
- ?line kill_port_and_fail(Port, unexpected_end_of_input).
+ kill_port_and_fail(Port, unexpected_end_of_input).
kill_port_and_fail(Port, Reason) ->
unlink(Port),
@@ -201,52 +201,52 @@ next_random(X) ->
%% and uncompressed archives.
%% Also test the 'cooked' option.
atomic(Config) when is_list(Config) ->
- ?line ok = file:set_cwd(?config(priv_dir, Config)),
- ?line DataFiles = data_files(),
- ?line Names = [Name || {Name,_,_} <- DataFiles],
+ ok = file:set_cwd(?config(priv_dir, Config)),
+ DataFiles = data_files(),
+ Names = [Name || {Name,_,_} <- DataFiles],
io:format("Names: ~p", [Names]),
%% Create an uncompressed archive. The compressed flag should still be
%% allowed when listing contents or extracting.
- ?line Tar1 = "uncompressed.tar",
- ?line erl_tar:create(Tar1, Names, []),
- ?line {ok, Names} = erl_tar:table(Tar1, []),
- ?line {ok, Names} = erl_tar:table(Tar1, [compressed]),
- ?line {ok, Names} = erl_tar:table(Tar1, [cooked]),
- ?line {ok, Names} = erl_tar:table(Tar1, [compressed,cooked]),
-
+ Tar1 = "uncompressed.tar",
+ erl_tar:create(Tar1, Names, []),
+ {ok, Names} = erl_tar:table(Tar1, []),
+ {ok, Names} = erl_tar:table(Tar1, [compressed]),
+ {ok, Names} = erl_tar:table(Tar1, [cooked]),
+ {ok, Names} = erl_tar:table(Tar1, [compressed,cooked]),
+
%% Create a compressed archive.
- ?line Tar2 = "compressed.tar",
- ?line erl_tar:create(Tar2, Names, [compressed]),
- ?line {ok, Names} = erl_tar:table(Tar2, [compressed]),
- ?line {error, Reason} = erl_tar:table(Tar2, []),
- ?line {ok, Names} = erl_tar:table(Tar2, [compressed,cooked]),
- ?line {error, Reason} = erl_tar:table(Tar2, [cooked]),
- ?line ok = io:format("No compressed option: ~p, ~s",
- [Reason, erl_tar:format_error(Reason)]),
+ Tar2 = "compressed.tar",
+ erl_tar:create(Tar2, Names, [compressed]),
+ {ok, Names} = erl_tar:table(Tar2, [compressed]),
+ {error, Reason} = erl_tar:table(Tar2, []),
+ {ok, Names} = erl_tar:table(Tar2, [compressed,cooked]),
+ {error, Reason} = erl_tar:table(Tar2, [cooked]),
+ ok = io:format("No compressed option: ~p, ~s",
+ [Reason, erl_tar:format_error(Reason)]),
%% Same test again, but this time created with 'cooked'
- ?line Tar3 = "uncompressed_cooked.tar",
- ?line erl_tar:create(Tar3, Names, [cooked]),
- ?line {ok, Names} = erl_tar:table(Tar3, []),
- ?line {ok, Names} = erl_tar:table(Tar3, [compressed]),
- ?line {ok, Names} = erl_tar:table(Tar3, [cooked]),
- ?line {ok, Names} = erl_tar:table(Tar3, [compressed,cooked]),
-
- ?line Tar4 = "compressed_cooked.tar",
- ?line erl_tar:create(Tar4, Names, [compressed,cooked]),
- ?line {ok, Names} = erl_tar:table(Tar4, [compressed]),
- ?line {error, Reason} = erl_tar:table(Tar4, []),
- ?line {ok, Names} = erl_tar:table(Tar4, [compressed,cooked]),
- ?line {error, Reason} = erl_tar:table(Tar4, [cooked]),
- ?line ok = io:format("No compressed option: ~p, ~s",
- [Reason, erl_tar:format_error(Reason)]),
+ Tar3 = "uncompressed_cooked.tar",
+ erl_tar:create(Tar3, Names, [cooked]),
+ {ok, Names} = erl_tar:table(Tar3, []),
+ {ok, Names} = erl_tar:table(Tar3, [compressed]),
+ {ok, Names} = erl_tar:table(Tar3, [cooked]),
+ {ok, Names} = erl_tar:table(Tar3, [compressed,cooked]),
+
+ Tar4 = "compressed_cooked.tar",
+ erl_tar:create(Tar4, Names, [compressed,cooked]),
+ {ok, Names} = erl_tar:table(Tar4, [compressed]),
+ {error, Reason} = erl_tar:table(Tar4, []),
+ {ok, Names} = erl_tar:table(Tar4, [compressed,cooked]),
+ {error, Reason} = erl_tar:table(Tar4, [cooked]),
+ ok = io:format("No compressed option: ~p, ~s",
+ [Reason, erl_tar:format_error(Reason)]),
%% Clean up.
- ?line delete_files([Tar1,Tar2,Tar3,Tar4|Names]),
+ delete_files([Tar1,Tar2,Tar3,Tar4|Names]),
ok.
@@ -279,35 +279,35 @@ create_files([]) ->
%% Test to extract an Unix tar file containing filenames longer than
%% 100 characters and empty directories.
long_names(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line Long = filename:join(DataDir, "long_names.tar"),
+ DataDir = ?config(data_dir, Config),
+ Long = filename:join(DataDir, "long_names.tar"),
run_in_short_tempdir(Config,
fun() -> do_long_names(Long) end).
do_long_names(Long) ->
%% Try table/2 and extract/2.
- ?line case erl_tar:table(Long, [verbose]) of
- {ok,List} when is_list(List) ->
- ?line io:format("~p\n", [List])
- end,
+ case erl_tar:table(Long, [verbose]) of
+ {ok,List} when is_list(List) ->
+ io:format("~p\n", [List])
+ end,
- ?line {ok,Cwd} = file:get_cwd(),
- ?line ok = erl_tar:extract(Long),
- ?line Base = filename:join([Cwd, "original_software", "written_by",
- "a_bunch_of_hackers",
- "spending_all_their_nights",
- "still", "not_long_enough",
- "but_soon_it_will_be"]),
+ {ok,Cwd} = file:get_cwd(),
+ ok = erl_tar:extract(Long),
+ Base = filename:join([Cwd, "original_software", "written_by",
+ "a_bunch_of_hackers",
+ "spending_all_their_nights",
+ "still", "not_long_enough",
+ "but_soon_it_will_be"]),
%% Verify that the empty directory was created.
- ?line EmptyDir = filename:join(Base, "empty_directory"),
- ?line {ok, #file_info{type=directory}} = file:read_file_info(EmptyDir),
+ EmptyDir = filename:join(Base, "empty_directory"),
+ {ok, #file_info{type=directory}} = file:read_file_info(EmptyDir),
%% Verify that the files were created.
- ?line {ok,First} = file:read_file(filename:join(Base, "first_file")),
- ?line {ok,Second} = file:read_file(filename:join(Base, "second_file")),
- ?line "Here"++_ = binary_to_list(First),
- ?line "And"++_ = binary_to_list(Second),
+ {ok,First} = file:read_file(filename:join(Base, "first_file")),
+ {ok,Second} = file:read_file(filename:join(Base, "second_file")),
+ "Here"++_ = binary_to_list(First),
+ "And"++_ = binary_to_list(Second),
ok.
@@ -315,9 +315,9 @@ do_long_names(Long) ->
%% longer than 100 characters).
create_long_names(Config) when is_list(Config) ->
run_in_short_tempdir(Config, fun create_long_names/0).
-
+
create_long_names() ->
- ?line {ok,Dir} = file:get_cwd(),
+ {ok,Dir} = file:get_cwd(),
Dirs = ["aslfjkshjkhliuf",
"asdhjfehnbfsky",
"sahajfskdfhsz",
@@ -325,45 +325,45 @@ create_long_names() ->
"f7nafhjgffagkhsfkhsjk",
"dfjasldkfjsdkfjashbv"],
- ?line DeepDir = make_dirs(Dirs, []),
- ?line AFile = filename:join(DeepDir, "a_file"),
- ?line Hello = "hello, world\n",
- ?line ok = file:write_file(AFile, Hello),
- ?line TarName = filename:join(Dir, "my_tar_with_long_names.tar"),
- ?line ok = erl_tar:create(TarName, [AFile]),
+ DeepDir = make_dirs(Dirs, []),
+ AFile = filename:join(DeepDir, "a_file"),
+ Hello = "hello, world\n",
+ ok = file:write_file(AFile, Hello),
+ TarName = filename:join(Dir, "my_tar_with_long_names.tar"),
+ ok = erl_tar:create(TarName, [AFile]),
%% Print contents.
- ?line ok = erl_tar:tt(TarName),
+ ok = erl_tar:tt(TarName),
%% Extract and verify.
- ?line ExtractDir = "extract_dir",
- ?line ok = file:make_dir(ExtractDir),
- ?line ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]),
- ?line {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)),
- ?line Hello = binary_to_list(Bin),
+ ExtractDir = "extract_dir",
+ ok = file:make_dir(ExtractDir),
+ ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]),
+ {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)),
+ Hello = binary_to_list(Bin),
ok.
make_dirs([Dir|Rest], []) ->
- ?line ok = file:make_dir(Dir),
- ?line make_dirs(Rest, Dir);
+ ok = file:make_dir(Dir),
+ make_dirs(Rest, Dir);
make_dirs([Dir|Rest], Parent) ->
- ?line Name = filename:join(Parent, Dir),
- ?line ok = file:make_dir(Name),
- ?line make_dirs(Rest, Name);
+ Name = filename:join(Parent, Dir),
+ ok = file:make_dir(Name),
+ make_dirs(Rest, Name);
make_dirs([], Dir) ->
Dir.
%% Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files.
bad_tar(Config) when is_list(Config) ->
- ?line try_bad("bad_checksum", bad_header, Config),
- ?line try_bad("bad_octal", bad_header, Config),
- ?line try_bad("bad_too_short", eof, Config),
- ?line try_bad("bad_even_shorter", eof, Config),
+ try_bad("bad_checksum", bad_header, Config),
+ try_bad("bad_octal", bad_header, Config),
+ try_bad("bad_too_short", eof, Config),
+ try_bad("bad_even_shorter", eof, Config),
ok.
try_bad(Name0, Reason, Config) ->
- %% Intentionally no ?line macros here.
+ %% Intentionally no macros here.
DataDir = ?config(data_dir, Config),
PrivDir = ?config(priv_dir, Config),
@@ -392,22 +392,22 @@ try_bad(Name0, Reason, Config) ->
%% Tests that some common errors return correct error codes
%% and that format_error/1 handles them correctly.
errors(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
+ PrivDir = ?config(priv_dir, Config),
%% Give the tar file the same name as a directory.
- ?line BadTar = filename:join(PrivDir, "bad_tarfile.tar"),
- ?line ok = file:make_dir(BadTar),
- ?line try_error(erl_tar, create, [BadTar, []], {BadTar, eisdir}),
+ BadTar = filename:join(PrivDir, "bad_tarfile.tar"),
+ ok = file:make_dir(BadTar),
+ try_error(erl_tar, create, [BadTar, []], {BadTar, eisdir}),
%% Try including non-existent files in the tar file.
- ?line NonExistent = "non_existent_file",
- ?line GoodTar = filename:join(PrivDir, "a_good_tarfile.tar"),
- ?line try_error(erl_tar, create, [GoodTar, [NonExistent]],
- {NonExistent, enoent}),
+ NonExistent = "non_existent_file",
+ GoodTar = filename:join(PrivDir, "a_good_tarfile.tar"),
+ try_error(erl_tar, create, [GoodTar, [NonExistent]],
+ {NonExistent, enoent}),
%% Clean up.
- ?line delete_files([GoodTar,BadTar]),
-
+ delete_files([GoodTar,BadTar]),
+
ok.
try_error(M, F, A, Error) ->
@@ -439,102 +439,102 @@ remove_prefix(_, Result) ->
%% Test extracting a tar archive from a binary.
extract_from_binary(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Long = filename:join(DataDir, "no_fancy_stuff.tar"),
- ?line ExtractDir = filename:join(PrivDir, "extract_from_binary"),
- ?line ok = file:make_dir(ExtractDir),
-
+ DataDir = ?config(data_dir, Config),
+ PrivDir = ?config(priv_dir, Config),
+ Long = filename:join(DataDir, "no_fancy_stuff.tar"),
+ ExtractDir = filename:join(PrivDir, "extract_from_binary"),
+ ok = file:make_dir(ExtractDir),
+
%% Read a tar file into a binary and extract from the binary.
- ?line {ok, Bin} = file:read_file(Long),
- ?line ok = erl_tar:extract({binary, Bin}, [{cwd,ExtractDir}]),
+ {ok, Bin} = file:read_file(Long),
+ ok = erl_tar:extract({binary, Bin}, [{cwd,ExtractDir}]),
%% Verify.
Dir = filename:join(ExtractDir, "no_fancy_stuff"),
- ?line true = filelib:is_dir(Dir),
- ?line true = filelib:is_file(filename:join(Dir, "a_dir_list")),
- ?line true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
+ true = filelib:is_dir(Dir),
+ true = filelib:is_file(filename:join(Dir, "a_dir_list")),
+ true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
%% Clean up.
- ?line delete_files([ExtractDir]),
+ delete_files([ExtractDir]),
ok.
extract_from_binary_compressed(Config) when is_list(Config) ->
%% Test extracting a compressed tar archive from a binary.
- ?line DataDir = ?config(data_dir, Config),
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
- ?line ExtractDir = filename:join(PrivDir, "extract_from_binary_compressed"),
- ?line ok = file:make_dir(ExtractDir),
- ?line {ok,Bin} = file:read_file(Name),
+ DataDir = ?config(data_dir, Config),
+ PrivDir = ?config(priv_dir, Config),
+ Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
+ ExtractDir = filename:join(PrivDir, "extract_from_binary_compressed"),
+ ok = file:make_dir(ExtractDir),
+ {ok,Bin} = file:read_file(Name),
%% Try taking contents.
- ?line {ok,Files} = erl_tar:table({binary,Bin}, [compressed]),
- ?line io:format("~p\n", [Files]),
- ?line 19 = length(Files),
-
+ {ok,Files} = erl_tar:table({binary,Bin}, [compressed]),
+ io:format("~p\n", [Files]),
+ 19 = length(Files),
+
%% Trying extracting from a binary.
- ?line ok = erl_tar:extract({binary,Bin}, [compressed,{cwd,ExtractDir}]),
- ?line {ok,List} = file:list_dir(filename:join(ExtractDir, "ddll_SUITE_data")),
- ?line io:format("~p\n", [List]),
- ?line 19 = length(List),
+ ok = erl_tar:extract({binary,Bin}, [compressed,{cwd,ExtractDir}]),
+ {ok,List} = file:list_dir(filename:join(ExtractDir, "ddll_SUITE_data")),
+ io:format("~p\n", [List]),
+ 19 = length(List),
%% Clean up while at the same time testing that all file
%% were extracted as expected.
lists:foreach(fun(N) ->
File = filename:join(ExtractDir, N),
io:format("Deleting: ~p\n", [File]),
- ?line ok = file:delete(File)
+ ok = file:delete(File)
end, Files),
%% Clean up the rest.
- ?line delete_files([ExtractDir]),
+ delete_files([ExtractDir]),
ok.
%% Test extracting a tar archive from an open file.
extract_from_open_file(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Long = filename:join(DataDir, "no_fancy_stuff.tar"),
- ?line ExtractDir = filename:join(PrivDir, "extract_from_open_file"),
- ?line ok = file:make_dir(ExtractDir),
+ DataDir = ?config(data_dir, Config),
+ PrivDir = ?config(priv_dir, Config),
+ Long = filename:join(DataDir, "no_fancy_stuff.tar"),
+ ExtractDir = filename:join(PrivDir, "extract_from_open_file"),
+ ok = file:make_dir(ExtractDir),
- ?line {ok, File} = file:open(Long, [read]),
- ?line ok = erl_tar:extract({file, File}, [{cwd,ExtractDir}]),
+ {ok, File} = file:open(Long, [read]),
+ ok = erl_tar:extract({file, File}, [{cwd,ExtractDir}]),
%% Verify.
Dir = filename:join(ExtractDir, "no_fancy_stuff"),
- ?line true = filelib:is_dir(Dir),
- ?line true = filelib:is_file(filename:join(Dir, "a_dir_list")),
- ?line true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
+ true = filelib:is_dir(Dir),
+ true = filelib:is_file(filename:join(Dir, "a_dir_list")),
+ true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
%% Close open file.
- ?line ok = file:close(File),
+ ok = file:close(File),
%% Clean up.
- ?line delete_files([ExtractDir]),
+ delete_files([ExtractDir]),
ok.
%% Test that archives containing symlinks can be created and extracted.
symlinks(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Dir = filename:join(PrivDir, "symlinks"),
- ?line ok = file:make_dir(Dir),
- ?line ABadSymlink = filename:join(Dir, "bad_symlink"),
- ?line PointsTo = "/a/definitely/non_existing/path",
- ?line Res = case make_symlink("/a/definitely/non_existing/path", ABadSymlink) of
- {error, enotsup} ->
- {skip, "Symbolic links not supported on this platform"};
- ok ->
- symlinks(Dir, "bad_symlink", PointsTo),
- long_symlink(Dir)
- end,
+ PrivDir = ?config(priv_dir, Config),
+ Dir = filename:join(PrivDir, "symlinks"),
+ ok = file:make_dir(Dir),
+ ABadSymlink = filename:join(Dir, "bad_symlink"),
+ PointsTo = "/a/definitely/non_existing/path",
+ Res = case make_symlink("/a/definitely/non_existing/path", ABadSymlink) of
+ {error, enotsup} ->
+ {skip, "Symbolic links not supported on this platform"};
+ ok ->
+ symlinks(Dir, "bad_symlink", PointsTo),
+ long_symlink(Dir)
+ end,
%% Clean up.
- ?line delete_files([Dir]),
+ delete_files([Dir]),
Res.
make_symlink(Path, Link) ->
@@ -559,103 +559,103 @@ make_symlink(Path, Link) ->
_ ->
file:make_symlink(Path, Link)
end.
-
+
symlinks(Dir, BadSymlink, PointsTo) ->
- ?line Tar = filename:join(Dir, "symlink.tar"),
- ?line DerefTar = filename:join(Dir, "dereference.tar"),
+ Tar = filename:join(Dir, "symlink.tar"),
+ DerefTar = filename:join(Dir, "dereference.tar"),
%% Create the archive.
- ?line ok = file:set_cwd(Dir),
- ?line GoodSymlink = "good_symlink",
- ?line AFile = "a_good_file",
- ?line ALine = "A line of text for a file.",
- ?line ok = file:write_file(AFile, ALine),
- ?line ok = file:make_symlink(AFile, GoodSymlink),
- ?line ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]),
+ ok = file:set_cwd(Dir),
+ GoodSymlink = "good_symlink",
+ AFile = "a_good_file",
+ ALine = "A line of text for a file.",
+ ok = file:write_file(AFile, ALine),
+ ok = file:make_symlink(AFile, GoodSymlink),
+ ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]),
%% List contents of tar file.
- ?line ok = erl_tar:tt(Tar),
+ ok = erl_tar:tt(Tar),
%% Also create another archive with the dereference flag.
- ?line ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]),
+ ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]),
%% Extract files to a new directory.
- ?line NewDir = filename:join(Dir, "extracted"),
- ?line ok = file:make_dir(NewDir),
- ?line ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]),
+ NewDir = filename:join(Dir, "extracted"),
+ ok = file:make_dir(NewDir),
+ ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]),
%% Verify that the files are there.
- ?line ok = file:set_cwd(NewDir),
- ?line {ok, #file_info{type=symlink}} = file:read_link_info(BadSymlink),
- ?line {ok, PointsTo} = file:read_link(BadSymlink),
- ?line {ok, #file_info{type=symlink}} = file:read_link_info(GoodSymlink),
- ?line {ok, AFile} = file:read_link(GoodSymlink),
- ?line Expected = list_to_binary(ALine),
- ?line {ok, Expected} = file:read_file(GoodSymlink),
+ ok = file:set_cwd(NewDir),
+ {ok, #file_info{type=symlink}} = file:read_link_info(BadSymlink),
+ {ok, PointsTo} = file:read_link(BadSymlink),
+ {ok, #file_info{type=symlink}} = file:read_link_info(GoodSymlink),
+ {ok, AFile} = file:read_link(GoodSymlink),
+ Expected = list_to_binary(ALine),
+ {ok, Expected} = file:read_file(GoodSymlink),
%% Extract the "dereferenced archive" to a new directory.
- ?line NewDirDeref = filename:join(Dir, "extracted_deref"),
- ?line ok = file:make_dir(NewDirDeref),
- ?line ok = erl_tar:extract(DerefTar, [{cwd, NewDirDeref}, verbose]),
+ NewDirDeref = filename:join(Dir, "extracted_deref"),
+ ok = file:make_dir(NewDirDeref),
+ ok = erl_tar:extract(DerefTar, [{cwd, NewDirDeref}, verbose]),
%% Verify that the files are there.
- ?line ok = file:set_cwd(NewDirDeref),
- ?line {ok, #file_info{type=regular}} = file:read_link_info(GoodSymlink),
- ?line {ok, #file_info{type=regular}} = file:read_link_info(AFile),
- ?line {ok, Expected} = file:read_file(GoodSymlink),
- ?line {ok, Expected} = file:read_file(AFile),
+ ok = file:set_cwd(NewDirDeref),
+ {ok, #file_info{type=regular}} = file:read_link_info(GoodSymlink),
+ {ok, #file_info{type=regular}} = file:read_link_info(AFile),
+ {ok, Expected} = file:read_file(GoodSymlink),
+ {ok, Expected} = file:read_file(AFile),
ok.
long_symlink(Dir) ->
- ?line Tar = filename:join(Dir, "long_symlink.tar"),
- ?line ok = file:set_cwd(Dir),
-
- ?line AFile = "long_symlink",
- ?line FarTooLong = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed",
- ?line ok = file:make_symlink(FarTooLong, AFile),
- ?line {error,Error} = erl_tar:create(Tar, [AFile], [verbose]),
- ?line io:format("Error: ~s\n", [erl_tar:format_error(Error)]),
- ?line {FarTooLong,symbolic_link_too_long} = Error,
+ Tar = filename:join(Dir, "long_symlink.tar"),
+ ok = file:set_cwd(Dir),
+
+ AFile = "long_symlink",
+ FarTooLong = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed",
+ ok = file:make_symlink(FarTooLong, AFile),
+ {error,Error} = erl_tar:create(Tar, [AFile], [verbose]),
+ io:format("Error: ~s\n", [erl_tar:format_error(Error)]),
+ {FarTooLong,symbolic_link_too_long} = Error,
ok.
open_add_close(Config) when is_list(Config) ->
- ?line PrivDir = ?config(priv_dir, Config),
- ?line ok = file:set_cwd(PrivDir),
- ?line Dir = filename:join(PrivDir, "open_add_close"),
- ?line ok = file:make_dir(Dir),
-
- ?line [{FileOne,_,_},{FileTwo,_,_},{FileThree,_,_}] = oac_files(),
- ?line ADir = "empty_dir",
- ?line AnotherDir = "another_dir",
- ?line SomeContent = filename:join(AnotherDir, "some_content"),
- ?line ok = file:make_dir(ADir),
- ?line ok = file:make_dir(AnotherDir),
- ?line ok = file:make_dir(SomeContent),
-
- ?line TarOne = filename:join(Dir, "archive1.tar"),
- ?line {ok,AD} = erl_tar:open(TarOne, [write]),
- ?line ok = erl_tar:add(AD, FileOne, []),
- ?line ok = erl_tar:add(AD, FileTwo, "second file", []),
- ?line ok = erl_tar:add(AD, FileThree, [verbose]),
- ?line ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]),
- ?line ok = erl_tar:add(AD, ADir, [verbose]),
- ?line ok = erl_tar:add(AD, AnotherDir, [verbose]),
- ?line ok = erl_tar:close(AD),
-
- ?line ok = erl_tar:t(TarOne),
- ?line ok = erl_tar:tt(TarOne),
-
- ?line {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]} = erl_tar:table(TarOne),
-
- ?line delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]),
+ PrivDir = ?config(priv_dir, Config),
+ ok = file:set_cwd(PrivDir),
+ Dir = filename:join(PrivDir, "open_add_close"),
+ ok = file:make_dir(Dir),
+
+ [{FileOne,_,_},{FileTwo,_,_},{FileThree,_,_}] = oac_files(),
+ ADir = "empty_dir",
+ AnotherDir = "another_dir",
+ SomeContent = filename:join(AnotherDir, "some_content"),
+ ok = file:make_dir(ADir),
+ ok = file:make_dir(AnotherDir),
+ ok = file:make_dir(SomeContent),
+
+ TarOne = filename:join(Dir, "archive1.tar"),
+ {ok,AD} = erl_tar:open(TarOne, [write]),
+ ok = erl_tar:add(AD, FileOne, []),
+ ok = erl_tar:add(AD, FileTwo, "second file", []),
+ ok = erl_tar:add(AD, FileThree, [verbose]),
+ ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]),
+ ok = erl_tar:add(AD, ADir, [verbose]),
+ ok = erl_tar:add(AD, AnotherDir, [verbose]),
+ ok = erl_tar:close(AD),
+
+ ok = erl_tar:t(TarOne),
+ ok = erl_tar:tt(TarOne),
+
+ {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]} = erl_tar:table(TarOne),
+
+ delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]),
ok.
@@ -668,54 +668,54 @@ oac_files() ->
cooked_compressed(Config) when is_list(Config) ->
%% Test that a compressed archive can be read in cooked mode.
- ?line DataDir = ?config(data_dir, Config),
- ?line PrivDir = ?config(priv_dir, Config),
- ?line Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
+ DataDir = ?config(data_dir, Config),
+ PrivDir = ?config(priv_dir, Config),
+ Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
%% Try table/2 and extract/2.
- ?line {ok,List} = erl_tar:table(Name, [cooked,compressed]),
- ?line io:format("~p\n", [List]),
- ?line 19 = length(List),
- ?line ok = erl_tar:extract(Name, [cooked,compressed,{cwd,PrivDir}]),
+ {ok,List} = erl_tar:table(Name, [cooked,compressed]),
+ io:format("~p\n", [List]),
+ 19 = length(List),
+ ok = erl_tar:extract(Name, [cooked,compressed,{cwd,PrivDir}]),
%% Clean up while at the same time testing that all file
%% were extracted as expected.
lists:foreach(fun(N) ->
File = filename:join(PrivDir, N),
io:format("Deleting: ~p\n", [File]),
- ?line ok = file:delete(File)
+ ok = file:delete(File)
end, List),
%% Clean up.
- ?line delete_files([filename:join(PrivDir, "ddll_SUITE_data")]),
+ delete_files([filename:join(PrivDir, "ddll_SUITE_data")]),
ok.
%% Test that an archive can be created directly from binaries and
%% that an archive can be extracted into binaries.
memory(Config) when is_list(Config) ->
- ?line DataDir = ?config(data_dir, Config),
-
- ?line FileBins = [{"bar/fum", <<"BARFUM">>},{"foo", <<"FOO">>}],
- ?line Name1 = filename:join(DataDir, "memory.tar"),
- ?line ok = erl_tar:create(Name1, FileBins, [write,verbose]),
- ?line {ok,Extracted1} = erl_tar:extract(Name1, [memory,verbose]),
- ?line FileBins1 = lists:sort(Extracted1),
-
- ?line io:format("FileBins: ~p\n", [FileBins]),
- ?line io:format("FileBins1: ~p\n", [FileBins1]),
- ?line FileBins = FileBins1,
-
- ?line Name2 = filename:join(DataDir, "memory2.tar"),
- ?line {ok,Fd} = erl_tar:open(Name2, [write]),
- ?line [ok,ok] = [erl_tar:add(Fd, B, N, [write,verbose]) || {N,B} <- FileBins],
- ?line ok = erl_tar:close(Fd),
- ?line {ok,Extracted2} = erl_tar:extract(Name2, [memory,verbose]),
- ?line FileBins2 = lists:sort(Extracted2),
- ?line io:format("FileBins2: ~p\n", [FileBins2]),
- ?line FileBins = FileBins2,
+ DataDir = ?config(data_dir, Config),
+
+ FileBins = [{"bar/fum", <<"BARFUM">>},{"foo", <<"FOO">>}],
+ Name1 = filename:join(DataDir, "memory.tar"),
+ ok = erl_tar:create(Name1, FileBins, [write,verbose]),
+ {ok,Extracted1} = erl_tar:extract(Name1, [memory,verbose]),
+ FileBins1 = lists:sort(Extracted1),
+
+ io:format("FileBins: ~p\n", [FileBins]),
+ io:format("FileBins1: ~p\n", [FileBins1]),
+ FileBins = FileBins1,
+
+ Name2 = filename:join(DataDir, "memory2.tar"),
+ {ok,Fd} = erl_tar:open(Name2, [write]),
+ [ok,ok] = [erl_tar:add(Fd, B, N, [write,verbose]) || {N,B} <- FileBins],
+ ok = erl_tar:close(Fd),
+ {ok,Extracted2} = erl_tar:extract(Name2, [memory,verbose]),
+ FileBins2 = lists:sort(Extracted2),
+ io:format("FileBins2: ~p\n", [FileBins2]),
+ FileBins = FileBins2,
%% Clean up.
- ?line ok = delete_files([Name1,Name2]),
+ ok = delete_files([Name1,Name2]),
ok.
%% Test filenames with characters outside the US ASCII range.
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 4702d9cf61..d4bbd39d50 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -98,7 +98,7 @@ big_test(N) ->
Result = analyze_report(Report),
%%io:format("big_test is done: ~w~n", [Result]),
Result.
-
+
big_loop(_C, 0, []) ->
%%io:format("All processes are done!~n", []),
ok;
@@ -109,8 +109,8 @@ big_loop(C, 0, Pids) ->
{'EXIT', Pid, done} ->
big_loop(C, 0, lists:delete(Pid, Pids));
{'EXIT', Pid, Error} ->
- ?line ok = io:format("XXX Pid ~w died with reason ~p~n",
- [Pid, Error]),
+ ok = io:format("XXX Pid ~w died with reason ~p~n",
+ [Pid, Error]),
big_loop(C, 0, lists:delete(Pid, Pids))
end;
big_loop(C, N, Pids) ->
@@ -119,14 +119,14 @@ big_loop(C, N, Pids) ->
{'EXIT', Pid, done} ->
big_loop(C, N, lists:delete(Pid, Pids));
{'EXIT', Pid, Error} ->
- ?line ok =io:format("XXX Internal error: Pid ~w died, reason ~p~n",
- [Pid, Error]),
+ ok =io:format("XXX Internal error: Pid ~w died, reason ~p~n",
+ [Pid, Error]),
big_loop(C, N, lists:delete(Pid, Pids))
after 0 ->
%% maybe start an interval timer test
Pids1 = maybe_start_i_test(Pids, C, rand:uniform(4)),
-
+
%% start 1-4 "after" tests
Pids2 = start_after_test(Pids1, C, rand:uniform(4)),
%%Pids2=Pids1,
@@ -136,7 +136,7 @@ big_loop(C, N, Pids) ->
%% spawn zero, one or two nrev to get some load ;-/
Pids3 = start_nrev(Pids2, rand:uniform(100)),
-
+
big_loop(C, N-1, Pids3)
end.
@@ -149,7 +149,7 @@ start_nrev(Pids, _N) ->
NrevPid1 = spawn_link(timer_SUITE, do_nrev, [rand:uniform(1000)*10]),
NrevPid2 = spawn_link(timer_SUITE, do_nrev, [1]),
[NrevPid1,NrevPid2|Pids].
-
+
start_after_test(Pids, C, 1) ->
TO1 = rand:uniform(100)*47,
@@ -177,8 +177,8 @@ a_t(C, TimeOut) ->
watchdog ->
Stop = system_time(),
report(C, Start,Stop,TimeOut),
- ?line ok = io:format("Internal watchdog timeout (a), not good!!~n",
- []),
+ ok = io:format("Internal watchdog timeout (a), not good!!~n",
+ []),
exit(done)
end.
@@ -208,8 +208,8 @@ i_wait(Start, Prev, Times, TimeOut, Times, Ref, C) ->
Now = system_time(),
report_interval(C, {final,Times}, Start, Prev, Now, TimeOut),
timer:cancel(Ref),
- ?line ok = io:format("Internal watchdog timeout (i), not good!!~n",
- []),
+ ok = io:format("Internal watchdog timeout (i), not good!!~n",
+ []),
exit(done)
end;
i_wait(Start, Prev, Count, TimeOut, Times, Ref, C) ->
@@ -221,8 +221,8 @@ i_wait(Start, Prev, Count, TimeOut, Times, Ref, C) ->
watchdog ->
Now = system_time(),
report_interval(C, {final,Count}, Start, Prev, Now, TimeOut),
- ?line ok = io:format("Internal watchdog timeout (j), not good!!~n",
- []),
+ ok = io:format("Internal watchdog timeout (j), not good!!~n",
+ []),
exit(done)
end.
@@ -372,10 +372,10 @@ nrev([]) ->
[];
nrev([H|T]) ->
append(nrev(T), [H]).
-
+
append([H|T],Z) ->
- [H|append(T,Z)];
+ [H|append(T,Z)];
append([],X) ->
- X.
+ X.
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index a13dc7f9da..64fce2a4b2 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -91,196 +91,196 @@ init_per_testcase(_, Config) when is_list(Config) ->
%% Test of apply_after, with sending of message.
apply_after(Config) when is_list(Config) ->
- ?line timer:apply_after(500, ?MODULE, send, [self(), ok_apply]),
- ?line ok = get_mess(1000, ok_apply).
+ timer:apply_after(500, ?MODULE, send, [self(), ok_apply]),
+ ok = get_mess(1000, ok_apply).
%% Test of send_after with time = 0.
send_after1(Config) when is_list(Config) ->
- ?line timer:send_after(0, ok_send1),
- ?line ok = get_mess(1000, ok_send1).
+ timer:send_after(0, ok_send1),
+ ok = get_mess(1000, ok_send1).
%% Test of send_after with time = 500.
send_after2(Config) when is_list(Config) ->
- ?line timer:send_after(500, self(), ok_send2),
- ?line ok = get_mess(2000, ok_send2).
+ timer:send_after(500, self(), ok_send2),
+ ok = get_mess(2000, ok_send2).
%% Test of send_after with time = 500, with receiver a registered
%% process. [OTP-2735]
send_after3(Config) when is_list(Config) ->
- ?line Name = list_to_atom(pid_to_list(self())),
- ?line register(Name, self()),
- ?line timer:send_after(500, Name, ok_send3),
- ?line ok = get_mess(2000, ok_send3),
- ?line unregister(Name).
+ Name = list_to_atom(pid_to_list(self())),
+ register(Name, self()),
+ timer:send_after(500, Name, ok_send3),
+ ok = get_mess(2000, ok_send3),
+ unregister(Name).
%% Test of exit_after with time = 1000.
exit_after1(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Pid = spawn_link(?MODULE, forever, []),
- ?line timer:exit_after(1000, Pid, exit_test1),
- ?line ok = get_mess(5000, {'EXIT', Pid, exit_test1}).
+ process_flag(trap_exit, true),
+ Pid = spawn_link(?MODULE, forever, []),
+ timer:exit_after(1000, Pid, exit_test1),
+ ok = get_mess(5000, {'EXIT', Pid, exit_test1}).
%% Test of exit_after with time = 1000. The process to exit is the
%% name of a registered process. [OTP-2735]
exit_after2(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Pid = spawn_link(?MODULE, forever, []),
- ?line Name = list_to_atom(pid_to_list(Pid)),
- ?line register(Name, Pid),
- ?line timer:exit_after(1000, Name, exit_test2),
- ?line ok = get_mess(2000, {'EXIT', Pid, exit_test2}).
+ process_flag(trap_exit, true),
+ Pid = spawn_link(?MODULE, forever, []),
+ Name = list_to_atom(pid_to_list(Pid)),
+ register(Name, Pid),
+ timer:exit_after(1000, Name, exit_test2),
+ ok = get_mess(2000, {'EXIT', Pid, exit_test2}).
%% Test of kill_after with time = 1000.
kill_after1(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Pid = spawn_link(?MODULE, forever, []),
- ?line timer:kill_after(1000, Pid),
- ?line ok = get_mess(2000, {'EXIT', Pid, killed}).
+ process_flag(trap_exit, true),
+ Pid = spawn_link(?MODULE, forever, []),
+ timer:kill_after(1000, Pid),
+ ok = get_mess(2000, {'EXIT', Pid, killed}).
%% Test of kill_after with time = 1000. The process to exit is the
%% name of a registered process. [OTP-2735]
kill_after2(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Pid = spawn_link(?MODULE, forever, []),
- ?line Name = list_to_atom(pid_to_list(Pid)),
- ?line register(Name, Pid),
- ?line timer:kill_after(1000, Name),
- ?line ok = get_mess(2000, {'EXIT', Pid, killed}).
+ process_flag(trap_exit, true),
+ Pid = spawn_link(?MODULE, forever, []),
+ Name = list_to_atom(pid_to_list(Pid)),
+ register(Name, Pid),
+ timer:kill_after(1000, Name),
+ ok = get_mess(2000, {'EXIT', Pid, killed}).
%% Test of apply_interval by sending messages. Receive
%% 3 messages, cancel the timer, and check that we do
%% not get any more messages.
apply_interval(Config) when is_list(Config) ->
- ?line {ok, Ref} = timer:apply_interval(1000, ?MODULE, send,
+ {ok, Ref} = timer:apply_interval(1000, ?MODULE, send,
[self(), apply_int]),
- ?line ok = get_mess(1500, apply_int, 3),
- ?line timer:cancel(Ref),
- ?line nor = get_mess(1000, apply_int).
+ ok = get_mess(1500, apply_int, 3),
+ timer:cancel(Ref),
+ nor = get_mess(1000, apply_int).
%% Test of send_interval/2. Receive 5 messages, cancel the timer, and
%% check that we do not get any more messages.
send_interval1(Config) when is_list(Config) ->
{ok, Ref} = timer:send_interval(1000, send_int),
- ?line ok = get_mess(1500, send_int, 5),
+ ok = get_mess(1500, send_int, 5),
timer:cancel(Ref),
- ?line nor = get_mess(1000, send_int). % We should receive only five
+ nor = get_mess(1000, send_int). % We should receive only five
%% Test of send_interval/3. Receive 2 messages, cancel the timer, and
%% check that we do not get any more messages.
send_interval2(Config) when is_list(Config) ->
{ok, Ref} = timer:send_interval(1000, self(), send_int2),
- ?line ok = get_mess(1500, send_int2, 2),
+ ok = get_mess(1500, send_int2, 2),
timer:cancel(Ref),
- ?line nor = get_mess(1000, send_int2). % We should receive only two
+ nor = get_mess(1000, send_int2). % We should receive only two
%% Test of send_interval/3. Receive 2 messages, cancel the timer, and
%% check that we do not get any more messages. The receiver is the
%% name of a registered process. [OTP-2735]
send_interval3(Config) when is_list(Config) ->
- ?line process_flag(trap_exit, true),
- ?line Name = list_to_atom(pid_to_list(self())),
- ?line register(Name, self()),
- ?line {ok, Ref} = timer:send_interval(1000, Name, send_int3),
- ?line ok = get_mess(1500, send_int3, 2),
+ process_flag(trap_exit, true),
+ Name = list_to_atom(pid_to_list(self())),
+ register(Name, self()),
+ {ok, Ref} = timer:send_interval(1000, Name, send_int3),
+ ok = get_mess(1500, send_int3, 2),
timer:cancel(Ref),
- ?line nor = get_mess(1000, send_int3), % We should receive only two
- ?line unregister(Name).
+ nor = get_mess(1000, send_int3), % We should receive only two
+ unregister(Name).
%% Test that send interval stops sending msg when the receiving
%% process terminates.
send_interval4(Config) when is_list(Config) ->
- ?line timer:send_interval(500, one_time_only),
+ timer:send_interval(500, one_time_only),
receive
one_time_only -> ok
end,
- ?line timer_server ! {'EXIT', self(), normal}, % Should remove the timer
- ?line timer:send_after(600, send_intv_ok),
- ?line send_intv_ok = receive
- Msg -> Msg
- end.
+ timer_server ! {'EXIT', self(), normal}, % Should remove the timer
+ timer:send_after(600, send_intv_ok),
+ send_intv_ok = receive
+ Msg -> Msg
+ end.
%% Test that we can cancel a timer.
cancel1(Config) when is_list(Config) ->
- ?line {ok, Ref} = timer:send_after(1000, this_should_be_canceled),
- ?line timer:cancel(Ref),
- ?line nor = get_mess(2000, this_should_be_canceled). % We should rec 0 msgs
+ {ok, Ref} = timer:send_after(1000, this_should_be_canceled),
+ timer:cancel(Ref),
+ nor = get_mess(2000, this_should_be_canceled). % We should rec 0 msgs
%% Test cancel/1 with bad argument.
cancel2(Config) when is_list(Config) ->
- ?line {error, badarg} = timer:cancel(no_reference).
+ {error, badarg} = timer:cancel(no_reference).
%% Test sleep/1 and tc/3.
tc(Config) when is_list(Config) ->
%% This should test both sleep and tc/3
- ?line {Res1, ok} = timer:tc(timer, sleep, [500]),
- ?line ok = if
+ {Res1, ok} = timer:tc(timer, sleep, [500]),
+ ok = if
Res1 < 500*1000 -> {too_early, Res1}; % Too early
Res1 > 800*1000 -> {too_late, Res1}; % Too much time
true -> ok
end,
%% tc/2
- ?line {Res2, ok} = timer:tc(fun(T) -> timer:sleep(T) end, [500]),
- ?line ok = if
+ {Res2, ok} = timer:tc(fun(T) -> timer:sleep(T) end, [500]),
+ ok = if
Res2 < 500*1000 -> {too_early, Res2}; % Too early
Res2 > 800*1000 -> {too_late, Res2}; % Too much time
true -> ok
end,
-
+
%% tc/1
- ?line {Res3, ok} = timer:tc(fun() -> timer:sleep(500) end),
- ?line ok = if
+ {Res3, ok} = timer:tc(fun() -> timer:sleep(500) end),
+ ok = if
Res3 < 500*1000 -> {too_early, Res3}; % Too early
Res3 > 800*1000 -> {too_late, Res3}; % Too much time
true -> ok
end,
%% Check that timer:tc don't catch errors
- ?line ok = try timer:tc(erlang, exit, [foo])
- catch exit:foo -> ok
- end,
-
- ?line ok = try timer:tc(fun(Reason) -> 1 = Reason end, [foo])
- catch error:{badmatch,_} -> ok
- end,
-
- ?line ok = try timer:tc(fun() -> throw(foo) end)
- catch foo -> ok
- end,
-
+ ok = try timer:tc(erlang, exit, [foo])
+ catch exit:foo -> ok
+ end,
+
+ ok = try timer:tc(fun(Reason) -> 1 = Reason end, [foo])
+ catch error:{badmatch,_} -> ok
+ end,
+
+ ok = try timer:tc(fun() -> throw(foo) end)
+ catch foo -> ok
+ end,
+
%% Check that return values are propageted
Self = self(),
- ?line {_, Self} = timer:tc(erlang, self, []),
- ?line {_, Self} = timer:tc(fun(P) -> P end, [self()]),
- ?line {_, Self} = timer:tc(fun() -> self() end),
-
- ?line Sec = timer:seconds(4),
- ?line Min = timer:minutes(4),
- ?line Hour = timer:hours(4),
- ?line MyRes = 4*1000 + 4*60*1000 + 4*60*60*1000,
- ?line if MyRes == Sec + Min + Hour -> ok end,
- ?line TimerRes = timer:hms(4,4,4),
- ?line if MyRes == TimerRes -> ok end,
+ {_, Self} = timer:tc(erlang, self, []),
+ {_, Self} = timer:tc(fun(P) -> P end, [self()]),
+ {_, Self} = timer:tc(fun() -> self() end),
+
+ Sec = timer:seconds(4),
+ Min = timer:minutes(4),
+ Hour = timer:hours(4),
+ MyRes = 4*1000 + 4*60*1000 + 4*60*60*1000,
+ if MyRes == Sec + Min + Hour -> ok end,
+ TimerRes = timer:hms(4,4,4),
+ if MyRes == TimerRes -> ok end,
ok.
%% Test that cancellations of one-shot timers do not accidentally
%% cancel interval timers. [OTP-2771].
unique_refs(Config) when is_list(Config) ->
- ?line ITimers = repeat_send_interval(10), % 10 interval timers
- ?line eat_refs(?MAXREF - ?REFMARG),
- ?line set_and_cancel_one_shots(?REFMARG),
- ?line NumLeft = num_timers(),
- ?line io:format("~w timers left, should be 10\n", [NumLeft]),
- ?line cancel(ITimers),
- ?line receive_nisse(),
- ?line 10 = NumLeft.
+ ITimers = repeat_send_interval(10), % 10 interval timers
+ eat_refs(?MAXREF - ?REFMARG),
+ set_and_cancel_one_shots(?REFMARG),
+ NumLeft = num_timers(),
+ io:format("~w timers left, should be 10\n", [NumLeft]),
+ cancel(ITimers),
+ receive_nisse(),
+ 10 = NumLeft.
repeat_send_interval(0) ->
[];
repeat_send_interval(M) ->
- ?line {ok, Ref} = timer:send_interval(6000,self(), nisse),
- ?line [Ref| repeat_send_interval(M - 1)].
+ {ok, Ref} = timer:send_interval(6000,self(), nisse),
+ [Ref| repeat_send_interval(M - 1)].
eat_refs(0) ->
0;
@@ -298,8 +298,8 @@ set_and_cancel_one_shots(N) ->
set_and_cancel_one_shots(N-1).
cancel([T| Ts]) ->
- ?line timer:cancel(T),
- ?line cancel(Ts);
+ timer:cancel(T),
+ cancel(Ts);
cancel([]) ->
ok.
@@ -322,7 +322,7 @@ get_mess(Time, Mess, N) ->
receive
Mess -> get_mess(Time, Mess, N-1)
after Time
- -> nor % Not Received
+ -> nor % Not Received
end.
forever() ->
@@ -349,7 +349,7 @@ performance(Mod) ->
big_test(M) ->
Load_Pids = start_nrev(20, M), % Increase if more load wanted :)
-
+
LPids = spawn_timers(5, M, 10000, 5),
apply(M, sleep, [4000]),
@@ -359,7 +359,7 @@ big_test(M) ->
SPids = spawn_timers(15, M, 100, 3),
Res = wait(SPids ++ MPids ++ LPids, [], 0, M),
-
+
lists:foreach(fun(Pid) -> exit(Pid, kill) end, Load_Pids),
Res.
@@ -450,11 +450,11 @@ nrev([]) ->
[];
nrev([H|T]) ->
append(nrev(T), [H]).
-
+
append([H|T],Z) ->
- [H|append(T,Z)];
+ [H|append(T,Z)];
append([],X) ->
- X.
+ X.
system_time() ->
erlang:monotonic_time(micro_seconds).
@@ -520,11 +520,11 @@ get_ivals(List) ->
LTot = lists:map(fun(X) -> element(2, X) end, List),
LMin = lists:map(fun(X) -> element(4, X) end, List),
LMax = lists:map(fun(X) -> element(5, X) end, List),
-
+
MaxTot = lists:max(LTot),
MinTot = lists:min(LTot),
AverTot = lists:sum(LTot) div Len,
-
+
IterMax = lists:max(LMax),
IterMin = lists:min(LMin),
IterAver= AverTot div Num,
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index be492bb1c1..d2ee5d19a4 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -37,7 +37,7 @@
ex_binaries_errors_utf16_big/1,
ex_binaries_errors_utf32_little/1,
ex_binaries_errors_utf32_big/1]).
-
+
init_per_testcase(_Case, Config) ->
Config.
@@ -80,7 +80,7 @@ binaries_errors_limit(Config) when is_list(Config) ->
ex_binaries_errors_utf8(Config),
setlimit(default),
ok.
-
+
ex_binaries_errors_utf8(Config) when is_list(Config) ->
%% Original smoke test, we should not forget the original offset...
<<_:8,_:8,RR2/binary>> = <<$a,$b,164,165,$c>>,
@@ -151,10 +151,10 @@ utf16_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) ->
utf16_inner_loop(List, BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian);
utf16_inner_loop([], _, _, _, _, _) ->
ok.
-
+
ex_binaries_errors_utf32_big(Config) when is_list(Config) ->
ex_binaries_errors_utf32(big).
-
+
ex_binaries_errors_utf32_little(Config) when is_list(Config) ->
ex_binaries_errors_utf32(little).
@@ -180,7 +180,7 @@ ex_binaries_errors_utf32(Endian) ->
PartlyBroken, PBSz, Endian)
end || N <- lists:seq(1, 16, 3) ],
ok.
-
+
utf32_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) ->
Sz = length(List)*4 + BrokenSz,
Chomped = binary:part(PartlyBroken, PBSz - Sz, Sz),
@@ -199,115 +199,115 @@ exceptions(Config) when is_list(Config) ->
ex_exceptions(Config).
ex_exceptions(Config) when is_list(Config) ->
- ?line L = lists:seq(0,255),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],unicode)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],latin1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,gnarfl)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,L)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,{latin1})),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,[latin1])),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1.0)),
+ L = lists:seq(0,255),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],unicode)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],latin1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,gnarfl)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,L)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,{latin1})),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,[latin1])),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1.0)),
Encodings = [unicode, utf8,utf16,utf32,{utf16,big},
{utf16,little},{utf32,big},{utf32,little}],
[ begin
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,unicode,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},unicode,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,unicode,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,unicode,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',unicode,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],unicode,
- Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],unicode,
- Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,latin1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},latin1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,latin1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,latin1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',latin1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],latin1,
- Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],latin1,
- Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,gnarfl,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,L,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,{latin1},Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,[latin1],Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1.0,Enc))
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,unicode,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},unicode,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,unicode,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,unicode,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',unicode,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],unicode,
+ Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],unicode,
+ Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L++255,latin1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary({1,2,3},latin1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1,latin1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(1.0,latin1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary('1',latin1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,apa],latin1,
+ Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary([1,2,3,4.0],latin1,
+ Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,gnarfl,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,L,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,{latin1},Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,[latin1],Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_binary(L,1.0,Enc))
end || Enc <- Encodings ],
Encodings2 = [latin1, unicode, utf8,utf16,utf32,{utf16,big},
- {utf16,little},{utf32,big},{utf32,little}],
+ {utf16,little},{utf32,big},{utf32,little}],
[ begin
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L++255,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list({1,2,3},Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(1,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(1.0,Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list('1',Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list([1,2,3,apa],Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list([1,2,3,4.0],Enc)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,{Enc})),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,[Enc]))
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L++255,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list({1,2,3},Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(1,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(1.0,Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list('1',Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list([1,2,3,apa],Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list([1,2,3,4.0],Enc)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,{Enc})),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,[Enc]))
end || Enc <- Encodings2 ],
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,gnarfl)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,L)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,1)),
- ?line {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,1.0)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,gnarfl)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,L)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,1)),
+ {'EXIT',{badarg,_}} = (catch unicode:characters_to_list(L,1.0)),
[ begin
- ?line Bx = unicode:characters_to_binary(L,latin1, Enc),
- ?line L = unicode:characters_to_list(Bx,Enc)
+ Bx = unicode:characters_to_binary(L,latin1, Enc),
+ L = unicode:characters_to_list(Bx,Enc)
end || Enc <- Encodings ],
- ?line B = unicode:characters_to_binary(L,latin1),
- ?line L = unicode:characters_to_list(B,unicode),
- ?line L = unicode:characters_to_list(list_to_binary(L),latin1),
- ?line More = <<B/binary,0,1,2>>,
- ?line B2 = list_to_binary([254,255]),
- ?line B3 = list_to_binary([0,1,2,254,255]),
- ?line {error,B,Rest1} = unicode:characters_to_binary([L,B2],unicode),
- ?line B2 = iolist_to_binary(Rest1),
- ?line {error,More,Rest2} = unicode:characters_to_binary([L,B3],unicode),
- [ begin ?line {error,_,_} = unicode:characters_to_binary([L,B2],unicode,Enc) end
+ B = unicode:characters_to_binary(L,latin1),
+ L = unicode:characters_to_list(B,unicode),
+ L = unicode:characters_to_list(list_to_binary(L),latin1),
+ More = <<B/binary,0,1,2>>,
+ B2 = list_to_binary([254,255]),
+ B3 = list_to_binary([0,1,2,254,255]),
+ {error,B,Rest1} = unicode:characters_to_binary([L,B2],unicode),
+ B2 = iolist_to_binary(Rest1),
+ {error,More,Rest2} = unicode:characters_to_binary([L,B3],unicode),
+ [ begin {error,_,_} = unicode:characters_to_binary([L,B2],unicode,Enc) end
|| Enc <- Encodings ],
- ?line Valid0 = unicode:characters_to_binary([L,254,255],unicode),
- ?line Valid1 = unicode:characters_to_binary([L,254,255],latin1),
- ?line Valid2 = unicode:characters_to_binary([L,254,255,256,257],unicode),
- ?line Valid3 = unicode:characters_to_binary([L,B2],latin1),
- ?line true = is_binary(Valid0),
- ?line true = is_binary(Valid1),
- ?line true = is_binary(Valid2),
- ?line true = is_binary(Valid3),
- ?line Valid4 = unicode:characters_to_binary([L,B3],latin1),
- ?line true = is_binary(Valid4),
- ?line B2 = iolist_to_binary(Rest2),
- ?line true = (L ++ [254,255] =:= unicode:characters_to_list(Valid0,unicode)),
- ?line true = (L ++ [254,255,256,257] =:= unicode:characters_to_list(Valid2,unicode)),
+ Valid0 = unicode:characters_to_binary([L,254,255],unicode),
+ Valid1 = unicode:characters_to_binary([L,254,255],latin1),
+ Valid2 = unicode:characters_to_binary([L,254,255,256,257],unicode),
+ Valid3 = unicode:characters_to_binary([L,B2],latin1),
+ true = is_binary(Valid0),
+ true = is_binary(Valid1),
+ true = is_binary(Valid2),
+ true = is_binary(Valid3),
+ Valid4 = unicode:characters_to_binary([L,B3],latin1),
+ true = is_binary(Valid4),
+ B2 = iolist_to_binary(Rest2),
+ true = (L ++ [254,255] =:= unicode:characters_to_list(Valid0,unicode)),
+ true = (L ++ [254,255,256,257] =:= unicode:characters_to_list(Valid2,unicode)),
lists:foreach(fun(Enco) ->
- ?line Valid0x = unicode:characters_to_binary([L,254,255],unicode,Enco),
- ?line Valid1x = unicode:characters_to_binary([L,254,255],latin1,Enco),
- ?line Valid2x = unicode:characters_to_binary([L,254,255,256,257],unicode,Enco),
- ?line Valid3x = unicode:characters_to_binary([L,B2],latin1,Enco),
- ?line true = is_binary(Valid0x),
- ?line true = is_binary(Valid1x),
- ?line true = is_binary(Valid2x),
- ?line true = is_binary(Valid3x)
+ Valid0x = unicode:characters_to_binary([L,254,255],unicode,Enco),
+ Valid1x = unicode:characters_to_binary([L,254,255],latin1,Enco),
+ Valid2x = unicode:characters_to_binary([L,254,255,256,257],unicode,Enco),
+ Valid3x = unicode:characters_to_binary([L,B2],latin1,Enco),
+ true = is_binary(Valid0x),
+ true = is_binary(Valid1x),
+ true = is_binary(Valid2x),
+ true = is_binary(Valid3x)
end, Encodings),
ok.
-
+
latin1(Config) when is_list(Config) ->
setlimit(10),
@@ -316,132 +316,132 @@ latin1(Config) when is_list(Config) ->
ex_latin1(Config).
ex_latin1(Config) when is_list(Config) ->
- ?line All = lists:seq(0,255),
- ?line AllBin = list_to_binary(All),
- ?line AllUtf8 = unicode:characters_to_binary(All,latin1),
- ?line AllUtf8 = unicode:characters_to_binary(AllBin,latin1),
- ?line AllUtf8 = unicode:characters_to_binary([AllBin],latin1),
- ?line AllUtf8 = unicode:characters_to_binary(make_unaligned(AllBin),latin1),
- ?line AllUtf8 = unicode:characters_to_binary([make_unaligned(AllBin)],latin1),
- ?line AllUtf8 = list_to_utf8_bsyntax([AllBin],latin1),
- ?line AllUtf8 = list_to_utf8_bsyntax([make_unaligned(AllBin)],latin1),
- ?line AllUtf8 = unicode_mixed_to_utf8_1(All),
-
- ?line AllUtf16_Big = unicode:characters_to_binary(All,latin1,utf16),
- ?line AllUtf16_Big = unicode:characters_to_binary(AllBin,latin1,utf16),
- ?line AllUtf16_Big = unicode:characters_to_binary([AllBin],latin1,utf16),
- ?line AllUtf16_Big = unicode:characters_to_binary(make_unaligned(AllBin),latin1,utf16),
- ?line AllUtf16_Big = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,utf16),
- ?line AllUtf16_Big = list_to_utf16_big_bsyntax([AllBin],latin1),
- ?line AllUtf16_Big = list_to_utf16_big_bsyntax([make_unaligned(AllBin)],latin1),
-
- ?line AllUtf16_Little = unicode:characters_to_binary(All,latin1,{utf16,little}),
- ?line AllUtf16_Little = unicode:characters_to_binary(AllBin,latin1,{utf16,little}),
- ?line AllUtf16_Little = unicode:characters_to_binary([AllBin],latin1,{utf16,little}),
- ?line AllUtf16_Little = unicode:characters_to_binary(make_unaligned(AllBin),latin1,
- {utf16,little}),
- ?line AllUtf16_Little = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,
- {utf16,little}),
- ?line AllUtf16_Little = list_to_utf16_little_bsyntax([AllBin],latin1),
- ?line AllUtf16_Little = list_to_utf16_little_bsyntax([make_unaligned(AllBin)],latin1),
-
- ?line AllUtf32_Big = unicode:characters_to_binary(All,latin1,utf32),
- ?line AllUtf32_Big = unicode:characters_to_binary(AllBin,latin1,utf32),
- ?line AllUtf32_Big = unicode:characters_to_binary([AllBin],latin1,utf32),
- ?line AllUtf32_Big = unicode:characters_to_binary(make_unaligned(AllBin),latin1,utf32),
- ?line AllUtf32_Big = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,utf32),
- ?line AllUtf32_Big = list_to_utf32_big_bsyntax([AllBin],latin1),
- ?line AllUtf32_Big = list_to_utf32_big_bsyntax([make_unaligned(AllBin)],latin1),
-
- ?line AllUtf32_Little = unicode:characters_to_binary(All,latin1,{utf32,little}),
- ?line AllUtf32_Little = unicode:characters_to_binary(AllBin,latin1,{utf32,little}),
- ?line AllUtf32_Little = unicode:characters_to_binary([AllBin],latin1,{utf32,little}),
- ?line AllUtf32_Little = unicode:characters_to_binary(make_unaligned(AllBin),latin1,
- {utf32,little}),
- ?line AllUtf32_Little = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,
- {utf32,little}),
- ?line AllUtf32_Little = list_to_utf32_little_bsyntax([AllBin],latin1),
- ?line AllUtf32_Little = list_to_utf32_little_bsyntax([make_unaligned(AllBin)],latin1),
-
- ?line DoubleUtf8 = <<AllUtf8/binary,AllUtf8/binary>>,
- ?line DoubleUtf8 = unicode:characters_to_binary([All,AllBin],latin1),
- ?line DoubleUtf8 =
+ All = lists:seq(0,255),
+ AllBin = list_to_binary(All),
+ AllUtf8 = unicode:characters_to_binary(All,latin1),
+ AllUtf8 = unicode:characters_to_binary(AllBin,latin1),
+ AllUtf8 = unicode:characters_to_binary([AllBin],latin1),
+ AllUtf8 = unicode:characters_to_binary(make_unaligned(AllBin),latin1),
+ AllUtf8 = unicode:characters_to_binary([make_unaligned(AllBin)],latin1),
+ AllUtf8 = list_to_utf8_bsyntax([AllBin],latin1),
+ AllUtf8 = list_to_utf8_bsyntax([make_unaligned(AllBin)],latin1),
+ AllUtf8 = unicode_mixed_to_utf8_1(All),
+
+ AllUtf16_Big = unicode:characters_to_binary(All,latin1,utf16),
+ AllUtf16_Big = unicode:characters_to_binary(AllBin,latin1,utf16),
+ AllUtf16_Big = unicode:characters_to_binary([AllBin],latin1,utf16),
+ AllUtf16_Big = unicode:characters_to_binary(make_unaligned(AllBin),latin1,utf16),
+ AllUtf16_Big = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,utf16),
+ AllUtf16_Big = list_to_utf16_big_bsyntax([AllBin],latin1),
+ AllUtf16_Big = list_to_utf16_big_bsyntax([make_unaligned(AllBin)],latin1),
+
+ AllUtf16_Little = unicode:characters_to_binary(All,latin1,{utf16,little}),
+ AllUtf16_Little = unicode:characters_to_binary(AllBin,latin1,{utf16,little}),
+ AllUtf16_Little = unicode:characters_to_binary([AllBin],latin1,{utf16,little}),
+ AllUtf16_Little = unicode:characters_to_binary(make_unaligned(AllBin),latin1,
+ {utf16,little}),
+ AllUtf16_Little = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,
+ {utf16,little}),
+ AllUtf16_Little = list_to_utf16_little_bsyntax([AllBin],latin1),
+ AllUtf16_Little = list_to_utf16_little_bsyntax([make_unaligned(AllBin)],latin1),
+
+ AllUtf32_Big = unicode:characters_to_binary(All,latin1,utf32),
+ AllUtf32_Big = unicode:characters_to_binary(AllBin,latin1,utf32),
+ AllUtf32_Big = unicode:characters_to_binary([AllBin],latin1,utf32),
+ AllUtf32_Big = unicode:characters_to_binary(make_unaligned(AllBin),latin1,utf32),
+ AllUtf32_Big = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,utf32),
+ AllUtf32_Big = list_to_utf32_big_bsyntax([AllBin],latin1),
+ AllUtf32_Big = list_to_utf32_big_bsyntax([make_unaligned(AllBin)],latin1),
+
+ AllUtf32_Little = unicode:characters_to_binary(All,latin1,{utf32,little}),
+ AllUtf32_Little = unicode:characters_to_binary(AllBin,latin1,{utf32,little}),
+ AllUtf32_Little = unicode:characters_to_binary([AllBin],latin1,{utf32,little}),
+ AllUtf32_Little = unicode:characters_to_binary(make_unaligned(AllBin),latin1,
+ {utf32,little}),
+ AllUtf32_Little = unicode:characters_to_binary([make_unaligned(AllBin)],latin1,
+ {utf32,little}),
+ AllUtf32_Little = list_to_utf32_little_bsyntax([AllBin],latin1),
+ AllUtf32_Little = list_to_utf32_little_bsyntax([make_unaligned(AllBin)],latin1),
+
+ DoubleUtf8 = <<AllUtf8/binary,AllUtf8/binary>>,
+ DoubleUtf8 = unicode:characters_to_binary([All,AllBin],latin1),
+ DoubleUtf8 =
unicode:characters_to_binary([All,make_unaligned(AllBin)],latin1),
- ?line DoubleUtf8 = unicode:characters_to_binary([All|AllBin],latin1),
- ?line DoubleUtf8 =
+ DoubleUtf8 = unicode:characters_to_binary([All|AllBin],latin1),
+ DoubleUtf8 =
unicode:characters_to_binary([All|make_unaligned(AllBin)],latin1),
- ?line DoubleUtf8 = unicode:characters_to_binary([AllBin,All],latin1),
- ?line DoubleUtf8 = unicode:characters_to_binary([AllBin|All],latin1),
- ?line DoubleUtf8 = list_to_utf8_bsyntax([AllBin|All],latin1),
+ DoubleUtf8 = unicode:characters_to_binary([AllBin,All],latin1),
+ DoubleUtf8 = unicode:characters_to_binary([AllBin|All],latin1),
+ DoubleUtf8 = list_to_utf8_bsyntax([AllBin|All],latin1),
- ?line DoubleUtf16 = <<AllUtf16_Big/binary,AllUtf16_Big/binary>>,
- ?line DoubleUtf16 = unicode:characters_to_binary([All,AllBin],latin1,{utf16,big}),
- ?line DoubleUtf16 =
+ DoubleUtf16 = <<AllUtf16_Big/binary,AllUtf16_Big/binary>>,
+ DoubleUtf16 = unicode:characters_to_binary([All,AllBin],latin1,{utf16,big}),
+ DoubleUtf16 =
unicode:characters_to_binary([All,make_unaligned(AllBin)],latin1,{utf16,big}),
- ?line DoubleUtf16 = unicode:characters_to_binary([All|AllBin],latin1,{utf16,big}),
- ?line DoubleUtf16 =
+ DoubleUtf16 = unicode:characters_to_binary([All|AllBin],latin1,{utf16,big}),
+ DoubleUtf16 =
unicode:characters_to_binary([All|make_unaligned(AllBin)],latin1,{utf16,big}),
- ?line DoubleUtf16 = unicode:characters_to_binary([AllBin,All],latin1,{utf16,big}),
- ?line DoubleUtf16 = unicode:characters_to_binary([AllBin|All],latin1,{utf16,big}),
- ?line DoubleUtf16 = list_to_utf16_big_bsyntax([AllBin|All],latin1),
-
- ?line All = unicode:characters_to_list(AllUtf8,unicode),
- ?line All = unicode:characters_to_list(make_unaligned(AllUtf8),unicode),
- ?line All = utf8_to_list_bsyntax(AllUtf8),
- ?line AllAll = All ++ All,
- ?line AllAll = unicode:characters_to_list(DoubleUtf8,unicode),
- ?line AllAll = unicode:characters_to_list(make_unaligned(DoubleUtf8),unicode),
- ?line AllAll = utf8_to_list_bsyntax(DoubleUtf8),
- ?line {error,AllUtf8,Rest1} = unicode:characters_to_binary(All++[16#FFF],latin1),
- ?line [16#FFF] = lists:flatten(Rest1),
- ?line {error,DoubleUtf8,Rest2} =
+ DoubleUtf16 = unicode:characters_to_binary([AllBin,All],latin1,{utf16,big}),
+ DoubleUtf16 = unicode:characters_to_binary([AllBin|All],latin1,{utf16,big}),
+ DoubleUtf16 = list_to_utf16_big_bsyntax([AllBin|All],latin1),
+
+ All = unicode:characters_to_list(AllUtf8,unicode),
+ All = unicode:characters_to_list(make_unaligned(AllUtf8),unicode),
+ All = utf8_to_list_bsyntax(AllUtf8),
+ AllAll = All ++ All,
+ AllAll = unicode:characters_to_list(DoubleUtf8,unicode),
+ AllAll = unicode:characters_to_list(make_unaligned(DoubleUtf8),unicode),
+ AllAll = utf8_to_list_bsyntax(DoubleUtf8),
+ {error,AllUtf8,Rest1} = unicode:characters_to_binary(All++[16#FFF],latin1),
+ [16#FFF] = lists:flatten(Rest1),
+ {error,DoubleUtf8,Rest2} =
unicode:characters_to_binary([All,AllBin,16#FFF],latin1),
- ?line {error,DoubleUtf16,Rest2x} =
+ {error,DoubleUtf16,Rest2x} =
unicode:characters_to_binary([All,AllBin,16#FFF],latin1,utf16),
- ?line [16#FFF] = lists:flatten(Rest2),
- ?line [16#FFF] = lists:flatten(Rest2x),
- ?line {error,AllUtf8,Rest3} =
+ [16#FFF] = lists:flatten(Rest2),
+ [16#FFF] = lists:flatten(Rest2x),
+ {error,AllUtf8,Rest3} =
unicode:characters_to_binary([All,16#FFF,AllBin,16#FFF],
- latin1),
- ?line {error,AllUtf8,Rest3} =
+ latin1),
+ {error,AllUtf8,Rest3} =
unicode:characters_to_binary([All,16#FFF,make_unaligned(AllBin),16#FFF],
- latin1),
- ?line {error,AllUtf16_Big,Rest3x} =
+ latin1),
+ {error,AllUtf16_Big,Rest3x} =
unicode:characters_to_binary([All,16#FFF,AllBin,16#FFF],
- latin1,{utf16,big}),
- ?line {error,AllUtf16_Big,Rest3x} =
+ latin1,{utf16,big}),
+ {error,AllUtf16_Big,Rest3x} =
unicode:characters_to_binary([All,16#FFF,make_unaligned(AllBin),16#FFF],
- latin1,{utf16,big}),
- ?line [16#FFF,AllBin,16#FFF] = lists:flatten(Rest3),
- ?line [16#FFF,AllBin,16#FFF] = lists:flatten(Rest3x),
- ?line DoubleSize = byte_size(DoubleUtf8),
- ?line AllBut1 = DoubleSize - 1,
- ?line AllBut2 = DoubleSize - 2,
- ?line <<MissingLastByte:AllBut1/binary,_>> = DoubleUtf8,
- ?line <<_:AllBut2/binary,MissingStart:1/binary,_>> = DoubleUtf8,
- ?line {ChompedList,_} = lists:split(length(AllAll) - 1,AllAll),
- ?line {incomplete,ChompedList,MissingStart} =
+ latin1,{utf16,big}),
+ [16#FFF,AllBin,16#FFF] = lists:flatten(Rest3),
+ [16#FFF,AllBin,16#FFF] = lists:flatten(Rest3x),
+ DoubleSize = byte_size(DoubleUtf8),
+ AllBut1 = DoubleSize - 1,
+ AllBut2 = DoubleSize - 2,
+ <<MissingLastByte:AllBut1/binary,_>> = DoubleUtf8,
+ <<_:AllBut2/binary,MissingStart:1/binary,_>> = DoubleUtf8,
+ {ChompedList,_} = lists:split(length(AllAll) - 1,AllAll),
+ {incomplete,ChompedList,MissingStart} =
unicode:characters_to_list(MissingLastByte,unicode),
- ?line {incomplete,ChompedList,MissingStart} =
+ {incomplete,ChompedList,MissingStart} =
unicode:characters_to_list(make_unaligned(MissingLastByte),unicode),
- ?line DoubleSize16 = byte_size(DoubleUtf16),
- ?line DoubleUtf16_2 = list_to_binary([DoubleUtf16,<<16#FFFFF/utf16-big>>]),
- ?line DoubleSize16_2 = byte_size(DoubleUtf16_2),
- ?line AllBut1_16 = DoubleSize16 - 1,
- ?line AllBut2_16_2 = DoubleSize16_2 - 2,
- ?line <<MissingLastBytes16:AllBut2_16_2/binary,_,_>> = DoubleUtf16_2,
- ?line <<MissingLastByte16:AllBut1_16/binary,_>> = DoubleUtf16,
- ?line {incomplete,AllAll,_} =
+ DoubleSize16 = byte_size(DoubleUtf16),
+ DoubleUtf16_2 = list_to_binary([DoubleUtf16,<<16#FFFFF/utf16-big>>]),
+ DoubleSize16_2 = byte_size(DoubleUtf16_2),
+ AllBut1_16 = DoubleSize16 - 1,
+ AllBut2_16_2 = DoubleSize16_2 - 2,
+ <<MissingLastBytes16:AllBut2_16_2/binary,_,_>> = DoubleUtf16_2,
+ <<MissingLastByte16:AllBut1_16/binary,_>> = DoubleUtf16,
+ {incomplete,AllAll,_} =
unicode:characters_to_list(MissingLastBytes16,utf16),
- ?line {incomplete,AllAll,_} =
+ {incomplete,AllAll,_} =
unicode:characters_to_list(make_unaligned(MissingLastBytes16),utf16),
- ?line {incomplete,ChompedList,_} =
+ {incomplete,ChompedList,_} =
unicode:characters_to_list(MissingLastByte16,utf16),
- ?line {incomplete,ChompedList,_} =
+ {incomplete,ChompedList,_} =
unicode:characters_to_list(make_unaligned(MissingLastByte16),utf16),
ok.
-
+
roundtrips(Config) when is_list(Config) ->
setlimit(10),
ex_roundtrips(Config),
@@ -449,21 +449,21 @@ roundtrips(Config) when is_list(Config) ->
ex_roundtrips(Config).
ex_roundtrips(Config) when is_list(Config) ->
- ?line L1 = ranges(0, 16#D800 - 1,
- erlang:system_info(context_reductions) * 11),
- ?line L2 = ranges(16#DFFF + 1, 16#10000 - 1,
- erlang:system_info(context_reductions) * 11),
- ?line L3 = ranges(16#FFFFF, 16#10FFFF,
- erlang:system_info(context_reductions) * 11),
- ?line L = L1 ++ L2 ++ L3,
- ?line LLen = length(L),
- ?line Parts = erlang:system_info(schedulers),
- ?line Lists = splitup(L,LLen,Parts),
- ?line PidRefs = [spawn_monitor(fun() ->
- do_roundtrips(MyPart)
- end) || MyPart <- Lists],
- ?line [receive {'DOWN',Ref,process,Pid,Reason} -> normal=Reason end ||
- {Pid,Ref} <- PidRefs],
+ L1 = ranges(0, 16#D800 - 1,
+ erlang:system_info(context_reductions) * 11),
+ L2 = ranges(16#DFFF + 1, 16#10000 - 1,
+ erlang:system_info(context_reductions) * 11),
+ L3 = ranges(16#FFFFF, 16#10FFFF,
+ erlang:system_info(context_reductions) * 11),
+ L = L1 ++ L2 ++ L3,
+ LLen = length(L),
+ Parts = erlang:system_info(schedulers),
+ Lists = splitup(L,LLen,Parts),
+ PidRefs = [spawn_monitor(fun() ->
+ do_roundtrips(MyPart)
+ end) || MyPart <- Lists],
+ [receive {'DOWN',Ref,process,Pid,Reason} -> normal=Reason end ||
+ {Pid,Ref} <- PidRefs],
ok.
do_roundtrips([]) ->
@@ -527,10 +527,10 @@ ex_random_lists(Config) when is_list(Config) ->
PlainFlatten4 = fun(L) ->
iolist_to_binary([int_to_utf8(X) || X <- unicode:characters_to_list(flatb(L),latin1)])
end,
- ?line random_iolist:run(150, PlainFlatten1, PlainFlatten3),
- ?line random_iolist:run(150, PlainFlatten2, PlainFlatten3),
- ?line random_iolist:run(150, PlainFlatten1, PlainFlatten2),
- ?line random_iolist:run(150, PlainFlatten1, PlainFlatten4),
+ random_iolist:run(150, PlainFlatten1, PlainFlatten3),
+ random_iolist:run(150, PlainFlatten2, PlainFlatten3),
+ random_iolist:run(150, PlainFlatten1, PlainFlatten2),
+ random_iolist:run(150, PlainFlatten1, PlainFlatten4),
SelfMade = fun(L) ->
iolist_to_binary(lists:map(fun(X) ->
int_to_utf8(X)
@@ -546,52 +546,52 @@ ex_random_lists(Config) when is_list(Config) ->
Other
end
end,
- ?line random_iolist:run(150, PlainFlatten1, SelfMade),
- ?line random_iolist:run(150, PlainFlatten2, SelfMadeA),
+ random_iolist:run(150, PlainFlatten1, SelfMade),
+ random_iolist:run(150, PlainFlatten2, SelfMadeA),
RoundTrip11 = fun(L) ->
- unicode:characters_to_list(unicode:characters_to_binary(L,latin1),unicode)
- end,
+ unicode:characters_to_list(unicode:characters_to_binary(L,latin1),unicode)
+ end,
RoundTrip21 = fun(L) ->
- utf8_to_list_bsyntax(unicode:characters_to_binary(L,latin1))
- end,
+ utf8_to_list_bsyntax(unicode:characters_to_binary(L,latin1))
+ end,
RoundTrip31 = fun(L) ->
- unicode:characters_to_list(list_to_utf8_bsyntax(L,latin1),unicode)
- end,
+ unicode:characters_to_list(list_to_utf8_bsyntax(L,latin1),unicode)
+ end,
RoundTrip41 = fun(L) ->
- utf8_to_list_bsyntax(list_to_utf8_bsyntax(L,latin1))
- end,
+ utf8_to_list_bsyntax(list_to_utf8_bsyntax(L,latin1))
+ end,
RoundTrip51 = fun(L) ->
- unicode:characters_to_list(L,latin1)
- end,
- ?line random_iolist:run(150, RoundTrip11,RoundTrip21),
- ?line random_iolist:run(150, RoundTrip21,RoundTrip31),
- ?line random_iolist:run(150, RoundTrip31,RoundTrip41),
- ?line random_iolist:run(150, RoundTrip11,RoundTrip41),
- ?line random_iolist:run(150, RoundTrip21,RoundTrip41),
- ?line random_iolist:run(150, RoundTrip11,RoundTrip31),
- ?line random_iolist:run(150, RoundTrip11,RoundTrip51),
+ unicode:characters_to_list(L,latin1)
+ end,
+ random_iolist:run(150, RoundTrip11,RoundTrip21),
+ random_iolist:run(150, RoundTrip21,RoundTrip31),
+ random_iolist:run(150, RoundTrip31,RoundTrip41),
+ random_iolist:run(150, RoundTrip11,RoundTrip41),
+ random_iolist:run(150, RoundTrip21,RoundTrip41),
+ random_iolist:run(150, RoundTrip11,RoundTrip31),
+ random_iolist:run(150, RoundTrip11,RoundTrip51),
UniFlatten1 = fun(L) ->
unicode:characters_to_binary(flat(L),unicode)
end,
UniFlatten2 = fun(L) ->
- unicode:characters_to_binary(L,unicode)
+ unicode:characters_to_binary(L,unicode)
end,
UniFlatten3 = fun(L) ->
- unicode:characters_to_binary(flatx(L),unicode)
+ unicode:characters_to_binary(flatx(L),unicode)
end,
UniFlatten4 = fun(L) ->
- unicode:characters_to_binary(unicode:characters_to_list(L,unicode),unicode)
+ unicode:characters_to_binary(unicode:characters_to_list(L,unicode),unicode)
end,
- ?line random_unicode_list:run(150, UniFlatten1,UniFlatten2),
- ?line random_unicode_list:run(150, UniFlatten1,UniFlatten3),
- ?line random_unicode_list:run(150, UniFlatten2,UniFlatten4),
- ?line random_unicode_list:run(150, UniFlatten2,UniFlatten3),
+ random_unicode_list:run(150, UniFlatten1,UniFlatten2),
+ random_unicode_list:run(150, UniFlatten1,UniFlatten3),
+ random_unicode_list:run(150, UniFlatten2,UniFlatten4),
+ random_unicode_list:run(150, UniFlatten2,UniFlatten3),
- ?line Encodings = [utf8,{utf16,big},
- {utf16,little},{utf32,big},{utf32,little}],
+ Encodings = [utf8,{utf16,big},
+ {utf16,little},{utf32,big},{utf32,little}],
lists:foreach(fun(OutEnc1) ->
lists:foreach(fun(InEnc1) ->
Uni16BigFlatten1 = fun(L) ->
@@ -606,10 +606,10 @@ ex_random_lists(Config) when is_list(Config) ->
Uni16BigFlatten4 = fun(L) ->
unicode:characters_to_binary(unicode:characters_to_list(L,InEnc1),InEnc1,OutEnc1)
end,
- ?line random_unicode_list:run(150, Uni16BigFlatten1,Uni16BigFlatten2,InEnc1),
- ?line random_unicode_list:run(150, Uni16BigFlatten1,Uni16BigFlatten3,InEnc1),
- ?line random_unicode_list:run(150, Uni16BigFlatten2,Uni16BigFlatten4,InEnc1),
- ?line random_unicode_list:run(150, Uni16BigFlatten2,Uni16BigFlatten3,InEnc1)
+ random_unicode_list:run(150, Uni16BigFlatten1,Uni16BigFlatten2,InEnc1),
+ random_unicode_list:run(150, Uni16BigFlatten1,Uni16BigFlatten3,InEnc1),
+ random_unicode_list:run(150, Uni16BigFlatten2,Uni16BigFlatten4,InEnc1),
+ random_unicode_list:run(150, Uni16BigFlatten2,Uni16BigFlatten3,InEnc1)
end, Encodings)
end, Encodings),
SelfMade1 = fun(L) ->
@@ -621,10 +621,10 @@ ex_random_lists(Config) when is_list(Config) ->
SelfMade3 = fun(L) ->
list_to_utf8_bsyntax(L,unicode)
end,
- ?line random_unicode_list:run(150, SelfMade1,SelfMade2),
- ?line random_unicode_list:run(150, UniFlatten2, SelfMade1),
- ?line random_unicode_list:run(150, UniFlatten2, SelfMade2),
- ?line random_unicode_list:run(150, UniFlatten2, SelfMade3),
+ random_unicode_list:run(150, SelfMade1,SelfMade2),
+ random_unicode_list:run(150, UniFlatten2, SelfMade1),
+ random_unicode_list:run(150, UniFlatten2, SelfMade2),
+ random_unicode_list:run(150, UniFlatten2, SelfMade3),
RoundTrip1 = fun(L) ->
unicode:characters_to_list(unicode:characters_to_binary(L,unicode),unicode)
end,
@@ -637,12 +637,12 @@ ex_random_lists(Config) when is_list(Config) ->
RoundTrip4 = fun(L) ->
utf8_to_list_bsyntax(list_to_utf8_bsyntax(L,unicode))
end,
- ?line random_unicode_list:run(150, RoundTrip1,RoundTrip2),
- ?line random_unicode_list:run(150, RoundTrip2,RoundTrip3),
- ?line random_unicode_list:run(150, RoundTrip3,RoundTrip4),
- ?line random_unicode_list:run(150, RoundTrip1,RoundTrip4),
- ?line random_unicode_list:run(150, RoundTrip2,RoundTrip4),
- ?line random_unicode_list:run(150, RoundTrip1,RoundTrip3),
+ random_unicode_list:run(150, RoundTrip1,RoundTrip2),
+ random_unicode_list:run(150, RoundTrip2,RoundTrip3),
+ random_unicode_list:run(150, RoundTrip3,RoundTrip4),
+ random_unicode_list:run(150, RoundTrip1,RoundTrip4),
+ random_unicode_list:run(150, RoundTrip2,RoundTrip4),
+ random_unicode_list:run(150, RoundTrip1,RoundTrip3),
lists:foreach(fun(OutEnc2) ->
lists:foreach(fun(InEnc2) ->
RoundTripUtf16_Big_1 = fun(L) ->
@@ -657,12 +657,12 @@ ex_random_lists(Config) when is_list(Config) ->
RoundTripUtf16_Big_4 = fun(L) ->
x_to_list_bsyntax(InEnc2,list_to_x_bsyntax(InEnc2,L,InEnc2))
end,
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_2,InEnc2),
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_2,RoundTripUtf16_Big_3,InEnc2),
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_3,RoundTripUtf16_Big_4,InEnc2),
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_4,InEnc2),
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_2,RoundTripUtf16_Big_4,InEnc2),
- ?line random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_3,InEnc2)
+ random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_2,InEnc2),
+ random_unicode_list:run(150, RoundTripUtf16_Big_2,RoundTripUtf16_Big_3,InEnc2),
+ random_unicode_list:run(150, RoundTripUtf16_Big_3,RoundTripUtf16_Big_4,InEnc2),
+ random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_4,InEnc2),
+ random_unicode_list:run(150, RoundTripUtf16_Big_2,RoundTripUtf16_Big_4,InEnc2),
+ random_unicode_list:run(150, RoundTripUtf16_Big_1,RoundTripUtf16_Big_3,InEnc2)
end, Encodings)
end, Encodings),
ToList1 = fun(L) ->
@@ -677,12 +677,12 @@ ex_random_lists(Config) when is_list(Config) ->
ToList4 = fun(L) ->
utf8_to_list(unicode_mixed_to_utf8_2(L))
end,
- ?line random_unicode_list:run(150, ToList1,ToList2),
- ?line random_unicode_list:run(150, ToList2,ToList3),
- ?line random_unicode_list:run(150, ToList3,ToList4),
- ?line random_unicode_list:run(150, ToList1,ToList4),
- ?line random_unicode_list:run(150, ToList2,ToList4),
- ?line random_unicode_list:run(150, ToList1,ToList3),
+ random_unicode_list:run(150, ToList1,ToList2),
+ random_unicode_list:run(150, ToList2,ToList3),
+ random_unicode_list:run(150, ToList3,ToList4),
+ random_unicode_list:run(150, ToList1,ToList4),
+ random_unicode_list:run(150, ToList2,ToList4),
+ random_unicode_list:run(150, ToList1,ToList3),
ok.
@@ -693,13 +693,13 @@ utf16_illegal_sequences_bif(Config) when is_list(Config) ->
ex_utf16_illegal_sequences_bif(Config).
ex_utf16_illegal_sequences_bif(Config) when is_list(Config) ->
- ?line utf16_fail_range_bif_simple(16#10FFFF+1, 16#10FFFF+512), %Too large.
- ?line utf16_fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
+ utf16_fail_range_bif_simple(16#10FFFF+1, 16#10FFFF+512), %Too large.
+ utf16_fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
+
+ lonely_hi_surrogate_bif(16#D800, 16#DBFF,incomplete),
+ lonely_hi_surrogate_bif(16#DC00, 16#DFFF,error),
+ leading_lo_surrogate_bif(16#DC00, 16#DFFF),
- ?line lonely_hi_surrogate_bif(16#D800, 16#DBFF,incomplete),
- ?line lonely_hi_surrogate_bif(16#DC00, 16#DFFF,error),
- ?line leading_lo_surrogate_bif(16#DC00, 16#DFFF),
-
ok.
utf16_fail_range_bif(Char, End) when Char =< End ->
@@ -767,20 +767,20 @@ utf8_illegal_sequences_bif(Config) when is_list(Config) ->
ex_utf8_illegal_sequences_bif(Config).
ex_utf8_illegal_sequences_bif(Config) when is_list(Config) ->
- ?line fail_range_bif(16#10FFFF+1, 16#10FFFF+512), %Too large.
- ?line fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
+ fail_range_bif(16#10FFFF+1, 16#10FFFF+512), %Too large.
+ fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
%% Illegal first character.
- ?line [fail_bif(<<I,16#8F,16#8F,16#8F>>,unicode) || I <- lists:seq(16#80, 16#BF)],
+ [fail_bif(<<I,16#8F,16#8F,16#8F>>,unicode) || I <- lists:seq(16#80, 16#BF)],
%% Short sequences.
- ?line short_sequences_bif(16#80, 16#10FFFF),
+ short_sequences_bif(16#80, 16#10FFFF),
%% Overlong sequences. (Using more bytes than necessary
%% is not allowed.)
- ?line overlong_bif(0, 127, 2),
- ?line overlong_bif(128, 16#7FF, 3),
- ?line overlong_bif(16#800, 16#FFFF, 4),
+ overlong_bif(0, 127, 2),
+ overlong_bif(128, 16#7FF, 3),
+ overlong_bif(16#800, 16#FFFF, 4),
ok.
fail_range_bif(Char, End) when Char =< End ->
@@ -914,8 +914,8 @@ only_fail_bif_1(Bin,Coding) ->
Other ->
exit({faulty_encoding_accepted,[Bin],Coding,Other})
end.
-
-
+
+
fail_bif(Bin,Coding) ->
@@ -1017,9 +1017,9 @@ unicode_mixed_to_utf8_2(L) ->
int_to_utf8(E)
end || E <- Flist ],
iolist_to_binary([ExpList]).
-
-
-
+
+
+
utf8_to_list_bsyntax(<<>>) ->
[];
@@ -1038,8 +1038,8 @@ list_to_utf8_bsyntax(List,latin1) ->
FList = flatb(List),
list_to_binary([ <<E/utf8>> || E <- FList ]).
-
-
+
+
%%
@@ -1062,7 +1062,7 @@ int_to_utf16_little(U) when U >= 16#10000, U =< 16#10FFFF ->
LO = (16#DC00 bor (UPrim band 16#3FF)),
<<HI:16/little,LO:16/little>>.
-
+
%% This function intentionally allows construction of
%% UTF-8 sequence in illegal ranges.
int_to_utf8(I) when I =< 16#7F ->
@@ -1089,7 +1089,7 @@ int_to_utf8(I) when I =< 16#3FFFFFF ->
B2 = (I bsr 18),
B1 = (I bsr 24),
<<1:1,1:1,1:1,1:1,1:1,0:1,B1:2,1:1,0:1,B2:6,1:1,0:1,B3:6,1:1,0:1,B4:6,
- 1:1,0:1,B5:6>>.
+ 1:1,0:1,B5:6>>.
utf16_big_to_list_bsyntax(<<>>) ->
[];
@@ -1127,7 +1127,7 @@ list_to_utf16_little_bsyntax(List,latin1) ->
list_to_binary([ <<E/utf16-little>> || E <- FList ]).
-
+
utf32_big_to_list_bsyntax(<<>>) ->
[];
utf32_big_to_list_bsyntax(<<C/utf32-big,R/binary>>) ->
@@ -1158,12 +1158,12 @@ list_to_utf32_little_bsyntax(List,{utf32,little}) ->
E;
true ->
<<E/utf32-little>>
- end || E <- FList ]);
+ end || E <- FList ]);
list_to_utf32_little_bsyntax(List,latin1) ->
FList = flatb(List),
list_to_binary([ <<E/utf32-little>> || E <- FList ]).
-
+
%% int_to_utf8(I, NumberOfBytes) -> Binary.
%% This function can be used to construct overlong sequences.
@@ -1207,7 +1207,7 @@ utf8_to_int(<<1:1,1:1,0:1,B1:5,1:1,0:1,B2:6>>) ->
utf8_to_int(<<1:1,1:1,1:1,0:1,B1:4,1:1,0:1,B2:6,1:1,0:1,B3:6>>) ->
(B1 bsl 12) bor (B2 bsl 6) bor B3;
utf8_to_int(<<1:1,1:1,1:1,1:1,0:1,B1:3,1:1,0:1,
- B2:6,1:1,0:1,B3:6,1:1,0:1,B4:6>>) ->
+ B2:6,1:1,0:1,B3:6,1:1,0:1,B4:6>>) ->
Res = (B1 bsl 18) bor (B2 bsl 12) bor (B3 bsl 6) bor B4,
case Res of
X when X > 16#10FFFF ->
@@ -1291,7 +1291,7 @@ list_to_x_bsyntax({utf32,big},L,Enc) ->
list_to_utf32_big_bsyntax(L,Enc);
list_to_x_bsyntax({utf32,little},L,Enc) ->
list_to_utf32_little_bsyntax(L,Enc).
-
+
make_unaligned(Bin0) when is_binary(Bin0) ->
Bin1 = <<0:3,Bin0/binary,31:5>>,
diff --git a/lib/stdlib/test/win32reg_SUITE.erl b/lib/stdlib/test/win32reg_SUITE.erl
index a0edf706a8..62619dff47 100644
--- a/lib/stdlib/test/win32reg_SUITE.erl
+++ b/lib/stdlib/test/win32reg_SUITE.erl
@@ -94,9 +94,9 @@ evil_write(Config) when is_list(Config) ->
ok.
evil_write_1(Reg, [_|[_|_]=Key]=Key0) ->
- ?line io:format("Key = ~p\n", [Key0]),
- ?line ok = win32reg:set_value(Reg, Key0, "A good value for me"),
- ?line {ok,_Val} = win32reg:value(Reg, Key0),
- ?line ok = win32reg:delete_value(Reg, Key0),
+ io:format("Key = ~p\n", [Key0]),
+ ok = win32reg:set_value(Reg, Key0, "A good value for me"),
+ {ok,_Val} = win32reg:value(Reg, Key0),
+ ok = win32reg:delete_value(Reg, Key0),
evil_write_1(Reg, Key);
evil_write_1(_, [_]) -> ok.
diff --git a/lib/stdlib/test/y2k_SUITE.erl b/lib/stdlib/test/y2k_SUITE.erl
index fb95df9440..7828eb26ed 100644
--- a/lib/stdlib/test/y2k_SUITE.erl
+++ b/lib/stdlib/test/y2k_SUITE.erl
@@ -57,78 +57,78 @@ end_per_group(_GroupName, Config) ->
%% #1 : 1999-01-01: test roll-over from 1998-12-31 to 1999-01-01.
date_1999_01_01(Config) when is_list(Config) ->
- ?line Date = {1998, 12, 31}, NextDate = {1999, 1, 1},
- ?line match(next_date(Date), NextDate),
+ Date = {1998, 12, 31}, NextDate = {1999, 1, 1},
+ match(next_date(Date), NextDate),
TZD = tzd(Date),
if
TZD > 0 ->
- ?line Time = {24 - TZD, 0, 0},
- ?line {NDate, _NTime} =
+ Time = {24 - TZD, 0, 0},
+ {NDate, _NTime} =
erlang:localtime_to_universaltime({Date, Time}),
- ?line match(NDate, NextDate);
+ match(NDate, NextDate);
TZD < 0 ->
- ?line Time = {24 + TZD, 0, 0},
- ?line {NDate, _NTime} =
+ Time = {24 + TZD, 0, 0},
+ {NDate, _NTime} =
erlang:universaltime_to_localtime({Date, Time}),
- ?line match(NDate, NextDate);
+ match(NDate, NextDate);
true ->
ok
end.
-
+
%% #2 : 1999-02-28: test roll-over from 1999-02-28 to 1999-03-01.
date_1999_02_28(Config) when is_list(Config) ->
- ?line Date = {1999, 2, 28}, NextDate = {1999, 3, 1},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate).
+ Date = {1999, 2, 28}, NextDate = {1999, 3, 1},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate).
%% #3 : 1999-09-09: test roll-over from 1999-09-08 to 1999-09-09.
date_1999_09_09(Config) when is_list(Config) ->
- ?line Date = {1999, 9, 8}, NextDate = {1999, 9, 9},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate).
+ Date = {1999, 9, 8}, NextDate = {1999, 9, 9},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate).
%% #4 : 2000-01-01: test roll-over from 1999-12-31 to 2000-01-01 to
%% 2000-01-02.;
date_2000_01_01(Config) when is_list(Config) ->
- ?line Date = {1999, 12, 31}, NextDate = {2000, 1, 1},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate),
- ?line NextDate1 = {2000, 1, 2},
- ?line match(next_date(NextDate), NextDate1),
- ?line match(tz_next_date(NextDate), NextDate1).
+ Date = {1999, 12, 31}, NextDate = {2000, 1, 1},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate),
+ NextDate1 = {2000, 1, 2},
+ match(next_date(NextDate), NextDate1),
+ match(tz_next_date(NextDate), NextDate1).
%% #5 : 2000-02-29: test roll-over from 2000-02-28 to 2000-02-29 to
%% 2000-03-01.
date_2000_02_29(Config) when is_list(Config) ->
- ?line Date = {2000, 2, 28}, NextDate = {2000, 2, 29},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate),
- ?line NextDate1 = {2000, 3, 1},
- ?line match(next_date(NextDate), NextDate1),
- ?line match(tz_next_date(NextDate), NextDate1).
+ Date = {2000, 2, 28}, NextDate = {2000, 2, 29},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate),
+ NextDate1 = {2000, 3, 1},
+ match(next_date(NextDate), NextDate1),
+ match(tz_next_date(NextDate), NextDate1).
%% #6 : 2001-01-01: test roll-over from 2000-12-31 to 2001-01-01.
date_2001_01_01(Config) when is_list(Config) ->
- ?line Date = {2000, 12, 31}, NextDate = {2001, 1, 1},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate).
+ Date = {2000, 12, 31}, NextDate = {2001, 1, 1},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate).
%% #7 : 2001-02-29: test roll-over from 2001-02-28 to 2001-03-01.
date_2001_02_29(Config) when is_list(Config) ->
- ?line Date = {2001, 2, 28}, NextDate = {2001, 3, 1},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate).
+ Date = {2001, 2, 28}, NextDate = {2001, 3, 1},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate).
%% #8 : 2004-02-29: test roll-over from 2004-02-28 to 2004-02-29 to
%% 2004-03-01.
date_2004_02_29(Config) when is_list(Config) ->
- ?line Date = {2004, 2, 28}, NextDate = {2004, 2, 29},
- ?line match(next_date(Date), NextDate),
- ?line match(tz_next_date(Date), NextDate),
- ?line NextDate1 = {2004, 3, 1},
- ?line match(next_date(NextDate), NextDate1),
- ?line match(tz_next_date(NextDate), NextDate1).
-
+ Date = {2004, 2, 28}, NextDate = {2004, 2, 29},
+ match(next_date(Date), NextDate),
+ match(tz_next_date(Date), NextDate),
+ NextDate1 = {2004, 3, 1},
+ match(next_date(NextDate), NextDate1),
+ match(tz_next_date(NextDate), NextDate1).
+
%%
%% Local functions
%%
@@ -138,7 +138,7 @@ next_date(Date) ->
%% timezonediff
%%
tzd(Date) ->
- ?line {_LDate, {LH, _LM, _LS}} =
+ {_LDate, {LH, _LM, _LS}} =
erlang:universaltime_to_localtime({Date, {12, 0, 0}}),
12 - LH.
@@ -146,15 +146,15 @@ tz_next_date(Date) ->
TZD = tzd(Date),
if
TZD > 0 ->
- ?line Time = {24 - TZD, 0, 0},
- ?line {NDate, _NTime} =
+ Time = {24 - TZD, 0, 0},
+ {NDate, _NTime} =
erlang:localtime_to_universaltime({Date, Time}),
- ?line NDate;
+ NDate;
TZD < 0 ->
- ?line Time = {24 + TZD, 0, 0},
- ?line {NDate, _NTime} =
+ Time = {24 + TZD, 0, 0},
+ {NDate, _NTime} =
erlang:universaltime_to_localtime({Date, Time}),
- ?line NDate;
+ NDate;
true ->
Date
end.
@@ -165,6 +165,3 @@ tz_next_date(Date) ->
match(X, X) ->
ok.
-
-
-
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index c1da498f49..68bf8fa845 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -311,7 +311,7 @@ zip_api(Config) when is_list(Config) ->
%% Clean up.
delete_files([Names]),
- ok.
+ ok.
%% Test that zip doesn't leak processes and ports where the
%% controlling process dies without closing an zip opened with
@@ -362,19 +362,19 @@ unzip_options(Config) when is_list(Config) ->
FList = ["quotes/rain.txt","wikipedia.txt"],
%% Unzip a zip file in Subdir
- ?line {ok, RetList} = zip:unzip(Long, [{cwd, Subdir},
- {file_list, FList}]),
+ {ok, RetList} = zip:unzip(Long, [{cwd, Subdir},
+ {file_list, FList}]),
%% Verify.
- ?line true = (length(FList) =:= length(RetList)),
- ?line lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
- {ok,B} = file:read_file(filename:join(Subdir, F)) end,
- FList),
- ?line lists:foreach(fun(F)-> ok = file:delete(F) end,
- RetList),
+ true = (length(FList) =:= length(RetList)),
+ lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
+ {ok,B} = file:read_file(filename:join(Subdir, F)) end,
+ FList),
+ lists:foreach(fun(F)-> ok = file:delete(F) end,
+ RetList),
%% Clean up and verify no more files.
- ?line 0 = delete_files([Subdir]),
+ 0 = delete_files([Subdir]),
ok.
%% Test unzip a jar file (OTP-7382).
@@ -393,14 +393,14 @@ unzip_jar(Config) when is_list(Config) ->
{ok, RetList} = zip:unzip(JarFile),
%% Verify.
- ?line lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
- {ok,B} = file:read_file(filename:join(Subdir, F)) end,
- FList),
- ?line lists:foreach(fun(F)-> ok = file:delete(F) end,
- RetList),
+ lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
+ {ok,B} = file:read_file(filename:join(Subdir, F)) end,
+ FList),
+ lists:foreach(fun(F)-> ok = file:delete(F) end,
+ RetList),
%% Clean up and verify no more files.
- ?line 0 = delete_files([Subdir]),
+ 0 = delete_files([Subdir]),
ok.
%% Test the options for unzip, only cwd currently.
@@ -811,26 +811,26 @@ foldl(Config) ->
FooBin = <<"FOO">>,
BarBin = <<"BAR">>,
Files = [{"foo", FooBin}, {"bar", BarBin}],
- ?line {ok, {File, Bin}} = zip:create(File, Files, [memory]),
+ {ok, {File, Bin}} = zip:create(File, Files, [memory]),
ZipFun = fun(N, I, B, Acc) -> [{N, B(), I()} | Acc] end,
- ?line {ok, FileSpec} = zip:foldl(ZipFun, [], {File, Bin}),
- ?line [{"bar", BarBin, #file_info{}}, {"foo", FooBin, #file_info{}}] = FileSpec,
- ?line {ok, {File, Bin}} = zip:create(File, lists:reverse(FileSpec), [memory]),
- ?line {foo_bin, FooBin} =
+ {ok, FileSpec} = zip:foldl(ZipFun, [], {File, Bin}),
+ [{"bar", BarBin, #file_info{}}, {"foo", FooBin, #file_info{}}] = FileSpec,
+ {ok, {File, Bin}} = zip:create(File, lists:reverse(FileSpec), [memory]),
+ {foo_bin, FooBin} =
try
zip:foldl(fun("foo", _, B, _) -> throw(B()); (_, _, _, Acc) -> Acc end, [], {File, Bin})
catch
throw:FooBin ->
{foo_bin, FooBin}
end,
- ?line ok = file:write_file(File, Bin),
- ?line {ok, FileSpec} = zip:foldl(ZipFun, [], File),
+ ok = file:write_file(File, Bin),
+ {ok, FileSpec} = zip:foldl(ZipFun, [], File),
- ?line {error, einval} = zip:foldl(fun() -> ok end, [], File),
- ?line {error, einval} = zip:foldl(ZipFun, [], 42),
- ?line {error, einval} = zip:foldl(ZipFun, [], {File, 42}),
+ {error, einval} = zip:foldl(fun() -> ok end, [], File),
+ {error, einval} = zip:foldl(ZipFun, [], 42),
+ {error, einval} = zip:foldl(ZipFun, [], {File, 42}),
- ?line ok = file:delete(File),
- ?line {error, enoent} = zip:foldl(ZipFun, [], File),
+ ok = file:delete(File),
+ {error, enoent} = zip:foldl(ZipFun, [], File),
ok.