aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/base64_SUITE.erl14
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl9
-rw-r--r--lib/stdlib/test/dets_SUITE.erl72
-rw-r--r--lib/stdlib/test/dict_SUITE.erl20
-rw-r--r--lib/stdlib/test/dict_test_lib.erl55
-rw-r--r--lib/stdlib/test/digraph_SUITE.erl4
-rw-r--r--lib/stdlib/test/epp_SUITE.erl91
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl39
-rw-r--r--lib/stdlib/test/erl_expand_records_SUITE.erl16
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl65
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl111
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl214
-rw-r--r--lib/stdlib/test/escript_SUITE.erl42
-rw-r--r--lib/stdlib/test/escript_SUITE_data/emulator_flags_no_shebang10
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode114
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode214
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode313
-rw-r--r--lib/stdlib/test/ets_SUITE.erl76
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl57
-rw-r--r--lib/stdlib/test/filename_SUITE.erl248
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl17
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl11
-rw-r--r--lib/stdlib/test/id_transform_SUITE.erl15
-rw-r--r--lib/stdlib/test/io_SUITE.erl63
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl2
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl31
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl42
-rw-r--r--lib/stdlib/test/re_SUITE.erl27
-rw-r--r--lib/stdlib/test/re_testoutput1_replacement_test.erl55
-rw-r--r--lib/stdlib/test/re_testoutput1_split_test.erl81
-rw-r--r--lib/stdlib/test/sets_SUITE.erl342
-rw-r--r--lib/stdlib/test/sets_test_lib.erl82
-rw-r--r--lib/stdlib/test/shell_SUITE.erl218
-rw-r--r--lib/stdlib/test/stdlib.cover15
-rw-r--r--lib/stdlib/test/stdlib.spec.vxworks8
-rw-r--r--lib/stdlib/test/string_SUITE.erl7
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl39
-rw-r--r--lib/stdlib/test/supervisor_SUITE_data/Makefile.src15
-rw-r--r--lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app10
-rw-r--r--lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl17
-rw-r--r--lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl32
-rw-r--r--lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl17
-rw-r--r--lib/stdlib/test/sys_SUITE.erl88
-rw-r--r--lib/stdlib/test/timer_SUITE.erl8
44 files changed, 1498 insertions, 928 deletions
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index c64a961ffa..b28df94221 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -20,7 +21,6 @@
-module(base64_SUITE).
-include_lib("common_test/include/ct.hrl").
--include("test_server_line.hrl").
%% Test server specific exports
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
@@ -33,7 +33,7 @@
mime_decode_to_string/1, roundtrip/1]).
init_per_testcase(_, Config) ->
- Dog = test_server:timetrap(?t:minutes(2)),
+ Dog = test_server:timetrap(?t:minutes(4)),
NewConfig = lists:keydelete(watchdog, 1, Config),
[{watchdog, Dog} | NewConfig].
@@ -180,7 +180,7 @@ mime_decode(Config) when is_list(Config) ->
<<"o">> = base64:mime_decode(<<"b=w=====">>),
%% Test misc white space and illegals with embedded padding
<<"one">> = base64:mime_decode(<<" b~2=\r\n5()l===">>),
- <<"on">> = base64:mime_decode(<<"\tb =2\"�4=�= ==">>),
+ <<"on">> = base64:mime_decode(<<"\tb =2\"¤4=¤= ==">>),
<<"o">> = base64:mime_decode(<<"\nb=w=====">>),
%% Two pads
<<"Aladdin:open sesame">> =
@@ -189,7 +189,7 @@ mime_decode(Config) when is_list(Config) ->
<<"Hello World!!">> = base64:mime_decode(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
%% No pad
<<"Aladdin:open sesam">> =
- base64:mime_decode("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
+ base64:mime_decode("QWxhZGRpbjpvcG¤\")(VuIHNlc2Ft"),
%% Encoded base 64 strings may be divided by non base 64 chars.
%% In this cases whitespaces.
<<"0123456789!@#0^&*();:<>,. []{}">> =
@@ -223,7 +223,7 @@ mime_decode_to_string(Config) when is_list(Config) ->
"o" = base64:mime_decode_to_string(<<"b=w=====">>),
%% Test misc white space and illegals with embedded padding
"one" = base64:mime_decode_to_string(<<" b~2=\r\n5()l===">>),
- "on" = base64:mime_decode_to_string(<<"\tb =2\"�4=�= ==">>),
+ "on" = base64:mime_decode_to_string(<<"\tb =2\"¤4=¤= ==">>),
"o" = base64:mime_decode_to_string(<<"\nb=w=====">>),
%% Two pads
"Aladdin:open sesame" =
@@ -232,7 +232,7 @@ mime_decode_to_string(Config) when is_list(Config) ->
"Hello World!!" = base64:mime_decode_to_string(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
%% No pad
"Aladdin:open sesam" =
- base64:mime_decode_to_string("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
+ base64:mime_decode_to_string("QWxhZGRpbjpvcG¤\")(VuIHNlc2Ft"),
%% Encoded base 64 strings may be divided by non base 64 chars.
%% In this cases whitespaces.
"0123456789!@#0^&*();:<>,. []{}" =
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index bac59a3107..9b6f628aa9 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -1331,9 +1332,9 @@ one_random_number(N) ->
one_random(N) ->
M = ((N - 1) rem 68) + 1,
element(M,{$a,$b,$c,$d,$e,$f,$g,$h,$i,$j,$k,$l,$m,$n,$o,$p,$q,$r,$s,$t,
- $u,$v,$w,$x,$y,$z,$�,$�,$�,$A,$B,$C,$D,$E,$F,$G,$H,
- $I,$J,$K,$L,$M,$N,$O,$P,$Q,$R,$S,$T,$U,$V,$W,$X,$Y,$Z,$�,
- $�,$�,$0,$1,$2,$3,$4,$5,$6,$7,$8,$9}).
+ $u,$v,$w,$x,$y,$z,$å,$ä,$ö,$A,$B,$C,$D,$E,$F,$G,$H,
+ $I,$J,$K,$L,$M,$N,$O,$P,$Q,$R,$S,$T,$U,$V,$W,$X,$Y,$Z,$Å,
+ $Ä,$Ö,$0,$1,$2,$3,$4,$5,$6,$7,$8,$9}).
random_number({Min,Max}) -> % Min and Max are *length* of number in
% decimal positions
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 6f77cff2b9..66799f4d05 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -38,7 +38,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
- not_run/1, newly_started/1, basic_v8/1, basic_v9/1,
+ newly_started/1, basic_v8/1, basic_v9/1,
open_v8/1, open_v9/1, sets_v8/1, sets_v9/1, bags_v8/1,
bags_v9/1, duplicate_bags_v8/1, duplicate_bags_v9/1,
access_v8/1, access_v9/1, dirty_mark/1, dirty_mark2/1,
@@ -95,27 +95,25 @@ end_per_testcase(_Case, _Config) ->
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- case os:type() of
- vxworks -> [not_run];
- _ ->
- [basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9,
- bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9,
- newly_started, open_file_v8, open_file_v9,
- init_table_v8, init_table_v9, repair_v8, repair_v9,
- access_v8, access_v9, oldbugs_v8, oldbugs_v9,
- unsafe_assumptions, truncated_segment_array_v8,
- truncated_segment_array_v9, dirty_mark, dirty_mark2,
- bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8,
- fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9,
- select_v8, select_v9, update_counter, badarg,
- cache_sets_v8, cache_sets_v9, cache_bags_v8,
- cache_bags_v9, cache_duplicate_bags_v8,
- cache_duplicate_bags_v9, otp_4208, otp_4989,
- many_clients, otp_4906, otp_5402, simultaneous_open,
- insert_new, repair_continuation, otp_5487, otp_6206,
- otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898,
- otp_8899, otp_8903, otp_8923, otp_9282, otp_9607]
- end.
+ [
+ basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9,
+ bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9,
+ newly_started, open_file_v8, open_file_v9,
+ init_table_v8, init_table_v9, repair_v8, repair_v9,
+ access_v8, access_v9, oldbugs_v8, oldbugs_v9,
+ unsafe_assumptions, truncated_segment_array_v8,
+ truncated_segment_array_v9, dirty_mark, dirty_mark2,
+ bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8,
+ fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9,
+ select_v8, select_v9, update_counter, badarg,
+ cache_sets_v8, cache_sets_v9, cache_bags_v8,
+ cache_bags_v9, cache_duplicate_bags_v8,
+ cache_duplicate_bags_v9, otp_4208, otp_4989,
+ many_clients, otp_4906, otp_5402, simultaneous_open,
+ insert_new, repair_continuation, otp_5487, otp_6206,
+ otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898,
+ otp_8899, otp_8903, otp_8923, otp_9282, otp_9607
+ ].
groups() ->
[].
@@ -132,10 +130,6 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
-not_run(suite) -> [];
-not_run(Conf) when is_list(Conf) ->
- {comment, "Not runnable VxWorks/NFS"}.
-
newly_started(doc) ->
["OTP-3621"];
newly_started(suite) ->
@@ -1949,7 +1943,7 @@ match(Config, Version) ->
%% match, badarg
MSpec = [{'_',[],['$_']}],
?line check_badarg(catch dets:match(no_table, '_'),
- dets, safe_fixtable, [no_table,true]),
+ dets, match, [no_table,'_']),
?line check_badarg(catch dets:match(T, '_', not_a_number),
dets, match, [T,'_',not_a_number]),
?line {EC1, _} = dets:select(T, MSpec, 1),
@@ -1958,7 +1952,7 @@ match(Config, Version) ->
%% match_object, badarg
?line check_badarg(catch dets:match_object(no_table, '_'),
- dets, safe_fixtable, [no_table,true]),
+ dets, match_object, [no_table,'_']),
?line check_badarg(catch dets:match_object(T, '_', not_a_number),
dets, match_object, [T,'_',not_a_number]),
?line {EC2, _} = dets:select(T, MSpec, 1),
@@ -2127,7 +2121,7 @@ select(Config, Version) ->
%% badarg
MSpec = [{'_',[],['$_']}],
?line check_badarg(catch dets:select(no_table, MSpec),
- dets, safe_fixtable, [no_table,true]),
+ dets, select, [no_table,MSpec]),
?line check_badarg(catch dets:select(T, <<17>>),
dets, select, [T,<<17>>]),
?line check_badarg(catch dets:select(T, []),
@@ -2330,7 +2324,7 @@ badarg(Config) when is_list(Config) ->
%% match_delete
?line check_badarg(catch dets:match_delete(no_table, '_'),
- dets, safe_fixtable, [no_table,true]),
+ dets, match_delete, [no_table,'_']),
%% delete_all_objects
?line check_badarg(catch dets:delete_all_objects(no_table),
@@ -2339,17 +2333,19 @@ badarg(Config) when is_list(Config) ->
%% select_delete
MSpec = [{'_',[],['$_']}],
?line check_badarg(catch dets:select_delete(no_table, MSpec),
- dets, safe_fixtable, [no_table,true]),
+ dets, select_delete, [no_table,MSpec]),
?line check_badarg(catch dets:select_delete(T, <<17>>),
dets, select_delete, [T, <<17>>]),
%% traverse, fold
- ?line check_badarg(catch dets:traverse(no_table, fun(_) -> continue end),
- dets, safe_fixtable, [no_table,true]),
- ?line check_badarg(catch dets:foldl(fun(_, A) -> A end, [], no_table),
- dets, safe_fixtable, [no_table,true]),
- ?line check_badarg(catch dets:foldr(fun(_, A) -> A end, [], no_table),
- dets, safe_fixtable, [no_table,true]),
+ TF = fun(_) -> continue end,
+ ?line check_badarg(catch dets:traverse(no_table, TF),
+ dets, traverse, [no_table,TF]),
+ FF = fun(_, A) -> A end,
+ ?line check_badarg(catch dets:foldl(FF, [], no_table),
+ dets, foldl, [FF,[],no_table]),
+ ?line check_badarg(catch dets:foldr(FF, [], no_table),
+ dets, foldl, [FF,[],no_table]),
%% close
?line ok = dets:close(T),
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index c46fc47b34..df9c769c67 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -53,7 +53,7 @@ end_per_group(_GroupName, Config) ->
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?t:minutes(5)),
+ Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -65,22 +65,22 @@ create(Config) when is_list(Config) ->
test_all(fun create_1/1).
create_1(M) ->
- ?line D0 = M:empty(),
- ?line [] = M:to_list(D0),
- ?line 0 = M:size(D0),
+ D0 = M(empty, []),
+ [] = M(to_list, D0),
+ 0 = M(size, D0),
D0.
store(Config) when is_list(Config) ->
test_all([{0,132},{253,258},{510,514}], fun store_1/2).
store_1(List, M) ->
- ?line D0 = M:from_list(List),
+ D0 = M(from_list, List),
%% Make sure that we get the same result by inserting
%% elements one at the time.
- ?line D1 = foldl(fun({K,V}, Dict) -> M:enter(K, V, Dict) end,
- M:empty(), List),
- ?line true = M:equal(D0, D1),
+ D1 = foldl(fun({K,V}, Dict) -> M(enter, {K,V,Dict}) end,
+ M(empty, []), List),
+ true = M(equal, {D0,D1}),
D0.
%%%
@@ -98,7 +98,7 @@ dict_mods() ->
[Orddict,Dict,Gb].
test_all(Tester) ->
- ?line Pids = [spawn_tester(M, Tester) || M <- dict_mods()],
+ Pids = [spawn_tester(M, Tester) || M <- dict_mods()],
collect_all(Pids, []).
spawn_tester(M, Tester) ->
@@ -106,7 +106,7 @@ spawn_tester(M, Tester) ->
spawn_link(fun() ->
random:seed(1, 2, 42),
S = Tester(M),
- Res = {M:size(S),lists:sort(M:to_list(S))},
+ Res = {M(size, S),lists:sort(M(to_list, S))},
Parent ! {result,self(),Res}
end).
diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl
index 92a75dad89..7167014310 100644
--- a/lib/stdlib/test/dict_test_lib.erl
+++ b/lib/stdlib/test/dict_test_lib.erl
@@ -17,67 +17,48 @@
%% %CopyrightEnd%
%%
--module(dict_test_lib, [Mod,Equal]).
+-module(dict_test_lib).
--export([module/0,equal/2,empty/0,size/1,to_list/1,from_list/1,
- enter/3,delete/2,lookup/2]).
+-export([new/2]).
-module() ->
- Mod.
-
-equal(X, Y) ->
- Equal(X, Y).
+new(Mod, Eq) ->
+ fun (enter, {K,V,D}) -> enter(Mod, K, V, D);
+ (empty, []) -> empty(Mod);
+ (equal, {D1,D2}) -> Eq(D1, D2);
+ (from_list, L) -> from_list(Mod, L);
+ (module, []) -> Mod;
+ (size, D) -> Mod:size(D);
+ (to_list, D) -> to_list(Mod, D)
+ end.
-empty() ->
+empty(Mod) ->
case erlang:function_exported(Mod, new, 0) of
false -> Mod:empty();
true -> Mod:new()
end.
-size(S) ->
- Mod:size(S).
-
-to_list(S) ->
- Mod:to_list(S).
+to_list(Mod, D) ->
+ Mod:to_list(D).
-from_list(S) ->
+from_list(Mod, L) ->
case erlang:function_exported(Mod, from_orddict, 1) of
false ->
- Mod:from_list(S);
+ Mod:from_list(L);
true ->
%% The gb_trees module has no from_list/1 function.
%%
%% The keys in S are not unique. To make sure
%% that we pick the same key/value pairs as
%% dict/orddict, first convert the list to an orddict.
- Orddict = orddict:from_list(S),
+ Orddict = orddict:from_list(L),
Mod:from_orddict(Orddict)
end.
%% Store new value into dictionary or update previous value in dictionary.
-enter(Key, Val, Dict) ->
+enter(Mod, Key, Val, Dict) ->
case erlang:function_exported(Mod, store, 3) of
false ->
Mod:enter(Key, Val, Dict);
true ->
Mod:store(Key, Val, Dict)
end.
-
-%% Delete an EXISTING key.
-delete(Key, Dict) ->
- case erlang:function_exported(Mod, delete, 2) of
- true -> Mod:delete(Key, Dict);
- false -> Mod:erase(Key, Dict)
- end.
-
-%% -> none | {value,Value}
-lookup(Key, Dict) ->
- case erlang:function_exported(Mod, lookup, 2) of
- false ->
- case Mod:find(Key, Dict) of
- error -> none;
- {ok,Value} -> {value,Value}
- end;
- true ->
- Mod:lookup(Key, Dict)
- end.
diff --git a/lib/stdlib/test/digraph_SUITE.erl b/lib/stdlib/test/digraph_SUITE.erl
index 1d1326d60e..ed01b32a59 100644
--- a/lib/stdlib/test/digraph_SUITE.erl
+++ b/lib/stdlib/test/digraph_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -400,7 +400,7 @@ sane1(G) ->
lists:foreach(
fun(V) ->
InEs = digraph:in_edges(G, V),
- %% Nu har man *alla* inkanter f�r V
+ %% *All* in-edoges of V
lists:foreach(
fun(E) ->
case digraph:edge(G, E) of
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index f79414db49..606bbbcbb2 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -25,7 +25,7 @@
variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
- otp_8562/1, otp_8665/1, otp_8911/1]).
+ otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1]).
-export([epp_parse_erl_form/2]).
@@ -67,7 +67,7 @@ all() ->
{group, variable}, otp_4870, otp_4871, otp_5362, pmod,
not_circular, skip_header, otp_6277, otp_7702, otp_8130,
overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
- otp_8665, otp_8911].
+ otp_8665, otp_8911, otp_10302].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -582,12 +582,13 @@ otp_8130(suite) ->
otp_8130(Config) when is_list(Config) ->
true = os:putenv("epp_inc1", "stdlib"),
Ts = [{otp_8130_1,
- %% The scanner handles UNICODE in a special way. Hopefully
- %% temporarily.
<<"-define(M(A), ??A). "
"t() -> "
- " \"{ 34 , [ $1 , 2730 ] , \\\"34\\\" , X . a , 2730 }\" = "
- " ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}), ok. ">>,
+ " L = \"{ 34 , \\\"1\\\\x{AAA}\\\" , \\\"34\\\" , X . a , $\\\\x{AAA} }\", "
+ " R = ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}),"
+ " Lt = erl_scan:string(L, 1, [unicode]),"
+ " Rt = erl_scan:string(R, 1, [unicode]),"
+ " Lt = Rt, ok. ">>,
ok},
{otp_8130_2,
@@ -1236,6 +1237,13 @@ otp_8911(doc) ->
otp_8911(suite) ->
[];
otp_8911(Config) when is_list(Config) ->
+ case test_server:is_cover() of
+ true ->
+ {skip, "Testing cover, so can not run when cover is already running"};
+ false ->
+ do_otp_8911(Config)
+ end.
+do_otp_8911(Config) ->
?line {ok, CWD} = file:get_cwd(),
?line ok = file:set_cwd(?config(priv_dir, Config)),
@@ -1277,6 +1285,75 @@ otp_8665(Config) when is_list(Config) ->
?line [] = compile(Config, Cs),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) ->
+ [];
+otp_10302(Config) when is_list(Config) ->
+ %% Two messages (one too many). Keeps otp_4871 happy.
+ Cs = [{otp_8562,
+ <<"%% coding: utf-8\n \n \x{E4}">>,
+ {errors,[{3,epp,cannot_parse},
+ {3,file_io_server,invalid_unicode}],[]}}
+ ],
+ [] = compile(Config, Cs),
+ Dir = ?config(priv_dir, Config),
+ File = filename:join(Dir, "otp_10302.erl"),
+ utf8 = encoding("coding: utf-8", File),
+ utf8 = encoding("coding: UTF-8", File),
+ latin1 = encoding("coding: Latin-1", File),
+ latin1 = encoding("coding: latin-1", File),
+ none = encoding_com("coding: utf-8", File),
+ none = encoding_com("\n\n%% coding: utf-8", File),
+ none = encoding_nocom("\n\n coding: utf-8", File),
+ utf8 = encoding_com("\n%% coding: utf-8", File),
+ utf8 = encoding_nocom("\n coding: utf-8", File),
+ none = encoding("coding: \nutf-8", File),
+ latin1 = encoding("Encoding : latin-1", File),
+ utf8 = encoding("ccoding: UTF-8", File),
+ utf8 = encoding("coding= utf-8", File),
+ utf8 = encoding_com(" %% coding= utf-8", File),
+ utf8 = encoding("coding = utf-8", File),
+ none = encoding("coding: utf-16 coding: utf-8", File), %first is bad
+ none = encoding("Coding: utf-8", File), %capital c
+ utf8 = encoding("-*- coding: utf-8 -*-", File),
+ utf8 = encoding("-*-coding= utf-8-*-", File),
+ utf8 = encoding("codingcoding= utf-8", File),
+ ok = prefix("coding: utf-8", File, utf8),
+
+ "coding: latin-1" = epp:encoding_to_string(latin1),
+ "coding: utf-8" = epp:encoding_to_string(utf8),
+ true = lists:member(epp:default_encoding(), [latin1, utf8]),
+
+ ok.
+
+prefix(S, File, Enc) ->
+ prefix(0, S, File, Enc).
+
+prefix(100, _S, _File, _) ->
+ ok;
+prefix(N, S, File, Enc) ->
+ Enc = encoding(lists:duplicate(N, $\s) ++ S, File),
+ prefix(N+1, S, File, Enc).
+
+encoding(Enc, File) ->
+ E = encoding_com("%% " ++ Enc, File),
+ none = encoding_com(Enc, File),
+ E = encoding_nocom(Enc, File).
+
+encoding_com(Enc, File) ->
+ ok = file:write_file(File, Enc),
+ {ok, Fd} = file:open(File, [read]),
+ E = epp:set_encoding(Fd),
+ ok = file:close(Fd),
+ E = epp:read_encoding(File).
+
+encoding_nocom(Enc, File) ->
+ ok = file:write_file(File, Enc),
+ {ok, Fd} = file:open(File, [read]),
+ ok = file:close(Fd),
+ epp:read_encoding(File, [{in_comment_only, false}]).
+
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index b0c7d562d5..47792d1052 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -216,13 +216,13 @@ guard_4(doc) ->
guard_4(suite) ->
[];
guard_4(Config) when is_list(Config) ->
- ?line check(fun() -> if {erlang,'+'}(3,a) -> true ; true -> false end end,
- "if {erlang,'+'}(3,a) -> true ; true -> false end.",
- false),
- ?line check(fun() -> if {erlang,is_integer}(3) -> true ; true -> false end
- end,
- "if {erlang,is_integer}(3) -> true ; true -> false end.",
- true),
+ check(fun() -> if erlang:'+'(3,a) -> true ; true -> false end end,
+ "if erlang:'+'(3,a) -> true ; true -> false end.",
+ false),
+ check(fun() -> if erlang:is_integer(3) -> true ; true -> false end
+ 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]),
@@ -230,11 +230,11 @@ guard_4(Config) when is_list(Config) ->
end,
"if is_atom(is_integer(a)) -> true ; true -> false end.",
true),
- ?line 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),
+ 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),
@@ -1077,11 +1077,6 @@ do_funs(LFH, EFH) ->
concat(["begin F1 = fun(F,N) -> apply(", M,
",count_down,[F, N]) end, F1(F1,1000) end."]),
0, ['F1'], LFH, EFH),
- ?line 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() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);
(_F,0) -> ok end,
F(F, 1000)
@@ -1113,11 +1108,11 @@ do_funs(LFH, EFH) ->
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),
- ?line check(fun() -> F = fun(X) -> {erlang,'+'}(X,2) end,
- true = 3 == F(1) end,
- "begin F = fun(X) -> {erlang,'+'}(X,2) end,"
- " true = 3 == F(1) end.", true, ['F'],
- LFH, EFH),
+ check(fun() -> F = fun(X) -> erlang:'+'(X,2) end,
+ true = 3 == F(1) end,
+ "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,
?MODULE:do_apply(F,<<"hej">>) end,
concat(["begin F = fun(X) -> size(X) end,",
diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl
index 01cdb92d7b..e51c05a22c 100644
--- a/lib/stdlib/test/erl_expand_records_SUITE.erl
+++ b/lib/stdlib/test/erl_expand_records_SUITE.erl
@@ -107,8 +107,7 @@ attributes(doc) ->
attributes(suite) -> [];
attributes(Config) when is_list(Config) ->
Ts = [
- <<"-import(erl_expand_records_SUITE).
- -import(lists, [append/2, reverse/1]).
+ <<"-import(lists, [append/2, reverse/1]).
-record(r, {a,b}).
@@ -157,13 +156,13 @@ expr(Config) when is_list(Config) ->
One = 1 = fun f/1(1),
2 = fun(X) -> X end(One + One),
3 = fun exprec_test:f/1(3),
- 4 = {exprec_test,f}(4),
- 5 = ''.f(5),
+ 4 = exprec_test:f(4),
+ 5 = f(5),
L = receive
{a,message,L0} ->
L0
end,
- case catch a.b.c:foo(bar) of
+ case catch a:foo(bar) of
{'EXIT', _} -> ok
end,
_ = receive %Suppress warning.
@@ -263,8 +262,7 @@ pattern(doc) ->
pattern(suite) -> [];
pattern(Config) when is_list(Config) ->
Ts = [
- <<"-import(erl_expand_records_SUITE).
- -import(lists, [append/2, reverse/1]).
+ <<"-import(lists, [append/2, reverse/1]).
-record(r, {a,b}).
@@ -292,10 +290,10 @@ pattern(Config) when is_list(Config) ->
21 = t(#r{a = #r{}}),
22 = t(2),
23 = t(#r{a = #r{}, b = b}),
- 24 = t(a.b.c),
+ 24 = t(abc),
ok.
- t(a.b.c) ->
+ t(abc) ->
24;
t($a) ->
2;
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 9f9d97b619..774229fca9 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -50,7 +50,8 @@
unsafe_vars_try/1,
guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
- otp_5917/1, otp_6585/1, otp_6885/1, export_all/1,
+ otp_5917/1, otp_6585/1, otp_6885/1, otp_10436/1,
+ export_all/1,
bif_clash/1,
behaviour_basic/1, behaviour_multiple/1,
otp_7550/1,
@@ -80,7 +81,7 @@ all() ->
unsafe_vars, unsafe_vars2, unsafe_vars_try, guard,
otp_4886, otp_4988, otp_5091, otp_5276, otp_5338,
otp_5362, otp_5371, otp_7227, otp_5494, otp_5644,
- otp_5878, otp_5917, otp_6585, otp_6885, export_all,
+ otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, export_all,
bif_clash, behaviour_basic, behaviour_multiple,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments].
@@ -1307,44 +1308,30 @@ guard(Config) when is_list(Config) ->
foo;
t3(A) when erlang:is_record(A, {apa}) ->
foo;
- t3(A) when {erlang,is_record}(A, {apa}) ->
- foo;
t3(A) when is_record(A, {apa}, 1) ->
foo;
t3(A) when erlang:is_record(A, {apa}, 1) ->
foo;
- t3(A) when {erlang,is_record}(A, {apa}, 1) ->
- foo;
t3(A) when is_record(A, apa, []) ->
foo;
t3(A) when erlang:is_record(A, apa, []) ->
foo;
- t3(A) when {erlang,is_record}(A, apa, []) ->
- foo;
t3(A) when record(A, apa) ->
foo;
t3(A) when is_record(A, apa) ->
foo;
t3(A) when erlang:is_record(A, apa) ->
- foo;
- t3(A) when {erlang,is_record}(A, apa) ->
foo.
">>,
[warn_unused_vars, nowarn_obsolete_guard],
- {error,[{2,erl_lint,illegal_guard_expr},
- {4,erl_lint,illegal_guard_expr},
- {6,erl_lint,illegal_guard_expr},
- {8,erl_lint,illegal_guard_expr},
- {10,erl_lint,illegal_guard_expr},
- {12,erl_lint,illegal_guard_expr},
- {14,erl_lint,illegal_guard_expr},
- {16,erl_lint,illegal_guard_expr},
- {18,erl_lint,illegal_guard_expr},
- {20,erl_lint,illegal_guard_expr}],
- [{8,erl_lint,deprecated_tuple_fun},
- {14,erl_lint,deprecated_tuple_fun},
- {20,erl_lint,deprecated_tuple_fun},
- {28,erl_lint,deprecated_tuple_fun}]}},
+ {errors,[{2,erl_lint,illegal_guard_expr},
+ {4,erl_lint,illegal_guard_expr},
+ {6,erl_lint,illegal_guard_expr},
+ {8,erl_lint,illegal_guard_expr},
+ {10,erl_lint,illegal_guard_expr},
+ {12,erl_lint,illegal_guard_expr},
+ {14,erl_lint,illegal_guard_expr}],
+ []}},
{guard6,
<<"-record(apa,{a=a,b=foo:bar()}).
apa() ->
@@ -1745,7 +1732,7 @@ otp_5362(Config) when is_list(Config) ->
{otp_5362_2,
<<"-export([inline/0]).
- -import(lists.foo, [a/1,b/1]). % b/1 is not used
+ -import(lists, [a/1,b/1]). % b/1 is not used
-compile([{inline,{inl,7}}]). % undefined
-compile([{inline,[{inl,17}]}]). % undefined
@@ -1777,7 +1764,7 @@ otp_5362(Config) when is_list(Config) ->
{6,erl_lint,{bad_inline,{inl,17}}},
{11,erl_lint,{undefined_function,{fipp,0}}},
{22,erl_lint,{bad_nowarn_unused_function,{and_not_used,2}}}],
- [{3,erl_lint,{unused_import,{{b,1},'lists.foo'}}},
+ [{3,erl_lint,{unused_import,{{b,1},lists}}},
{9,erl_lint,{unused_function,{foop,0}}},
{19,erl_lint,{unused_function,{not_used,0}}},
{23,erl_lint,{unused_function,{and_not_used,1}}}]}},
@@ -2400,6 +2387,28 @@ otp_6885(Config) when is_list(Config) ->
[]} = run_test2(Config, Ts, []),
ok.
+otp_10436(doc) ->
+ "OTP-6885. Warnings for opaque types.";
+otp_10436(suite) -> [];
+otp_10436(Config) when is_list(Config) ->
+ Ts = <<"-module(otp_10436).
+ -export_type([t1/0]).
+ -opaque t1() :: {i, integer()}.
+ -opaque t2() :: {a, atom()}.
+ ">>,
+ {warnings,[{4,erl_lint,{not_exported_opaque,{t2,0}}},
+ {4,erl_lint,{unused_type,{t2,0}}}]} =
+ run_test2(Config, Ts, []),
+ Ts2 = <<"-module(otp_10436_2).
+ -export_type([t1/0, t2/0]).
+ -opaque t1() :: term().
+ -opaque t2() :: any().
+ ">>,
+ {warnings,[{3,erl_lint,{underspecified_opaque,{t1,0}}},
+ {4,erl_lint,{underspecified_opaque,{t2,0}}}]} =
+ run_test2(Config, Ts2, []),
+ ok.
+
export_all(doc) ->
"OTP-7392. Warning for export_all.";
export_all(Config) when is_list(Config) ->
@@ -2848,10 +2857,10 @@ otp_8051(doc) ->
otp_8051(Config) when is_list(Config) ->
Ts = [{otp_8051,
<<"-opaque foo() :: bar().
+ -export_type([foo/0]).
">>,
[],
- {error,[{1,erl_lint,{undefined_type,{bar,0}}}],
- [{1,erl_lint,{unused_type,{foo,0}}}]}}],
+ {errors,[{1,erl_lint,{undefined_type,{bar,0}}}],[]}}],
?line [] = run(Config, Ts),
ok.
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 64853ca078..db416b03b0 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -40,7 +40,7 @@
init_per_testcase/2, end_per_testcase/2]).
-export([ func/1, call/1, recs/1, try_catch/1, if_then/1,
- receive_after/1, bits/1, head_tail/1, package/1,
+ receive_after/1, bits/1, head_tail/1,
cond1/1, block/1, case1/1, ops/1, messages/1,
old_mnemosyne_syntax/1,
import_export/1, misc_attrs/1,
@@ -48,7 +48,8 @@
neg_indent/1,
otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
- otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1]).
+ otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
+ otp_10302/1]).
%% Internal export.
-export([ehook/6]).
@@ -74,12 +75,12 @@ all() ->
groups() ->
[{expr, [],
[func, call, recs, try_catch, if_then, receive_after,
- bits, head_tail, package, cond1, block, case1, ops,
+ bits, head_tail, cond1, block, case1, ops,
messages, old_mnemosyne_syntax]},
{attributes, [], [misc_attrs, import_export]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
- otp_8473, otp_8522, otp_8567, otp_8664, otp_9147]}].
+ otp_8473, otp_8522, otp_8567, otp_8664, otp_9147, otp_10302]}].
init_per_suite(Config) ->
Config.
@@ -438,9 +439,6 @@ bits(Config) when is_list(Config) ->
?line ok = pp_expr(<<"<<{a,b}/binary>>">>),
?line ok = pp_expr(<<"<<{foo:bar(),b}/binary>>">>),
?line ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>),
- ?line ok = pp_expr(<<"<<(foo.bar)/binary>>">>),
- ?line ok = pp_expr(<<"<<(foo.bar):all/binary>>">>),
- ?line ok = pp_expr(<<"<<(foo.bar):(foo.bar)/binary>>">>),
ok.
head_tail(suite) ->
@@ -462,17 +460,6 @@ head_tail(Config) when is_list(Config) ->
?line compile(Config, Ts),
ok.
-package(suite) ->
- [];
-package(Config) when is_list(Config) ->
- Ts = [{package_1,
- <<"t() -> a.b:foo().">>},
- {package_2,
- <<"t() -> .lists:sort([]).">>}
- ],
- ?line compile(Config, Ts),
- ok.
-
cond1(suite) ->
[];
cond1(Config) when is_list(Config) ->
@@ -614,13 +601,11 @@ misc_attrs(suite) ->
[];
misc_attrs(Config) when is_list(Config) ->
?line ok = pp_forms(<<"-module(m). ">>),
- ?line ok = pp_forms(<<"-module(m.p, [A,B]). ">>),
?line ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk,"
"Blsjfdlslfjsdf]). ">>),
?line ok = pp_forms(<<"-export([]). ">>),
?line ok = pp_forms(<<"-export([foo/2, bar/0]). ">>),
?line ok = pp_forms(<<"-export([bar/0]). ">>),
- ?line ok = pp_forms(<<"-import(.lists). ">>),
?line ok = pp_forms(<<"-import(lists, []). ">>),
?line ok = pp_forms(<<"-import(lists, [map/2]). ">>),
?line ok = pp_forms(<<"-import(lists, [map/2, foreach/2]). ">>),
@@ -634,8 +619,12 @@ misc_attrs(Config) when is_list(Config) ->
hook(suite) ->
[];
hook(Config) when is_list(Config) ->
+ F = fun(H) -> H end,
+ do_hook(F).
+
+do_hook(HookFun) ->
Lc = parse_expr(binary_to_list(<<"[X || X <- [1,2,3]].">>)),
- H = fun hook/4,
+ H = HookFun(fun hook/4),
Expr = {call,0,{atom,0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]},
EChars = lists:flatten(erl_pp:expr(Expr, 0, H)),
Call = {call,0,{atom,0,foo},[Lc]},
@@ -692,7 +681,7 @@ hook(Config) when is_list(Config) ->
GChars2 = erl_pp:guard(G2),
?line true = GChars =:= lists:flatten(GChars2),
- EH = {?MODULE, ehook, [foo,bar]},
+ EH = HookFun({?MODULE, ehook, [foo,bar]}),
XEChars = erl_pp:expr(Expr, -1, EH),
?line true = remove_indentation(EChars) =:= lists:flatten(XEChars),
XEChars2 = erl_pp:expr(Expr, EH),
@@ -1068,6 +1057,43 @@ otp_9147(Config) when is_list(Config) ->
string:tokens(binary_to_list(Bin), "\n")),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) -> [];
+otp_10302(Config) when is_list(Config) ->
+ Ts = [{uni_1,
+ <<"t() -> <<(<<\"abc\\x{aaa}\">>):3/binary>>.">>}
+ ],
+ compile(Config, Ts),
+ ok = pp_expr(<<"$\\x{aaa}">>),
+ ok = pp_expr(<<"\"1\\x{aaa}\"">>),
+ ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>),
+ ok = pp_expr(<<"<< <<\"1\\x{aaa}\">>/binary>>">>),
+
+ U = [{encoding,unicode}],
+
+ do_hook(fun(H) -> [{hook,H}] end),
+ do_hook(fun(H) -> [{hook,H}]++U end),
+
+ ok = pp_expr(<<"$\\x{aaa}">>, [{hook,fun hook/4}]),
+
+ Opts = [{hook, fun unicode_hook/4},{encoding,unicode}],
+ Lc = parse_expr("[X || X <- [\"\x{400}\",\"\xFF\"]]."),
+ Expr = {call,0,{atom,0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]},
+ EChars = lists:flatten(erl_pp:expr(Expr, 0, Opts)),
+ Call = {call,0,{atom,0,foo},[{call,0,{atom,0,foo},[Lc]}]},
+ Expr2 = {call,0,{atom,0,fff},[Call,Call]},
+ EChars2 = erl_pp:exprs([Expr2], U),
+ EChars = lists:flatten(EChars2),
+ [$\x{400},$\x{400}] = [C || C <- EChars, C > 255],
+
+ ok = pp_forms(<<"function() -> {\"\x{400}\",$\x{400}}. "/utf8>>, U),
+ ok = pp_forms("function() -> {\"\x{400}\",$\x{400}}. ", []),
+ ok.
+
+unicode_hook({foo,E}, I, P, H) ->
+ erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H).
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
@@ -1137,9 +1163,11 @@ flat_expr(Expr) ->
pp_forms(Bin) ->
pp_forms(Bin, none).
-pp_forms(Bin, Hook) ->
- PP1 = (catch parse_and_pp_forms(binary_to_list(Bin), Hook)),
- PP2 = (catch parse_and_pp_forms(PP1, Hook)),
+pp_forms(Bin, Options) when is_binary(Bin) ->
+ pp_forms(to_list(Bin, Options), Options);
+pp_forms(List, Options) when is_list(List) ->
+ PP1 = (catch parse_and_pp_forms(List, Options)),
+ PP2 = (catch parse_and_pp_forms(PP1, Options)),
case PP1 =:= PP2 of % same line numbers
true ->
test_max_line(PP1);
@@ -1147,8 +1175,8 @@ pp_forms(Bin, Hook) ->
not_ok
end.
-parse_and_pp_forms(String, Hook) ->
- lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Hook)
+parse_and_pp_forms(String, Options) ->
+ lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Options)
end, parse_forms(String))).
parse_forms(Chars) ->
@@ -1158,7 +1186,7 @@ parse_forms(Chars) ->
parse_forms2([], _Cont, _Line, Forms) ->
lists:reverse(Forms);
parse_forms2(String, Cont0, Line, Forms) ->
- case erl_scan:tokens(Cont0, String, Line) of
+ case erl_scan:tokens(Cont0, String, Line, [unicode]) of
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
@@ -1174,10 +1202,12 @@ pp_expr(Bin) ->
pp_expr(Bin, none).
%% Final dot is added.
-pp_expr(Bin, Hook) ->
- PP1 = (catch parse_and_pp_expr(binary_to_list(Bin), 0, Hook)),
- PPneg = (catch parse_and_pp_expr(binary_to_list(Bin), -1, Hook)),
- PP2 = (catch parse_and_pp_expr(PPneg, 0, Hook)),
+pp_expr(Bin, Options) when is_binary(Bin) ->
+ pp_expr(to_list(Bin, Options), Options);
+pp_expr(List, Options) when is_list(List) ->
+ PP1 = (catch parse_and_pp_expr(List, 0, Options)),
+ PPneg = (catch parse_and_pp_expr(List, -1, Options)),
+ PP2 = (catch parse_and_pp_expr(PPneg, 0, Options)),
if
PP1 =:= PP2 -> % same line numbers
case
@@ -1192,15 +1222,24 @@ pp_expr(Bin, Hook) ->
not_ok
end.
-parse_and_pp_expr(String, Indent, Hook) ->
+parse_and_pp_expr(String, Indent, Options) ->
StringDot = lists:flatten(String) ++ ".",
- erl_pp:expr(parse_expr(StringDot), Indent, Hook).
+ erl_pp:expr(parse_expr(StringDot), Indent, Options).
parse_expr(Chars) ->
- {ok, Tokens, _} = erl_scan:string(Chars),
+ {ok, Tokens, _} = erl_scan:string(Chars, 1, [unicode]),
{ok, [Expr]} = erl_parse:parse_exprs(Tokens),
Expr.
+to_list(Bin, Options) when is_list(Options) ->
+ case proplists:get_value(encoding, Options) of
+ unicode -> unicode:characters_to_list(Bin);
+ encoding -> binary_to_list(Bin);
+ undefined -> binary_to_list(Bin)
+ end;
+to_list(Bin, _Hook) ->
+ binary_to_list(Bin).
+
test_new_line(String) ->
case string:chr(String, $\n) of
0 -> ok;
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 4298b2c701..34e1b99abe 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -20,7 +21,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2]).
--export([ error_1/1, error_2/1, iso88591/1, otp_7810/1]).
+-export([ error_1/1, error_2/1, iso88591/1, otp_7810/1, otp_10302/1]).
-import(lists, [nth/2,flatten/1]).
-import(io_lib, [print/1]).
@@ -59,7 +60,7 @@ end_per_testcase(_Case, Config) ->
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [{group, error}, iso88591, otp_7810].
+ [{group, error}, iso88591, otp_7810, otp_10302].
groups() ->
[{error, [], [error_1, error_2]}].
@@ -131,10 +132,10 @@ 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],
+ V1s = [$Á,$á,$é,$ë],
+ V2s = [$N,$ä,$r],
+ A1s = [$h,$ä,$r],
+ A2s = [$ö,$r,$e],
%% Test parsing atom and variable characters.
{ok,Ts1,_} = erl_scan:string(V1s ++ " " ++ V2s ++
"\327" ++
@@ -214,8 +215,8 @@ atoms() ->
?line test_string("'a b'", [{atom,1,'a b'}]),
?line test_string("a", [{atom,1,a}]),
?line test_string("a@2", [{atom,1,a@2}]),
- ?line test_string([39,65,200,39], [{atom,1,'A�'}]),
- ?line test_string("�rlig �sten", [{atom,1,�rlig},{atom,1,�sten}]),
+ ?line test_string([39,65,200,39], [{atom,1,'AÈ'}]),
+ ?line test_string("ärlig östen", [{atom,1,ärlig},{atom,1,östen}]),
?line {ok,[{atom,_,'$a'}],{1,6}} =
erl_scan:string("'$\\a'", {1,1}),
?line test("'$\\a'"),
@@ -289,7 +290,7 @@ errors() ->
?line {error,{1,erl_scan,{string,$","str"}},1} = %"
erl_scan:string("\"str"), %"
?line {error,{1,erl_scan,char},1} = erl_scan:string("$"),
- ?line test_string([34,65,200,34], [{string,1,"A�"}]),
+ ?line test_string([34,65,200,34], [{string,1,"AÈ"}]),
?line test_string("\\", [{'\\',1}]),
?line {'EXIT',_} =
(catch {foo, erl_scan:string('$\\a', {1,1})}), % type error
@@ -354,7 +355,7 @@ dots() ->
{".\n", {ok,[{dot,1}],2}},
{".%", {ok,[{dot,1}],1}},
{".\210",{ok,[{dot,1}],1}},
- {".% �h",{ok,[{dot,1}],1}},
+ {".% öh",{ok,[{dot,1}],1}},
{".%\n", {ok,[{dot,1}],2}},
{".$", {error,{1,erl_scan,char},1}},
{".$\\", {error,{1,erl_scan,char},1}},
@@ -369,7 +370,7 @@ dots() ->
?line [{column,1},{length,1},{line,1},{text,"."}] =
erl_scan:token_info(T2, [column, length, line, text]),
?line {ok,[{dot,_}=T3],{1,6}} =
- erl_scan:string(".% �h", {1,1}, text),
+ erl_scan:string(".% öh", {1,1}, text),
?line [{column,1},{length,1},{line,1},{text,"."}] =
erl_scan:token_info(T3, [column, length, line, text]),
?line {error,{{1,2},erl_scan,char},{1,3}} =
@@ -472,11 +473,11 @@ chars() ->
variables() ->
- ?line test_string(" \237_Aou�eiy��", [{var,1,'_Aou�eiy��'}]),
+ ?line test_string(" \237_Aouåeiyäö", [{var,1,'_Aouåeiyäö'}]),
?line test_string("A_b_c@", [{var,1,'A_b_c@'}]),
?line test_string("V@2", [{var,1,'V@2'}]),
- ?line test_string("ABD�", [{var,1,'ABD�'}]),
- ?line test_string("�rlig �sten", [{var,1,'�rlig'},{var,1,'�sten'}]),
+ ?line test_string("ABDÀ", [{var,1,'ABDÀ'}]),
+ ?line test_string("Ärlig Östen", [{var,1,'Ärlig'},{var,1,'Östen'}]),
ok.
eof() ->
@@ -823,7 +824,7 @@ unicode() ->
?line {ok,[{char,1,1}],1} = erl_scan:string([$$,$\\,$^,1089]),
?line {error,{1,erl_scan,Error},1} = erl_scan:string("\"qa\x{aaa}"),
- ?line "unterminated string starting with \"qa\\x{AAA}\"" =
+ ?line "unterminated string starting with \"qa"++[2730]++"\"" =
erl_scan:format_error(Error),
?line {error,{{1,1},erl_scan,_},{1,11}} =
erl_scan:string("\"qa\\x{aaa}",{1,1}),
@@ -887,9 +888,10 @@ unicode() ->
{char,_,$d},{']',_}],{1,8}} = erl_scan:string(Str1, {1,1}),
?line test(Str1),
Comment = "%% "++[1089],
- ?line {ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
+ %% Returned a comment In R15B03:
+ {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string(Comment, 1, return),
- ?line {ok,[{comment,_,[$%,$%,$\s,1089]}],{1,5}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
erl_scan:string(Comment, {1,1}, return),
ok.
@@ -958,6 +960,182 @@ more_chars() ->
erl_scan:string("$\\xg", {1,1}),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) ->
+ [];
+otp_10302(Config) when is_list(Config) ->
+ %% From unicode():
+ {error,{1,erl_scan,{illegal,atom}},1} =
+ erl_scan:string("'a"++[1089]++"b'", 1, unicode),
+ {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
+ erl_scan:string("'qa\\x{aaa}'",{1,1},unicode),
+
+ {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1, unicode),
+ {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1,unicode),
+
+ Qs = "$\\x{aaa}",
+ {ok,[{char,1,2730}],1} = erl_scan:string(Qs,1,unicode),
+ {ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[unicode,text]),
+ [{category,char},{column,1},{length,8},
+ {line,1},{symbol,16#aaa},{text,Qs}] =
+ erl_scan:token_info(Q2),
+
+ Tags = [category, column, length, line, symbol, text],
+
+ U1 = "\"\\x{aaa}\"",
+ {ok,[T1],{1,10}} = erl_scan:string(U1, {1,1}, [unicode,text]),
+ [{category,string},{column,1},{length,9},{line,1},
+ {symbol,[16#aaa]},{text,U1}] = erl_scan:token_info(T1, Tags),
+
+ U2 = "\"\\x41\\x{fff}\\x42\"",
+ {ok,[{string,1,[65,4095,66]}],1} = erl_scan:string(U2, 1, unicode),
+
+ U3 = "\"a\n\\x{fff}\n\"",
+ {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1,unicode),
+
+ U4 = "\"\\^\n\\x{aaa}\\^\n\"",
+ {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[unicode]),
+
+ Str1 = "\"ab" ++ [1089] ++ "cd\"",
+ {ok,[{string,1,[97,98,1089,99,100]}],1} =
+ erl_scan:string(Str1,1,unicode),
+ {ok,[{string,{1,1},[97,98,1089,99,100]}],{1,8}} =
+ erl_scan:string(Str1, {1,1},unicode),
+
+ OK1 = 16#D800-1,
+ OK2 = 16#DFFF+1,
+ OK3 = 16#FFFE-1,
+ OK4 = 16#FFFF+1,
+ OKL = [OK1,OK2,OK3,OK4],
+
+ Illegal1 = 16#D800,
+ Illegal2 = 16#DFFF,
+ Illegal3 = 16#FFFE,
+ Illegal4 = 16#FFFF,
+ IllegalL = [Illegal1,Illegal2,Illegal3,Illegal4],
+
+ [{ok,[{comment,1,[$%,$%,$\s,OK]}],1} =
+ erl_scan:string("%% "++[OK], 1, [unicode,return]) ||
+ OK <- OKL],
+ {ok,[{comment,_,[$%,$%,$\s,OK1]}],{1,5}} =
+ erl_scan:string("%% "++[OK1], {1,1}, [unicode,return]),
+ [{error,{1,erl_scan,{illegal,character}},1} =
+ erl_scan:string("%% "++[Illegal], 1, [unicode,return]) ||
+ Illegal <- IllegalL],
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
+ erl_scan:string("%% "++[Illegal1], {1,1}, [unicode,return]),
+
+ [{ok,[],1} = erl_scan:string("%% "++[OK], 1, [unicode]) ||
+ OK <- OKL],
+ {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, [unicode]),
+ [{error,{1,erl_scan,{illegal,character}},1} =
+ erl_scan:string("%% "++[Illegal], 1, [unicode]) ||
+ Illegal <- IllegalL],
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
+ erl_scan:string("%% "++[Illegal1], {1,1}, [unicode]),
+
+ [{ok,[{string,{1,1},[OK]}],{1,4}} =
+ erl_scan:string("\""++[OK]++"\"",{1,1},unicode) ||
+ OK <- OKL],
+ [{error,{{1,2},erl_scan,{illegal,character}},{1,3}} =
+ erl_scan:string("\""++[OK]++"\"",{1,1},unicode) ||
+ OK <- IllegalL],
+
+ [{error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ erl_scan:string([Illegal],{1,1},unicode) ||
+ Illegal <- IllegalL],
+
+ {ok,[{char,{1,1},OK1}],{1,3}} =
+ erl_scan:string([$$,OK1],{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ erl_scan:string([$$,Illegal1],{1,1},unicode),
+
+ {ok,[{char,{1,1},OK1}],{1,4}} =
+ erl_scan:string([$$,$\\,OK1],{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
+ erl_scan:string([$$,$\\,Illegal1],{1,1},unicode),
+
+ {ok,[{string,{1,1},[55295]}],{1,5}} =
+ erl_scan:string("\"\\"++[OK1]++"\"",{1,1},unicode),
+ {error,{{1,2},erl_scan,{illegal,character}},{1,4}} =
+ erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1},unicode),
+
+ {ok,[{char,{1,1},OK1}],{1,10}} =
+ erl_scan:string("$\\x{D7FF}",{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,10}} =
+ erl_scan:string("$\\x{D800}",{1,1},unicode),
+
+ %% Not erl_scan, but erl_parse.
+ {integer,0,1} = erl_parse:abstract(1),
+ Float = 3.14, {float,0,Float} = erl_parse:abstract(Float),
+ {nil,0} = erl_parse:abstract([]),
+ {bin,0,
+ [{bin_element,0,{integer,0,1},default,default},
+ {bin_element,0,{integer,0,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>),
+ {cons,0,{tuple,0,[{atom,0,a}]},{atom,0,b}} =
+ erl_parse:abstract([{a} | b]),
+ {string,0,"str"} = erl_parse:abstract("str"),
+ {cons,0,
+ {integer,0,$a},
+ {cons,0,{integer,0,1024},{string,0,"c"}}} =
+ erl_parse:abstract("a"++[1024]++"c"),
+
+ Line = 17,
+ {integer,Line,1} = erl_parse:abstract(1, Line),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Line),
+ {nil,Line} = erl_parse:abstract([], Line),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Line),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Line),
+ {string,Line,"str"} = erl_parse:abstract("str", Line),
+ {cons,Line,
+ {integer,Line,$a},
+ {cons,Line,{integer,Line,1024},{string,Line,"c"}}} =
+ erl_parse:abstract("a"++[1024]++"c", Line),
+
+ Opts1 = [{line,17}],
+ {integer,Line,1} = erl_parse:abstract(1, Opts1),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts1),
+ {nil,Line} = erl_parse:abstract([], Opts1),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Opts1),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Opts1),
+ {string,Line,"str"} = erl_parse:abstract("str", Opts1),
+ {cons,Line,
+ {integer,Line,$a},
+ {cons,Line,{integer,Line,1024},{string,Line,"c"}}} =
+ erl_parse:abstract("a"++[1024]++"c", Opts1),
+
+ [begin
+ {integer,Line,1} = erl_parse:abstract(1, Opts2),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts2),
+ {nil,Line} = erl_parse:abstract([], Opts2),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Opts2),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Opts2),
+ {string,Line,"str"} = erl_parse:abstract("str", Opts2),
+ {string,Line,[97,1024,99]} =
+ erl_parse:abstract("a"++[1024]++"c", Opts2)
+ end || Opts2 <- [[{encoding,unicode},{line,Line}],
+ [{encoding,utf8},{line,Line}]]],
+
+ {cons,0,
+ {integer,0,97},
+ {cons,0,{integer,0,1024},{string,0,"c"}}} =
+ erl_parse:abstract("a"++[1024]++"c", [{encoding,latin1}]),
+ ok.
+
test_string(String, Expected) ->
{ok, Expected, _End} = erl_scan:string(String),
test(String).
diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl
index 38c085616d..3749d594f2 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -26,6 +26,7 @@
errors/1,
strange_name/1,
emulator_flags/1,
+ emulator_flags_no_shebang/1,
module_script/1,
beam_script/1,
archive_script/1,
@@ -34,7 +35,8 @@
create_and_extract/1,
foldl/1,
overflow/1,
- verify_sections/3
+ verify_sections/3,
+ unicode/1
]).
-include_lib("test_server/include/test_server.hrl").
@@ -44,9 +46,10 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[basic, errors, strange_name, emulator_flags,
+ emulator_flags_no_shebang,
module_script, beam_script, archive_script, epp,
create_and_extract, foldl, overflow,
- archive_script_file_access].
+ archive_script_file_access, unicode].
groups() ->
[].
@@ -64,7 +67,7 @@ end_per_group(_GroupName, Config) ->
Config.
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?t:minutes(2)),
+ ?line Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -149,6 +152,21 @@ emulator_flags(Config) when is_list(Config) ->
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+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">>]),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Pick the source code from the emulator_flags script
%% Generate a new escript with a module header
@@ -618,7 +636,7 @@ compile_files([File | Files], SrcDir, OutDir) ->
case filename:extension(File) of
".erl" ->
AbsFile = filename:join([SrcDir, File]),
- case compile:file(AbsFile, [{outdir, OutDir}]) of
+ case compile:file(AbsFile, [{outdir, OutDir},report_errors]) of
{ok, _Mod} ->
compile_files(Files, SrcDir, OutDir);
Error ->
@@ -810,6 +828,8 @@ normalize_sections(Sections) ->
end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+
foldl(Config) when is_list(Config) ->
{NewFile, _FileInfo,
_EmuArg, _Source,
@@ -887,6 +907,20 @@ emulate_escript_foldl(Fun, Acc, File) ->
{error, Reason}
end.
+unicode(Config) when is_list(Config) ->
+ Data = ?config(data_dir, Config),
+ Dir = filename:absname(Data), %Get rid of trailing slash.
+ run(Dir, "unicode1",
+ [<<"escript: exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n "
+ "called as <<170>> / <<170>>\nExitCode:127">>]),
+ run(Dir, "unicode2",
+ [<<"escript: exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n "
+ "called as <<\"\xaa\">> / <<\"\xaa\">>\nExitCode:127">>]),
+ run(Dir, "unicode3", [<<"ExitCode:0">>]),
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
overflow(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/escript_SUITE_data/emulator_flags_no_shebang b/lib/stdlib/test/escript_SUITE_data/emulator_flags_no_shebang
new file mode 100644
index 0000000000..47d843ebe1
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/emulator_flags_no_shebang
@@ -0,0 +1,10 @@
+%% -*- erlang -*-
+%%! -nostick -mnesia dir a/directory -mnesia debug verbose
+
+main(MainArgs) ->
+ io:format("main:~p\n",[MainArgs]),
+ ErlArgs = init:get_arguments(),
+ io:format("nostick:~p\n",[[E || E <- ErlArgs, element(1, E) =:= nostick]]),
+ io:format("mnesia:~p\n", [[E || E <- ErlArgs, element(1, E) =:= mnesia]]),
+ io:format("ERL_FLAGS=~p\n", [os:getenv("ERL_FLAGS")]),
+ io:format("unknown:~p\n",[[E || E <- ErlArgs, element(1, E) =:= unknown]]).
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode1 b/lib/stdlib/test/escript_SUITE_data/unicode1
new file mode 100755
index 0000000000..a77574625e
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode1
@@ -0,0 +1,14 @@
+#!/usr/bin/env escript
+%% -*- erlang -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,unicode}]),
+ _D = erlang:system_flag(backtrace_depth, 0),
+ A = <<"\x{aa}">>,
+ S = lists:flatten(io_lib:format("~p/~p.", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode2 b/lib/stdlib/test/escript_SUITE_data/unicode2
new file mode 100755
index 0000000000..495188f6f0
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode2
@@ -0,0 +1,14 @@
+#!/usr/bin/env escript
+%% -*- erlang -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,latin1}]),
+ _D = erlang:system_flag(backtrace_depth, 0),
+ A = <<"\x{aa}">>,
+ S = lists:flatten(io_lib:format("~p/~p.", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode3 b/lib/stdlib/test/escript_SUITE_data/unicode3
new file mode 100755
index 0000000000..944487dcae
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode3
@@ -0,0 +1,13 @@
+#!/usr/bin/env escript
+%% -*- erlang; coding: utf-8 -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,unicode}]),
+ Bin1 = <<"örn_Ѐ שלום-שלום+של 日本語">>,
+
+ L = [246,114,110,95,1024,32,1513,1500,1493,1501,45,1513,1500,1493,
+ 1501,43,1513,1500,32,26085,26412,35486],
+ L = unicode:characters_to_list(Bin1, utf8),
+ ok.
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 95f10b1df3..dc17e5d33c 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -2170,20 +2170,29 @@ heir_do(Opts) ->
?line undefined = ets:info(foo),
%% When heir dies and pid reused before founder dies
- NextPidIx = erts_debug:get_internal_state(next_pid),
- {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(),
- erts_debug:set_internal_state(next_pid, NextPidIx),
- {Heir4,MrefH4_B} = spawn_monitor_with_pid(Heir4,
- fun()-> ?line die_please = receive_any() end),
- Founder4 ! die_please,
- ?line {'DOWN', MrefF4, process, Founder4, normal} = receive_any(),
- Heir4 ! die_please,
- ?line {'DOWN', MrefH4_B, process, Heir4, normal} = receive_any(),
- ?line undefined = ets:info(foo),
-
+ repeat_while(fun() ->
+ NextPidIx = erts_debug:get_internal_state(next_pid),
+ {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(),
+ erts_debug:set_internal_state(next_pid, NextPidIx),
+ DoppelGanger = spawn_monitor_with_pid(Heir4,
+ fun()-> ?line die_please = receive_any() end),
+ Founder4 ! die_please,
+ ?line {'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),
+ false;
+ failed ->
+ io:format("Failed to spawn process with pid ~p\n", [Heir4]),
+ true % try again
+ end
+ end),
+
?line verify_etsmem(EtsMem).
heir_founder(Master, HeirData, Opts) ->
@@ -4208,21 +4217,13 @@ heavy_lookup_element(Config) when is_list(Config) ->
repeat_for_opts(heavy_lookup_element_do).
heavy_lookup_element_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
- ?line ok = fill_tab2(Tab, 0, 7000),
- case os:type() of
- vxworks ->
- ?line ?t:do_times(5, ?MODULE, do_lookup_element,
- [Tab, 6999, 1]);
- % lookup ALL elements 5 times.
- _ ->
- ?line ?t:do_times(50, ?MODULE, do_lookup_element,
- [Tab, 6999, 1])
- % lookup ALL elements 50 times.
- end,
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ EtsMem = etsmem(),
+ Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
+ ok = fill_tab2(Tab, 0, 7000),
+ % lookup ALL elements 50 times
+ ?t:do_times(50, ?MODULE, do_lookup_element, [Tab, 6999, 1]),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
do_lookup_element(_Tab, 0, _) -> ok;
do_lookup_element(Tab, N, M) ->
@@ -5795,25 +5796,20 @@ receive_any_spinning(Loops, N, Tries) when N>0 ->
spawn_monitor_with_pid(Pid, Fun) when is_pid(Pid) ->
- spawn_monitor_with_pid(Pid, Fun, 1, 10).
+ spawn_monitor_with_pid(Pid, Fun, 10).
-spawn_monitor_with_pid(Pid, Fun, N, M) when N > M*10 ->
- spawn_monitor_with_pid(Pid, Fun, N, M*10);
-spawn_monitor_with_pid(Pid, Fun, N, M) ->
- ?line false = is_process_alive(Pid),
+spawn_monitor_with_pid(_, _, 0) ->
+ failed;
+spawn_monitor_with_pid(Pid, Fun, N) ->
case my_spawn(fun()-> case self() of
Pid -> Fun();
_ -> die
end
end) of
- Pid ->
+ Pid ->
{Pid, erlang:monitor(process, Pid)};
Other ->
- case N rem M of
- 0 -> io:format("Failed ~p times to get pid ~p (current = ~p)\n",[N,Pid,Other]);
- _ -> ok
- end,
- spawn_monitor_with_pid(Pid,Fun,N+1,M)
+ spawn_monitor_with_pid(Pid,Fun,N-1)
end.
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 1de639a166..1fd7518519 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -176,9 +176,64 @@ do_wildcard_5(Dir, Wcf) ->
%% Cleanup
?line del(Files),
- ?line foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs).
+ ?line foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs),
+ do_wildcard_6(Dir, Wcf).
+
+do_wildcard_6(Dir, Wcf) ->
+ ok = file:make_dir(filename:join(Dir, "xbin")),
+ All = ["xbin/a.x","xbin/b.x","xbin/c.x"],
+ Files = mkfiles(All, Dir),
+ All = Wcf("xbin/*.x"),
+ All = Wcf("xbin/*"),
+ ["xbin"] = Wcf("*"),
+ All = Wcf("*/*"),
+ del(Files),
+ ok = file:del_dir(filename:join(Dir, "xbin")),
+ do_wildcard_7(Dir, Wcf).
+
+do_wildcard_7(Dir, Wcf) ->
+ Dirs = ["blurf","xa","yyy"],
+ SubDirs = ["blurf/nisse"],
+ foreach(fun(D) ->
+ ok = file:make_dir(filename:join(Dir, D))
+ end, Dirs ++ SubDirs),
+ All = ["blurf/nisse/baz","xa/arne","xa/kalle","yyy/arne"],
+ Files = mkfiles(lists:reverse(All), Dir),
+ %% Test.
+ Listing = Wcf("**"),
+ ["blurf","blurf/nisse","blurf/nisse/baz",
+ "xa","xa/arne","xa/kalle","yyy","yyy/arne"] = Listing,
+ Listing = Wcf("**/*"),
+ ["xa/arne","yyy/arne"] = Wcf("**/arne"),
+ ["blurf/nisse"] = Wcf("**/nisse"),
+ [] = Wcf("mountain/**"),
+
+ %% Cleanup
+ del(Files),
+ foreach(fun(D) ->
+ ok = file:del_dir(filename:join(Dir, D))
+ end, SubDirs ++ Dirs),
+ do_wildcard_8(Dir, Wcf).
+
+do_wildcard_8(Dir, Wcf) ->
+ Dirs0 = ["blurf"],
+ Dirs1 = ["blurf/nisse"],
+ Dirs2 = ["blurf/nisse/a", "blurf/nisse/b"],
+ foreach(fun(D) ->
+ ok = file:make_dir(filename:join(Dir, D))
+ end, Dirs0 ++ Dirs1 ++ Dirs2),
+ All = ["blurf/nisse/a/1.txt", "blurf/nisse/b/2.txt", "blurf/nisse/b/3.txt"],
+ Files = mkfiles(lists:reverse(All), Dir),
+ %% Test.
+ All = Wcf("**/blurf/**/*.txt"),
+
+ %% Cleanup
+ del(Files),
+ foreach(fun(D) ->
+ ok = file:del_dir(filename:join(Dir, D))
+ end, Dirs2 ++ Dirs1 ++ Dirs0).
fold_files(Config) when is_list(Config) ->
?line Dir = filename:join(?config(priv_dir, Config), "fold_files"),
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index 8817f5a55b..232df6a13f 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -112,19 +112,6 @@ absname(Config) when is_list(Config) ->
?line "/erlang/src" = filename:absname(["/erl",'a','ng',"/",'s',"rc"]),
?line "/erlang/src" = filename:absname("/erlang///src"),
?line "/file_sorter.erl" = filename:absname([file_sorter|'.erl']),
- ok;
- vxworks ->
- Test_dir = ?config(priv_dir, Config),
- Test1 = Test_dir ++ "/foo",
- Test2 = Test_dir ++ "/ebin",
- ?line ok = file:set_cwd(Test_dir),
- ?line Test1 = filename:absname(foo),
- ?line Test1= filename:absname("foo"),
- ?line Test2 = filename:absname("foo/../ebin"),
- ?line "/erlang" = filename:absname("/erlang"),
- ?line "/erlang/src" = filename:absname("/erlang/src"),
- ?line "/erlang/src" = filename:absname(["/erlan",'g/s',"rc"]),
- ?line "/erlang/src" = filename:absname("/erlang///src"),
ok
end.
@@ -179,15 +166,6 @@ absname_2(Config) when is_list(Config) ->
?line "/erlang" = filename:absname("/erlang", "/"),
?line "/erlang/src" = filename:absname("/erlang/src", "/"),
?line "/erlang/src" = filename:absname("/erlang///src", "/"),
- ok;
- vxworks ->
- ?line "/usr/foo" = filename:absname(foo, "/usr"),
- ?line "/usr/foo" = filename:absname("foo", "/usr"),
- ?line "/usr/ebin" = filename:absname("../ebin", "/usr"),
- ?line "/usr/ebin" = filename:absname("../ebin", "/usr/src"),
- ?line "/erlang" = filename:absname("/erlang", "/usr"),
- ?line "/erlang/src" = filename:absname("/erlang/src", "/usr"),
- ?line "/erlang/src" = filename:absname("/erlang///src", "/usr"),
ok
end.
@@ -213,11 +191,7 @@ basename_1(Config) when is_list(Config) ->
?line "foo" = filename:basename("A:foo");
{unix, _} ->
?line "strange\\but\\true" =
- filename:basename("strange\\but\\true");
- vxworks ->
- ?line "foo" = filename:basename(["usr\\foo\\"]),
- ?line "foo" = filename:basename("elrond:usr\\foo\\"),
- ?line "foo" = filename:basename("disk:/foo")
+ filename:basename("strange\\but\\true")
end,
?line test_server:timetrap_cancel(Dog),
ok.
@@ -249,15 +223,7 @@ basename_2(Config) when is_list(Config) ->
?line "strange\\but\\true" =
filename:basename("strange\\but\\true.erl", ".erl"),
?line "strange\\but\\true" =
- filename:basename("strange\\but\\true", ".erl");
- vxworks ->
- ?line "foo" = filename:basename("net:foo", ".erl"),
- ?line "foo.erl" = filename:basename("net:\\usr\\foo.erl",
- ".hrl"),
- ?line "foo.erl" =
- filename:basename("/disk0:\\usr.hrl\\foo.erl",
- ".hrl"),
- ?line "foo" = filename:basename("/home\\usr\\foo", ".hrl")
+ filename:basename("strange\\but\\true", ".erl")
end,
?line test_server:timetrap_cancel(Dog),
ok.
@@ -267,37 +233,25 @@ basename_2(Config) when is_list(Config) ->
dirname(Config) when is_list(Config) ->
case os:type() of
{win32,_} ->
- ?line "A:/usr" = filename:dirname("A:/usr/foo.erl"),
- ?line "A:usr" = filename:dirname("A:usr/foo.erl"),
- ?line "/usr" = filename:dirname("\\usr\\foo.erl"),
- ?line "/" = filename:dirname("\\usr"),
- ?line "A:" = filename:dirname("A:");
- vxworks ->
- ?line "net:/usr" = filename:dirname("net:/usr/foo.erl"),
- ?line "/disk0:/usr" = filename:dirname("/disk0:/usr/foo.erl"),
- ?line "/usr" = filename:dirname("\\usr\\foo.erl"),
- ?line "/usr" = filename:dirname("\\usr"),
- ?line "net:" = filename:dirname("net:");
+ "A:/usr" = filename:dirname("A:/usr/foo.erl"),
+ "A:usr" = filename:dirname("A:usr/foo.erl"),
+ "/usr" = filename:dirname("\\usr\\foo.erl"),
+ "/" = filename:dirname("\\usr"),
+ "A:" = filename:dirname("A:");
_ -> true
end,
- ?line "usr" = filename:dirname("usr///foo.erl"),
- ?line "." = filename:dirname("foo.erl"),
- ?line "." = filename:dirname("."),
- ?line "usr" = filename:dirname('usr/foo.erl'),
- ?line "usr" = filename:dirname(['usr','/foo.erl']),
- ?line "usr" = filename:dirname(['us','r/foo.erl']),
- ?line "usr" = filename:dirname(['usr/','/foo.erl']),
- ?line "usr" = filename:dirname(['usr/','foo.erl']),
- ?line "usr" = filename:dirname(['usr/'|'foo.erl']),
- ?line "usr" = filename:dirname(['usr/f','oo.erl']),
- case os:type() of
- vxworks ->
- ?line "/" = filename:dirname("/"),
- ?line "/usr" = filename:dirname("/usr");
- _ ->
- ?line "/" = filename:dirname("/"),
- ?line "/" = filename:dirname("/usr")
- end,
+ "usr" = filename:dirname("usr///foo.erl"),
+ "." = filename:dirname("foo.erl"),
+ "." = filename:dirname("."),
+ "usr" = filename:dirname('usr/foo.erl'),
+ "usr" = filename:dirname(['usr','/foo.erl']),
+ "usr" = filename:dirname(['us','r/foo.erl']),
+ "usr" = filename:dirname(['usr/','/foo.erl']),
+ "usr" = filename:dirname(['usr/','foo.erl']),
+ "usr" = filename:dirname(['usr/'|'foo.erl']),
+ "usr" = filename:dirname(['usr/f','oo.erl']),
+ "/" = filename:dirname("/"),
+ "/" = filename:dirname("/usr"),
ok.
@@ -319,12 +273,6 @@ extension(Config) when is_list(Config) ->
filename:extension("A:/usr.bar/foo.nisse.erl"),
?line "" = filename:extension("A:/usr.bar/foo"),
ok;
- vxworks ->
- ?line "" = filename:extension("/disk0:\\usr\\foo"),
- ?line ".erl" =
- filename:extension("net:/usr.bar/foo.nisse.erl"),
- ?line "" = filename:extension("net:/usr.bar/foo"),
- ok;
_ -> ok
end.
@@ -369,25 +317,6 @@ join(Config) when is_list(Config) ->
filename:join(["A:","C:usr","foo.erl"]),
?line "d:/foo" = filename:join([$D, $:, $/, []], "foo"),
ok;
- vxworks ->
- ?line "Net:" = filename:join(["Net:/"]),
- ?line "net:" = filename:join(["net:\\"]),
- ?line "net:/abc" = filename:join(["net:/", "abc"]),
- ?line "net:/abc" = filename:join(["net:", "abc"]),
- ?line "a/b/c/d/e/f/g" =
- filename:join(["a//b\\c//\\/\\d/\\e/f\\g"]),
- ?line "net:/usr/foo.erl" =
- filename:join(["net:","usr","foo.erl"]),
- ?line "/usr/foo.erl" =
- filename:join(["net:","/usr","foo.erl"]),
- ?line "/target:usr" = filename:join("net:","/target:usr"),
- ?line "kernel:/usr" = filename:join("net:", "kernel:/usr"),
- ?line "foo:/usr/foo.erl" =
- filename:join(["A:","foo:/usr","foo.erl"]),
- ?line "/disk0:usr/foo.erl" =
- filename:join(["kalle:","/disk0:usr","foo.erl"]),
- ?line "D:/foo" = filename:join([$D, $:, $/, []], "foo"),
- ok;
{unix, _} ->
ok
end.
@@ -406,10 +335,6 @@ pathtype(Config) when is_list(Config) ->
{unix, _} ->
?line absolute = filename:pathtype("/"),
?line absolute = filename:pathtype("/usr/local/bin"),
- ok;
- vxworks ->
- ?line absolute = filename:pathtype("/usr/local/bin"),
- ?line absolute = filename:pathtype("net:usr/local/bin"),
ok
end.
@@ -424,12 +349,7 @@ rootname(Config) when is_list(Config) ->
ok.
split(Config) when is_list(Config) ->
- case os:type() of
- vxworks ->
- ?line ["/usr","local","bin"] = filename:split("/usr/local/bin");
- _ ->
- ?line ["/","usr","local","bin"] = filename:split("/usr/local/bin")
- end,
+ ?line ["/","usr","local","bin"] = filename:split("/usr/local/bin"),
?line ["foo","bar"]= filename:split("foo/bar"),
?line ["foo", "bar", "hello"]= filename:split("foo////bar//hello"),
?line ["foo", "bar", "hello"]= filename:split(["foo//",'//bar//h',"ello"]),
@@ -447,18 +367,6 @@ split(Config) when is_list(Config) ->
?line ["a:","msdev","include"] =
filename:split("a:msdev\\include"),
ok;
- vxworks ->
- ?line ["net:","msdev","include"] =
- filename:split("net:/msdev/include"),
- ?line ["Target:","msdev","include"] =
- filename:split("Target:/msdev/include"),
- ?line ["msdev","include"] =
- filename:split("msdev\\include"),
- ?line ["/disk0:","msdev","include"] =
- filename:split("/disk0:\\msdev\\include"),
- ?line ["a:","msdev","include"] =
- filename:split("a:msdev\\include"),
- ok;
_ ->
ok
end.
@@ -657,56 +565,38 @@ basename_bin_2(Config) when is_list(Config) ->
dirname_bin(Config) when is_list(Config) ->
case os:type() of
{win32,_} ->
- ?line <<"A:/usr">> = filename:dirname(<<"A:/usr/foo.erl">>),
- ?line <<"A:usr">> = filename:dirname(<<"A:usr/foo.erl">>),
- ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>),
- ?line <<"/">> = filename:dirname(<<"\\usr">>),
- ?line <<"A:">> = filename:dirname(<<"A:">>);
- vxworks ->
- ?line <<"net:/usr">> = filename:dirname(<<"net:/usr/foo.erl">>),
- ?line <<"/disk0:/usr">> = filename:dirname(<<"/disk0:/usr/foo.erl">>),
- ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>),
- ?line <<"/usr">> = filename:dirname(<<"\\usr">>),
- ?line <<"net:">> = filename:dirname(<<"net:">>);
+ <<"A:/usr">> = filename:dirname(<<"A:/usr/foo.erl">>),
+ <<"A:usr">> = filename:dirname(<<"A:usr/foo.erl">>),
+ <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>),
+ <<"/">> = filename:dirname(<<"\\usr">>),
+ <<"A:">> = filename:dirname(<<"A:">>);
_ -> true
end,
- ?line <<"usr">> = filename:dirname(<<"usr///foo.erl">>),
- ?line <<".">> = filename:dirname(<<"foo.erl">>),
- ?line <<".">> = filename:dirname(<<".">>),
- case os:type() of
- vxworks ->
- ?line <<"/">> = filename:dirname(<<"/">>),
- ?line <<"/usr">> = filename:dirname(<<"/usr">>);
- _ ->
- ?line <<"/">> = filename:dirname(<<"/">>),
- ?line <<"/">> = filename:dirname(<<"/usr">>)
- end,
+ <<"usr">> = filename:dirname(<<"usr///foo.erl">>),
+ <<".">> = filename:dirname(<<"foo.erl">>),
+ <<".">> = filename:dirname(<<".">>),
+ <<"/">> = filename:dirname(<<"/">>),
+ <<"/">> = filename:dirname(<<"/usr">>),
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
extension_bin(Config) when is_list(Config) ->
- ?line <<".erl">> = filename:extension(<<"A:/usr/foo.erl">>),
- ?line <<".erl">> = filename:extension(<<"A:/usr/foo.nisse.erl">>),
- ?line <<".erl">> = filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
- ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
- ?line <<"">> = filename:extension(<<"A:/usr/foo">>),
- ?line case os:type() of
- {win32, _} ->
- ?line <<"">> = filename:extension(<<"A:\\usr\\foo">>),
- ?line <<".erl">> =
- filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
- ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
- ok;
- vxworks ->
- ?line <<"">> = filename:extension(<<"/disk0:\\usr\\foo">>),
- ?line <<".erl">> =
- filename:extension(<<"net:/usr.bar/foo.nisse.erl">>),
- ?line <<"">> = filename:extension(<<"net:/usr.bar/foo">>),
- ok;
- _ -> ok
- end.
+ <<".erl">> = filename:extension(<<"A:/usr/foo.erl">>),
+ <<".erl">> = filename:extension(<<"A:/usr/foo.nisse.erl">>),
+ <<".erl">> = filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
+ <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
+ <<"">> = filename:extension(<<"A:/usr/foo">>),
+ case os:type() of
+ {win32, _} ->
+ ?line <<"">> = filename:extension(<<"A:\\usr\\foo">>),
+ ?line <<".erl">> =
+ filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
+ ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
+ ok;
+ _ -> ok
+ end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -754,50 +644,45 @@ join_bin(Config) when is_list(Config) ->
end.
pathtype_bin(Config) when is_list(Config) ->
- ?line relative = filename:pathtype(<<"..">>),
- ?line relative = filename:pathtype(<<"foo">>),
- ?line relative = filename:pathtype(<<"foo/bar">>),
- ?line relative = filename:pathtype('foo/bar'),
+ relative = filename:pathtype(<<"..">>),
+ relative = filename:pathtype(<<"foo">>),
+ relative = filename:pathtype(<<"foo/bar">>),
+ relative = filename:pathtype('foo/bar'),
case os:type() of
{win32, _} ->
- ?line volumerelative = filename:pathtype(<<"/usr/local/bin">>),
- ?line volumerelative = filename:pathtype(<<"A:usr/local/bin">>),
+ volumerelative = filename:pathtype(<<"/usr/local/bin">>),
+ volumerelative = filename:pathtype(<<"A:usr/local/bin">>),
ok;
{unix, _} ->
- ?line absolute = filename:pathtype(<<"/">>),
- ?line absolute = filename:pathtype(<<"/usr/local/bin">>),
+ absolute = filename:pathtype(<<"/">>),
+ absolute = filename:pathtype(<<"/usr/local/bin">>),
ok
end.
rootname_bin(Config) when is_list(Config) ->
- ?line <<"/jam.src/kalle">> = filename:rootname(<<"/jam.src/kalle">>),
- ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>),
- ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>, <<".erl">>),
- ?line <<"/jam.src/foo.jam">> = filename:rootname(<<"/jam.src/foo.jam">>, <<".erl">>),
- ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j',"am"],<<".erl">>),
- ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j'|am],<<".erl">>),
+ <<"/jam.src/kalle">> = filename:rootname(<<"/jam.src/kalle">>),
+ <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>),
+ <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>, <<".erl">>),
+ <<"/jam.src/foo.jam">> = filename:rootname(<<"/jam.src/foo.jam">>, <<".erl">>),
+ <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j',"am"],<<".erl">>),
+ <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j'|am],<<".erl">>),
ok.
split_bin(Config) when is_list(Config) ->
- case os:type() of
- vxworks ->
- ?line [<<"/usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>);
- _ ->
- ?line [<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>)
- end,
- ?line [<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>),
- ?line [<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>),
+ [<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>),
+ [<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>),
+ [<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>),
case os:type() of
{win32,_} ->
- ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ [<<"a:/">>,<<"msdev">>,<<"include">>] =
filename:split(<<"a:/msdev/include">>),
- ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ [<<"a:/">>,<<"msdev">>,<<"include">>] =
filename:split(<<"A:/msdev/include">>),
- ?line [<<"msdev">>,<<"include">>] =
+ [<<"msdev">>,<<"include">>] =
filename:split(<<"msdev\\include">>),
- ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ [<<"a:/">>,<<"msdev">>,<<"include">>] =
filename:split(<<"a:\\msdev\\include">>),
- ?line [<<"a:">>,<<"msdev">>,<<"include">>] =
+ [<<"a:">>,<<"msdev">>,<<"include">>] =
filename:split(<<"a:msdev\\include">>),
ok;
_ ->
@@ -814,4 +699,3 @@ t_nativename_bin(Config) when is_list(Config) ->
?line <<"/usr/tmp/arne">> =
filename:nativename(<<"/usr/tmp//arne/">>)
end.
-
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index bdb4ea65b5..22f66a6c14 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -281,21 +281,12 @@ start12(Config) when is_list(Config) ->
%% Check that time outs in calls work
abnormal1(suite) -> [];
abnormal1(Config) when is_list(Config) ->
- ?line {ok, _Pid} =
- gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
+ {ok, _Pid} = gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
%% timeout call.
- case os:type() of
- vxworks ->
- %% timeout call for VxWorks must be in 16ms increments.
- ?line delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 17),
- ?line {'EXIT',{timeout,_}} =
- (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,17}, 1));
- _ ->
- ?line delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100),
- ?line {'EXIT',{timeout,_}} =
- (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1))
- end,
+ 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)),
test_server:messages_get(),
ok.
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index c930d90e1c..dffeadb423 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -231,14 +231,6 @@ start(Config) when is_list(Config) ->
end,
test_server:messages_get(),
- %% Must wait for all error messages before going to next test.
- %% (otherwise it interferes too much with real time characteristics).
- case os:type() of
- vxworks ->
- receive after 5000 -> ok end;
- _ ->
- ok
- end,
process_flag(trap_exit, OldFl),
ok.
@@ -1054,8 +1046,9 @@ call_with_huge_message_queue(Config) when is_list(Config) ->
io:format("Time for empty message queue: ~p", [Time]),
io:format("Time for huge message queue: ~p", [NewTime]),
+ IsCover = test_server:is_cover(),
case (NewTime+1) / (Time+1) of
- Q when Q < 10 ->
+ Q when Q < 10; IsCover ->
ok;
Q ->
io:format("Q = ~p", [Q]),
diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl
index e1972a100e..ee97ffe7b3 100644
--- a/lib/stdlib/test/id_transform_SUITE.erl
+++ b/lib/stdlib/test/id_transform_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2003-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2003-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -26,7 +26,7 @@
id_transform/1]).
-export([check/2,check2/1,g/0,f/1,t/1,t1/1,t2/1,t3/1,t4/1,
- t5/1,t6/1,apa/1,new_fun/0]).
+ t5/1,apa/1,new_fun/0]).
% Serves as test...
-hej(hopp).
@@ -61,7 +61,7 @@ id_transform(Config) when is_list(Config) ->
?line {module,erl_id_trans}=code:load_binary(erl_id_trans,File,Bin),
?line case test_server:purify_is_running() of
false ->
- Dog = ?t:timetrap(?t:hours(1)),
+ Dog = ct:timetrap(?t:hours(1)),
?line Res = run_in_test_suite(),
?t:timetrap_cancel(Dog),
Res;
@@ -388,8 +388,6 @@ t3(A) when is_tuple(A) or is_tuple(A) ->
is_tuple;
t3(A) when record(A, apa) ->
foo;
-t3(A) when {erlang,is_record}(A, apa) ->
- foo;
t3(A) when erlang:is_record(A, apa) ->
foo;
t3(A) when is_record(A, apa) ->
@@ -397,13 +395,10 @@ t3(A) when is_record(A, apa) ->
t3(A) when record({apa}, apa) ->
{A,foo}.
-t4(_) when {erlang,is_record}({apa}, apa) ->
- foo.
-
-t5(A) when erlang:is_record({apa}, apa) ->
+t4(A) when erlang:is_record({apa}, apa) ->
{A,foo}.
-t6(A) when is_record({apa}, apa) ->
+t5(A) when is_record({apa}, apa) ->
{A,foo}.
-record(apa2,{a=a,b=foo:bar()}).
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index bb02a879c2..521d7255ea 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -27,7 +28,8 @@
otp_6282/1, otp_6354/1, otp_6495/1, otp_6517/1, otp_6502/1,
manpage/1, otp_6708/1, otp_7084/1, otp_7421/1,
io_lib_collect_line_3_wb/1, cr_whitespace_in_string/1,
- io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1]).
+ io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1,
+ io_lib_print_binary_depth_one/1, otp_10302/1]).
%-define(debug, true).
@@ -62,7 +64,8 @@ all() ->
otp_6282, otp_6354, otp_6495, otp_6517, otp_6502,
manpage, otp_6708, otp_7084, otp_7421,
io_lib_collect_line_3_wb, cr_whitespace_in_string,
- io_fread_newlines, otp_8989, io_lib_fread_literal].
+ io_fread_newlines, otp_8989, io_lib_fread_literal,
+ io_lib_print_binary_depth_one, otp_10302].
groups() ->
[].
@@ -892,7 +895,7 @@ otp_6354(Config) when is_list(Config) ->
?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�\"" =
+ ?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),
@@ -2021,3 +2024,55 @@ io_lib_fread_literal(Suite) when is_list(Suite) ->
?line {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"),
?line {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"),
ok.
+
+io_lib_print_binary_depth_one(doc) ->
+ "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]),
+ ok.
+
+otp_10302(doc) ->
+ "OTP-10302. Unicode";
+otp_10302(Suite) when is_list(Suite) ->
+ "\"\x{400}\"" = pretty("\x{400}", -1),
+ "<<\"\x{400}\"/utf8>>" = pretty(<<"\x{400}"/utf8>>, -1),
+
+ "<<\"\x{400}foo\"/utf8>>" = pretty(<<"\x{400}foo"/utf8>>, 2),
+ "<<\"äppl\"/utf8>>" = pretty(<<"äppl"/utf8>>, 2),
+ "<<\"äppl\"/utf8...>>" = pretty(<<"äpple"/utf8>>, 2),
+ "<<\"apel\">>" = pretty(<<"apel">>, 2),
+ "<<\"apel\"...>>" = pretty(<<"apelsin">>, 2),
+ "<<228,112,112,108>>" = fmt("~tp", [<<"äppl">>]),
+ "<<228,...>>" = fmt("~tP", [<<"äppl">>, 2]),
+
+ Chars = lists:seq(0, 512), % just a few...
+ [] = [C || C <- Chars, S <- io_lib:write_unicode_char_as_latin1(C),
+ not is_latin1(S)],
+ L1 = [S || C <- Chars, S <- io_lib:write_unicode_char(C),
+ not is_latin1(S)],
+ L1 = lists:seq(256, 512),
+
+ [] = [C || C <- Chars, S <- io_lib:write_unicode_string_as_latin1([C]),
+ not is_latin1(S)],
+ L2 = [S || C <- Chars, S <- io_lib:write_unicode_string([C]),
+ not is_latin1(S)],
+ L2 = lists:seq(256, 512),
+
+ ok.
+
+pretty(Term, Depth) when is_integer(Depth) ->
+ Opts = [{column, 1}, {line_length, 20},
+ {depth, Depth}, {max_chars, 60},
+ {encoding, unicode}],
+ pretty(Term, Opts);
+pretty(Term, Opts) when is_list(Opts) ->
+ R = io_lib_pretty:print(Term, Opts),
+ lists:flatten(io_lib:format("~ts", [R])).
+
+is_latin1(S) ->
+ S >= 0 andalso S =< 255.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 17e69f7c1c..299daf0e42 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -736,7 +736,7 @@ binary_options(Config) when is_list(Config) ->
{getline_re, ".*<<\"hej\\\\n\">>"},
{putline, "io:get_line('')."},
{putline, binary_to_list(<<"\345\344\366"/utf8>>)},
- {getline_re, ".*<<\""++binary_to_list(unicode:characters_to_binary(<<"\345\344\366"/utf8>>,latin1,utf8))++"\\\\n\">>"}
+ {getline_re, ".*<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\\\n\"/utf8>>"}
],[],[],"-oldshell"),
ok.
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index c95089117c..8dca69bac4 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -28,7 +28,7 @@
crash/1, sync_start_nolink/1, sync_start_link/1,
spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1,
hibernate/1]).
--export([ otp_6345/1]).
+-export([ otp_6345/1, init_dont_hang/1]).
-export([hib_loop/1, awaken/1]).
@@ -36,7 +36,7 @@
handle_event/2, handle_call/2, handle_info/2,
terminate/2]).
--export([otp_6345_init/1]).
+-export([otp_6345_init/1, init_dont_hang_init/1]).
-ifdef(STANDALONE).
@@ -52,7 +52,7 @@ all() ->
{group, tickets}].
groups() ->
- [{tickets, [], [otp_6345]},
+ [{tickets, [], [otp_6345, init_dont_hang]},
{sync_start, [], [sync_start_nolink, sync_start_link]}].
init_per_suite(Config) ->
@@ -343,6 +343,29 @@ otp_6345_loop() ->
otp_6345_loop()
end.
+%% OTP-9803
+init_dont_hang(suite) ->
+ [];
+init_dont_hang(doc) ->
+ ["Check that proc_lib:start don't hang if spawned process crashes before proc_lib:init_ack/2"];
+init_dont_hang(Config) when is_list(Config) ->
+ %% Start should behave as start_link
+ process_flag(trap_exit, true),
+ StartLinkRes = proc_lib:start_link(?MODULE, init_dont_hang_init, [self()]),
+ try
+ StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000),
+ StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000, []),
+ ok
+ catch _:Error ->
+ io:format("Error ~p /= ~p ~n",[erlang:get_stacktrace(), StartLinkRes]),
+ exit(Error)
+ end.
+
+init_dont_hang_init(Parent) ->
+ 1 = 2.
+
+
+
%%-----------------------------------------------------------------
%% The error_logger handler used.
%%-----------------------------------------------------------------
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 192268f90e..cac8309bd9 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -2969,15 +2969,6 @@ lookup1(Config) when is_list(Config) ->
[3] = lookup_keys(Q)
end, [{1,a},{3,3}])">>,
- {cres,
- <<"A = 3,
- etsc(fun(E) ->
- Q = qlc:q([X || X <- ets:table(E), A =:= {erlang,element}(1, X)]),
- [{3,3}] = qlc:e(Q),
- [3] = lookup_keys(Q)
- end, [{1,a},{3,3}])">>,
- {warnings,[{3,erl_lint,deprecated_tuple_fun}]}},
-
<<"etsc(fun(E) ->
A = 3,
Q = qlc:q([X || X <- ets:table(E),
@@ -3442,14 +3433,6 @@ lookup2(Config) when is_list(Config) ->
[r] = lookup_keys(Q)
end, [{keypos,1}], [#r{}])">>,
{cres,
- <<"etsc(fun(E) ->
- Q = qlc:q([element(1, X) || X <- ets:table(E),
- {erlang,is_record}(X, r, 2)]),
- [r] = qlc:e(Q),
- [r] = lookup_keys(Q)
- end, [{keypos,1}], [#r{}])">>,
- {warnings,[{4,erl_lint,deprecated_tuple_fun}]}},
- {cres,
<<"etsc(fun(E) ->
Q = qlc:q([element(1, X) || X <- ets:table(E),
record(X, r)]),
@@ -3468,15 +3451,7 @@ lookup2(Config) when is_list(Config) ->
is_record(X, r)]),
[r] = qlc:e(Q),
[r] = lookup_keys(Q)
- end, [{keypos,1}], [#r{}])">>,
- {cres,
- <<"etsc(fun(E) ->
- Q = qlc:q([element(1, X) || X <- ets:table(E),
- {erlang,is_record}(X, r)]),
- [r] = qlc:e(Q),
- [r] = lookup_keys(Q)
- end, [{keypos,1}], [#r{}])">>,
- {warnings,[{4,erl_lint,deprecated_tuple_fun}]}}
+ end, [{keypos,1}], [#r{}])">>
],
?line run(Config, <<"-record(r, {a}).\n">>, TsR),
@@ -6087,21 +6062,6 @@ otp_6673(Config) when is_list(Config) ->
],
?line run(Config, Ts_RT),
- %% Ulf Wiger provided a patch that makes QLC work with packages:
- Dir = filename:join(?privdir, "p"),
- ?line ok = filelib:ensure_dir(filename:join(Dir, ".")),
- File = filename:join(Dir, "p.erl"),
- ?line ok = file:write_file(File,
- <<"-module(p.p).\n"
- "-export([q/0]).\n"
- "-include_lib(\"stdlib/include/qlc.hrl\").\n"
- "q() ->\n"
- " .qlc:q([X || X <- [1,2]]).">>),
- ?line {ok, 'p.p'} = compile:file(File, [{outdir,Dir}]),
- ?line code:purge('p.p'),
- ?line {module, 'p.p'} = code:load_abs(filename:rootname(File), 'p.p'),
- ?line [1,2] = qlc:e(p.p:q()),
-
ok.
otp_6964(doc) ->
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index a542745e67..500f5fadb9 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -1,3 +1,4 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
@@ -291,10 +292,10 @@ global_capture(Config) when is_list(Config) ->
?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]),
+ ?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]),
?t:timetrap_cancel(Dog),
ok.
@@ -314,20 +315,26 @@ replace_return(Config) when is_list(Config) ->
Dog = ?t:timetrap(?t:minutes(3)),
?line {'EXIT',{badarg,_}} = (catch re:replace("na","(a","")),
?line <<"nasse">> = re:replace(<<"nisse">>,"i","a",[{return,binary}]),
- ?line <<"ABC�XABCXA">> = re:replace("ABC\305abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary}]),
+ ?line <<"ABCÅXABCXA">> = re:replace("ABC\305abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary}]),
- ?line [<<"ABC�">>,
+ ?line [<<"ABCÅ">>,
<<"X">>,
<<"ABC">>,
<<"X">> |
<<"A">> ] =
- re:replace("ABC�abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,iodata}]),
- ?line "ABC�XABCXA" = re:replace("ABC�abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,list},unicode]),
- ?line <<65,66,67,195,133,88,65,66,67,88,65>> = re:replace("ABC�abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary},unicode]),
- ?line <<65,66,67,195,133,88,65,66,67,97,98,99,100,65>> = re:replace("ABC�abcdABCabcdA","a(?<FOO>bcd)","X",[{return,binary},unicode]),
+ re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,iodata}]),
+ ?line "ABCÅXABCXA" = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,list},unicode]),
+ ?line <<65,66,67,195,133,88,65,66,67,88,65>> = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary},unicode]),
+ ?line <<65,66,67,195,133,88,65,66,67,97,98,99,100,65>> = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[{return,binary},unicode]),
?line <<"iXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\9X",[{return,binary}]),
?line <<"jXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\10X",[{return,binary}]),
?line <<"Xk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\11X",[{return,binary}]),
+ ?line <<"9X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g9X",[{return,binary}]),
+ ?line <<"0X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g10X",[{return,binary}]),
+ ?line <<"X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g11X",[{return,binary}]),
+ ?line <<"971">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{9}7",[{return,binary}]),
+ ?line <<"071">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{10}7",[{return,binary}]),
+ ?line <<"71">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{11}7",[{return,binary}]),
?line "a\x{400}bcX" = re:replace("a\x{400}bcd","d","X",[global,{return,list},unicode]),
?line <<"a",208,128,"bcX">> = re:replace("a\x{400}bcd","d","X",[global,{return,binary},unicode]),
?line "a\x{400}bcd" = re:replace("a\x{400}bcd","Z","X",[global,{return,list},unicode]),
diff --git a/lib/stdlib/test/re_testoutput1_replacement_test.erl b/lib/stdlib/test/re_testoutput1_replacement_test.erl
index 69cb140e0d..8f8d8762ad 100644
--- a/lib/stdlib/test/re_testoutput1_replacement_test.erl
+++ b/lib/stdlib/test/re_testoutput1_replacement_test.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -274,10 +275,10 @@ run() ->
?line <<"dthing">> = iolist_to_binary(re:replace("dthing","^[^]cde]","y\\1I&MoqRPG&GQa\\1l",[global])),
?line <<"ething">> = iolist_to_binary(re:replace("ething","^[^]cde]","AsxwUn\\1GqkWNdgRJk",[])),
?line <<"ething">> = iolist_to_binary(re:replace("ething","^[^]cde]","AsxwUn\\1GqkWNdgRJk",[global])),
-?line <<"RornKmOnaFr�tWgtW">> = iolist_to_binary(re:replace("�","^\\�","R\\1o\\1r\\1nKmOnaFr&tWgtW",[])),
-?line <<"RornKmOnaFr�tWgtW">> = iolist_to_binary(re:replace("�","^\\�","R\\1o\\1r\\1nKmOnaFr&tWgtW",[global])),
-?line <<"ufbmbfOYuK�wf�E�dx">> = iolist_to_binary(re:replace("�","^�","ufbmbfOYuK&wf&E&\\1dx",[])),
-?line <<"ufbmbfOYuK�wf�E�dx">> = iolist_to_binary(re:replace("�","^�","ufbmbfOYuK&wf&E&\\1dx",[global])),
+?line <<"RornKmOnaFrtWgtW">> = iolist_to_binary(re:replace("","^\\","R\\1o\\1r\\1nKmOnaFr&tWgtW",[])),
+?line <<"RornKmOnaFrtWgtW">> = iolist_to_binary(re:replace("","^\\","R\\1o\\1r\\1nKmOnaFr&tWgtW",[global])),
+?line <<"ufbmbfOYuKÿwfÿEÿdx">> = iolist_to_binary(re:replace("ÿ","^ÿ","ufbmbfOYuK&wf&E&\\1dx",[])),
+?line <<"ufbmbfOYuKÿwfÿEÿdx">> = iolist_to_binary(re:replace("ÿ","^ÿ","ufbmbfOYuK&wf&E&\\1dx",[global])),
?line <<"oAdJme0jw">> = iolist_to_binary(re:replace("0","^[0-9]+$","oAdJme\\1&jw",[])),
?line <<"oAdJme0jw">> = iolist_to_binary(re:replace("0","^[0-9]+$","oAdJme\\1&jw",[global])),
?line <<"1aoKN">> = iolist_to_binary(re:replace("1","^[0-9]+$","&aoKN",[])),
@@ -14972,10 +14973,10 @@ def">> = iolist_to_binary(re:replace("abc
def","abc$","M",[global])),
?line <<"abcWCabcSYXGPjRugTabcVGabcSX">> = iolist_to_binary(re:replace("abcS","(abc)\\123","\\1WC&YXGPjRugT\\1VG&X",[])),
?line <<"abcWCabcSYXGPjRugTabcVGabcSX">> = iolist_to_binary(re:replace("abcS","(abc)\\123","\\1WC&YXGPjRugT\\1VG&X",[global])),
-?line <<"fabc�Uabc�UmiqabceCsabcabc�">> = iolist_to_binary(re:replace("abc�","(abc)\\223","f&U&Umiq\\1eCs\\1&",[])),
-?line <<"fabc�Uabc�UmiqabceCsabcabc�">> = iolist_to_binary(re:replace("abc�","(abc)\\223","f&U&Umiq\\1eCs\\1&",[global])),
-?line <<"JRFabcxnbabc�Vkabc�fWigQMuaY">> = iolist_to_binary(re:replace("abc�","(abc)\\323","JRF\\1xnb&Vk&fWigQMuaY",[])),
-?line <<"JRFabcxnbabc�Vkabc�fWigQMuaY">> = iolist_to_binary(re:replace("abc�","(abc)\\323","JRF\\1xnb&Vk&fWigQMuaY",[global])),
+?line <<"fabc“Uabc“UmiqabceCsabcabc“">> = iolist_to_binary(re:replace("abc“","(abc)\\223","f&U&Umiq\\1eCs\\1&",[])),
+?line <<"fabc“Uabc“UmiqabceCsabcabc“">> = iolist_to_binary(re:replace("abc“","(abc)\\223","f&U&Umiq\\1eCs\\1&",[global])),
+?line <<"JRFabcxnbabcÓVkabcÓfWigQMuaY">> = iolist_to_binary(re:replace("abcÓ","(abc)\\323","JRF\\1xnb&Vk&fWigQMuaY",[])),
+?line <<"JRFabcxnbabcÓVkabcÓfWigQMuaY">> = iolist_to_binary(re:replace("abcÓ","(abc)\\323","JRF\\1xnb&Vk&fWigQMuaY",[global])),
?line <<"vgabc@QQ">> = iolist_to_binary(re:replace("abc@","(abc)\\100","vg&QQ",[])),
?line <<"vgabc@QQ">> = iolist_to_binary(re:replace("abc@","(abc)\\100","vg&QQ",[global])),
?line <<"abc@OkvNytabc@abcabc@a">> = iolist_to_binary(re:replace("abc@","(abc)\\100","&OkvNyt&\\1&a",[])),
@@ -18343,24 +18344,24 @@ xb","(?!^)x","\\1tysI\\1v\\1BVwx\\1FOWG\\1&C",[multiline,
?line <<"cY">> = iolist_to_binary(re:replace("M","\\M","cY\\1",[global])),
?line <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(re:replace("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b","yWOTIFhIX\\1H",[])),
?line <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(re:replace("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b","yWOTIFhIX\\1H",[global])),
-?line <<"NREGularsRREGularWEYrVRr">> = iolist_to_binary(re:replace("REGular","(?i)reg(?:ul(?:[a�]|ae)r|ex)","N&\\1sR&WEYrVRr",[])),
-?line <<"NREGularsRREGularWEYrVRr">> = iolist_to_binary(re:replace("REGular","(?i)reg(?:ul(?:[a�]|ae)r|ex)","N&\\1sR&WEYrVRr",[global])),
-?line <<"G">> = iolist_to_binary(re:replace("regulaer","(?i)reg(?:ul(?:[a�]|ae)r|ex)","G",[])),
-?line <<"G">> = iolist_to_binary(re:replace("regulaer","(?i)reg(?:ul(?:[a�]|ae)r|ex)","G",[global])),
-?line <<"PSsXtwlmy">> = iolist_to_binary(re:replace("Regex","(?i)reg(?:ul(?:[a�]|ae)r|ex)","PSsXtwlmy",[])),
-?line <<"PSsXtwlmy">> = iolist_to_binary(re:replace("Regex","(?i)reg(?:ul(?:[a�]|ae)r|ex)","PSsXtwlmy",[global])),
-?line <<"regul�rmiYTi">> = iolist_to_binary(re:replace("regul�r","(?i)reg(?:ul(?:[a�]|ae)r|ex)","&miYTi\\1\\1",[])),
-?line <<"regul�rmiYTi">> = iolist_to_binary(re:replace("regul�r","(?i)reg(?:ul(?:[a�]|ae)r|ex)","&miYTi\\1\\1",[global])),
-?line <<"W�����rxh�����yUoaLOIegmSA">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","W&rxh&yUoaL\\1OIegmS\\1A",[])),
-?line <<"W�����rxh�����yUoaLOIegmSA">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","W&rxh&yUoaL\\1OIegmS\\1A",[global])),
-?line <<"F�����gnWPyHeh�����tXTQ">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","F&gnWPyHe\\1h&tXTQ",[])),
-?line <<"F�����gnWPyHeh�����tXTQ">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","F&gnWPyHe\\1h&tXTQ",[global])),
-?line <<"sHerHnAhAdx">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","sHer\\1HnA\\1h\\1Adx",[])),
-?line <<"sHerHnAhAdx">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","sHer\\1HnA\\1h\\1Adx",[global])),
-?line <<"trobAQoU�����n">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","tr\\1obAQoU&n",[])),
-?line <<"trobAQoU�����n">> = iolist_to_binary(re:replace("�����","����[�-��-�]+","tr\\1obAQoU&n",[global])),
-?line <<"�XAZSd">> = iolist_to_binary(re:replace("�XAZXB","(?<=Z)X.","Sd",[])),
-?line <<"�XAZSd">> = iolist_to_binary(re:replace("�XAZXB","(?<=Z)X.","Sd",[global])),
+?line <<"NREGularsRREGularWEYrVRr">> = iolist_to_binary(re:replace("REGular","(?i)reg(?:ul(?:[aä]|ae)r|ex)","N&\\1sR&WEYrVRr",[])),
+?line <<"NREGularsRREGularWEYrVRr">> = iolist_to_binary(re:replace("REGular","(?i)reg(?:ul(?:[aä]|ae)r|ex)","N&\\1sR&WEYrVRr",[global])),
+?line <<"G">> = iolist_to_binary(re:replace("regulaer","(?i)reg(?:ul(?:[aä]|ae)r|ex)","G",[])),
+?line <<"G">> = iolist_to_binary(re:replace("regulaer","(?i)reg(?:ul(?:[aä]|ae)r|ex)","G",[global])),
+?line <<"PSsXtwlmy">> = iolist_to_binary(re:replace("Regex","(?i)reg(?:ul(?:[aä]|ae)r|ex)","PSsXtwlmy",[])),
+?line <<"PSsXtwlmy">> = iolist_to_binary(re:replace("Regex","(?i)reg(?:ul(?:[aä]|ae)r|ex)","PSsXtwlmy",[global])),
+?line <<"regulärmiYTi">> = iolist_to_binary(re:replace("regulär","(?i)reg(?:ul(?:[aä]|ae)r|ex)","&miYTi\\1\\1",[])),
+?line <<"regulärmiYTi">> = iolist_to_binary(re:replace("regulär","(?i)reg(?:ul(?:[aä]|ae)r|ex)","&miYTi\\1\\1",[global])),
+?line <<"WÅæåäàrxhÅæåäàyUoaLOIegmSA">> = iolist_to_binary(re:replace("Åæåäà","Åæåä[à-ÿÀ-ß]+","W&rxh&yUoaL\\1OIegmS\\1A",[])),
+?line <<"WÅæåäàrxhÅæåäàyUoaLOIegmSA">> = iolist_to_binary(re:replace("Åæåäà","Åæåä[à-ÿÀ-ß]+","W&rxh&yUoaL\\1OIegmS\\1A",[global])),
+?line <<"FÅæåäÿgnWPyHehÅæåäÿtXTQ">> = iolist_to_binary(re:replace("Åæåäÿ","Åæåä[à-ÿÀ-ß]+","F&gnWPyHe\\1h&tXTQ",[])),
+?line <<"FÅæåäÿgnWPyHehÅæåäÿtXTQ">> = iolist_to_binary(re:replace("Åæåäÿ","Åæåä[à-ÿÀ-ß]+","F&gnWPyHe\\1h&tXTQ",[global])),
+?line <<"sHerHnAhAdx">> = iolist_to_binary(re:replace("ÅæåäÀ","Åæåä[à-ÿÀ-ß]+","sHer\\1HnA\\1h\\1Adx",[])),
+?line <<"sHerHnAhAdx">> = iolist_to_binary(re:replace("ÅæåäÀ","Åæåä[à-ÿÀ-ß]+","sHer\\1HnA\\1h\\1Adx",[global])),
+?line <<"trobAQoUÅæåäßn">> = iolist_to_binary(re:replace("Åæåäß","Åæåä[à-ÿÀ-ß]+","tr\\1obAQoU&n",[])),
+?line <<"trobAQoUÅæåäßn">> = iolist_to_binary(re:replace("Åæåäß","Åæåä[à-ÿÀ-ß]+","tr\\1obAQoU&n",[global])),
+?line <<"„XAZSd">> = iolist_to_binary(re:replace("„XAZXB","(?<=Z)X.","Sd",[])),
+?line <<"„XAZSd">> = iolist_to_binary(re:replace("„XAZXB","(?<=Z)X.","Sd",[global])),
?line <<"A">> = iolist_to_binary(re:replace("ab cd defg","ab cd (?x) de fg","\\1A\\1",[])),
?line <<"A">> = iolist_to_binary(re:replace("ab cd defg","ab cd (?x) de fg","\\1A\\1",[global])),
?line <<"fab cddefgLdtKCtPab cddefgxvVUHDah">> = iolist_to_binary(re:replace("ab cddefg","ab cd(?x) de fg","f&LdtKC\\1\\1tP&xvVUHDah",[])),
diff --git a/lib/stdlib/test/re_testoutput1_split_test.erl b/lib/stdlib/test/re_testoutput1_split_test.erl
index e86a04b008..4fc85b95c0 100644
--- a/lib/stdlib/test/re_testoutput1_split_test.erl
+++ b/lib/stdlib/test/re_testoutput1_split_test.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -524,14 +525,14 @@ run() ->
?line <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[{parts,
2}]))),
?line <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�","^\\�",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�","^\\�",[{parts,
+?line <<"">> = iolist_to_binary(join(re:split("","^\\",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("","^\\",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�","^\\�",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�","^�",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�","^�",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("","^\\",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("ÿ","^ÿ",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("ÿ","^ÿ",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�","^�",[]))),
+?line <<":">> = iolist_to_binary(join(re:split("ÿ","^ÿ",[]))),
?line <<"">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[trim]))),
?line <<":">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[{parts,
2}]))),
@@ -22879,14 +22880,14 @@ def","abc$",[]))),
?line <<":abc:">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[{parts,
2}]))),
?line <<":abc:">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[]))),
-?line <<":abc">> = iolist_to_binary(join(re:split("abc�","(abc)\\223",[trim]))),
-?line <<":abc:">> = iolist_to_binary(join(re:split("abc�","(abc)\\223",[{parts,
+?line <<":abc">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[trim]))),
+?line <<":abc:">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[{parts,
2}]))),
-?line <<":abc:">> = iolist_to_binary(join(re:split("abc�","(abc)\\223",[]))),
-?line <<":abc">> = iolist_to_binary(join(re:split("abc�","(abc)\\323",[trim]))),
-?line <<":abc:">> = iolist_to_binary(join(re:split("abc�","(abc)\\323",[{parts,
+?line <<":abc:">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[]))),
+?line <<":abc">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[trim]))),
+?line <<":abc:">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[{parts,
2}]))),
-?line <<":abc:">> = iolist_to_binary(join(re:split("abc�","(abc)\\323",[]))),
+?line <<":abc:">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[]))),
?line <<":abc">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[trim]))),
?line <<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[{parts,
2}]))),
@@ -28929,42 +28930,42 @@ xb","(?!^)x",[multiline]))),
?line <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[{parts,
2}]))),
?line <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[{parts,
+?line <<"">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("REGular","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("regulaer","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("regul�r","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("regul�r","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("Regex","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("regulär","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("regulär","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("regul�r","(?i)reg(?:ul(?:[a�]|ae)r|ex)",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("regulär","(?i)reg(?:ul(?:[aä]|ae)r|ex)",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("Åæåäà","Åæåä[à-ÿÀ-ß]+",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäà","Åæåä[à-ÿÀ-ß]+",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäà","Åæåä[à-ÿÀ-ß]+",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("Åæåäÿ","Åæåä[à-ÿÀ-ß]+",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäÿ","Åæåä[à-ÿÀ-ß]+",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäÿ","Åæåä[à-ÿÀ-ß]+",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("ÅæåäÀ","Åæåä[à-ÿÀ-ß]+",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("ÅæåäÀ","Åæåä[à-ÿÀ-ß]+",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[]))),
-?line <<"">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[trim]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("ÅæåäÀ","Åæåä[à-ÿÀ-ß]+",[]))),
+?line <<"">> = iolist_to_binary(join(re:split("Åæåäß","Åæåä[à-ÿÀ-ß]+",[trim]))),
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäß","Åæåä[à-ÿÀ-ß]+",[{parts,
2}]))),
-?line <<":">> = iolist_to_binary(join(re:split("�����","����[�-��-�]+",[]))),
-?line <<"�XAZ">> = iolist_to_binary(join(re:split("�XAZXB","(?<=Z)X.",[trim]))),
-?line <<"�XAZ:">> = iolist_to_binary(join(re:split("�XAZXB","(?<=Z)X.",[{parts,
+?line <<":">> = iolist_to_binary(join(re:split("Åæåäß","Åæåä[à-ÿÀ-ß]+",[]))),
+?line <<"„XAZ">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[trim]))),
+?line <<"„XAZ:">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[{parts,
2}]))),
-?line <<"�XAZ:">> = iolist_to_binary(join(re:split("�XAZXB","(?<=Z)X.",[]))),
+?line <<"„XAZ:">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[]))),
?line <<"">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[trim]))),
?line <<":">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[{parts,
2}]))),
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index f284276bd7..e2bcdd18ce 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -35,7 +35,7 @@
-import(lists, [foldl/3,reverse/1]).
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?t:minutes(5)),
+ Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -70,65 +70,65 @@ create(Config) when is_list(Config) ->
test_all(fun create_1/1).
create_1(M) ->
- ?line S0 = M:empty(),
- ?line [] = M:to_list(S0),
- ?line 0 = M:size(S0),
- ?line true = M:is_empty(S0),
+ S0 = M(empty, []),
+ [] = M(to_list, S0),
+ 0 = M(size, S0),
+ true = M(is_empty, S0),
E = make_ref(),
- ?line One = M:singleton(E),
- ?line 1 = M:size(One),
- ?line false = M:is_empty(One),
- [E] = M:to_list(One),
+ One = M(singleton, E),
+ 1 = M(size, One),
+ false = M(is_empty, One),
+ [E] = M(to_list, One),
S0.
add_element(Config) when is_list(Config) ->
test_all([{0,132},{253,258},{510,514}], fun add_element_1/2).
add_element_1(List, M) ->
- ?line S = M:from_list(List),
- ?line SortedSet = lists:usort(List),
- ?line SortedSet = lists:sort(M:to_list(S)),
+ S = M(from_list, List),
+ SortedSet = lists:usort(List),
+ SortedSet = lists:sort(M(to_list, S)),
%% Make sure that we get the same result by inserting
%% elements one at the time.
- ?line S2 = foldl(fun(El, Set) -> M:add_element(El, Set) end,
- M:empty(), List),
- ?line true = M:equal(S, S2),
+ S2 = foldl(fun(El, Set) -> M(add_element, {El,Set}) end,
+ M(empty, []), List),
+ true = M(equal, {S,S2}),
%% Insert elements, randomly delete inserted elements,
%% and re-inserted all deleted elements at the end.
- ?line S3 = add_element_del(List, M, M:empty(), [], []),
- ?line true = M:equal(S2, S3),
- ?line true = M:equal(S, S3),
+ S3 = add_element_del(List, M, M(empty, []), [], []),
+ true = M(equal, {S2,S3}),
+ true = M(equal, {S,S3}),
S.
add_element_del([H|T], M, S, Del, []) ->
- add_element_del(T, M, M:add_element(H, S), Del, [H]);
+ add_element_del(T, M, M(add_element, {H,S}), Del, [H]);
add_element_del([H|T], M, S0, Del, Inserted) ->
- S1 = M:add_element(H, S0),
+ S1 = M(add_element, {H,S0}),
case random:uniform(3) of
1 ->
OldEl = lists:nth(random:uniform(length(Inserted)), Inserted),
- S = M:del_element(OldEl, S1),
+ S = M(del_element, {OldEl,S1}),
add_element_del(T, M, S, [OldEl|Del], [H|Inserted]);
_ ->
add_element_del(T, M, S1, Del, [H|Inserted])
end;
add_element_del([], M, S, Del, _) ->
- M:union(S, M:from_list(Del)).
+ M(union, {S,M(from_list, Del)}).
del_element(Config) when is_list(Config) ->
test_all([{0,132},{253,258},{510,514},{1022,1026}], fun del_element_1/2).
del_element_1(List, M) ->
- ?line S0 = M:from_list(List),
- ?line Empty = foldl(fun(El, Set) -> M:del_element(El, Set) end, S0, List),
- ?line Empty = M:empty(),
- ?line M:is_empty(Empty),
- ?line S1 = foldl(fun(El, Set) ->
- M:add_element(El, Set)
- end, S0, reverse(List)),
- ?line true = M:equal(S0, S1),
+ S0 = M(from_list, List),
+ Empty = foldl(fun(El, Set) -> M(del_element, {El,Set}) end, S0, List),
+ Empty = M(empty, []),
+ true = M(is_empty, Empty),
+ S1 = foldl(fun(El, Set) ->
+ M(add_element, {El,Set})
+ end, S0, reverse(List)),
+ true = M(equal, {S0,S1}),
S1.
subtract(Config) when is_list(Config) ->
@@ -138,23 +138,23 @@ subtract(Config) when is_list(Config) ->
test_all([{2,69},{126,130},{253,258},511,512,{1023,1030}], fun subtract_1/2).
subtract_empty(M) ->
- ?line Empty = M:empty(),
- ?line true = M:is_empty(M:subtract(Empty, Empty)),
- M:subtract(Empty, Empty).
+ Empty = M(empty, []),
+ true = M(is_empty, M(subtract, {Empty,Empty})),
+ M(subtract, {Empty,Empty}).
subtract_1(List, M) ->
- ?line S0 = M:from_list(List),
- ?line Empty = M:empty(),
+ S0 = M(from_list, List),
+ Empty = M(empty, []),
%% Trivial cases.
- ?line true = M:is_empty(M:subtract(Empty, S0)),
- ?line true = M:equal(S0, M:subtract(S0, Empty)),
+ true = M(is_empty, M(subtract, {Empty,S0})),
+ true = M(equal, {S0,M(subtract, {S0,Empty})}),
%% Not so trivial.
- ?line subtract_check(List, mutate_some(remove_some(List, 0.4)), M),
- ?line subtract_check(List, rnd_list(length(List) div 2 + 5), M),
- ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M),
- ?line subtract_check(List, mutate_some(List), M).
+ subtract_check(List, mutate_some(remove_some(List, 0.4)), M),
+ subtract_check(List, rnd_list(length(List) div 2 + 5), M),
+ subtract_check(List, rnd_list(length(List) div 7 + 9), M),
+ subtract_check(List, mutate_some(List), M).
subtract_check(A, B, M) ->
one_subtract_check(B, A, M),
@@ -163,12 +163,12 @@ subtract_check(A, B, M) ->
one_subtract_check(A, B, M) ->
ASorted = lists:usort(A),
BSorted = lists:usort(B),
- ASet = M:from_list(A),
- BSet = M:from_list(B),
- DiffSet = M:subtract(ASet, BSet),
+ ASet = M(from_list, A),
+ BSet = M(from_list, B),
+ DiffSet = M(subtract, {ASet,BSet}),
Diff = ASorted -- BSorted,
- true = M:equal(DiffSet, M:from_list(Diff)),
- Diff = lists:sort(M:to_list(DiffSet)),
+ true = M(equal, {DiffSet,M(from_list, Diff)}),
+ Diff = lists:sort(M(to_list, DiffSet)),
DiffSet.
intersection(Config) when is_list(Config) ->
@@ -176,60 +176,60 @@ intersection(Config) when is_list(Config) ->
test_all([{1,65},{126,130},{253,259},{499,513},{1023,1025}], fun intersection_1/2).
intersection_1(List, M) ->
- ?line S0 = M:from_list(List),
+ S0 = M(from_list, List),
%% Intersection with self.
- ?line true = M:equal(S0, M:intersection(S0, S0)),
- ?line true = M:equal(S0, M:intersection([S0,S0])),
- ?line true = M:equal(S0, M:intersection([S0,S0,S0])),
- ?line true = M:equal(S0, M:intersection([S0])),
+ true = M(equal, {S0,M(intersection, {S0,S0})}),
+ true = M(equal, {S0,M(intersection, [S0,S0])}),
+ true = M(equal, {S0,M(intersection, [S0,S0,S0])}),
+ true = M(equal, {S0,M(intersection, [S0])}),
%% Intersection with empty.
- ?line Empty = M:empty(),
- ?line true = M:equal(Empty, M:intersection(S0, Empty)),
- ?line true = M:equal(Empty, M:intersection([S0,Empty,S0,Empty])),
+ Empty = M(empty, []),
+ true = M(equal, {Empty,M(intersection, {S0,Empty})}),
+ true = M(equal, {Empty,M(intersection, [S0,Empty,S0,Empty])}),
%% The intersection of no sets is undefined.
- ?line {'EXIT',_} = (catch M:intersection([])),
+ {'EXIT',_} = (catch M(intersection, [])),
%% Disjoint sets.
- ?line Disjoint = [{El} || El <- List],
- ?line DisjointSet = M:from_list(Disjoint),
- ?line M:is_empty(M:intersection(S0, DisjointSet)),
+ Disjoint = [{El} || El <- List],
+ DisjointSet = M(from_list, Disjoint),
+ true = M(is_empty, M(intersection, {S0,DisjointSet})),
%% Disjoint, different sizes.
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.3)))),
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.7)))),
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.9)))),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.3)), DisjointSet)),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.5)), DisjointSet)),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.9)), DisjointSet)),
+ [begin
+ SomeRemoved = M(from_list, remove_some(Disjoint, HowMuch)),
+ true = M(is_empty, M(intersection, {S0,SomeRemoved})),
+ MoreRemoved = M(from_list, remove_some(List, HowMuch)),
+ true = M(is_empty, M(intersection, {MoreRemoved,DisjointSet}))
+ end || HowMuch <- [0.3,0.5,0.7,0.9]],
%% Partial overlap (one or more elements in result set).
%% The sets have almost the same size. (Almost because a duplicated
%% element in the original list could be mutated and not mutated
%% at the same time.)
- ?line PartialOverlap = mutate_some(List, []),
- ?line IntersectionSet = check_intersection(List, PartialOverlap, M),
- ?line false = M:is_empty(IntersectionSet),
+ PartialOverlap = mutate_some(List, []),
+ IntersectionSet = check_intersection(List, PartialOverlap, M),
+ false = M(is_empty, IntersectionSet),
%% Partial overlap, different set sizes. (Intersection possibly empty.)
- ?line check_intersection(List, remove_some(PartialOverlap, 0.1), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.3), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.5), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.7), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.9), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.1), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.3), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.5), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.7), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.9), M),
IntersectionSet.
check_intersection(Orig, Mutated, M) ->
- OrigSet = M:from_list(Orig),
- MutatedSet = M:from_list(Mutated),
+ OrigSet = M(from_list, Orig),
+ MutatedSet = M(from_list, Mutated),
Intersection = [El || El <- Mutated, not is_tuple(El)],
SortedIntersection = lists:usort(Intersection),
- IntersectionSet = M:intersection(OrigSet, MutatedSet),
- true = M:equal(IntersectionSet, M:from_list(SortedIntersection)),
- SortedIntersection = lists:sort(M:to_list(IntersectionSet)),
+ IntersectionSet = M(intersection, {OrigSet,MutatedSet}),
+ true = M(equal, {IntersectionSet,M(from_list, SortedIntersection)}),
+ SortedIntersection = lists:sort(M(to_list, IntersectionSet)),
IntersectionSet.
@@ -239,63 +239,63 @@ union(Config) when is_list(Config) ->
test_all([{1,71},{125,129},{254,259},{510,513},{1023,1025}], fun union_1/2).
union_1(List, M) ->
- ?line S = M:from_list(List),
+ S = M(from_list, List),
%% Union with self and empty.
- ?line Empty = M:empty(),
- ?line true = M:equal(S, M:union(S, S)),
- ?line true = M:equal(S, M:union([S,S])),
- ?line true = M:equal(S, M:union([S,S,Empty])),
- ?line true = M:equal(S, M:union([S,Empty,S])),
- ?line true = M:equal(S, M:union(S, Empty)),
- ?line true = M:equal(S, M:union([S])),
- ?line true = M:is_empty(M:union([])),
+ Empty = M(empty, []),
+ true = M(equal, {S,M(union, {S,S})}),
+ true = M(equal, {S,M(union, [S,S])}),
+ true = M(equal, {S,M(union, [S,S,Empty])}),
+ true = M(equal, {S,M(union, [S,Empty,S])}),
+ true = M(equal, {S,M(union, {S,Empty})}),
+ true = M(equal, {S,M(union, [S])}),
+ true = M(is_empty, M(union, [])),
%% Partial overlap.
- ?line check_union(List, remove_some(mutate_some(List), 0.9), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.7), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.5), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.3), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.1), M),
-
- ?line check_union(List, mutate_some(remove_some(List, 0.9)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.7)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.5)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.3)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.1)), M).
+ check_union(List, remove_some(mutate_some(List), 0.9), M),
+ check_union(List, remove_some(mutate_some(List), 0.7), M),
+ check_union(List, remove_some(mutate_some(List), 0.5), M),
+ check_union(List, remove_some(mutate_some(List), 0.3), M),
+ check_union(List, remove_some(mutate_some(List), 0.1), M),
+
+ check_union(List, mutate_some(remove_some(List, 0.9)), M),
+ check_union(List, mutate_some(remove_some(List, 0.7)), M),
+ check_union(List, mutate_some(remove_some(List, 0.5)), M),
+ check_union(List, mutate_some(remove_some(List, 0.3)), M),
+ check_union(List, mutate_some(remove_some(List, 0.1)), M).
check_union(Orig, Other, M) ->
- OrigSet = M:from_list(Orig),
- OtherSet = M:from_list(Other),
+ OrigSet = M(from_list, Orig),
+ OtherSet = M(from_list, Other),
Union = Orig++Other,
SortedUnion = lists:usort(Union),
- UnionSet = M:union(OrigSet, OtherSet),
- SortedUnion = lists:sort(M:to_list(UnionSet)),
- M:equal(UnionSet, M:from_list(Union)),
+ UnionSet = M(union, {OrigSet,OtherSet}),
+ SortedUnion = lists:sort(M(to_list, UnionSet)),
+ M(equal, {UnionSet,M(from_list, Union)}),
UnionSet.
is_subset(Config) when is_list(Config) ->
test_all([{1,132},{253,270},{299,311}], fun is_subset_1/2).
is_subset_1(List, M) ->
- ?line S = M:from_list(List),
- ?line Empty = M:empty(),
+ S = M(from_list, List),
+ Empty = M(empty, []),
%% Subset of empty and self.
- ?line true = M:is_subset(Empty, Empty),
- ?line true = M:is_subset(Empty, S),
- ?line false = M:is_subset(S, Empty),
- ?line true = M:is_subset(S, S),
+ true = M(is_subset, {Empty,Empty}),
+ true = M(is_subset, {Empty,S}),
+ false = M(is_subset, {S,Empty}),
+ true = M(is_subset, {S,S}),
%% Other cases.
- Res = [?line false = M:is_subset(M:singleton(make_ref()), S),
- ?line true = M:is_subset(M:singleton(hd(List)), S),
- ?line true = check_subset(remove_some(List, 0.1), List, M),
- ?line true = check_subset(remove_some(List, 0.5), List, M),
- ?line true = check_subset(remove_some(List, 0.9), List, M),
- ?line check_subset(mutate_some(List), List, M),
- ?line check_subset(rnd_list(length(List) div 2 + 5), List, M),
- ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M)
+ Res = [false = M(is_subset, {M(singleton, make_ref()),S}),
+ true = M(is_subset, {M(singleton, hd(List)),S}),
+ true = check_subset(remove_some(List, 0.1), List, M),
+ true = check_subset(remove_some(List, 0.5), List, M),
+ true = check_subset(remove_some(List, 0.9), List, M),
+ check_subset(mutate_some(List), List, M),
+ check_subset(rnd_list(length(List) div 2 + 5), List, M),
+ subtract_check(List, rnd_list(length(List) div 7 + 9), M)
],
res_to_set(Res, M, 0, []).
@@ -304,12 +304,12 @@ check_subset(X, Y, M) ->
check_one_subset(X, Y, M).
check_one_subset(X, Y, M) ->
- XSet = M:from_list(X),
- YSet = M:from_list(Y),
+ XSet = M(from_list, X),
+ YSet = M(from_list, Y),
SortedX = lists:usort(X),
SortedY = lists:usort(Y),
IsSubSet = length(SortedY--SortedX) =:= length(SortedY) - length(SortedX),
- IsSubSet = M:is_subset(XSet, YSet),
+ IsSubSet = M(is_subset, {XSet,YSet}),
IsSubSet.
%% Encode all test results as a set to return.
@@ -317,54 +317,54 @@ res_to_set([true|T], M, I, Acc) ->
res_to_set(T, M, I+1, [I|Acc]);
res_to_set([_|T], M, I, Acc) ->
res_to_set(T, M, I+1, Acc);
-res_to_set([], M, _, Acc) -> M:from_list(Acc).
+res_to_set([], M, _, Acc) -> M(from_list, Acc).
is_set(Config) when is_list(Config) ->
%% is_set/1 is tested in the other test cases when its argument
%% is a set. Here test some arguments that makes it return false.
- ?line false = gb_sets:is_set([a,b]),
- ?line false = gb_sets:is_set({a,very,bad,tuple}),
+ false = gb_sets:is_set([a,b]),
+ false = gb_sets:is_set({a,very,bad,tuple}),
- ?line false = sets:is_set([a,b]),
- ?line false = sets:is_set({a,very,bad,tuple}),
+ false = sets:is_set([a,b]),
+ false = sets:is_set({a,very,bad,tuple}),
- ?line false = ordsets:is_set([b,a]),
- ?line false = ordsets:is_set({bad,tuple}),
+ false = ordsets:is_set([b,a]),
+ false = ordsets:is_set({bad,tuple}),
%% Now test values that are known to be bad for all set representations.
test_all(fun is_set_1/1).
is_set_1(M) ->
- ?line false = M:is_set(self()),
- ?line false = M:is_set(blurf),
- ?line false = M:is_set(make_ref()),
- ?line false = M:is_set(<<1,2,3>>),
- ?line false = M:is_set(42),
- ?line false = M:is_set(math:pi()),
- ?line false = M:is_set({}),
- M:empty().
+ false = M(is_set, self()),
+ false = M(is_set, blurf),
+ false = M(is_set, make_ref()),
+ false = M(is_set, <<1,2,3>>),
+ false = M(is_set, 42),
+ false = M(is_set, math:pi()),
+ false = M(is_set, {}),
+ M(empty, []).
fold(Config) when is_list(Config) ->
test_all([{0,71},{125,129},{254,259},{510,513},{1023,1025},{9999,10001}],
fun fold_1/2).
fold_1(List, M) ->
- ?line S = M:from_list(List),
- ?line L = M:fold(fun(E, A) -> [E|A] end, [], S),
- ?line true = lists:sort(L) =:= lists:usort(List),
- M:empty().
+ S = M(from_list, List),
+ L = M(fold, {fun(E, A) -> [E|A] end,[],S}),
+ true = lists:sort(L) =:= lists:usort(List),
+ M(empty, []).
filter(Config) when is_list(Config) ->
test_all([{0,69},{126,130},{254,259},{510,513},{1023,1025},{7999,8000}],
fun filter_1/2).
filter_1(List, M) ->
- ?line S = M:from_list(List),
+ S = M(from_list, List),
IsNumber = fun(X) -> is_number(X) end,
- ?line M:equal(M:from_list(lists:filter(IsNumber, List)),
- M:filter(IsNumber, S)),
- ?line M:filter(fun(X) -> is_atom(X) end, S).
+ M(equal, {M(from_list, lists:filter(IsNumber, List)),
+ M(filter, {IsNumber,S})}),
+ M(filter, {fun(X) -> is_atom(X) end,S}).
%%%
%%% Test specifics for gb_sets.
@@ -375,26 +375,26 @@ take_smallest(Config) when is_list(Config) ->
fun take_smallest_1/2).
take_smallest_1(List, M) ->
- case M:module() of
+ case M(module, []) of
gb_sets -> take_smallest_2(List, M);
_ -> ok
end,
- M:empty().
+ M(empty, []).
take_smallest_2(List0, M) ->
- ?line List = lists:usort(List0),
- ?line S = M:from_list(List0),
+ List = lists:usort(List0),
+ S = M(from_list, List0),
take_smallest_3(S, List, M).
take_smallest_3(S0, List0, M) ->
- case M:is_empty(S0) of
+ case M(is_empty, S0) of
true -> ok;
false ->
- ?line Smallest = hd(List0),
- ?line Smallest = gb_sets:smallest(S0),
- ?line {Smallest,S} = gb_sets:take_smallest(S0),
- ?line List = tl(List0),
- ?line true = gb_sets:to_list(S) =:= List,
+ Smallest = hd(List0),
+ Smallest = gb_sets:smallest(S0),
+ {Smallest,S} = gb_sets:take_smallest(S0),
+ List = tl(List0),
+ true = gb_sets:to_list(S) =:= List,
take_smallest_3(S, List, M)
end.
@@ -403,26 +403,26 @@ take_largest(Config) when is_list(Config) ->
fun take_largest_1/2).
take_largest_1(List, M) ->
- case M:module() of
+ case M(module, []) of
gb_sets -> take_largest_2(List, M);
_ -> ok
end,
- M:empty().
+ M(empty, []).
take_largest_2(List0, M) ->
- ?line List = reverse(lists:usort(List0)),
- ?line S = M:from_list(List0),
+ List = reverse(lists:usort(List0)),
+ S = M(from_list, List0),
take_largest_3(S, List, M).
take_largest_3(S0, List0, M) ->
- case M:is_empty(S0) of
+ case M(is_empty, S0) of
true -> ok;
false ->
- ?line Largest = hd(List0),
- ?line Largest = gb_sets:largest(S0),
- ?line {Largest,S} = gb_sets:take_largest(S0),
- ?line List = tl(List0),
- ?line true = gb_sets:to_list(S) =:= reverse(List),
+ Largest = hd(List0),
+ Largest = gb_sets:largest(S0),
+ {Largest,S} = gb_sets:take_largest(S0),
+ List = tl(List0),
+ true = gb_sets:to_list(S) =:= reverse(List),
take_largest_3(S, List, M)
end.
@@ -441,23 +441,23 @@ sets_mods() ->
[Ordsets,Sets,Gb].
test_all(Tester) ->
- ?line Res = [begin
- random:seed(1, 2, 42),
- S = Tester(M),
- {M:size(S),lists:sort(M:to_list(S))}
- end || M <- sets_mods()],
- ?line all_same(Res).
+ Res = [begin
+ random:seed(1, 2, 42),
+ S = Tester(M),
+ {M(size, S),lists:sort(M(to_list, S))}
+ end || M <- sets_mods()],
+ all_same(Res).
test_all([{Low,High}|T], Tester) ->
test_all(lists:seq(Low, High)++T, Tester);
test_all([Sz|T], Tester) when is_integer(Sz) ->
List = rnd_list(Sz),
- ?line Res = [begin
+ Res = [begin
random:seed(19, 2, Sz),
S = Tester(List, M),
- {M:size(S),lists:sort(M:to_list(S))}
+ {M(size, S),lists:sort(M(to_list, S))}
end || M <- sets_mods()],
- ?line all_same(Res),
+ all_same(Res),
test_all(T, Tester);
test_all([], _) -> ok.
diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl
index bdfb0d59d2..fd4ec2bac3 100644
--- a/lib/stdlib/test/sets_test_lib.erl
+++ b/lib/stdlib/test/sets_test_lib.erl
@@ -17,91 +17,89 @@
%% %CopyrightEnd%
%%
--module(sets_test_lib, [Mod,Equal]).
-
--export([module/0,equal/2,empty/0,from_list/1,to_list/1,singleton/1,
- add_element/2,del_element/2,size/1,is_empty/1,is_set/1,
- intersection/1,intersection/2,subtract/2,
- union/1,union/2,is_subset/2,fold/3,filter/2]).
-
-module() ->
- Mod.
-
-equal(X, Y) ->
- Equal(X, Y).
-
-empty() ->
- Mod:new().
-
-from_list(L) ->
- Mod:from_list(L).
-
-to_list(S) ->
- Mod:to_list(S).
+-module(sets_test_lib).
+
+-export([new/2]).
+
+new(Mod, Eq) ->
+ fun (add_element, {El,S}) -> add_element(Mod, El, S);
+ (del_element, {El,S}) -> del_element(Mod, El, S);
+ (empty, []) -> Mod:new();
+ (equal, {S1,S2}) -> Eq(S1, S2);
+ (filter, {F,S}) -> filter(Mod, F, S);
+ (fold, {F,A,S}) -> fold(Mod, F, A, S);
+ (from_list, L) -> Mod:from_list(L);
+ (intersection, {S1,S2}) -> intersection(Mod, Eq, S1, S2);
+ (intersection, Ss) -> intersection(Mod, Eq, Ss);
+ (is_empty, S) -> is_empty(Mod, S);
+ (is_set, S) -> Mod:is_set(S);
+ (is_subset, {S,Set}) -> is_subset(Mod, Eq, S, Set);
+ (module, []) -> Mod;
+ (singleton, E) -> singleton(Mod, E);
+ (size, S) -> Mod:size(S);
+ (subtract, {S1,S2}) -> subtract(Mod, S1, S2);
+ (to_list, S) -> Mod:to_list(S);
+ (union, {S1,S2}) -> union(Mod, Eq, S1, S2);
+ (union, Ss) -> union(Mod, Eq, Ss)
+ end.
-singleton(E) ->
+singleton(Mod, E) ->
case erlang:function_exported(Mod, singleton, 1) of
true -> Mod:singleton(E);
- false -> from_list([E])
+ false -> Mod:from_list([E])
end.
-add_element(El, S0) ->
+add_element(Mod, El, S0) ->
S = Mod:add_element(El, S0),
true = Mod:is_element(El, S),
- false = is_empty(S),
+ false = is_empty(Mod, S),
true = Mod:is_set(S),
S.
-del_element(El, S0) ->
+del_element(Mod, El, S0) ->
S = Mod:del_element(El, S0),
false = Mod:is_element(El, S),
true = Mod:is_set(S),
S.
-size(S) ->
- Mod:size(S).
-
-is_empty(S) ->
+is_empty(Mod, S) ->
true = Mod:is_set(S),
case erlang:function_exported(Mod, is_empty, 1) of
true -> Mod:is_empty(S);
false -> Mod:size(S) == 0
end.
-is_set(S) ->
- Mod:is_set(S).
-
-intersection(S1, S2) ->
+intersection(Mod, Equal, S1, S2) ->
S = Mod:intersection(S1, S2),
true = Equal(S, Mod:intersection(S2, S1)),
- Disjoint = is_empty(S),
+ Disjoint = is_empty(Mod, S),
Disjoint = Mod:is_disjoint(S1, S2),
Disjoint = Mod:is_disjoint(S2, S1),
S.
-intersection(Ss) ->
+intersection(Mod, Equal, Ss) ->
S = Mod:intersection(Ss),
true = Equal(S, Mod:intersection(lists:reverse(Ss))),
S.
-subtract(S1, S2) ->
+subtract(Mod, S1, S2) ->
S = Mod:subtract(S1, S2),
true = Mod:is_set(S),
true = Mod:size(S) =< Mod:size(S1),
S.
-union(S1, S2) ->
+union(Mod, Equal, S1, S2) ->
S = Mod:union(S1, S2),
true = Equal(S, Mod:union(S2, S1)),
true = Mod:is_set(S),
S.
-union(Ss) ->
+union(Mod, Equal, Ss) ->
S = Mod:union(Ss),
true = Equal(S, Mod:union(lists:reverse(Ss))),
S.
-is_subset(S, Set) ->
+is_subset(Mod, Equal, S, Set) ->
case Mod:is_subset(S, Set) of
false -> false;
true ->
@@ -115,10 +113,10 @@ is_subset(S, Set) ->
true
end.
-fold(F, A, S) ->
+fold(Mod, F, A, S) ->
true = Mod:is_set(S),
Mod:fold(F, A, S).
-filter(F, S) ->
+filter(Mod, F, S) ->
true = Mod:is_set(S),
Mod:filter(F, S).
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 4b83e42ee0..a32f846bd2 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -29,7 +29,7 @@
progex_bit_syntax/1, progex_records/1,
progex_lc/1, progex_funs/1,
otp_5990/1, otp_6166/1, otp_6554/1, otp_6785/1,
- otp_7184/1, otp_7232/1, otp_8393/1]).
+ otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1]).
-export([ start_restricted_from_shell/1,
start_restricted_on_command_line/1,restricted_local/1]).
@@ -93,7 +93,7 @@ groups() ->
progex_funs]},
{tickets, [],
[otp_5990, otp_6166, otp_6554, otp_6785, otp_7184,
- otp_7232, otp_8393]}].
+ otp_7232, otp_8393, otp_10302]}].
init_per_suite(Config) ->
Config.
@@ -108,7 +108,7 @@ end_per_group(_GroupName, Config) ->
Config.
--record(state, {bin, reply, leader}).
+-record(state, {bin, reply, leader, unic = latin1}).
start_restricted_from_shell(doc) ->
@@ -374,15 +374,18 @@ records(Config) when is_list(Config) ->
MS = ?MODULE_STRING,
RR1 = "rr(" ++ MS ++ "). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR1),
RR2 = "rr(" ++ MS ++ ",[state]). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR2),
RR3 = "rr(" ++ MS ++ ",'_'). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR3),
RR4 = "rr(" ++ MS ++ ", '_', {d,test1}).",
?line [[state]] = scan(RR4),
@@ -817,9 +820,6 @@ otp_5916(Config) when is_list(Config) ->
true = if is_record(#r1{},r1,3) -> true; true -> false end,
false = if 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,
-
ok.">>,
[ok] = scan(C),
ok.
@@ -2282,12 +2282,6 @@ otp_5990(doc) ->
otp_5990(suite) -> [];
otp_5990(Config) when is_list(Config) ->
?line [true] =
- scan(<<"rd(foo,{bar}), {erlang,is_record}(#foo{}, foo).">>),
- ?line [3] =
- scan(<<"rd(foo,{bar}), A = #foo{}, "
- "{if {erlang,is_record}(A, foo) -> erlang; "
- "true -> not_a_module end, length}([1,2,3]).">>),
- ?line [true] =
scan(<<"rd('OrdSet', {orddata = {},ordtype = type}), "
"S = #'OrdSet'{ordtype = {}}, "
"if tuple(S#'OrdSet'.ordtype) -> true; true -> false end.">>),
@@ -2757,6 +2751,143 @@ prompt_err(B) ->
S = string:strip(S2, both, $"),
string:strip(S, right, $.).
+otp_10302(doc) ->
+ "OTP-10302. Unicode.";
+otp_10302(suite) -> [];
+otp_10302(Config) when is_list(Config) ->
+ Test1 =
+ <<"begin
+ io:setopts([{encoding,utf8}]),
+ [1024] = \"\\x{400}\",
+ rd(rec, {a = \"\\x{400}\"}),
+ ok = rl(rec)
+ end.">>,
+ "-record(rec,{a = \"\x{400}\"}).\nok.\n" = t(Test1),
+
+ Test3 =
+ <<"io:setopts([{encoding,utf8}]).
+ rd(rec, {a = \"\\x{400}\"}).
+ ok = rp(#rec{}).">>,
+ "ok.\nrec\n#rec{a = \"\x{400}\"}.\nok.\n" = t(Test3),
+
+ Test4 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = [1024] = \"\\x{400}\".
+ b().
+ h().">>,
+
+ "ok.\n\"\x{400}\"\nA = \"\x{400}\".\nok.\n"
+ "1: io:setopts([{encoding,utf8}])\n-> ok.\n"
+ "2: A = [1024] = \"\x{400}\"\n-> \"\x{400}\"\n"
+ "3: b()\n-> ok.\nok.\n" = t(Test4),
+
+ Test5 =
+ <<"begin
+ io:setopts([{encoding,utf8}]),
+ results(0),
+ A = [1024] = \"\\x{400}\",
+ b(),
+ h()
+ end.">>,
+ "A = \"\x{400}\".\nok.\n" = t(Test5),
+
+ %% One $" is "lost":
+ true =
+ "\x{400}\": command not found" =:=
+ prompt_err({<<"io:setopts([{encoding,utf8}]). v(\"\x{400}\")."/utf8>>,
+ unicode}),
+
+ "ok.\ndefault\n* Bad prompt function: \"\x{400}\".\n" =
+ t({<<"io:setopts([{encoding,utf8}]). "
+ "shell:prompt_func(\"\x{400}\")."/utf8>>,
+ unicode}),
+ _ = shell:prompt_func(default),
+
+ %% Test lib:format_exception() (cf. OTP-6554)
+ Test6 =
+ <<"begin
+ A = <<\"\\xaa\">>,
+ S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B)
+ end.">>,
+
+ "** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as <<\"\xaa\">> / <<\"\xaa\">>.\n" = t(Test6),
+ Test7 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = <<\"\\xaa\">>,
+ S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).">>,
+
+ "ok.\n** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as <<170>> / <<170>>.\n" = t(Test7),
+ Test8 =
+ <<"begin
+ A = [1089],
+ S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B)
+ end.">>,
+ "** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as [1089] / [1089].\n" = t(Test8),
+ Test9 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = [1089],
+ S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).">>,
+
+ "ok.\n** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as \"\x{441}\" / \"\x{441}\".\n" = t(Test9),
+ Test10 =
+ <<"A = {\"1\\xaa\",
+ $\\xaa,
+ << <<\"hi\">>/binary >>,
+ <<\"1\xaa\">>},
+ fun(a) -> true end(A).">>,
+ "** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'"
+ "({\"1\xc2\xaa\",170,<<\"hi\">>,\n "
+ " <<\"1\xc2\xaa\">>}) .\n" = t(Test10),
+ Test11 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = {\"1\\xaa\",
+ $\\xaa,
+ << <<\"hi\">>/binary >>,
+ <<\"1\xaa\">>},
+ fun(a) -> true end(A).">>,
+
+ "ok.\n** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'"
+ "({\"1\xaa\",170,<<\"hi\">>,\n "
+ " <<\"1\xaa\"/utf8>>}) .\n" = t(Test11),
+ Test12 = <<"fun(a, b) -> false end(65, [1089]).">>,
+ "** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'(65,[1089])"
+ " .\n" = t(Test12),
+ Test13 =
+ <<"io:setopts([{encoding,utf8}]).
+ fun(a, b) -> false end(65, [1089]).">>,
+ "ok.\n** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'(65,\"\x{441}\")"
+ " .\n" = t(Test13),
+
+ ok.
+
scan(B) ->
F = fun(Ts) ->
case erl_parse:parse_term(Ts) of
@@ -2770,7 +2901,7 @@ scan(B) ->
scan(t(B), F).
scan(S0, F) ->
- case erl_scan:tokens([], S0, 1) of
+ case erl_scan:tokens([], S0, 1, [unicode]) of
{done,{ok,Ts,_},S} ->
[F(Ts) | scan(S, F)];
_Else ->
@@ -2778,29 +2909,36 @@ scan(S0, F) ->
end.
t({Node,Bin}) when is_atom(Node),is_binary(Bin) ->
- t0(Bin, fun() -> start_new_shell(Node) end);
+ t0({Bin,latin1}, fun() -> start_new_shell(Node) end);
t(Bin) when is_binary(Bin) ->
- t0(Bin, fun() -> start_new_shell() end);
+ t0({Bin,latin1}, fun() -> start_new_shell() end);
+t({Bin,Enc}) when is_binary(Bin), is_atom(Enc) ->
+ t0({Bin,Enc}, fun() -> start_new_shell() end);
t(L) ->
t(list_to_binary(L)).
-t0(Bin, F) ->
+t0({Bin,Enc}, F) ->
%% Spawn a process so that io_request messages do not interfer.
P = self(),
- C = spawn(fun() -> t1(P, Bin, F) end),
+ C = spawn(fun() -> t1(P, {Bin, Enc}, F) end),
receive {C, R} -> R end.
-t1(Parent, Bin, F) ->
- %% io:format("*** Testing ~s~n", [binary_to_list(Bin)]),
- S = #state{bin = Bin, reply = [], leader = group_leader()},
+t1(Parent, {Bin,Enc}, F) ->
+ io:format("*** Testing ~s~n", [binary_to_list(Bin)]),
+ S = #state{bin = Bin, unic = Enc, reply = [], leader = group_leader()},
group_leader(self(), self()),
_Shell = F(),
try
server_loop(S)
catch exit:R -> Parent ! {self(), R};
- throw:{?MODULE,LoopReply} ->
+ throw:{?MODULE,LoopReply,latin1} ->
L0 = binary_to_list(list_to_binary(LoopReply)),
[$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
+ Parent ! {self(), dotify(L1)};
+ throw:{?MODULE,LoopReply,_Uni} ->
+ Tmp = unicode:characters_to_binary(LoopReply),
+ L0 = unicode:characters_to_list(Tmp),
+ [$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
Parent ! {self(), dotify(L1)}
after group_leader(S#state.leader, self())
end.
@@ -2844,7 +2982,7 @@ do_io_request(Req, From, S, ReplyAs) ->
case io_requests([Req], [], S) of
{_Status,{eof,_},S1} ->
io_reply(From, ReplyAs, {error,terminated}),
- throw({?MODULE,S1#state.reply});
+ throw({?MODULE,S1#state.reply,S1#state.unic});
{_Status,Reply,S1} ->
io_reply(From, ReplyAs, Reply),
S1
@@ -2867,13 +3005,34 @@ io_requests([], [Rs|Cont], S) ->
io_requests([], [], S) ->
{ok,ok,S}.
+io_request({setopts, Opts}, S) ->
+ #state{unic = OldEnc, bin = Bin} = S,
+ NewEnc = case proplists:get_value(encoding, Opts) of
+ undefined -> OldEnc;
+ utf8 -> unicode;
+ New -> New
+ end,
+ NewBin = case {OldEnc, NewEnc} of
+ {E, E} -> Bin;
+ {latin1, _} ->
+ unicode:characters_to_binary(Bin, latin1, unicode);
+ {_, latin1} ->
+ unicode:characters_to_binary(Bin, unicode, latin1);
+ {_, _} -> Bin
+ end,
+ {ok, ok, S#state{unic = NewEnc, bin = NewBin}};
+io_request(getopts, S) ->
+ {ok,[{encoding,S#state.unic}],S};
io_request({get_geometry,columns}, S) ->
{ok,80,S};
io_request({get_geometry,rows}, S) ->
{ok,24,S};
io_request({put_chars,Chars}, S) ->
{ok,ok,S#state{reply = [S#state.reply | Chars]}};
-io_request({put_chars,_,Chars}, S) ->
+io_request({put_chars,latin1,Chars}, S) ->
+ {ok,ok,S#state{reply = [S#state.reply | Chars]}};
+io_request({put_chars,unicode,Chars0}, S) ->
+ Chars = unicode:characters_to_list(Chars0),
{ok,ok,S#state{reply = [S#state.reply | Chars]}};
io_request({put_chars,Mod,Func,Args}, S) ->
case catch apply(Mod, Func, Args) of
@@ -2899,9 +3058,12 @@ get_until_loop(M, F, As, S, {more,Cont}, Enc) ->
0 ->
get_until_loop(M, F, As, S,
catch apply(M, F, [Cont,eof|As]), Enc);
+ _ when S#state.unic =:= latin1 ->
+ get_until_loop(M, F, As, S#state{bin = <<>>},
+ catch apply(M, F, [Cont,binary_to_list(Bin)|As]), Enc);
_ ->
get_until_loop(M, F, As, S#state{bin = <<>>},
- catch apply(M, F, [Cont,binary_to_list(Bin)|As]), Enc)
+ catch apply(M, F, [Cont,unicode:characters_to_list(Bin)|As]), Enc)
end;
get_until_loop(_M, _F, _As, S, {done,Res,Buf}, Enc) ->
{ok,Res,S#state{bin = buf2bin(Buf, Enc)}};
@@ -2912,6 +3074,8 @@ buf2bin(eof,_) ->
<<>>;
buf2bin(Buf,latin1) ->
list_to_binary(Buf);
+buf2bin(Buf,utf8) ->
+ unicode:characters_to_binary(Buf,unicode,unicode);
buf2bin(Buf,unicode) ->
unicode:characters_to_binary(Buf,unicode,unicode).
diff --git a/lib/stdlib/test/stdlib.cover b/lib/stdlib/test/stdlib.cover
index 61f4f064b9..e71be880cb 100644
--- a/lib/stdlib/test/stdlib.cover
+++ b/lib/stdlib/test/stdlib.cover
@@ -1,17 +1,2 @@
%% -*- erlang -*-
{incl_app,stdlib,details}.
-
-{excl_mods,stdlib,
- [erl_parse,
- erl_eval,
- ets,
- filename,
- gen_event,
- gen_server,
- gen,
- lists,
- io,
- io_lib,
- io_lib_format,
- io_lib_pretty,
- proc_lib]}.
diff --git a/lib/stdlib/test/stdlib.spec.vxworks b/lib/stdlib/test/stdlib.spec.vxworks
deleted file mode 100644
index ddc804b831..0000000000
--- a/lib/stdlib/test/stdlib.spec.vxworks
+++ /dev/null
@@ -1,8 +0,0 @@
-{topcase, {dir, "../stdlib_test"}}.
-{skip,{dets_SUITE,"Not runnable VxWorks/NFS"}}.
-{skip,{slave_SUITE,"VxWorks: slave nodes are not supported"}}.
-{skip,{tar_SUITE,errors,"VxWorks filesystem too primitive"}}.
-{skip,{tar_SUITE,create_long_names,"VxWorks names too short"}}.
-{skip,{epp_SUITE,"Test not adopted to VxWorks"}}.
-{skip,{select_SUITE,"Test too memory consuming for VxWorks"}}.
-{skip,{beam_lib_SUITE,error,"All sections not present in stripped beam files"}}.
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl
index 6969c095a0..96e653985f 100644
--- a/lib/stdlib/test/string_SUITE.erl
+++ b/lib/stdlib/test/string_SUITE.erl
@@ -1,7 +1,8 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -473,8 +474,8 @@ to_upper_to_lower(suite) ->
to_upper_to_lower(doc) ->
[];
to_upper_to_lower(Config) when is_list(Config) ->
- ?line "1234ABCDEF���=" = string:to_upper("1234abcdef���="),
- ?line "����������abc()" = string:to_lower("����������abc()"),
+ ?line "1234ABCDEFÅÄÖ=" = string:to_upper("1234abcdefåäö="),
+ ?line "éèíúùòóåäöabc()" = string:to_lower("ÉÈÍÚÙÒÓÅÄÖabc()"),
?line All = lists:seq(0, 255),
?line UC = string:to_upper(All),
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 767ae3d62c..569c66959e 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -46,6 +46,7 @@
temporary_normal/1,
permanent_shutdown/1, transient_shutdown/1,
temporary_shutdown/1,
+ faulty_application_shutdown/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1, temporary_bystander/1]).
@@ -98,7 +99,8 @@ groups() ->
{normal_termination, [],
[permanent_normal, transient_normal, temporary_normal]},
{shutdown_termination, [],
- [permanent_shutdown, transient_shutdown, temporary_shutdown]},
+ [permanent_shutdown, transient_shutdown, temporary_shutdown,
+ faulty_application_shutdown]},
{abnormal_termination, [],
[permanent_abnormal, transient_abnormal,
temporary_abnormal]},
@@ -659,6 +661,39 @@ temporary_shutdown(Config) when is_list(Config) ->
[0,0,0,0] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
+%% Faulty application should shutdown and pass on errors
+faulty_application_shutdown(Config) when is_list(Config) ->
+
+ %% Set some paths
+ AppDir = filename:join(?config(data_dir, Config), "app_faulty"),
+ EbinDir = filename:join(AppDir, "ebin"),
+
+ %% Start faulty app
+ code:add_patha(EbinDir),
+
+ %% {error,
+ %% {{shutdown,
+ %% {failed_to_start_child,
+ %% app_faulty,
+ %% {undef,
+ %% [{an_undefined_module_with,an_undefined_function,[argument1,argument2],
+ %% []},
+ %% {app_faulty_server,init,1,
+ %% [{file,"app_faulty/src/app_faulty_server.erl"},{line,16}]},
+ %% {gen_server,init_it,6,
+ %% [{file,"gen_server.erl"},{line,304}]},
+ %% {proc_lib,init_p_do_apply,3,
+ %% [{file,"proc_lib.erl"},{line,227}]}]}}},
+ %% {app_faulty,start,[normal,[]]}}}
+
+ {error, Error} = application:start(app_faulty),
+ {{shutdown, {failed_to_start_child,app_faulty,{undef, CallStack}}},
+ {app_faulty,start,_}} = Error,
+ [{an_undefined_module_with,an_undefined_function,_,_}|_] = CallStack,
+ ok = application:unload(app_faulty),
+ ok.
+
+%%-------------------------------------------------------------------------
%% A permanent child should always be restarted.
permanent_abnormal(Config) when is_list(Config) ->
{ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
diff --git a/lib/stdlib/test/supervisor_SUITE_data/Makefile.src b/lib/stdlib/test/supervisor_SUITE_data/Makefile.src
new file mode 100644
index 0000000000..dbc5729f47
--- /dev/null
+++ b/lib/stdlib/test/supervisor_SUITE_data/Makefile.src
@@ -0,0 +1,15 @@
+EFLAGS=+debug_info
+
+APP_FAULTY= \
+ app_faulty/ebin/app_faulty_sup.@EMULATOR@ \
+ app_faulty/ebin/app_faulty_server.@EMULATOR@ \
+ app_faulty/ebin/app_faulty.@EMULATOR@ \
+
+all: $(APP_FAULTY)
+
+app_faulty/ebin/app_faulty_server.@EMULATOR@: app_faulty/src/app_faulty_server.erl
+ erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty_server.erl
+app_faulty/ebin/app_faulty_sup.@EMULATOR@: app_faulty/src/app_faulty_sup.erl
+ erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty_sup.erl
+app_faulty/ebin/app_faulty.@EMULATOR@: app_faulty/src/app_faulty.erl
+ erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty.erl
diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app
new file mode 100644
index 0000000000..d4ab07e485
--- /dev/null
+++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app
@@ -0,0 +1,10 @@
+{application, app_faulty,
+ [{description, "very simple example faulty application"},
+ {id, "app_faulty"},
+ {vsn, "1.0"},
+ {modules, [app_faulty, app_faulty_sup, app_faulty_server]},
+ {registered, [app_faulty]},
+ {applications, [kernel, stdlib]},
+ {env, [{var,val1}]},
+ {mod, {app_faulty, []}}
+ ]}.
diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl
new file mode 100644
index 0000000000..c65b411cd6
--- /dev/null
+++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl
@@ -0,0 +1,17 @@
+-module(app_faulty).
+
+-behaviour(application).
+
+%% Application callbacks
+-export([start/2, stop/1]).
+
+start(_Type, _StartArgs) ->
+ case app_faulty_sup:start_link() of
+ {ok, Pid} ->
+ {ok, Pid};
+ Error ->
+ Error
+ end.
+
+stop(_State) ->
+ ok.
diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl
new file mode 100644
index 0000000000..6628f92210
--- /dev/null
+++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl
@@ -0,0 +1,32 @@
+-module(app_faulty_server).
+
+-behaviour(gen_server).
+
+%% API
+-export([start_link/0]).
+
+%% gen_server callbacks
+-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
+ terminate/2, code_change/3]).
+
+start_link() ->
+ gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
+
+init([]) ->
+ an_undefined_module_with:an_undefined_function(argument1, argument2),
+ {ok, []}.
+
+handle_call(_Request, _From, State) ->
+ {reply, ok, State}.
+
+handle_cast(_Msg, State) ->
+ {noreply, State}.
+
+handle_info(_Info, State) ->
+ {noreply, State}.
+
+terminate(_Reason, _State) ->
+ ok.
+
+code_change(_OldVsn, State, _Extra) ->
+ {ok, State}.
diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl
new file mode 100644
index 0000000000..8115a88809
--- /dev/null
+++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl
@@ -0,0 +1,17 @@
+-module(app_faulty_sup).
+
+-behaviour(supervisor).
+
+%% API
+-export([start_link/0]).
+
+%% Supervisor callbacks
+-export([init/1]).
+
+start_link() ->
+ supervisor:start_link(?MODULE, []).
+
+init([]) ->
+ AChild = {app_faulty,{app_faulty_server,start_link,[]},
+ permanent,2000,worker,[app_faulty_server]},
+ {ok,{{one_for_all,0,1}, [AChild]}}.
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index fe039e8bcc..b2e1d12b2a 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_SUITE.erl
@@ -56,70 +56,60 @@ end_per_group(_GroupName, Config) ->
log(suite) -> [];
log(Config) when is_list(Config) ->
- ?line {ok,_Server} = start(),
- ?line ok = sys:log(?server,true),
- ?line {ok,-44} = public_call(44),
- ?line ok = sys:log(?server,false),
- ?line ok = sys:log(?server,print),
- ?line stop(),
+ {ok,_Server} = start(),
+ ok = sys:log(?server,true),
+ {ok,-44} = public_call(44),
+ ok = sys:log(?server,false),
+ ok = sys:log(?server,print),
+ stop(),
ok.
log_to_file(suite) -> [];
log_to_file(Config) when is_list(Config) ->
TempName = test_server:temp_name(?config(priv_dir,Config) ++ "sys."),
- ?line {ok,_Server} = start(),
- ?line ok = sys:log_to_file(?server,TempName),
- ?line {ok,-44} = public_call(44),
- ?line ok = sys:log_to_file(?server,false),
- ?line {ok,Fd} = file:open(TempName,[read]),
- ?line Msg1 = io:get_line(Fd,''),
- ?line Msg2 = io:get_line(Fd,''),
- ?line file:close(Fd),
- ?line lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1),
- ?line lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2),
- ?line stop(),
+ {ok,_Server} = start(),
+ ok = sys:log_to_file(?server,TempName),
+ {ok,-44} = public_call(44),
+ ok = sys:log_to_file(?server,false),
+ {ok,Fd} = file:open(TempName,[read]),
+ Msg1 = io:get_line(Fd,''),
+ Msg2 = io:get_line(Fd,''),
+ file:close(Fd),
+ lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1),
+ lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2),
+ stop(),
ok.
stats(suite) -> [];
stats(Config) when is_list(Config) ->
- ?line Self = self(),
- ?line {ok,_Server} = start(),
- ?line ok = sys:statistics(?server,true),
- ?line {ok,-44} = public_call(44),
- ?line {ok,Stats} = sys:statistics(?server,get),
- ?line lists:member({messages_in,1},Stats),
- ?line lists:member({messages_out,1},Stats),
- ?line ok = sys:statistics(?server,false),
- ?line {status,_Pid,{module,_Mod},[_PDict,running,Self,_,_]} =
+ Self = self(),
+ {ok,_Server} = start(),
+ ok = sys:statistics(?server,true),
+ {ok,-44} = public_call(44),
+ {ok,Stats} = sys:statistics(?server,get),
+ lists:member({messages_in,1},Stats),
+ lists:member({messages_out,1},Stats),
+ ok = sys:statistics(?server,false),
+ {status,_Pid,{module,_Mod},[_PDict,running,Self,_,_]} =
sys:get_status(?server),
- ?line {ok,no_statistics} = sys:statistics(?server,get),
- ?line stop(),
+ {ok,no_statistics} = sys:statistics(?server,get),
+ stop(),
ok.
trace(suite) -> [];
trace(Config) when is_list(Config) ->
- ?line {ok,_Server} = start(),
- case os:type() of
- vxworks ->
- ?line test_server:sleep(20000);
- _ ->
- ?line test_server:sleep(2000)
- end,
- ?line test_server:capture_start(),
- ?line sys:trace(?server,true),
- ?line {ok,-44} = public_call(44),
+ {ok,_Server} = start(),
+ test_server:sleep(2000),
+ test_server:capture_start(),
+ sys:trace(?server,true),
+ {ok,-44} = public_call(44),
%% ho, hum, allow for the io to reach us..
- case os:type() of
- vxworks ->
- ?line test_server:sleep(10000);
- _ ->
- ?line test_server:sleep(1000)
- end,
- ?line test_server:capture_stop(),
- ?line [Msg1,Msg2] = test_server:capture_get(),
- ?line lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1),
- ?line lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2),
- ?line stop(),
+ test_server:sleep(1000),
+ test_server:capture_stop(),
+ [Msg1,Msg2] = test_server:capture_get(),
+ lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1),
+ lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2),
+ stop(),
ok.
suspend(suite) -> [];
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index f84c72b0f8..1110891ab8 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -32,7 +32,6 @@
%% functions I guess. But I don't have time for that now.
%%
%% Expect it to run for at least 5-10 minutes!
-%% Except for VxWorks of course, where a couple of hours is more apropriate...
%% The main test case in this module is "do_big_test", which
@@ -77,12 +76,7 @@ end_per_group(_GroupName, Config) ->
do_big_test(TConfig) when is_list(TConfig) ->
Dog = ?t:timetrap(?t:minutes(20)),
Save = process_flag(trap_exit, true),
- Result = case os:type() of
- vxworks ->
- big_test(10);
- _ ->
- big_test(200)
- end,
+ Result = big_test(200),
process_flag(trap_exit, Save),
?t:timetrap_cancel(Dog),
report_result(Result).