diff options
Diffstat (limited to 'lib/stdlib/test')
| -rw-r--r-- | lib/stdlib/test/erl_scan_SUITE.erl | 246 | ||||
| -rw-r--r-- | lib/stdlib/test/filelib_SUITE.erl | 112 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 39 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_server_SUITE.erl | 41 | ||||
| -rw-r--r-- | lib/stdlib/test/maps_SUITE.erl | 33 | ||||
| -rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/test/stdlib_SUITE.erl | 18 | 
7 files changed, 361 insertions, 133 deletions
| diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 35067e8116..9be9f641c8 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -204,20 +204,20 @@ reserved_words() ->      [begin           ?line {RW, true} = {RW, erl_scan:reserved_word(RW)},           S = atom_to_list(RW), -         Ts = [{RW,1}], +         Ts = [{RW,{1,1}}],           ?line test_string(S, Ts)       end || RW <- L],      ok.  atoms() -> -    ?line test_string("a -                 b", [{atom,1,a},{atom,2,b}]), -    ?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}]), +    test_string("a +                 b", [{atom,{1,1},a},{atom,{2,18},b}]), +    test_string("'a b'", [{atom,{1,1},'a b'}]), +    test_string("a", [{atom,{1,1},a}]), +    test_string("a@2", [{atom,{1,1},a@2}]), +    test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]), +    test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]),      ?line {ok,[{atom,_,'$a'}],{1,6}} =          erl_scan:string("'$\\a'", {1,1}),      ?line test("'$\\a'"), @@ -230,7 +230,7 @@ punctuations() ->      %% One token at a time:      [begin           W = list_to_atom(S), -         Ts = [{W,1}], +         Ts = [{W,{1,1}}],           ?line test_string(S, Ts)       end || S <- L],      Three = ["/=:=", "<=:=", "==:=", ">=:="], % three tokens... @@ -246,53 +246,60 @@ punctuations() ->      [begin           W1 = list_to_atom(S1),           W2 = list_to_atom(S2), -         Ts = [{W1,1},{W2,1}], +         Ts = [{W1,{1,1}},{W2,{1,-L2+1}}],           ?line test_string(S, Ts) -     end || {S,[{_,S1,S2}|_]}  <- SL], +     end || {S,[{L2,S1,S2}|_]}  <- SL], -    PTs1 = [{'!',1},{'(',1},{')',1},{',',1},{';',1},{'=',1},{'[',1}, -            {']',1},{'{',1},{'|',1},{'}',1}], +    PTs1 = [{'!',{1,1}},{'(',{1,2}},{')',{1,3}},{',',{1,4}},{';',{1,5}}, +            {'=',{1,6}},{'[',{1,7}},{']',{1,8}},{'{',{1,9}},{'|',{1,10}}, +            {'}',{1,11}}],      ?line test_string("!(),;=[]{|}", PTs1), -    PTs2 = [{'#',1},{'&',1},{'*',1},{'+',1},{'/',1}, -            {':',1},{'<',1},{'>',1},{'?',1},{'@',1}, -            {'\\',1},{'^',1},{'`',1},{'~',1}], +    PTs2 = [{'#',{1,1}},{'&',{1,2}},{'*',{1,3}},{'+',{1,4}},{'/',{1,5}}, +            {':',{1,6}},{'<',{1,7}},{'>',{1,8}},{'?',{1,9}},{'@',{1,10}}, +            {'\\',{1,11}},{'^',{1,12}},{'`',{1,13}},{'~',{1,14}}],      ?line test_string("#&*+/:<>?@\\^`~", PTs2), -    ?line test_string(".. ", [{'..',1}]), -    ?line test("1 .. 2"), -    ?line test_string("...", [{'...',1}]), +    test_string(".. ", [{'..',{1,1}}]), +    test_string("1 .. 2", +                [{integer,{1,1},1},{'..',{1,3}},{integer,{1,6},2}]), +    test_string("...", [{'...',{1,1}}]),      ok.  comments() ->      ?line test("a %%\n b"),      ?line {ok,[],1} = erl_scan:string("%"),      ?line test("a %%\n b"), -    ?line {ok,[{atom,_,a},{atom,_,b}],{2,3}} = +    {ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} =          erl_scan:string("a %%\n b",{1,1}), -    ?line {ok,[{atom,_,a},{comment,_,"%%"},{atom,_,b}],{2,3}} = +    {ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} =          erl_scan:string("a %%\n b",{1,1}, [return_comments]), -    ?line {ok,[{atom,_,a}, -               {white_space,_," "}, -               {white_space,_,"\n "}, -               {atom,_,b}], -           {2,3}} = +    {ok,[{atom,{1,1},a}, +         {white_space,{1,2}," "}, +         {white_space,{1,5},"\n "}, +         {atom,{2,2},b}], +     {2,3}} =          erl_scan:string("a %%\n b",{1,1},[return_white_spaces]), -    ?line {ok,[{atom,_,a}, -               {white_space,_," "}, -               {comment,_,"%%"}, -               {white_space,_,"\n "}, -               {atom,_,b}], -           {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]), +    {ok,[{atom,{1,1},a}, +         {white_space,{1,2}," "}, +         {comment,{1,3},"%%"}, +         {white_space,{1,5},"\n "}, +         {atom,{2,2},b}], +     {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]),      ok.  errors() ->      ?line {error,{1,erl_scan,{string,$',"qa"}},1} = erl_scan:string("'qa"), %' +    {error,{{1,1},erl_scan,{string,$',"qa"}},{1,4}} = %' +        erl_scan:string("'qa", {1,1}, []), %'      ?line {error,{1,erl_scan,{string,$","str"}},1} = %"          erl_scan:string("\"str"), %" +    {error,{{1,1},erl_scan,{string,$","str"}},{1,5}} = %" +        erl_scan:string("\"str", {1,1}, []), %"      ?line {error,{1,erl_scan,char},1} = erl_scan:string("$"), -    ?line test_string([34,65,200,34], [{string,1,"AÈ"}]), -    ?line test_string("\\", [{'\\',1}]), +    {error,{{1,1},erl_scan,char},{1,2}} = erl_scan:string("$", {1,1}, []), +    test_string([34,65,200,34], [{string,{1,1},"AÈ"}]), +    test_string("\\", [{'\\',{1,1}}]),      ?line {'EXIT',_} =          (catch {foo, erl_scan:string('$\\a', {1,1})}), % type error      ?line {'EXIT',_} = @@ -304,7 +311,7 @@ errors() ->  integers() ->      [begin           I = list_to_integer(S), -         Ts = [{integer,1,I}], +         Ts = [{integer,{1,1},I}],           ?line test_string(S, Ts)       end || S <- [[N] || N <- lists:seq($0, $9)] ++ ["2323","000"] ],      ok. @@ -313,14 +320,16 @@ base_integers() ->      [begin           B = list_to_integer(BS),           I = erlang:list_to_integer(S, B), -         Ts = [{integer,1,I}], +         Ts = [{integer,{1,1},I}],           ?line test_string(BS++"#"++S, Ts)       end || {BS,S} <- [{"2","11"}, {"5","23234"}, {"12","05a"},                         {"16","abcdef"}, {"16","ABCDEF"}] ],      ?line {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"), +    {error,{{1,1},erl_scan,{base,1}},{1,2}} = +        erl_scan:string("1#000", {1,1}, []), -    ?line test_string("12#bc", [{integer,1,11},{atom,1,c}]), +    test_string("12#bc", [{integer,{1,1},11},{atom,{1,5},c}]),      [begin           Str = BS ++ "#" ++ S, @@ -329,40 +338,53 @@ base_integers() ->       end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],      ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan:string("16#ef@"), -    ?line {ok,[{integer,1,14},{atom,1,g@}],1} = erl_scan:string("16#eg@"), +    {ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} = +        erl_scan:string("16#ef@", {1,1}, []), +    {ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} = +        erl_scan:string("16#eg@", {1,1}, []),      ok.  floats() ->      [begin           F = list_to_float(FS), -         Ts = [{float,1,F}], +         Ts = [{float,{1,1},F}],           ?line test_string(FS, Ts)       end || FS <- ["1.0","001.17","3.31200","1.0e0","1.0E17",                     "34.21E-18", "17.0E+14"]], -    ?line test_string("1.e2", [{integer,1,1},{'.',1},{atom,1,e2}]), +    test_string("1.e2", [{integer,{1,1},1},{'.',{1,2}},{atom,{1,3},e2}]),      ?line {error,{1,erl_scan,{illegal,float}},1} =          erl_scan:string("1.0e400"), +    {error,{{1,1},erl_scan,{illegal,float}},{1,8}} = +        erl_scan:string("1.0e400", {1,1}, []),      [begin -         ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S) +         {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S), +         {error,{{1,1},erl_scan,{illegal,float}},{1,_}} = +             erl_scan:string(S, {1,1}, [])       end || S <- ["1.14Ea"]],      ok.  dots() -> -    Dot = [{".",    {ok,[{dot,1}],1}}, -           {". ",   {ok,[{dot,1}],1}}, -           {".\n",  {ok,[{dot,1}],2}}, -           {".%",   {ok,[{dot,1}],1}}, -           {".\210",{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}}, -           {".a",   {ok,[{'.',1},{atom,1,a}],1}} +    Dot = [{".",    {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,2}}}, +           {". ",   {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, +           {".\n",  {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, +           {".%",   {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, +           {".\210",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, +           {".% öh",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,6}}}, +           {".%\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, +           {".$",   {error,{1,erl_scan,char},1}, +                    {error,{{1,2},erl_scan,char},{1,3}}}, +           {".$\\", {error,{1,erl_scan,char},1}, +                    {error,{{1,2},erl_scan,char},{1,4}}}, +           {".a",   {ok,[{'.',1},{atom,1,a}],1}, +                    {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}}            ], -    ?line [R = erl_scan:string(S) || {S, R} <- Dot], +    [begin +         R = erl_scan:string(S), +         R2 = erl_scan:string(S, {1,1}, []) +     end || {S, R, R2} <- Dot],      ?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text),      ?line [{column,1},{length,1},{line,1},{text,"."}] = @@ -379,55 +401,55 @@ dots() ->      ?line {error,{{1,2},erl_scan,char},{1,4}} =          erl_scan:string(".$\\", {1,1}), -    ?line test(". "), -    ?line test(".  "), -    ?line test(".\n"), -    ?line test(".\n\n"), -    ?line test(".\n\r"), -    ?line test(".\n\n\n"), -    ?line test(".\210"), -    ?line test(".%\n"), -    ?line test(".a"), - -    ?line test("%. \n. "), +    test_string(". ", [{dot,{1,1}}]), +    test_string(".  ", [{dot,{1,1}}]), +    test_string(".\n", [{dot,{1,1}}]), +    test_string(".\n\n", [{dot,{1,1}}]), +    test_string(".\n\r", [{dot,{1,1}}]), +    test_string(".\n\n\n", [{dot,{1,1}}]), +    test_string(".\210", [{dot,{1,1}}]), +    test_string(".%\n", [{dot,{1,1}}]), +    test_string(".a", [{'.',{1,1}},{atom,{1,2},a}]), + +    test_string("%. \n. ", [{dot,{2,1}}]),      ?line {more,C} = erl_scan:tokens([], "%. ",{1,1}, return), -    ?line {done,{ok,[{comment,_,"%. "}, -                     {white_space,_,"\n"}, -                     {dot,_}], -                 {2,3}}, ""} = +    {done,{ok,[{comment,{1,1},"%. "}, +               {white_space,{1,4},"\n"}, +               {dot,{2,1}}], +           {2,3}}, ""} =          erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options      ?line [test_string(S, R) || -              {S, R} <- [{".$\n",   [{'.',1},{char,1,$\n}]}, -                         {"$\\\n",  [{char,1,$\n}]}, -                         {"'\\\n'", [{atom,1,'\n'}]}, -                         {"$\n",    [{char,1,$\n}]}] ], +              {S, R} <- [{".$\n",   [{'.',{1,1}},{char,{1,2},$\n}]}, +                         {"$\\\n",  [{char,{1,1},$\n}]}, +                         {"'\\\n'", [{atom,{1,1},'\n'}]}, +                         {"$\n",    [{char,{1,1},$\n}]}] ],      ok.  chars() ->      [begin           L = lists:flatten(io_lib:format("$\\~.8b", [C])), -         Ts = [{char,1,C}], +         Ts = [{char,{1,1},C}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255)],      %% Leading zeroes...      [begin           L = lists:flatten(io_lib:format("$\\~3.8.0b", [C])), -         Ts = [{char,1,C}], +         Ts = [{char,{1,1},C}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255)],      %% $\^\n now increments the line...      [begin           L = "$\\^" ++ [C], -         Ts = [{char,1,C band 2#11111}], +         Ts = [{char,{1,1},C band 2#11111}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255)],      [begin           L = "$\\" ++ [C], -         Ts = [{char,1,V}], +         Ts = [{char,{1,1},V}],           ?line test_string(L, Ts)       end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v},                        {$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s}, @@ -440,45 +462,45 @@ chars() ->      No = EC ++ Ds ++ X ++ New,      [begin           L = "$\\" ++ [C], -         Ts = [{char,1,C}], +         Ts = [{char,{1,1},C}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255) -- No],      [begin           L = "'$\\" ++ [C] ++ "'", -         Ts = [{atom,1,list_to_atom("$"++[C])}], +         Ts = [{atom,{1,1},list_to_atom("$"++[C])}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255) -- No], -    ?line test_string("\"\\013a\\\n\"", [{string,1,"\va\n"}]), +    test_string("\"\\013a\\\n\"", [{string,{1,1},"\va\n"}]), -    ?line test_string("'\n'", [{atom,1,'\n'}]), -    ?line test_string("\"\n\a\"", [{string,1,"\na"}]), +    test_string("'\n'", [{atom,{1,1},'\n'}]), +    test_string("\"\n\a\"", [{string,{1,1},"\na"}]),      %% No escape      [begin           L = "$" ++ [C], -         Ts = [{char,1,C}], +         Ts = [{char,{1,1},C}],           ?line test_string(L, Ts)       end || C <- lists:seq(0, 255) -- (No ++ [$\\])], -    ?line test_string("$\n", [{char,1,$\n}]), +    test_string("$\n", [{char,{1,1},$\n}]),      ?line {error,{{1,1},erl_scan,char},{1,4}} =          erl_scan:string("$\\^",{1,1}), -    ?line test_string("$\\\n", [{char,1,$\n}]), +    test_string("$\\\n", [{char,{1,1},$\n}]),      %% Robert's scanner returns line 1: -    ?line test_string("$\\\n", [{char,1,$\n}]), -    ?line test_string("$\n\n", [{char,1,$\n}]), +    test_string("$\\\n", [{char,{1,1},$\n}]), +    test_string("$\n\n", [{char,{1,1},$\n}]),      ?line test("$\n\n"),      ok.  variables() -> -    ?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'}]), +    test_string("     \237_Aouåeiyäö", [{var,{1,7},'_Aouåeiyäö'}]), +    test_string("A_b_c@", [{var,{1,1},'A_b_c@'}]), +    test_string("V@2", [{var,{1,1},'V@2'}]), +    test_string("ABDÀ", [{var,{1,1},'ABDÀ'}]), +    test_string("Ärlig Östen", [{var,{1,1},'Ärlig'},{var,{1,7},'Östen'}]),      ok.  eof() -> @@ -508,11 +530,25 @@ eof() ->      ?line {done,{ok,[{atom,1,a}],1},eof} =          erl_scan:tokens(C5,eof,1), +    %% With column. +    {more, C6} = erl_scan:tokens([], "a", {1,1}), +    %% An error before R13A. +    %% {done,{error,{1,erl_scan,scan},1},eof} = +    {done,{ok,[{atom,{1,1},a}],{1,2}},eof} = +        erl_scan:tokens(C6,eof,1), +      %% A dot followed by eof is special:      ?line {more, C} = erl_scan:tokens([], "a.", 1),      ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan:tokens(C,eof,1),      ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan:string("foo."), +    %% With column. +    {more, CCol} = erl_scan:tokens([], "a.", {1,1}), +    {done,{ok,[{atom,{1,1},a},{dot,{1,2}}],{1,3}},eof} = +        erl_scan:tokens(CCol,eof,1), +    {ok,[{atom,{1,1},foo},{dot,{1,4}}],{1,5}} = +        erl_scan:string("foo.", {1,1}, []), +      ok.  illegal() -> @@ -816,34 +852,34 @@ unicode() ->          erl_scan:string([1089]),      ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =          erl_scan:string([1089], {1,1}), -    ?line {error,{1,erl_scan,{illegal,atom}},1} = +    {error,{1,erl_scan,{illegal,atom}},1} =          erl_scan:string("'a"++[1089]++"b'", 1), -    ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} = +    {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} =          erl_scan:string("'a"++[1089]++"b'", {1,1}),      ?line test("\"a"++[1089]++"b\""), -    ?line {ok,[{char,1,1}],1} = +    {ok,[{char,1,1}],1} =          erl_scan:string([$$,$\\,$^,1089], 1), -    ?line {error,{1,erl_scan,Error},1} = +    {error,{1,erl_scan,Error},1} =          erl_scan:string("\"qa\x{aaa}", 1), -    ?line "unterminated string starting with \"qa"++[2730]++"\"" = +    "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}), -    ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} = +    {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =          erl_scan:string("'qa\\x{aaa}'",{1,1}), -    ?line {ok,[{char,1,1089}],1} = +    {ok,[{char,1,1089}],1} =          erl_scan:string([$$,1089], 1), -    ?line {ok,[{char,1,1089}],1} = +    {ok,[{char,1,1089}],1} =          erl_scan:string([$$,$\\,1089], 1),      Qs = "$\\x{aaa}", -    ?line {ok,[{char,1,$\x{aaa}}],1} = +    {ok,[{char,1,$\x{aaa}}],1} =          erl_scan:string(Qs, 1), -    ?line {ok,[Q2],{1,9}} = +    {ok,[Q2],{1,9}} =          erl_scan:string("$\\x{aaa}", {1,1}, [text]), -    ?line [{category,char},{column,1},{length,8}, +    [{category,char},{column,1},{length,8},             {line,1},{symbol,16#aaa},{text,Qs}] =          erl_scan:token_info(Q2), @@ -1164,7 +1200,13 @@ otp_11807(Config) when is_list(Config) ->           (catch erl_parse:abstract("string", [{encoding,bad}])),     ok. -test_string(String, Expected) -> +test_string(String, ExpectedWithCol) -> +    {ok, ExpectedWithCol, _EndWithCol} = erl_scan:string(String, {1, 1}, []), +    Expected = [ begin +                     {L,_C} = element(2, T), +                     setelement(2, T, L) +                 end +                    || T <- ExpectedWithCol ],      {ok, Expected, _End} = erl_scan:string(String),      test(String). diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 1135828fae..bd313390b3 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2005-2013. All Rights Reserved. +%% Copyright Ericsson AB 2005-2014. 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 @@ -23,7 +23,8 @@  	 init_per_group/2,end_per_group/2,  	 init_per_testcase/2,end_per_testcase/2,  	 wildcard_one/1,wildcard_two/1,wildcard_errors/1, -	 fold_files/1,otp_5960/1,ensure_dir_eexist/1,symlinks/1]). +	 fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1, +	 wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1]).  -import(lists, [foreach/2]). @@ -43,7 +44,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}].  all() ->       [wildcard_one, wildcard_two, wildcard_errors, -     fold_files, otp_5960, ensure_dir_eexist, symlinks]. +     fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink, +     wildcard_symlink, is_file_symlink, file_props_symlink].  groups() ->       []. @@ -368,9 +370,28 @@ ensure_dir_eexist(Config) when is_list(Config) ->      ?line {error, eexist} = filelib:ensure_dir(NeedFileB),      ok. -symlinks(Config) when is_list(Config) -> +ensure_dir_symlink(Config) when is_list(Config) ->      PrivDir = ?config(priv_dir, Config), -    Dir = filename:join(PrivDir, ?MODULE_STRING++"_symlinks"), +    Dir = filename:join(PrivDir, "ensure_dir_symlink"), +    Name = filename:join(Dir, "same_name_as_file_and_dir"), +    ok = filelib:ensure_dir(Name), +    ok = file:write_file(Name, <<"some string\n">>), +    %% With a symlink to the directory. +    Symlink = filename:join(PrivDir, "ensure_dir_symlink_link"), +    case file:make_symlink(Dir, Symlink) of +        {error,enotsup} -> +            {skip,"Symlinks not supported on this platform"}; +        {error,eperm} -> +            {win32,_} = os:type(), +            {skip,"Windows user not privileged to create symlinks"}; +        ok -> +            SymlinkedName = filename:join(Symlink, "same_name_as_file_and_dir"), +            ok = filelib:ensure_dir(SymlinkedName) +    end. + +wildcard_symlink(Config) when is_list(Config) -> +    PrivDir = ?config(priv_dir, Config), +    Dir = filename:join(PrivDir, ?MODULE_STRING++"_wildcard_symlink"),      SubDir = filename:join(Dir, "sub"),      AFile = filename:join(SubDir, "a_file"),      Alias = filename:join(Dir, "symlink"), @@ -388,6 +409,18 @@ symlinks(Config) when is_list(Config) ->  		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))),  	    ["symlink"] =  		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), +	    ["sub","symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), +						erl_prim_loader)), +	    ["symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), +						erl_prim_loader)), +	    ["sub","symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), +						prim_file)), +	    ["symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), +						prim_file)),  	    ok = file:delete(AFile),  	    %% The symlink should still be visible even when its target  	    %% has been deleted. @@ -395,6 +428,18 @@ symlinks(Config) when is_list(Config) ->  		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))),  	    ["symlink"] =  		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), +	    ["sub","symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), +						erl_prim_loader)), +	    ["symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), +						erl_prim_loader)), +	    ["sub","symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), +						prim_file)), +	    ["symlink"] = +		basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), +						prim_file)),  	    ok      end. @@ -403,3 +448,60 @@ basenames(Dir, Files) ->  	 Dir = filename:dirname(F),  	 filename:basename(F)       end || F <- Files]. + +is_file_symlink(Config) -> +    PrivDir = ?config(priv_dir, Config), +    Dir = filename:join(PrivDir, ?MODULE_STRING++"_is_file_symlink"), +    SubDir = filename:join(Dir, "sub"), +    AFile = filename:join(SubDir, "a_file"), +    DirAlias = filename:join(Dir, "dir_symlink"), +    FileAlias = filename:join(Dir, "file_symlink"), +    ok = file:make_dir(Dir), +    ok = file:make_dir(SubDir), +    ok = file:write_file(AFile, "not that big\n"), +    case file:make_symlink(SubDir, DirAlias) of +	{error, enotsup} -> +	    {skip, "Links not supported on this platform"}; +	{error, eperm} -> +	    {win32,_} = os:type(), +	    {skip, "Windows user not privileged to create symlinks"}; +	ok -> +	    true = filelib:is_dir(DirAlias), +	    true = filelib:is_dir(DirAlias, erl_prim_loader), +	    true = filelib:is_dir(DirAlias, prim_file), +	    true = filelib:is_file(DirAlias), +	    true = filelib:is_file(DirAlias, erl_prim_loader), +	    true = filelib:is_file(DirAlias, prim_file), +	    ok = file:make_symlink(AFile,FileAlias), +	    true = filelib:is_file(FileAlias), +	    true = filelib:is_file(FileAlias, erl_prim_loader), +	    true = filelib:is_file(FileAlias, prim_file), +	    true = filelib:is_regular(FileAlias), +	    true = filelib:is_regular(FileAlias, erl_prim_loader), +	    true = filelib:is_regular(FileAlias, prim_file), +	    ok +    end. + +file_props_symlink(Config) -> +    PrivDir = ?config(priv_dir, Config), +    Dir = filename:join(PrivDir, ?MODULE_STRING++"_file_props_symlink"), +    AFile = filename:join(Dir, "a_file"), +    Alias = filename:join(Dir, "symlink"), +    ok = file:make_dir(Dir), +    ok = file:write_file(AFile, "not that big\n"), +    case file:make_symlink(AFile, Alias) of +	{error, enotsup} -> +	    {skip, "Links not supported on this platform"}; +	{error, eperm} -> +	    {win32,_} = os:type(), +	    {skip, "Windows user not privileged to create symlinks"}; +	ok -> +	    {_,_} = LastMod = filelib:last_modified(AFile), +	    LastMod = filelib:last_modified(Alias), +	    LastMod = filelib:last_modified(Alias, erl_prim_loader), +	    LastMod = filelib:last_modified(Alias, prim_file), +	    FileSize = filelib:file_size(AFile), +	    FileSize = filelib:file_size(Alias), +	    FileSize = filelib:file_size(Alias, erl_prim_loader), +	    FileSize = filelib:file_size(Alias, prim_file) +    end. diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index 8aeec07ae8..336065b258 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-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. 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 @@ -31,7 +31,9 @@  -export([shutdown/1]). --export([ sys1/1, call_format_status/1, error_format_status/1, get_state/1, replace_state/1]). +-export([ sys1/1, +	  call_format_status/1, error_format_status/1, terminate_crash_format/1, +	  get_state/1, replace_state/1]).  -export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]). @@ -66,7 +68,8 @@ groups() ->         start8, start9, start10, start11, start12]},       {abnormal, [], [abnormal1, abnormal2]},       {sys, [], -      [sys1, call_format_status, error_format_status, get_state, replace_state]}]. +      [sys1, call_format_status, error_format_status, terminate_crash_format, +       get_state, replace_state]}].  init_per_suite(Config) ->      Config. @@ -403,7 +406,7 @@ error_format_status(Config) when is_list(Config) ->      receive  	{error,_GroupLeader,{Pid,  			     "** State machine"++_, -			     [Pid,{_,_,badreturn},idle,StateData,_]}} -> +			     [Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} ->  	    ok;  	Other ->  	    ?line io:format("Unexpected: ~p", [Other]), @@ -413,6 +416,29 @@ error_format_status(Config) when is_list(Config) ->      process_flag(trap_exit, OldFl),      ok. +terminate_crash_format(Config) when is_list(Config) -> +    error_logger_forwarder:register(), +    OldFl = process_flag(trap_exit, true), +    StateData = crash_terminate, +    {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []), +    stop_it(Pid), +    receive +	{error,_GroupLeader,{Pid, +			     "** State machine"++_, +			     [Pid,{_,_,_},idle,{formatted, StateData},_]}} -> +	    ok; +	Other -> +	    io:format("Unexpected: ~p", [Other]), +	    ?t:fail() +    after 5000 -> +	    io:format("Timeout: expected error logger msg", []), +	    ?t:fail() +    end, +    [] = ?t:messages_get(), +    process_flag(trap_exit, OldFl), +    ok. + +  get_state(Config) when is_list(Config) ->      State = self(),      {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []), @@ -867,7 +893,8 @@ init({state_data, StateData}) ->  init(_) ->      {ok, idle, state_data}. - +terminate(_, _State, crash_terminate) -> +    exit({crash, terminate});  terminate({From, stopped}, State, _Data) ->      From ! {self(), {stopped, State}},      ok; @@ -1005,6 +1032,6 @@ handle_sync_event({get, _Pid}, _From, State, Data) ->      {reply, {state, State, Data}, State, Data}.  format_status(terminate, [_Pdict, StateData]) -> -    StateData; +    {formatted, StateData};  format_status(normal, [_Pdict, _StateData]) ->      [format_status_called]. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 960e7f60e7..42694d8b5d 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. 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 @@ -32,7 +32,8 @@  	 spec_init_local_registered_parent/1,   	 spec_init_global_registered_parent/1,  	 otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1, -	 error_format_status/1, get_state/1, replace_state/1, call_with_huge_message_queue/1 +	 error_format_status/1, terminate_crash_format/1, +	 get_state/1, replace_state/1, call_with_huge_message_queue/1  	]).  % spawn export @@ -56,7 +57,8 @@ all() ->       call_remote_n3, spec_init,       spec_init_local_registered_parent,       spec_init_global_registered_parent, otp_5854, hibernate, -     otp_7669, call_format_status, error_format_status, +     otp_7669, +     call_format_status, error_format_status, terminate_crash_format,       get_state, replace_state,       call_with_huge_message_queue]. @@ -273,7 +275,7 @@ crash(Config) when is_list(Config) ->      receive  	{error,_GroupLeader4,{Pid4,  			      "** Generic server"++_, -			      [Pid4,crash,state4,crashed]}} -> +			      [Pid4,crash,{formatted, state4},crashed]}} ->  	    ok;  	Other4a ->   	    ?line io:format("Unexpected: ~p", [Other4a]), @@ -1024,7 +1026,7 @@ error_format_status(Config) when is_list(Config) ->      receive  	{error,_GroupLeader,{Pid,  			     "** Generic server"++_, -			     [Pid,crash,State,crashed]}} -> +			     [Pid,crash,{formatted, State},crashed]}} ->  	    ok;  	Other ->  	    ?line io:format("Unexpected: ~p", [Other]), @@ -1034,6 +1036,31 @@ error_format_status(Config) when is_list(Config) ->      process_flag(trap_exit, OldFl),      ok. +%% Verify that error when terminating correctly calls our format_status/2 fun +%% +terminate_crash_format(Config) when is_list(Config) -> +    error_logger_forwarder:register(), +    OldFl = process_flag(trap_exit, true), +    State = crash_terminate, +    {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []), +    gen_server:call(Pid, stop), +    receive {'EXIT', Pid, {crash, terminate}} -> ok end, +    receive +	{error,_GroupLeader,{Pid, +			     "** Generic server"++_, +			     [Pid,stop, {formatted, State},{crash, terminate}]}} -> +	    ok; +	Other -> +	    io:format("Unexpected: ~p", [Other]), +	    ?t:fail() +    after 5000 -> +	    io:format("Timeout: expected error logger msg", []), +	    ?t:fail() +    end, +    ?t:messages_get(), +    process_flag(trap_exit, OldFl), +    ok. +  %% Verify that sys:get_state correctly returns gen_server state  %%  get_state(suite) -> @@ -1323,10 +1350,12 @@ terminate({From, stopped}, _State) ->  terminate({From, stopped_info}, _State) ->      From ! {self(), stopped_info},      ok; +terminate(_, crash_terminate) -> +    exit({crash, terminate});  terminate(_Reason, _State) ->      ok.  format_status(terminate, [_PDict, State]) -> -    State; +    {formatted, State};  format_status(normal, [_PDict, _State]) ->      format_status_called. diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl index c826ee731a..dda20a615b 100644 --- a/lib/stdlib/test/maps_SUITE.erl +++ b/lib/stdlib/test/maps_SUITE.erl @@ -24,10 +24,7 @@  -include_lib("test_server/include/test_server.hrl"). -% Default timetrap timeout (set in init_per_testcase). -% This should be set relatively high (10-15 times the expected -% max testcasetime). --define(default_timeout, ?t:minutes(4)). +-define(default_timeout, ?t:minutes(1)).  % Test server specific exports  -export([all/0]). @@ -37,13 +34,13 @@  -export([init_per_testcase/2]).  -export([end_per_testcase/2]). --export([get3/1]). +-export([t_get_3/1,t_with_2/1,t_without_2/1]).  suite() ->      [{ct_hooks, [ts_install_cth]}].  all() -> -    [get3]. +    [t_get_3,t_with_2,t_without_2].  init_per_suite(Config) ->      Config. @@ -52,7 +49,7 @@ end_per_suite(_Config) ->      ok.  init_per_testcase(_Case, Config) -> -    ?line Dog=test_server:timetrap(?default_timeout), +    Dog=test_server:timetrap(?default_timeout),      [{watchdog, Dog}|Config].  end_per_testcase(_Case, Config) -> @@ -60,10 +57,24 @@ end_per_testcase(_Case, Config) ->      test_server:timetrap_cancel(Dog),      ok. -get3(Config) when is_list(Config) -> +t_get_3(Config) when is_list(Config) ->      Map = #{ key1 => value1, key2 => value2 },      DefaultValue = "Default value", -    ?line value1 = maps:get(key1, Map, DefaultValue), -    ?line value2 = maps:get(key2, Map, DefaultValue), -    ?line DefaultValue = maps:get(key3, Map, DefaultValue), +    value1 = maps:get(key1, Map, DefaultValue), +    value2 = maps:get(key2, Map, DefaultValue), +    DefaultValue = maps:get(key3, Map, DefaultValue), +    ok. + +t_without_2(_Config) -> +    Ki = [11,22,33,44,55,66,77,88,99], +    M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]), +    M1 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100) -- Ki]), +    M1 = maps:without([{k,I}||I <- Ki],M0), +    ok. + +t_with_2(_Config) -> +    Ki = [11,22,33,44,55,66,77,88,99], +    M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]), +    M1 = maps:from_list([{{k,I},{v,I}}||I<-Ki]), +    M1 = maps:with([{k,I}||I <- Ki],M0),      ok. diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index e016432f4d..f841e2c4a6 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2532,6 +2532,11 @@ otp_6554(Config) when is_list(Config) ->            "\n    end.\nok.\n" =           t(<<"begin F = fun() -> foo end, 1 end. B = F(). C = 17. b().">>), +    ?line "3: command not found" = comm_err(<<"#{v(3) => v}.">>), +    ?line "3: command not found" = comm_err(<<"#{k => v(3)}.">>), +    ?line "3: command not found" = comm_err(<<"#{v(3) := v}.">>), +    ?line "3: command not found" = comm_err(<<"#{k := v(3)}.">>), +    ?line "3: command not found" = comm_err(<<"(v(3))#{}.">>),      %% Tests I'd like to do: (you should try them manually)      %% "catch spawn_link(fun() -> timer:sleep(1000), exit(foo) end)."      %%   "** exception error: foo" should be output after 1 second diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 59821220b4..3d09bd27ff 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -78,17 +78,29 @@ appup_test(_Config) ->  appup_tests(_App,{[],[]}) ->      {skip,"no previous releases available"}; -appup_tests(App,{OkVsns,NokVsns}) -> +appup_tests(App,{OkVsns0,NokVsns}) ->      application:load(App),      {_,_,Vsn} = lists:keyfind(App,1,application:loaded_applications()),      AppupFileName = atom_to_list(App) ++ ".appup",      AppupFile = filename:join([code:lib_dir(App),ebin,AppupFileName]),      {ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile),      ct:log("~p~n",[AppupScript]), -    ct:log("Testing ok versions: ~p~n",[OkVsns]), +    OkVsns = +	case OkVsns0 -- [Vsn] of +	    OkVsns0 -> +		OkVsns0; +	    Ok -> +		ct:log("Current version, ~p, is same as in previous release.~n" +		       "Removing this from the list of ok versions.", +		      [Vsn]), +		Ok +	end, +    ct:log("Testing that appup allows upgrade from these versions: ~p~n", +	   [OkVsns]),      check_appup(OkVsns,UpFrom,{ok,[restart_new_emulator]}),      check_appup(OkVsns,DownTo,{ok,[restart_new_emulator]}), -    ct:log("Testing not ok versions: ~p~n",[NokVsns]), +    ct:log("Testing that appup does not allow upgrade from these versions: ~p~n", +	   [NokVsns]),      check_appup(NokVsns,UpFrom,error),      check_appup(NokVsns,DownTo,error),      ok. | 
