diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 1 | ||||
-rw-r--r-- | lib/stdlib/test/dict_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/dict_test_lib.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 9 | ||||
-rw-r--r-- | lib/stdlib/test/erl_eval_SUITE.erl | 18 | ||||
-rw-r--r-- | lib/stdlib/test/erl_eval_helper.erl | 28 | ||||
-rw-r--r-- | lib/stdlib/test/erl_expand_records_SUITE.erl | 33 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 22 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 22 | ||||
-rw-r--r-- | lib/stdlib/test/erl_scan_SUITE.erl | 121 | ||||
-rw-r--r-- | lib/stdlib/test/escript_SUITE.erl | 19 | ||||
-rw-r--r-- | lib/stdlib/test/escript_SUITE_data/emulator_flags_no_shebang | 10 | ||||
-rw-r--r-- | lib/stdlib/test/filelib_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/test/sets_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/sets_test_lib.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 17 | ||||
-rw-r--r-- | lib/stdlib/test/sys_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/timer_SUITE.erl | 2 |
21 files changed, 124 insertions, 206 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index 29b8e28d3a..6aa09d7bd0 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -23,7 +23,6 @@ MODULES= \ dummy_via \ edlin_expand_SUITE \ epp_SUITE \ - erl_eval_helper \ erl_eval_SUITE \ erl_expand_records_SUITE \ erl_internal_SUITE \ diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl index df9c769c67..0223240479 100644 --- a/lib/stdlib/test/dict_SUITE.erl +++ b/lib/stdlib/test/dict_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2011. All Rights Reserved. +%% Copyright Ericsson AB 2008-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 diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl index 7167014310..e308fd0721 100644 --- a/lib/stdlib/test/dict_test_lib.erl +++ b/lib/stdlib/test/dict_test_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2010. All Rights Reserved. +%% Copyright Ericsson AB 2008-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 diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 606bbbcbb2..041d521514 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2012. All Rights Reserved. +%% Copyright Ericsson AB 1998-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 @@ -1342,6 +1342,8 @@ encoding(Enc, File) -> E = encoding_nocom(Enc, File). encoding_com(Enc, File) -> + B = list_to_binary(Enc), + E = epp:read_encoding_from_binary(B), ok = file:write_file(File, Enc), {ok, Fd} = file:open(File, [read]), E = epp:set_encoding(Fd), @@ -1349,10 +1351,13 @@ encoding_com(Enc, File) -> E = epp:read_encoding(File). encoding_nocom(Enc, File) -> + Options = [{in_comment_only, false}], + B = list_to_binary(Enc), + E = epp:read_encoding_from_binary(B, Options), ok = file:write_file(File, Enc), {ok, Fd} = file:open(File, [read]), ok = file:close(Fd), - epp:read_encoding(File, [{in_comment_only, false}]). + E = epp:read_encoding(File, Options). 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 47792d1052..04d49770cb 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -1160,24 +1160,6 @@ do_funs(LFH, EFH) -> concat(["begin F = fun(F, N) -> [", M, ":count_down(F,N) || X <-[1]] end, F(F,2) end."]), [[[0]]], ['F'], LFH, EFH), - - %% Tests for a bug found by the Dialyzer - used to crash. - case test_server:is_native(erl_eval) of - true -> - %% Parameterized modules are not supported by HiPE. - ok; - false -> - check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end, - "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.", - 47, - ['Pmod'], LFH, EFH), - check(fun() -> Pmod = erl_eval_helper:new(42), - B = Pmod:add(7), B end, - "begin Pmod = erl_eval_helper:new(42), " - "B = Pmod:add(7), B end.", - 49, - ['B','Pmod'], LFH, EFH) - end, ok. count_down(F, N) when N > 0 -> diff --git a/lib/stdlib/test/erl_eval_helper.erl b/lib/stdlib/test/erl_eval_helper.erl deleted file mode 100644 index 6863b40108..0000000000 --- a/lib/stdlib/test/erl_eval_helper.erl +++ /dev/null @@ -1,28 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2005-2010. 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 -%% compliance with the License. You should have received a copy of the -%% Erlang Public License along with this software. If not, it can be -%% retrieved online at http://www.erlang.org/. -%% -%% Software distributed under the License is distributed on an "AS IS" -%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See -%% the License for the specific language governing rights and limitations -%% under the License. -%% -%% %CopyrightEnd% -%% - --module(erl_eval_helper, [Base]). - --export([add/1]). - -add(Arg) -> - Base+Arg. - - - diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index e51c05a22c..94b4397a9c 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -35,7 +35,7 @@ init_per_group/2,end_per_group/2, init_per_testcase/2, end_per_testcase/2]). --export([abstract_module/1, attributes/1, expr/1, guard/1, +-export([attributes/1, expr/1, guard/1, init/1, pattern/1, strict/1, update/1, otp_5915/1, otp_7931/1, otp_5990/1, otp_7078/1, otp_7101/1]). @@ -55,7 +55,7 @@ end_per_testcase(_Case, _Config) -> suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [abstract_module, attributes, expr, guard, init, + [attributes, expr, guard, init, pattern, strict, update, {group, tickets}]. groups() -> @@ -75,33 +75,6 @@ end_per_group(_GroupName, Config) -> Config. -abstract_module(doc) -> - "Compile an abstract module."; -abstract_module(suite) -> []; -abstract_module(Config) when is_list(Config) -> - %% erl_expand_records does not handle abstract modules. But anyway... - File = filename("param.erl", Config), - Beam = filename("param.beam", Config), - Test = <<"-module(param, [A, B]). - - -export([args/1]). - - args(C) -> - X = local(C), - Z = new(A, B), - {X, Z}. - - local(C) -> - module_info(C). - ">>, - - ?line ok = file:write_file(File, Test), - ?line {ok, param} = compile:file(File, [{outdir,?privdir}]), - - ?line ok = file:delete(File), - ?line ok = file:delete(Beam), - ok. - attributes(doc) -> "Import module and functions."; attributes(suite) -> []; @@ -196,7 +169,7 @@ guard(suite) -> []; guard(Config) when is_list(Config) -> File = filename("guard.erl", Config), Beam = filename("guard.beam", Config), - Test = <<"-module(guard, [A, B]). + Test = <<"-module(guard). -export([t/1]). diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 774229fca9..564f27a512 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2187,27 +2187,9 @@ otp_5878(Config) when is_list(Config) -> ?line [] = run(Config, Ts), Abstr = <<"-module(lint_test, [A, B]). - - -export([args/1]). - - -record(r, {a = A, b = THIS}). % A and THIS are unbound - - %% param:args(compile,param:new(1,2)). - - args(C) -> - X = local(C), - Z = new(A, B), - F = fun(THIS) -> {x, A} end, % THIS unused and shadowed - {X, Z, THIS, F, #r{}}. - - local(C) -> - module_info(C). ">>, - ?line {error,[{5,erl_lint,{unbound_var,'A'}}, - {5,erl_lint,{unbound_var,'THIS'}}], - [{12,erl_lint,{unused_var,'THIS'}}, - {12,erl_lint,{shadowed_var,'THIS','fun'}}]} - = run_test2(Config, Abstr, [warn_unused_record]), + {errors,[{1,erl_lint,pmod_unsupported}],[]} = + run_test2(Config, Abstr, [warn_unused_record]), QLC1 = <<"-module(lint_test). -include_lib(\"stdlib/include/qlc.hrl\"). diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index db416b03b0..37be61d665 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -537,29 +537,9 @@ messages(Config) when is_list(Config) -> ?line true = "\n" =:= lists:flatten(erl_pp:form({eof,0})), ok. -old_mnemosyne_syntax(suite) -> - []; old_mnemosyne_syntax(Config) when is_list(Config) -> - %% Since we have kept the 'query' syntax and ':-' token, + %% Since we have kept the ':-' token, %% better test that we can pretty print it. - Q = {'query',6, - {lc,6, - {var,6,'X'}, - [{generate,6, - {var,6,'X'}, - {call,6,{atom,6,table},[{atom,6,tab}]}}, - {match,7, - {record_field,7,{var,7,'X'},{atom,7,foo}}, - {atom,7,bar}}]}}, - ?line "query\n" - " [ \n" % extra space... - " X ||\n" - " X <- table(tab),\n" - " X.foo = bar\n" - " ]\n" - "end" = - lists:flatten(erl_pp:expr(Q)), - R = {rule,12,sales,2, [{clause,12, [{var,12,'E'},{atom,12,employee}], diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 34e1b99abe..3f77d40a2e 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2012. All Rights Reserved. +%% Copyright Ericsson AB 1998-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 @@ -197,7 +197,7 @@ otp_7810(Config) when is_list(Config) -> reserved_words() -> L = ['after', 'begin', 'case', 'try', 'cond', 'catch', 'andalso', 'orelse', 'end', 'fun', 'if', 'let', 'of', - 'query', 'receive', 'when', 'bnot', 'not', 'div', + 'receive', 'when', 'bnot', 'not', 'div', 'rem', 'band', 'and', 'bor', 'bxor', 'bsl', 'bsr', 'or', 'xor'], [begin @@ -809,45 +809,52 @@ white_spaces() -> unicode() -> ?line {ok,[{char,1,83},{integer,1,45}],1} = - erl_scan:string("$\\12345"), % not unicode + erl_scan:string("$\\12345", 1, [{unicode,false}]), % not unicode ?line {error,{1,erl_scan,{illegal,character}},1} = - erl_scan:string([1089]), + erl_scan:string([1089], 1, [{unicode,false}]), ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} = - erl_scan:string([1089], {1,1}), + erl_scan:string([1089], {1,1}, [{unicode,false}]), ?line {error,{1,erl_scan,{illegal,character}},1} = %% ?line {error,{1,erl_scan,{illegal,atom}},1} = - erl_scan:string("'a"++[1089]++"b'"), + erl_scan:string("'a"++[1089]++"b'", 1, [{unicode,false}]), ?line {error,{{1,3},erl_scan,{illegal,character}},{1,4}} = - erl_scan:string("'a"++[1089]++"b'", {1,1}), + erl_scan:string("'a"++[1089]++"b'", {1,1}, [{unicode,false}]), ?line test("\"a"++[1089]++"b\""), - ?line {ok,[{char,1,1}],1} = erl_scan:string([$$,$\\,$^,1089]), + ?line {ok,[{char,1,1}],1} = + erl_scan:string([$$,$\\,$^,1089], 1, [{unicode,false}]), - ?line {error,{1,erl_scan,Error},1} = erl_scan:string("\"qa\x{aaa}"), + ?line {error,{1,erl_scan,Error},1} = + erl_scan:string("\"qa\x{aaa}", 1, [{unicode,false}]), ?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}), + erl_scan:string("\"qa\\x{aaa}",{1,1}, [{unicode,false}]), ?line {error,{{1,4},erl_scan,{illegal,character}},{1,11}} = - erl_scan:string("'qa\\x{aaa}'",{1,1}), + erl_scan:string("'qa\\x{aaa}'",{1,1}, [{unicode,false}]), Tags = [category, column, length, line, symbol, text], %% Workaround. No character codes greater than 255! To be changed. %% Note: don't remove these tests, just modify them! - ?line {ok,[{integer,1,1089}],1} = erl_scan:string([$$,1089]), - ?line {ok,[{integer,1,1089}],1} = erl_scan:string([$$,$\\,1089]), + ?line {ok,[{integer,1,1089}],1} = + erl_scan:string([$$,1089], 1, [{unicode,false}]), + ?line {ok,[{integer,1,1089}],1} = + erl_scan:string([$$,$\\,1089], 1, [{unicode,false}]), Qs = "$\\x{aaa}", - ?line {ok,[{integer,1,16#aaa}],1} = erl_scan:string(Qs), - ?line {ok,[Q2],{1,9}} = erl_scan:string("$\\x{aaa}", {1,1}, text), + ?line {ok,[{integer,1,16#aaa}],1} = + erl_scan:string(Qs, 1, [{unicode,false}]), + ?line {ok,[Q2],{1,9}} = + erl_scan:string("$\\x{aaa}", {1,1}, [text,{unicode,false}]), ?line [{category,integer},{column,1},{length,8}, {line,1},{symbol,16#aaa},{text,Qs}] = erl_scan:token_info(Q2), U1 = "\"\\x{aaa}\"", - ?line {ok,[T1,T2,T3],{1,10}} = erl_scan:string(U1, {1,1}, text), + ?line {ok,[T1,T2,T3],{1,10}} = + erl_scan:string(U1, {1,1}, [text,{unicode,false}]), ?line [{category,'['},{column,1},{length,1},{line,1}, {symbol,'['},{text,"\""}] = erl_scan:token_info(T1, Tags), ?line [{category,integer},{column,2},{length,7}, @@ -856,21 +863,23 @@ unicode() -> ?line [{category,']'},{column,9},{length,1},{line,1}, {symbol,']'},{text,"\""}] = erl_scan:token_info(T3, Tags), ?line {ok,[{'[',1},{integer,1,16#aaa},{']',1}],1} = - erl_scan:string(U1, 1), + erl_scan:string(U1, 1, [{unicode,false}]), U2 = "\"\\x41\\x{fff}\\x42\"", ?line {ok,[{'[',1},{char,1,16#41},{',',1},{integer,1,16#fff}, - {',',1},{char,1,16#42},{']',1}],1} = erl_scan:string(U2, 1), + {',',1},{char,1,16#42},{']',1}],1} = + erl_scan:string(U2, 1, [{unicode,false}]), U3 = "\"a\n\\x{fff}\n\"", ?line {ok,[{'[',1},{char,1,$a},{',',1},{char,1,$\n}, {',',2},{integer,2,16#fff},{',',2},{char,2,$\n}, {']',3}],3} = - erl_scan:string(U3, 1), + erl_scan:string(U3, 1, [{unicode,false}]), U4 = "\"\\^\n\\x{aaa}\\^\n\"", ?line {ok,[{'[',1},{char,1,$\n},{',',2},{integer,2,16#aaa}, - {',',2},{char,2,$\n},{']',3}],3} = erl_scan:string(U4, 1), + {',',2},{char,2,$\n},{']',3}],3} = + erl_scan:string(U4, 1, [{unicode,false}]), %% Keep these tests: ?line test(Qs), @@ -882,17 +891,19 @@ unicode() -> Str1 = "\"ab" ++ [1089] ++ "cd\"", ?line {ok,[{'[',1},{char,1,$a},{',',1},{char,1,$b},{',',1}, {integer,1,1089},{',',1},{char,1,$c},{',',1}, - {char,1,$d},{']',1}],1} = erl_scan:string(Str1), + {char,1,$d},{']',1}],1} = + erl_scan:string(Str1, 1, [{unicode,false}]), ?line {ok,[{'[',_},{char,_,$a},{',',_},{char,_,$b},{',',_}, {integer,_,1089},{',',_},{char,_,$c},{',',_}, - {char,_,$d},{']',_}],{1,8}} = erl_scan:string(Str1, {1,1}), + {char,_,$d},{']',_}],{1,8}} = + erl_scan:string(Str1, {1,1}, [{unicode,false}]), ?line test(Str1), Comment = "%% "++[1089], %% Returned a comment In R15B03: {error,{1,erl_scan,{illegal,character}},1} = - erl_scan:string(Comment, 1, return), + erl_scan:string(Comment, 1, [return,{unicode,false}]), {error,{{1,1},erl_scan,{illegal,character}},{1,5}} = - erl_scan:string(Comment, {1,1}, return), + erl_scan:string(Comment, {1,1}, [return,{unicode,false}]), ok. more_chars() -> @@ -967,16 +978,16 @@ 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), + erl_scan:string("'a"++[1089]++"b'", 1), {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} = - erl_scan:string("'qa\\x{aaa}'",{1,1},unicode), + erl_scan:string("'qa\\x{aaa}'",{1,1}), - {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1, unicode), - {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1,unicode), + {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1), + {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1), 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]), + {ok,[{char,1,2730}],1} = erl_scan:string(Qs,1), + {ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[text]), [{category,char},{column,1},{length,8}, {line,1},{symbol,16#aaa},{text,Qs}] = erl_scan:token_info(Q2), @@ -984,24 +995,24 @@ otp_10302(Config) when is_list(Config) -> Tags = [category, column, length, line, symbol, text], U1 = "\"\\x{aaa}\"", - {ok,[T1],{1,10}} = erl_scan:string(U1, {1,1}, [unicode,text]), + {ok,[T1],{1,10}} = erl_scan:string(U1, {1,1}, [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), + {ok,[{string,1,[65,4095,66]}],1} = erl_scan:string(U2, 1), U3 = "\"a\n\\x{fff}\n\"", - {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1,unicode), + {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1), U4 = "\"\\^\n\\x{aaa}\\^\n\"", - {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[unicode]), + {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[]), Str1 = "\"ab" ++ [1089] ++ "cd\"", {ok,[{string,1,[97,98,1089,99,100]}],1} = - erl_scan:string(Str1,1,unicode), + erl_scan:string(Str1,1), {ok,[{string,{1,1},[97,98,1089,99,100]}],{1,8}} = - erl_scan:string(Str1, {1,1},unicode), + erl_scan:string(Str1, {1,1}), OK1 = 16#D800-1, OK2 = 16#DFFF+1, @@ -1016,55 +1027,55 @@ otp_10302(Config) when is_list(Config) -> IllegalL = [Illegal1,Illegal2,Illegal3,Illegal4], [{ok,[{comment,1,[$%,$%,$\s,OK]}],1} = - erl_scan:string("%% "++[OK], 1, [unicode,return]) || + erl_scan:string("%% "++[OK], 1, [return]) || OK <- OKL], {ok,[{comment,_,[$%,$%,$\s,OK1]}],{1,5}} = - erl_scan:string("%% "++[OK1], {1,1}, [unicode,return]), + erl_scan:string("%% "++[OK1], {1,1}, [return]), [{error,{1,erl_scan,{illegal,character}},1} = - erl_scan:string("%% "++[Illegal], 1, [unicode,return]) || + erl_scan:string("%% "++[Illegal], 1, [return]) || Illegal <- IllegalL], {error,{{1,1},erl_scan,{illegal,character}},{1,5}} = - erl_scan:string("%% "++[Illegal1], {1,1}, [unicode,return]), + erl_scan:string("%% "++[Illegal1], {1,1}, [return]), - [{ok,[],1} = erl_scan:string("%% "++[OK], 1, [unicode]) || + [{ok,[],1} = erl_scan:string("%% "++[OK], 1, []) || OK <- OKL], - {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, [unicode]), + {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, []), [{error,{1,erl_scan,{illegal,character}},1} = - erl_scan:string("%% "++[Illegal], 1, [unicode]) || + erl_scan:string("%% "++[Illegal], 1, []) || Illegal <- IllegalL], {error,{{1,1},erl_scan,{illegal,character}},{1,5}} = - erl_scan:string("%% "++[Illegal1], {1,1}, [unicode]), + erl_scan:string("%% "++[Illegal1], {1,1}, []), [{ok,[{string,{1,1},[OK]}],{1,4}} = - erl_scan:string("\""++[OK]++"\"",{1,1},unicode) || + erl_scan:string("\""++[OK]++"\"",{1,1}) || OK <- OKL], [{error,{{1,2},erl_scan,{illegal,character}},{1,3}} = - erl_scan:string("\""++[OK]++"\"",{1,1},unicode) || + erl_scan:string("\""++[OK]++"\"",{1,1}) || OK <- IllegalL], [{error,{{1,1},erl_scan,{illegal,character}},{1,2}} = - erl_scan:string([Illegal],{1,1},unicode) || + erl_scan:string([Illegal],{1,1}) || Illegal <- IllegalL], {ok,[{char,{1,1},OK1}],{1,3}} = - erl_scan:string([$$,OK1],{1,1},unicode), + erl_scan:string([$$,OK1],{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,2}} = - erl_scan:string([$$,Illegal1],{1,1},unicode), + erl_scan:string([$$,Illegal1],{1,1}), {ok,[{char,{1,1},OK1}],{1,4}} = - erl_scan:string([$$,$\\,OK1],{1,1},unicode), + erl_scan:string([$$,$\\,OK1],{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,4}} = - erl_scan:string([$$,$\\,Illegal1],{1,1},unicode), + erl_scan:string([$$,$\\,Illegal1],{1,1}), {ok,[{string,{1,1},[55295]}],{1,5}} = - erl_scan:string("\"\\"++[OK1]++"\"",{1,1},unicode), + erl_scan:string("\"\\"++[OK1]++"\"",{1,1}), {error,{{1,2},erl_scan,{illegal,character}},{1,4}} = - erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1},unicode), + erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1}), {ok,[{char,{1,1},OK1}],{1,10}} = - erl_scan:string("$\\x{D7FF}",{1,1},unicode), + erl_scan:string("$\\x{D7FF}",{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,10}} = - erl_scan:string("$\\x{D800}",{1,1},unicode), + erl_scan:string("$\\x{D800}",{1,1}), %% Not erl_scan, but erl_parse. {integer,0,1} = erl_parse:abstract(1), diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl index 7634c21a17..be8fb1b37a 100644 --- a/lib/stdlib/test/escript_SUITE.erl +++ b/lib/stdlib/test/escript_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2012. All Rights Reserved. +%% Copyright Ericsson AB 2007-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 @@ -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, @@ -45,6 +46,7 @@ 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, unicode]. @@ -150,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 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/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 1fd7518519..27078f0914 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2005-2011. All Rights Reserved. +%% Copyright Ericsson AB 2005-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 diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index 22f66a6c14..a637a8543b 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 521d7255ea..4d2b53b265 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -2051,15 +2051,15 @@ otp_10302(Suite) when is_list(Suite) -> "<<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), + [] = [C || C <- Chars, S <- io_lib:write_char_as_latin1(C), not is_latin1(S)], - L1 = [S || C <- Chars, S <- io_lib:write_unicode_char(C), + L1 = [S || C <- Chars, S <- io_lib:write_char(C), not is_latin1(S)], L1 = lists:seq(256, 512), - [] = [C || C <- Chars, S <- io_lib:write_unicode_string_as_latin1([C]), + [] = [C || C <- Chars, S <- io_lib:write_string_as_latin1([C]), not is_latin1(S)], - L2 = [S || C <- Chars, S <- io_lib:write_unicode_string([C]), + L2 = [S || C <- Chars, S <- io_lib:write_string([C]), not is_latin1(S)], L2 = lists:seq(256, 512), diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index cac8309bd9..a9ea78a58b 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2012. All Rights Reserved. +%% Copyright Ericsson AB 2004-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 @@ -6663,7 +6663,7 @@ otp_7714(Config) when is_list(Config) -> {A,I1} <- ets:table(E1), {B,I2} <- ets:table(E2), I1 =:= I2],{join,merge}), - [{a,1},{a,2},{a,3}] = qlc:e(Q), + [{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)), ets:delete(E1), ets:delete(E2)">>], ?line run(Config, Ts). @@ -6728,7 +6728,7 @@ otp_6674(Config) when is_list(Config) -> [{join,lookup}]}}], []} = qlc:info(Q, {format,debug}), {0,1,0,0} = join_info(Q), - [{1.0,1},{2,2}] = qlc:e(Q), + [{1.0,1},{2,2}] = lists:sort(qlc:e(Q)), ets:delete(E1), ets:delete(E2)">>, <<"E1 = ets:new(join, [ordered_set]), diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl index e2bcdd18ce..c0cf1fc7e8 100644 --- a/lib/stdlib/test/sets_SUITE.erl +++ b/lib/stdlib/test/sets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2011. All Rights Reserved. +%% Copyright Ericsson AB 2004-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 diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl index fd4ec2bac3..86f009a8f9 100644 --- a/lib/stdlib/test/sets_test_lib.erl +++ b/lib/stdlib/test/sets_test_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2010. All Rights Reserved. +%% Copyright Ericsson AB 2004-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 diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index a32f846bd2..f22df96697 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -28,7 +28,7 @@ refman_bit_syntax/1, 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_5990/1, otp_6166/1, otp_6554/1, otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1]). -export([ start_restricted_from_shell/1, @@ -92,7 +92,7 @@ groups() -> [progex_bit_syntax, progex_records, progex_lc, progex_funs]}, {tickets, [], - [otp_5990, otp_6166, otp_6554, otp_6785, otp_7184, + [otp_5990, otp_6166, otp_6554, otp_7184, otp_7232, otp_8393, otp_10302]}]. init_per_suite(Config) -> @@ -2543,19 +2543,6 @@ otp_6554(Config) when is_list(Config) -> ok. -otp_6785(doc) -> - "OTP-6785. Parameterized modules."; -otp_6785(suite) -> []; -otp_6785(Config) when is_list(Config) -> - MFile = filename:join(?config(priv_dir, Config), "parameterized.erl"), - Contents = <<"-module(parameterized, [A]). " - "-export([test/0]). " - "test() -> A. ">>, - ?line ok = compile_file(Config, MFile, Contents, []), - ?line (parameterized:new(adsf)):test(), - file:delete(MFile), - ok. - otp_7184(doc) -> "OTP-7184. Propagate exit signals from dying evaluator process."; otp_7184(suite) -> []; diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl index b2e1d12b2a..c06ba545e7 100644 --- a/lib/stdlib/test/sys_SUITE.erl +++ b/lib/stdlib/test/sys_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl index 1110891ab8..bea2b3fb2a 100644 --- a/lib/stdlib/test/timer_SUITE.erl +++ b/lib/stdlib/test/timer_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 |