diff options
| author | Björn Gustavsson <[email protected]> | 2015-04-10 12:33:39 +0200 | 
|---|---|---|
| committer | Björn Gustavsson <[email protected]> | 2015-04-10 12:33:39 +0200 | 
| commit | 5c2c2f537e66f1637eb51b364cb962a69a7b0faf (patch) | |
| tree | 07d651ad9cbe26e19f7f30086a9b1dcd805f487b /lib/stdlib/test | |
| parent | f54392bc3c811d44cef2b31c20cac9fb11bf38e1 (diff) | |
| parent | 45560fa257526745e07115f244c80912061ecc87 (diff) | |
| download | otp-5c2c2f537e66f1637eb51b364cb962a69a7b0faf.tar.gz otp-5c2c2f537e66f1637eb51b364cb962a69a7b0faf.tar.bz2 otp-5c2c2f537e66f1637eb51b364cb962a69a7b0faf.zip | |
Merge branch 'bjorn/stdlib/cuddle-with-tests'
* bjorn/stdlib/cuddle-with-tests:
  Eliminate deprecated now/0 used as timestamp
  Eliminate use of now/0 for creating a unique filename
  Eliminate use of deprecated now/0 for measuring time
  Eliminate use of deprecated now/0 for random number generation
  Speed up timer_simple_SUITE:timer_perf/1
  Speed up timer_SUITE
  Optimize gen_server_SUITE:hibernate/1
  Optimize gen_event_SUITE:hibernate/1
  Optimize gen_fsm_SUITE:hibernate/1
  Optimize unicode_SUITE:ex_binaries_errors* test cases
  Optimize unicode_SUITE:binaries_errors/1
  binary_module_SUITE: Remove unnecessary calls to the binref module
  Optimize binary_module:random_ref_comp/1
  Optimize io_proto_SUITE:unicode_options_gen/1
Diffstat (limited to 'lib/stdlib/test')
| -rw-r--r-- | lib/stdlib/test/binary_module_SUITE.erl | 45 | ||||
| -rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 152 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_event_SUITE.erl | 173 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 220 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_server_SUITE.erl | 139 | ||||
| -rw-r--r-- | lib/stdlib/test/io_proto_SUITE.erl | 294 | ||||
| -rw-r--r-- | lib/stdlib/test/lists_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/random_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/select_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/string_SUITE.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/timer_SUITE.erl | 43 | ||||
| -rw-r--r-- | lib/stdlib/test/timer_simple_SUITE.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/test/unicode_SUITE.erl | 172 | ||||
| -rw-r--r-- | lib/stdlib/test/zip_SUITE.erl | 4 | 
15 files changed, 661 insertions, 597 deletions
| diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index f828c70b63..5248870744 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -1130,7 +1130,9 @@ do_random_matches_comp3(N,NeedleRange,HaystackRange) ->      Needles = [random_substring(NeedleRange,Haystack) ||  		  _ <- lists:duplicate(NumNeedles,a)],      RefRes = binref:matches(Haystack,Needles), -    true = do_matches_comp_loop(10000,Needles,Haystack, RefRes), +    RefRes = binary:matches(Haystack,Needles), +    Compiled = binary:compile_pattern(Needles), +    true = do_matches_comp_loop(10000,Compiled,Haystack, RefRes),      do_random_matches_comp3(N-1,NeedleRange,HaystackRange).  do_matches_comp_loop(0,_,_,_) -> @@ -1160,9 +1162,8 @@ do_matches_comp2(N,H,A) ->      end.  do_matches_comp(N,H) ->      A = ?MASK_ERROR(binref:matches(H,N)), -    B = ?MASK_ERROR(binref:matches(H,binref:compile_pattern(N))), -    C = ?MASK_ERROR(binary:matches(H,N)), -    D = ?MASK_ERROR(binary:matches(make_unaligned(H), +    B = ?MASK_ERROR(binary:matches(H,N)), +    C = ?MASK_ERROR(binary:matches(make_unaligned(H),  				   binary:compile_pattern([make_unaligned2(X) || X <- N]))),      if  	A =/= nomatch -> @@ -1170,14 +1171,14 @@ do_matches_comp(N,H) ->  	true ->  	    ok      end, -    case {(A =:= B), (B =:= C),(C =:= D)} of -	{true,true,true} -> +    case {(A =:= B), (B =:= C)} of +	{true,true} ->  	    true;  	_ ->  	    io:format("Failed to match ~p (needle) against ~s (haystack)~n",  		      [N,H]), -	    io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n", -		      [A,B,C,D]), +	    io:format("A:~p,~nB:~p,~n,C:~p,~n", +		      [A,B,C]),  	    exit(mismatch)      end. @@ -1219,46 +1220,44 @@ do_random_match_comp4(N,NeedleRange,HaystackRange) ->  do_match_comp(N,H) ->      A = ?MASK_ERROR(binref:match(H,N)), -    B = ?MASK_ERROR(binref:match(H,binref:compile_pattern([N]))), -    C = ?MASK_ERROR(binary:match(make_unaligned(H),N)), -    D = ?MASK_ERROR(binary:match(H,binary:compile_pattern([N]))), -    E = ?MASK_ERROR(binary:match(H,binary:compile_pattern(make_unaligned(N)))), +    B = ?MASK_ERROR(binary:match(make_unaligned(H),N)), +    C = ?MASK_ERROR(binary:match(H,binary:compile_pattern([N]))), +    D = ?MASK_ERROR(binary:match(H,binary:compile_pattern(make_unaligned(N)))),      if  	A =/= nomatch ->  	    put(success_counter,get(success_counter)+1);  	true ->  	    ok      end, -    case {(A =:= B), (B =:= C),(C =:= D),(D =:= E)} of -	{true,true,true,true} -> +    case {(A =:= B), (B =:= C),(C =:= D)} of +	{true,true,true} ->  	    true;  	_ ->  	    io:format("Failed to match ~s (needle) against ~s (haystack)~n",  		      [N,H]), -	    io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p,E:~p.~n", -		      [A,B,C,D,E]), +	    io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n", +		      [A,B,C,D]),  	    exit(mismatch)      end.  do_match_comp3(N,H) ->      A = ?MASK_ERROR(binref:match(H,N)), -    B = ?MASK_ERROR(binref:match(H,binref:compile_pattern(N))), -    C = ?MASK_ERROR(binary:match(H,N)), -    D = ?MASK_ERROR(binary:match(H,binary:compile_pattern(N))), +    B = ?MASK_ERROR(binary:match(H,N)), +    C = ?MASK_ERROR(binary:match(H,binary:compile_pattern(N))),      if  	A =/= nomatch ->  	    put(success_counter,get(success_counter)+1);  	true ->  	    ok      end, -    case {(A =:= B), (B =:= C),(C =:= D)} of -	{true,true,true} -> +    case {(A =:= B),(B =:= C)} of +	{true,true} ->  	    true;  	_ ->  	    io:format("Failed to match ~s (needle) against ~s (haystack)~n",  		      [N,H]), -	    io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n", -		      [A,B,C,D]), +	    io:format("A:~p,~nB:~p,~n,C:~p.~n", +		      [A,B,C]),  	    exit(mismatch)      end. diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 4de4a0cdb0..5774d774b5 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -1385,7 +1385,7 @@ random_test() ->  	       {ok,[X]} ->  		   X;  	       _ -> -		   {A,B,C} = erlang:now(), +		   {A,B,C} = erlang:timestamp(),  		   random:seed(A,B,C),  		   get(random_seed)  	   end, @@ -3541,12 +3541,9 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->  	fun () ->  		repeat(  		  fun () -> -			  {A, B, C} = now(), -			  ?line Name = list_to_atom( -					 TestCase -					 ++ "-" ++ integer_to_list(A) -					 ++ "-" ++ integer_to_list(B) -					 ++ "-" ++ integer_to_list(C)), +			  Uniq = erlang:unique_integer([positive]), +			  Name = list_to_atom(TestCase ++ "-" ++ +						  integer_to_list(Uniq)),  			  Tab = ets_new(Name, Flags),                            ForEachData(fun(Data) -> ets:insert(Tab, Data) end),  			  case Fix of @@ -4552,16 +4549,16 @@ build_table2(L1,L2,Num) ->      T.  time_match_object(Tab,Match, Res) -> -    T1 = erlang:now(), +    T1 = erlang:monotonic_time(micro_seconds),      Res = ets:match_object(Tab,Match), -    T2 = erlang:now(), -    nowdiff(T1,T2). +    T2 = erlang:monotonic_time(micro_seconds), +    T2 - T1.  time_match(Tab,Match) -> -    T1 = erlang:now(), +    T1 = erlang:monotonic_time(micro_seconds),      ets:match(Tab,Match), -    T2 = erlang:now(), -    nowdiff(T1,T2). +    T2 = erlang:monotonic_time(micro_seconds), +    T2 - T1.  seventyfive_percent_success(_,S,Fa,0) ->      true = (S > ((S + Fa) * 0.75)); @@ -4586,11 +4583,6 @@ fifty_percent_success({M,F,A},S,Fa,N) ->      end. -nowtonumber({Mega, Secs, Milli}) -> -    Milli + Secs * 1000000 + Mega * 1000000000000. -nowdiff(T1,T2) -> -    nowtonumber(T2) - nowtonumber(T1). -  create_random_string(0) ->      []; @@ -5118,17 +5110,29 @@ grow_pseudo_deleted_do(Type) ->      ?line Left = ets:info(T,size),      ?line Mult = get_kept_objects(T),      filltabstr(T,Mult), -    my_spawn_opt(fun()-> ?line true = ets:info(T,fixed), -			 Self ! start, -			 io:format("Starting to filltabstr... ~p\n",[now()]), -			 filltabstr(T,Mult,Mult+10000), -			 io:format("Done with filltabstr. ~p\n",[now()]), -			 Self ! done  -		 end, [link, {scheduler,2}]), +    my_spawn_opt( +      fun() -> +	      true = ets:info(T,fixed), +	      Self ! start, +	      io:put_chars("Starting to filltabstr...\n"), +	      do_tc(fun() -> +			    filltabstr(T, Mult, Mult+10000) +		    end, +		    fun(Elapsed) -> +			    io:format("Done with filltabstr in ~p ms\n", +				      [Elapsed]) +		    end), +	      Self ! done +      end, [link, {scheduler,2}]),      ?line start = receive_any(), -    io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]), -    ?line true = ets:safe_fixtable(T,false), -    io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]), +    io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]), +    do_tc(fun() -> +		  true = ets:safe_fixtable(T, false) +	  end, +	  fun(Elapsed) -> +		  io:format("Unfix table done in ~p ms. nitems=~p\n", +			    [Elapsed,ets:info(T, size)]) +	  end),      ?line false = ets:info(T,fixed),      ?line 0 = get_kept_objects(T),      ?line done = receive_any(), @@ -5158,17 +5162,28 @@ shrink_pseudo_deleted_do(Type) ->  				     [true]}]),          ?line Half = ets:info(T,size),      ?line Half = get_kept_objects(T), -    my_spawn_opt(fun()-> ?line true = ets:info(T,fixed), -			 Self ! start, -			 io:format("Starting to delete... ~p\n",[now()]), -			 del_one_by_one_set(T,1,Half+1), -			 io:format("Done with delete. ~p\n",[now()]), -			 Self ! done  -		 end, [link, {scheduler,2}]), +    my_spawn_opt( +      fun()-> true = ets:info(T,fixed), +	      Self ! start, +	      io:put_chars("Starting to delete... ~p\n"), +	      do_tc(fun() -> +			    del_one_by_one_set(T, 1, Half+1) +		    end, +		    fun(Elapsed) -> +			    io:format("Done with delete in ~p ms.\n", +				      [Elapsed]) +				end), +	      Self ! done +      end, [link, {scheduler,2}]),      ?line start = receive_any(), -    io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]), -    ?line true = ets:safe_fixtable(T,false), -    io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]), +    io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]), +    do_tc(fun() -> +		  true = ets:safe_fixtable(T, false) +	  end, +	  fun(Elapsed) -> +		  io:format("Unfix table done in ~p ms. nitems=~p\n", +			    [Elapsed,ets:info(T, size)]) +	  end),      ?line false = ets:info(T,fixed),      ?line 0 = get_kept_objects(T),      ?line done = receive_any(), @@ -5321,30 +5336,42 @@ smp_unfix_fix_do() ->      ?line Deleted = get_kept_objects(T),      {Child, Mref} =  -      my_spawn_opt(fun()-> ?line true = ets:info(T,fixed), -			   Parent ! start, -			   io:format("Child waiting for table to be unfixed... now=~p mem=~p\n", -				     [now(),ets:info(T,memory)]), -			   repeat_while(fun()-> ets:info(T,fixed) end), -			   io:format("Table unfixed. Child Fixating! now=~p mem=~p\n", -				     [now(),ets:info(T,memory)]),     -			   ?line true = ets:safe_fixtable(T,true), -			   repeat_while(fun(Key) when Key =< NumOfObjs ->  -						ets:delete(T,Key), {true,Key+1}; -					   (Key) -> {false,Key} -					end, -					Deleted), -			   ?line 0 = ets:info(T,size), -			   ?line true = get_kept_objects(T) >= Left,		       -			   ?line done = receive_any() -		   end,  -		   [link, monitor, {scheduler,2}]), +	my_spawn_opt( +	  fun()-> +		  true = ets:info(T,fixed), +		  Parent ! start, +		  io:format("Child waiting for table to be unfixed... mem=~p\n", +			    [ets:info(T, memory)]), +		  do_tc(fun() -> +				repeat_while(fun()-> ets:info(T, fixed) end) +			end, +			fun(Elapsed) -> +				io:format("Table unfixed in ~p ms." +					  " Child Fixating! mem=~p\n", +					  [Elapsed,ets:info(T,memory)]) +			end), +		  true = ets:safe_fixtable(T,true), +		  repeat_while(fun(Key) when Key =< NumOfObjs -> +				       ets:delete(T,Key), {true,Key+1}; +				  (Key) -> {false,Key} +			       end, +			       Deleted), +		  0 = ets:info(T,size), +		  true = get_kept_objects(T) >= Left, +		  done = receive_any() +	  end, +	  [link, monitor, {scheduler,2}]),      ?line start = receive_any(),              ?line true = ets:info(T,fixed), -    io:format("Parent starting to unfix... ~p\n",[now()]), -    ets:safe_fixtable(T,false), -    io:format("Parent done with unfix. ~p\n",[now()]), +    io:put_chars("Parent starting to unfix... ~p\n"), +    do_tc(fun() -> +		  ets:safe_fixtable(T, false) +	  end, +	  fun(Elapsed) -> +		  io:format("Parent done with unfix in ~p ms.\n", +			    [Elapsed]) +	  end),      Child ! done,      {'DOWN', Mref, process, Child, normal} = receive_any(),      ?line false = ets:info(T,fixed), @@ -6346,3 +6373,10 @@ repeat_for_opts_atom2list(compressed) -> [compressed,void].  ets_new(Name, Opts) ->      %%ets:new(Name, [compressed | Opts]).      ets:new(Name, Opts). + +do_tc(Do, Report) -> +    T1 = erlang:monotonic_time(), +    Do(), +    T2 = erlang:monotonic_time(), +    Elapsed = erlang:convert_time_unit(T2 - T1, native, milli_seconds), +    Report(Elapsed). diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index 576a5adfce..6c28eb00c3 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -131,90 +131,105 @@ start(Config) when is_list(Config) ->      ok. -hibernate(suite) -> [];  hibernate(Config) when is_list(Config) -> -    ?line {ok,Pid} = gen_event:start({local, my_dummy_handler}), -    ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), -    ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler), -    ?line true = gen_event:call(my_dummy_handler, dummy_h, hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)),     -    ?line later = gen_event:call(my_dummy_handler, dummy_h, hibernate_later), -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)),     -    ?line receive after 2000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)),     -    ?line gen_event:notify(my_dummy_handler,hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line gen_event:notify(my_dummy_handler,wakeup), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)),     -    ?line gen_event:notify(my_dummy_handler,hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line gen_event:sync_notify(my_dummy_handler,wakeup), -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)),     -    ?line ok = gen_event:sync_notify(my_dummy_handler,hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)), -    ?line ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [self()]), -    ?line [_,_] = gen_event:which_handlers(my_dummy_handler), -    ?line gen_event:notify(my_dummy_handler,hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line gen_event:notify(my_dummy_handler,wakeup), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)), -    ?line Pid ! gnurf, -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! sleep, -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Pid ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid,current_function)), -    ?line ok = gen_event:stop(my_dummy_handler), -    ?line {ok,Pid2} = gen_event:start({local, my_dummy_handler}), -    ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self(),hibernate]), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function), -    ?line sys:suspend(my_dummy_handler), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function), -    ?line sys:resume(my_dummy_handler), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function), -    ?line Pid2 ! wake, -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/=  -		  erlang:process_info(Pid2,current_function)), +    {ok,Pid} = gen_event:start({local, my_dummy_handler}), +    ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), +    [dummy_h] = gen_event:which_handlers(my_dummy_handler), +    true = gen_event:call(my_dummy_handler, dummy_h, hibernate), +    is_in_erlang_hibernate(Pid), + +    Pid ! wake, +    is_not_in_erlang_hibernate(Pid), +    later = gen_event:call(my_dummy_handler, dummy_h, hibernate_later), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    is_in_erlang_hibernate(Pid), + +    Pid ! wake, +    is_not_in_erlang_hibernate(Pid), +    gen_event:notify(my_dummy_handler, hibernate), +    is_in_erlang_hibernate(Pid), +    gen_event:notify(my_dummy_handler, wakeup), +    is_not_in_erlang_hibernate(Pid), +    gen_event:notify(my_dummy_handler, hibernate), +    is_in_erlang_hibernate(Pid), +    gen_event:sync_notify(my_dummy_handler, wakeup), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    ok = gen_event:sync_notify(my_dummy_handler, hibernate), +    is_in_erlang_hibernate(Pid), + +    Pid ! wake, +    is_not_in_erlang_hibernate(Pid), +    ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [self()]), +    [_,_] = gen_event:which_handlers(my_dummy_handler), +    gen_event:notify(my_dummy_handler, hibernate), +    is_in_erlang_hibernate(Pid), +    gen_event:notify(my_dummy_handler, wakeup), +    is_in_erlang_hibernate(Pid), + +    Pid ! wake, +    is_not_in_erlang_hibernate(Pid), + +    Pid ! gnurf, +    is_in_erlang_hibernate(Pid), + +    Pid ! sleep, +    is_in_erlang_hibernate(Pid), + +    Pid ! wake, +    is_not_in_erlang_hibernate(Pid), +    ok = gen_event:stop(my_dummy_handler), + +    {ok,Pid2} = gen_event:start({local, my_dummy_handler}), +    ok = gen_event:add_handler(my_dummy_handler, dummy_h, +				     [self(),hibernate]), +    is_in_erlang_hibernate(Pid2), +    sys:suspend(my_dummy_handler), +    is_in_erlang_hibernate(Pid2), +    sys:resume(my_dummy_handler), +    is_in_erlang_hibernate(Pid2), + +    Pid2 ! wake, +    is_not_in_erlang_hibernate(Pid2), - -    ?line ok = gen_event:stop(my_dummy_handler), +    ok = gen_event:stop(my_dummy_handler),      ok. +is_in_erlang_hibernate(Pid) -> +    receive after 1 -> ok end, +    is_in_erlang_hibernate_1(200, Pid). + +is_in_erlang_hibernate_1(0, Pid) -> +    io:format("~p\n", [erlang:process_info(Pid, current_function)]), +    ?t:fail(not_in_erlang_hibernate_3); +is_in_erlang_hibernate_1(N, Pid) -> +    {current_function,MFA} = erlang:process_info(Pid, current_function), +    case MFA of +	{erlang,hibernate,3} -> +	    ok; +	_ -> +	    receive after 10 -> ok end, +	    is_in_erlang_hibernate_1(N-1, Pid) +    end. + +is_not_in_erlang_hibernate(Pid) -> +    receive after 1 -> ok end, +    is_not_in_erlang_hibernate_1(200, Pid). + +is_not_in_erlang_hibernate_1(0, Pid) -> +    io:format("~p\n", [erlang:process_info(Pid, current_function)]), +    ?t:fail(not_in_erlang_hibernate_3); +is_not_in_erlang_hibernate_1(N, Pid) -> +    {current_function,MFA} = erlang:process_info(Pid, current_function), +    case MFA of +	{erlang,hibernate,3} -> +	    receive after 10 -> ok end, +	    is_not_in_erlang_hibernate_1(N-1, Pid); +	_ -> +	    ok +    end.  add_handler(doc) -> []; diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index dabc10aec4..f003630535 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -596,129 +596,123 @@ replace_state(Config) when is_list(Config) ->      ok.  %% Hibernation -hibernate(suite) -> [];  hibernate(Config) when is_list(Config) ->      OldFl = process_flag(trap_exit, true), -    ?line {ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid0,current_function), -    ?line stop_it(Pid0), +    {ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []), +    is_in_erlang_hibernate(Pid0), +    stop_it(Pid0),      test_server:messages_get(), - -    ?line {ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line hibernating = gen_fsm:sync_send_event(Pid,hibernate_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line good_morning  = gen_fsm:sync_send_event(Pid,wakeup_sync), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line hibernating = gen_fsm:sync_send_event(Pid,hibernate_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line five_more  = gen_fsm:sync_send_event(Pid,snooze_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line good_morning  = gen_fsm:sync_send_event(Pid,wakeup_sync), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line ok = gen_fsm:send_event(Pid,hibernate_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok  = gen_fsm:send_event(Pid,wakeup_async), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line ok = gen_fsm:send_event(Pid,hibernate_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok  = gen_fsm:send_event(Pid,snooze_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok = gen_fsm:send_event(Pid,wakeup_async), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line Pid ! hibernate_later, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line receive after 2000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line Pid ! hibernate_now, -    ?line receive after 1000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -     - -    ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line good_morning  = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line five_more  = gen_fsm:sync_send_all_state_event(Pid,snooze_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line good_morning  = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line ok = gen_fsm:send_all_state_event(Pid,hibernate_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok  = gen_fsm:send_all_state_event(Pid,wakeup_async), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line ok = gen_fsm:send_all_state_event(Pid,hibernate_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok  = gen_fsm:send_all_state_event(Pid,snooze_async), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line ok = gen_fsm:send_all_state_event(Pid,wakeup_async), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), - -    ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line sys:suspend(Pid), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line sys:resume(Pid), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), - -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} =  -	erlang:process_info(Pid,current_function), -    ?line good_morning  = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync), -    ?line receive after 1000 -> ok end, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line stop_it(Pid), +    {ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid,current_function)), +    hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync), +    is_in_erlang_hibernate(Pid), +    good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync), +    is_not_in_erlang_hibernate(Pid), +    hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync), +    is_in_erlang_hibernate(Pid), +    five_more = gen_fsm:sync_send_event(Pid, snooze_sync), +    is_in_erlang_hibernate(Pid), +    good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync), +    is_not_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_event(Pid, hibernate_async), +    is_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_event(Pid, wakeup_async), +    is_not_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_event(Pid, hibernate_async), +    is_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_event(Pid, snooze_async), +    is_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_event(Pid, wakeup_async), +    is_not_in_erlang_hibernate(Pid), + +    Pid ! hibernate_later, +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    is_in_erlang_hibernate(Pid), + +    'alive!' = gen_fsm:sync_send_event(Pid,'alive?'), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    Pid ! hibernate_now, +    is_in_erlang_hibernate(Pid), + +    'alive!' = gen_fsm:sync_send_event(Pid,'alive?'), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), + +    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync), +    is_in_erlang_hibernate(Pid), +    good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync), +    is_not_in_erlang_hibernate(Pid), +    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync), +    is_in_erlang_hibernate(Pid), +    five_more = gen_fsm:sync_send_all_state_event(Pid, snooze_sync), +    is_in_erlang_hibernate(Pid), +    good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync), +    is_not_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_all_state_event(Pid, hibernate_async), +    is_in_erlang_hibernate(Pid), +    ok  = gen_fsm:send_all_state_event(Pid, wakeup_async), +    is_not_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_all_state_event(Pid, hibernate_async), +    is_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_all_state_event(Pid, snooze_async), +    is_in_erlang_hibernate(Pid), +    ok = gen_fsm:send_all_state_event(Pid, wakeup_async), +    is_not_in_erlang_hibernate(Pid), + +    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync), +    is_in_erlang_hibernate(Pid), +    sys:suspend(Pid), +    is_in_erlang_hibernate(Pid), +    sys:resume(Pid), +    is_in_erlang_hibernate(Pid), +    receive after 1000 -> ok end, +    is_in_erlang_hibernate(Pid), + +    good_morning  = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync), +    is_not_in_erlang_hibernate(Pid), +    stop_it(Pid),      test_server:messages_get(),      process_flag(trap_exit, OldFl),      ok. +is_in_erlang_hibernate(Pid) -> +    receive after 1 -> ok end, +    is_in_erlang_hibernate_1(200, Pid). + +is_in_erlang_hibernate_1(0, Pid) -> +    io:format("~p\n", [erlang:process_info(Pid, current_function)]), +    ?t:fail(not_in_erlang_hibernate_3); +is_in_erlang_hibernate_1(N, Pid) -> +    {current_function,MFA} = erlang:process_info(Pid, current_function), +    case MFA of +	{erlang,hibernate,3} -> +	    ok; +	_ -> +	    receive after 10 -> ok end, +	    is_in_erlang_hibernate_1(N-1, Pid) +    end. +is_not_in_erlang_hibernate(Pid) -> +    receive after 1 -> ok end, +    is_not_in_erlang_hibernate_1(200, Pid). + +is_not_in_erlang_hibernate_1(0, Pid) -> +    io:format("~p\n", [erlang:process_info(Pid, current_function)]), +    ?t:fail(not_in_erlang_hibernate_3); +is_not_in_erlang_hibernate_1(N, Pid) -> +    {current_function,MFA} = erlang:process_info(Pid, current_function), +    case MFA of +	{erlang,hibernate,3} -> +	    receive after 10 -> ok end, +	    is_not_in_erlang_hibernate_1(N-1, Pid); +	_ -> +	    ok +    end.  %%sys1(suite) -> [];  %%sys1(_) -> diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 30dabf63c5..66341f495f 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -641,15 +641,13 @@ info(Config) when is_list(Config) ->  	  end,      ok. -hibernate(suite) -> [];  hibernate(Config) when is_list(Config) ->      OldFl = process_flag(trap_exit, true), -    ?line {ok, Pid0} = +    {ok, Pid0} =  	gen_server:start_link({local, my_test_name_hibernate0}, -			 gen_server_SUITE, hibernate, []), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid0,current_function), -    ?line ok = gen_server:call(my_test_name_hibernate0, stop), +			      gen_server_SUITE, hibernate, []), +    is_in_erlang_hibernate(Pid0), +    ok = gen_server:call(my_test_name_hibernate0, stop),      receive   	{'EXIT', Pid0, stopped} ->   	    ok @@ -657,70 +655,66 @@ hibernate(Config) when is_list(Config) ->  	    test_server:fail(gen_server_did_not_die)      end, -    ?line {ok, Pid} = +    {ok, Pid} =  	gen_server:start_link({local, my_test_name_hibernate}, -			 gen_server_SUITE, [], []), +			      gen_server_SUITE, [], []), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = gen_server:call(my_test_name_hibernate, hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line Parent = self(), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = gen_server:call(my_test_name_hibernate, hibernate), +    is_in_erlang_hibernate(Pid), +    Parent = self(),      Fun = fun() -> - 		  receive - 		      go -> - 			  ok - 		  end, - 		  receive  - 		  after 1000 -> - 			  ok  - 		  end, - 		  X = erlang:process_info(Pid,current_function), +		  receive go -> ok end, +		  receive after 1000 -> ok end, +		  X = erlang:process_info(Pid, current_function),   		  Pid ! continue,   		  Parent ! {result,X}   	  end, -    ?line Pid2 = spawn_link(Fun), -    ?line true = gen_server:call(my_test_name_hibernate, {hibernate_noreply,Pid2}), - -    ?line gen_server:cast(my_test_name_hibernate, hibernate_later), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line receive after 2000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line gen_server:cast(my_test_name_hibernate, hibernate_now), -    ?line receive after 1000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line Pid ! hibernate_later, -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line receive after 2000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line Pid ! hibernate_now, -    ?line receive after 1000 -> ok end, -    ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -    ?line receive - 	      {result,R} -> - 		  ?line  {current_function,{erlang,hibernate,3}} = R - 	  end, -    ?line true = gen_server:call(my_test_name_hibernate, hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line sys:suspend(my_test_name_hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line sys:resume(my_test_name_hibernate), -    ?line receive after 1000 -> ok end, -    ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function), -    ?line ok = gen_server:call(my_test_name_hibernate, started_p), -    ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), -     -    ?line ok = gen_server:call(my_test_name_hibernate, stop), +    Pid2 = spawn_link(Fun), +    true = gen_server:call(my_test_name_hibernate, {hibernate_noreply,Pid2}), + +    gen_server:cast(my_test_name_hibernate, hibernate_later), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    is_in_erlang_hibernate(Pid), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), + +    gen_server:cast(my_test_name_hibernate, hibernate_now), +    is_in_erlang_hibernate(Pid), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), + +    Pid ! hibernate_later, +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    is_in_erlang_hibernate(Pid), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), + +    Pid ! hibernate_now, +    is_in_erlang_hibernate(Pid), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = ({current_function,{erlang,hibernate,3}} =/= +		erlang:process_info(Pid, current_function)), +    receive +	{result,R} -> +	    {current_function,{erlang,hibernate,3}} = R +    end, + +    true = gen_server:call(my_test_name_hibernate, hibernate), +    is_in_erlang_hibernate(Pid), +    sys:suspend(my_test_name_hibernate), +    is_in_erlang_hibernate(Pid), +    sys:resume(my_test_name_hibernate), +    is_in_erlang_hibernate(Pid), +    ok = gen_server:call(my_test_name_hibernate, started_p), +    true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)), + +    ok = gen_server:call(my_test_name_hibernate, stop),      receive   	{'EXIT', Pid, stopped} ->   	    ok @@ -730,6 +724,23 @@ hibernate(Config) when is_list(Config) ->      process_flag(trap_exit, OldFl),      ok. +is_in_erlang_hibernate(Pid) -> +    receive after 1 -> ok end, +    is_in_erlang_hibernate_1(200, Pid). + +is_in_erlang_hibernate_1(0, Pid) -> +    io:format("~p\n", [erlang:process_info(Pid, current_function)]), +    ?t:fail(not_in_erlang_hibernate_3); +is_in_erlang_hibernate_1(N, Pid) -> +    {current_function,MFA} = erlang:process_info(Pid, current_function), +    case MFA of +	{erlang,hibernate,3} -> +	    ok; +	_ -> +	    receive after 10 -> ok end, +	    is_in_erlang_hibernate_1(N-1, Pid) +    end. +  %% --------------------------------------  %% Test gen_server:abcast and handle_cast.  %% Test all different return values from diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index c55836ff87..858a78b1d2 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -476,149 +476,182 @@ unicode_options(Config) when is_list(Config) ->      ok. -unicode_options_gen(suite) ->		    -    []; -unicode_options_gen(doc) -> -    ["Tests various unicode options on random generated files"]; +%% Tests various unicode options on random generated files.  unicode_options_gen(Config) when is_list(Config) -> -    ?line random:seed(1240,900586,553728), -    ?line PrivDir = ?config(priv_dir,Config), -    ?line AllModes = [utf8,utf16,{utf16,big},{utf16,little},utf32,{utf32,big},{utf32,little}], -    ?line FSize = 17*1024, -    ?line NumItersRead = 2, -    ?line NumItersWrite = 2, -    ?line Dir =  filename:join([PrivDir,"GENDATA1"]), -    ?line file:make_dir(Dir), - -    %dbg:tracer(process,{fun(A,_) -> erlang:display(A) end,true}), -    %dbg:tpl(file_io_server,x), -    %dbg:ctpl(file_io_server,cafu), -    %dbg:tp(unicode,x), - -    DoOneFile1 = fun(Encoding,N,M) -> -			 ?dbg({Encoding,M,N}), -			 io:format("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]), -			 io:format(standard_error,"Read test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]), -			 ?line Fname = filename:join([Dir,"genfile_"++enc2str(Encoding)++"_"++integer_to_list(N)]),  -			 ?dbg(?LINE), -			 ?line Ulist = random_unicode(FSize), -			 ?dbg(?LINE), -			 ?line my_write_file(Fname,Ulist,Encoding), -			 ?dbg(?LINE), -			 ?line {ok,F1} = file:open(Fname,[read,{encoding,Encoding}]), -			  -			 ?dbg(?LINE), -			 ?line Res1 = read_whole_file(fun(FD) -> io:get_line(FD,'') end,F1), -			 ?dbg(?LINE), -			 ?line Ulist = unicode:characters_to_list(Res1,unicode), -			 ?dbg(?LINE), -			 ?line file:close(F1), -			 ?line {ok,F2} = file:open(Fname, [read,binary,{encoding,Encoding}]), -			 ?line Res2 = read_whole_file(fun(FD) -> io:get_chars(FD,'',M) end,F2), -			 ?line Ulist = unicode:characters_to_list(Res2,unicode), -			 ?dbg(?LINE), -			 ?line file:close(F2), -			 ?line {ok,F3} = file:open(Fname, [read,binary,{encoding,Encoding}]), -			 ?dbg(?LINE), -%% 			 case {Encoding,M,N} of -%% 			     {{utf16,little},10,2} -> -%% 				 dbg:p(F3,call); -%% 			     _ -> -%% 				 ok -%% 			 end, - -			 ?line Res3 = read_whole_file(fun(FD) -> case io:fread(FD,'',"~ts") of {ok,D} -> D; O -> O end end, F3), -			 ?dbg(?LINE), -			 ?line Ulist2 = [ X || X <- Ulist, -					       X =/= $\n, X =/= $  ], -			 ?dbg(?LINE), -			 ?line Ulist2 = unicode:characters_to_list(Res3,unicode), -			 ?dbg(?LINE), -			 ?line file:close(F3), -			 ?line {ok,F4} = file:open(Fname, [read,{encoding,Encoding}]), -			 ?line Res4 = read_whole_file(fun(FD) -> case io:fread(FD,'',"~tc") of {ok,D} -> D; O -> O end end,F4), -			 ?line Ulist3 = [ X || X <- Ulist, -					       X =/= $\n ], -			 ?line Ulist3 = unicode:characters_to_list(Res4,unicode), -			 ?dbg(?LINE), -			 ?line file:close(F4), -			 ?line file:delete(Fname) -		 end, -     -    [ [ [ DoOneFile1(E,N,M) || E <- AllModes ] || M <- [10,1000,128,1024,8192,8193] ] || N <- lists:seq(1,NumItersRead)], -    DoOneFile2 = fun(Encoding,N,M) -> -			 ?dbg({Encoding,M,N}), -			 io:format("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]), -			 io:format(standard_error,"Write test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]), -			 ?line Fname = filename:join([Dir,"genfile_"++enc2str(Encoding)++"_"++integer_to_list(N)]),  -			 ?dbg(?LINE), -			 ?line Ulist = random_unicode(FSize), -			 ?dbg(?LINE), -			 ?line {ok,F1} = file:open(Fname,[write,{encoding,Encoding}]), -			 ?line io:put_chars(F1,Ulist), -			 ?line file:close(F1), -			 ?line Ulist = my_read_file(Fname,Encoding), -			 ?line file:delete(Fname), -			 ?line {ok,F2} = file:open(Fname,[write,binary,{encoding,Encoding}]), -			 ?line io:put_chars(F2,Ulist), -			 ?line file:close(F2), -			 ?line Ulist = my_read_file(Fname,Encoding), -			 ?line file:delete(Fname), -			 ?line {ok,F3} = file:open(Fname,[write,{encoding,Encoding}]), -			 ?line LL = string:tokens(Ulist,"\n"), -			 ?line Ulist2 = lists:flatten(LL), -			 ?line [ io:format(F3,"~ts",[L]) || L <- LL ], -			 ?line file:close(F3), -			 ?line Ulist2 = my_read_file(Fname,Encoding), -			 ?line file:delete(Fname), -			 ?line {ok,F4} = file:open(Fname,[write,{encoding,Encoding}]), -			 ?line [ io:format(F4,"~tc",[C]) || C <- Ulist ], -			 ?line file:close(F4), -			 ?line Ulist = my_read_file(Fname,Encoding), -			 ?line file:delete(Fname), -			 ?line {ok,F5} = file:open(Fname,[write,{encoding,Encoding}]), -			 ?line io:put_chars(F5,unicode:characters_to_binary(Ulist)), -			 ?line file:close(F5), -			 ?line Ulist = my_read_file(Fname,Encoding), -			 ?line file:delete(Fname), -			 ok -		 end, -    [ [ [ DoOneFile2(E,N,M) || E <- AllModes ] || M <- [10,1000,128,1024,8192,8193] ] || N <- lists:seq(1,NumItersWrite)], +    random:seed(1240, 900586, 553728), +    PrivDir = ?config(priv_dir, Config), +    AllModes = [utf8,utf16,{utf16,big},{utf16,little}, +		utf32,{utf32,big},{utf32,little}], +    FSize = 17*1024, +    NumItersRead = 2, +    NumItersWrite = 2, +    Dir = filename:join(PrivDir, "GENDATA1"), +    file:make_dir(Dir), + +    DoOneFile1 = +	fun(Encoding, N, M) -> +		?dbg({Encoding,M,N}), +		io:format("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]), +		io:format(standard_error, +			  "Read test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]), +		Fname = filename:join(Dir, +				      "genfile_"++enc2str(Encoding)++ +					  "_"++integer_to_list(N)), +		Ulist = random_unicode(FSize), +		Bin = unicode:characters_to_binary(Ulist, utf8, Encoding), +		ok = file:write_file(Fname, Bin), + +		Read1 = fun(FD) -> io:get_line(FD, '') end, +		Res1 = read_whole_file(Fname, +				       [read,read_ahead,{encoding,Encoding}], +				       Read1), + +		Read2 = fun(FD) -> io:get_chars(FD, '', M) end, +		Res2 = read_whole_file(Fname, +				       [read,binary, +					read_ahead,{encoding,Encoding}], +				       Read2), + +		Read3 = fun(FD) -> +				case io:fread(FD, '', "~ts") of +				    {ok,D} -> D; +				    Other -> Other end +			end, +		Res3 = read_whole_file(Fname, +				       [read,binary, +					read_ahead,{encoding,Encoding}], +				       Read3), + +		Read4 = fun(FD) -> +				case io:fread(FD, '', "~ts") of +				    {ok,D} -> D; +				    Other -> Other end +			end, +		Res4 = read_whole_file(Fname, +				       [read,read_ahead,{encoding,Encoding}], +				       Read4), + +		Ulist2 = [X || X <- Ulist, X =/= $\n, X =/= $\s], +		Ulist3 = [X || X <- Ulist, X =/= $\n], +		Ulist = done(Res1), +		Ulist = done(Res2), +		Ulist2 = done(Res3), +		Ulist3 = done(Res4), + +		file:delete(Fname) +	end, +    [ [ [ DoOneFile1(E, N, M) || E <- AllModes ] || +	  M <- [10,1000,128,1024,8192,8193] ] || +	N <- lists:seq(1, NumItersRead) ], + +    DoOneFile2 = +	fun(Encoding,N,M) -> +		?dbg({Encoding,M,N}), +		io:format("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]), +		io:format(standard_error, +			  "Write test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]), +		Fname = filename:join(Dir, +				      "genfile_"++enc2str(Encoding)++ +					  "_"++integer_to_list(N)), +		Ulist = random_unicode(FSize), + +		Res1 = write_read_file(Fname, 1, +				       [write], +				       Encoding, +				       fun(FD) -> io:put_chars(FD, Ulist) end), + +		Res2 = write_read_file(Fname, 2, +				       [write,binary], +				       Encoding, +				       fun(FD) -> io:put_chars(FD, Ulist) end), + +		Fun3 = fun(FD) -> +			       _ = [io:format(FD, "~tc", [C]) || C <- Ulist], +			       ok +		       end, +		Res3 = write_read_file(Fname, 3, +				       [write], +				       Encoding, +				       Fun3), + +		Fun4 = fun(FD) -> +			       io:put_chars(FD, +					    unicode:characters_to_binary(Ulist)) +		       end, +		Res4 = write_read_file(Fname, 4, +				       [write], +				       Encoding, +				       Fun4), + +		LL = string:tokens(Ulist, "\n"), +		Fun5 = fun(FD) -> +			       _ = [io:format(FD, "~ts", [L]) || L <- LL], +			       ok +		       end, +		Res5 = write_read_file(Fname, 5, +				       [write], +				       Encoding, +				       Fun5), + +		Ulist2 = lists:flatten(LL), +		ResBin = done(Res1), +		ResBin = done(Res2), +		ResBin = done(Res3), +		ResBin = done(Res4), +		Ulist = unicode:characters_to_list(ResBin, Encoding), + +		ResBin2 = done(Res5), +		Ulist2 = unicode:characters_to_list(ResBin2, Encoding), + +		ok +	end, +    [ [ [ DoOneFile2(E, N, M) || E <- AllModes ] || +	  M <- [10,1000,128,1024,8192,8193] ] || +	N <- lists:seq(1, NumItersWrite) ],      ok. +read_whole_file(Fname, Options, Fun) -> +    do(fun() -> +	       do_read_whole_file(Fname, Options, Fun) +       end). +do_read_whole_file(Fname, Options, Fun) -> +    {ok,F} = file:open(Fname, Options), +    Res = do_read_whole_file_1(Fun, F), +    ok = file:close(F), +    unicode:characters_to_list(Res, unicode). -			  -read_whole_file(Fun,F) ->			  +do_read_whole_file_1(Fun, F) ->      case Fun(F) of  	eof ->  	    [];  	{error,Error} -> -	    ?dbg(Error),  	    receive after 10000 -> ok end,  	    exit(Error);  	Other -> -	    %?dbg(Other), -	    [Other | read_whole_file(Fun,F)] +	    [Other|do_read_whole_file_1(Fun, F)]      end. -			 +write_read_file(Fname0, N, Options, Enc, Writer) -> +    Fname = Fname0 ++ "_" ++ integer_to_list(N), +    do(fun() -> +	       do_write_read_file(Fname, Options, Enc, Writer) +       end). + +do_write_read_file(Fname, Options, Encoding, Writer) -> +    {ok,F} = file:open(Fname, [{encoding,Encoding}|Options]), +    Writer(F), +    ok = file:close(F), +    {ok,Bin} = file:read_file(Fname), +    ok = file:delete(Fname), +    Bin. +			  enc2str(Atom) when is_atom(Atom) ->      atom_to_list(Atom);  enc2str({A1,A2}) when is_atom(A1), is_atom(A2) ->      atom_to_list(A1)++"_"++atom_to_list(A2). - - -my_write_file(Filename,UniList,Encoding) -> -    Bin = unicode:characters_to_binary(UniList,utf8,Encoding), -    file:write_file(Filename,Bin). - -my_read_file(Filename,Encoding) -> -    {ok,Bin} = file:read_file(Filename), -    unicode:characters_to_list(Bin,Encoding). -  random_unicode(0) ->      [];  random_unicode(N) -> @@ -1733,8 +1766,7 @@ toerl_loop(Port,Acc) ->      end.  millistamp() -> -    {Mega, Secs, Micros} = erlang:now(), -    (Micros div 1000) + Secs * 1000 + Mega * 1000000000. +    erlang:monotonic_time(milli_seconds).  get_data_within(Port, X, Acc) when X =< 0 ->      ?dbg({get_data_within, X, Acc, ?LINE}), @@ -1932,3 +1964,15 @@ chomp(<<Ch,Rest/binary>>) ->      <<Ch,X/binary>>;  chomp(Atom) ->      Atom. + +do(Fun) -> +    {_,Ref} = spawn_monitor(fun() -> +				    exit(Fun()) +			    end), +    Ref. + +done(Ref) -> +    receive +	{'DOWN',Ref,process,_,Result} -> +	    Result +    end. diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index f4589a8e24..01c138d94c 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -1704,7 +1704,7 @@ fun_pid(Fun) ->  get_seed() ->      case random:seed() of  	undefined -> -	    now(); +	    erlang:timestamp();  	Tuple ->  	    Tuple      end. diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl index ac9d1a6c06..22c0900651 100644 --- a/lib/stdlib/test/random_SUITE.erl +++ b/lib/stdlib/test/random_SUITE.erl @@ -82,7 +82,7 @@ seed(suite) ->      [];  seed(Config) when is_list(Config) ->      ?line Self = self(), -    ?line Seed = {S1, S2, S3} = now(), +    Seed = {S1, S2, S3} = erlang:timestamp(),      ?line _ = spawn(fun() ->      	random:seed(S1,S2,S3),      	Rands = lists:foldl(fun diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl index 546c25f954..201c38b25a 100644 --- a/lib/stdlib/test/select_SUITE.erl +++ b/lib/stdlib/test/select_SUITE.erl @@ -211,7 +211,7 @@ init_random(Config) ->  	       {ok,[X]} ->  		   X;  	       _ -> -		   {A,B,C} = erlang:now(), +		   {A,B,C} = erlang:timestamp(),  		   random:seed(A,B,C),  		   get(random_seed)  	   end, diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index a55c710d50..e9ea2e3522 100644 --- a/lib/stdlib/test/string_SUITE.erl +++ b/lib/stdlib/test/string_SUITE.erl @@ -120,7 +120,7 @@ chr_rchr(suite) ->  chr_rchr(doc) ->      [];  chr_rchr(Config) when is_list(Config) -> -    ?line {_,_,X} = now(), +    {_,_,X} = erlang:timestamp(),      ?line 0 = string:chr("", (X rem (255-32)) + 32),      ?line 0 = string:rchr("", (X rem (255-32)) + 32),      ?line 1 = string:chr("x", $x), @@ -144,7 +144,7 @@ str_rstr(suite) ->  str_rstr(doc) ->      [];  str_rstr(Config) when is_list(Config) -> -    ?line {_,_,X} = now(), +    {_,_,X} = erlang:timestamp(),      ?line 0 = string:str("", [(X rem (255-32)) + 32]),      ?line 0 = string:rstr("", [(X rem (255-32)) + 32]),      ?line 1 = string:str("x", "x"), diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 9b6d65011e..3b54cd0f34 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -89,7 +89,7 @@ borderline_test(Size, TempDir) ->      ?line io:format("Testing size ~p", [Size]),      %% Create a file and archive it. -    ?line {_, _, X0} = erlang:now(), +    X0 = erlang:monotonic_time(),      ?line file:write_file(Name, random_byte_list(X0, Size)),      ?line ok = erl_tar:create(Archive, [Name]),      ?line ok = file:delete(Name), diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl index bea2b3fb2a..ae32d98807 100644 --- a/lib/stdlib/test/timer_SUITE.erl +++ b/lib/stdlib/test/timer_SUITE.erl @@ -25,14 +25,11 @@  -include_lib("test_server/include/test_server.hrl"). -%% Test suite for timer module. This is a really nasty test it runs a -%% lot of timeouts and then checks in the end if any of them was -%% trigggered too early or if any late timeouts was much too -%% late. What should be added is more testing of the interface -%% functions I guess. But I don't have time for that now. +%% Random test of the timer module. This is a really nasty test, as it +%% runs a lot of timeouts and then checks in the end if any of them +%% was triggered too early or if any late timeouts was much too late.  %% -%% Expect it to run for at least 5-10 minutes! - +%% Running time on average is about 90 seconds.  %% The main test case in this module is "do_big_test", which  %% orders a large number of timeouts and measures how @@ -40,15 +37,8 @@  %% also a number of other concurrent processes running "nrev" at the same  %% time. The result is analyzed afterwards by trying to check if the  %% measured values are reasonable. It is hard to determine what is -%% reasonable on different machines therefore the test can sometimes -%% fail, even though the timer module is ok. I have checked against -%% previous versions of the timer module (which contained bugs) and it -%% seems it fails every time when running the buggy timer modules. -%%  -%% The solution is to rewrite the test suite. Possible strategies for a -%% rewrite: smarter math on the measuring data, test cases with varying -%% amount of load. The test suite should also include tests that test the -%% interface of the timer module. +%% reasonable on different machines; therefore the test can sometimes +%% fail, even though the timer module is ok.  suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -89,10 +79,7 @@ report_result(Error) -> ?line test_server:fail(Error).  big_test(N) ->      C = start_collect(),      system_time(), system_time(), system_time(), -    A1 = element(2, erlang:now()), -    A2 = A1 * 3, -    A3 = element(3, erlang:now()), -    random:seed(A1, A2, A3), +    random:seed(erlang:timestamp()),      random:uniform(100),random:uniform(100),random:uniform(100),      big_loop(C, N, []), @@ -146,7 +133,7 @@ big_loop(C, N, Pids) ->  	    %%Pids2=Pids1,  	    %% wait a little while -	    timer:sleep(random:uniform(200)*10), +	    timer:sleep(random:uniform(200)*3),  	    %% spawn zero, one or two nrev to get some load ;-/  	    Pids3 = start_nrev(Pids2, random:uniform(100)), @@ -166,14 +153,14 @@ start_nrev(Pids, _N) ->  start_after_test(Pids, C, 1) -> -    TO1 = random:uniform(100)*100, +    TO1 = random:uniform(100)*47,      [s_a_t(C, TO1)|Pids];  start_after_test(Pids, C, 2) -> -    TO1 = random:uniform(100)*100, -    TO2 = TO1 div random:uniform(3) + 200, +    TO1 = random:uniform(100)*47, +    TO2 = TO1 div random:uniform(3) + 101,      [s_a_t(C, TO1),s_a_t(C, TO2)|Pids];  start_after_test(Pids, C, N) -> -    TO1 = random:uniform(100)*100, +    TO1 = random:uniform(100)*47,      start_after_test([s_a_t(C, TO1)|Pids], C, N-1).  s_a_t(C, TimeOut) -> @@ -199,7 +186,7 @@ a_t(C, TimeOut) ->  maybe_start_i_test(Pids, C, 1) ->      %% ok do it -    TOI = random:uniform(100)*100, +    TOI = random:uniform(53)*49,      CountI = random:uniform(10) + 3,                      % at least 4 times      [spawn_link(timer_SUITE, i_t, [C, TOI, CountI])|Pids];  maybe_start_i_test(Pids, _C, _) -> @@ -374,9 +361,7 @@ res_combine({error,Es}, [{error,E}|T]) ->  system_time() -> -    %%element(1, statistics(wall_clock)). -    {M,S,U} = erlang:now(), -    1000000000 * M + 1000 * S + (U div 1000). +    erlang:monotonic_time(milli_seconds).  %% ------------------------------------------------------- %% diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl index dc751aad16..3c7e3c5f25 100644 --- a/lib/stdlib/test/timer_simple_SUITE.erl +++ b/lib/stdlib/test/timer_simple_SUITE.erl @@ -374,7 +374,6 @@ performance(Mod) ->  big_test(M) ->      Load_Pids = start_nrev(20, M),   % Increase if more load wanted :) -    apply(M, sleep, [9000]),      LPids = spawn_timers(5, M, 10000, 5),      apply(M, sleep, [4000]), @@ -483,8 +482,7 @@ append([],X) ->  	X.  system_time() ->     -    {M,S,U} = erlang:now(), -    1000000*(M*1000000 + S) + U. +    erlang:monotonic_time(micro_seconds).  %% ------------------------------------------------------- %% diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl index 10b29d0d28..613be99ccd 100644 --- a/lib/stdlib/test/unicode_SUITE.erl +++ b/lib/stdlib/test/unicode_SUITE.erl @@ -29,7 +29,13 @@  	 random_lists/1,  	 roundtrips/1,  	 latin1/1, -	 exceptions/1, binaries_errors/1]). +	 exceptions/1, +	 binaries_errors_limit/1, +	 ex_binaries_errors_utf8/1, +	 ex_binaries_errors_utf16_little/1, +	 ex_binaries_errors_utf16_big/1, +	 ex_binaries_errors_utf32_little/1, +	 ex_binaries_errors_utf32_big/1]).  init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->      Dog=?t:timetrap(?t:minutes(20)), @@ -44,10 +50,17 @@ suite() -> [{ct_hooks,[ts_install_cth]}].  all() ->       [utf8_illegal_sequences_bif,       utf16_illegal_sequences_bif, random_lists, roundtrips, -     latin1, exceptions, binaries_errors]. +     latin1, exceptions, +     binaries_errors_limit, +     {group,binaries_errors}].  groups() ->  -    []. +    [{binaries_errors,[parallel], +      [ex_binaries_errors_utf8, +       ex_binaries_errors_utf16_little, +       ex_binaries_errors_utf16_big, +       ex_binaries_errors_utf32_little, +       ex_binaries_errors_utf32_big]}].  init_per_suite(Config) ->      Config. @@ -61,15 +74,11 @@ init_per_group(_GroupName, Config) ->  end_per_group(_GroupName, Config) ->      Config. -binaries_errors(Config) when is_list(Config) -> +binaries_errors_limit(Config) when is_list(Config) ->      setlimit(10),      ex_binaries_errors_utf8(Config),      setlimit(default), -    ex_binaries_errors_utf8(Config), -    ex_binaries_errors_utf16_little(Config), -    ex_binaries_errors_utf16_big(Config), -    ex_binaries_errors_utf32_little(Config), -    ex_binaries_errors_utf32_big(Config). +    ok.  ex_binaries_errors_utf8(Config) when is_list(Config) ->      %% Original smoke test, we should not forget the original offset... @@ -102,109 +111,84 @@ ex_binaries_errors_utf8(Config) when is_list(Config) ->      ok.  ex_binaries_errors_utf16_little(Config) when is_list(Config) -> -    BrokenPart = << <<X:16/little>> || X <- lists:seq(16#DC00,16#DFFF) >>, -    BrokenSz = byte_size(BrokenPart), -    [ begin -	  OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))), -	  OKBin = unicode:characters_to_binary(OKList,unicode,{utf16,little}), -	  OKLen = length(OKList), -	  %% Copy to avoid that the binary get's writable -	  PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>), -	  PBSz = byte_size(PartlyBroken), -	  {error,OKList,DeepBrokenPart} =  -	      unicode:characters_to_list(PartlyBroken,{utf16,little}), -	  BrokenPart = iolist_to_binary(DeepBrokenPart), -	  [ begin -		NewList = lists:nthtail(X, OKList), -		NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf16,little})) +  -		    BrokenSz, -		Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz), -		true = (binary:referenced_byte_size(Chomped) =:= PBSz), -		{error,NewList,DeepBrokenPart2} =   -		    unicode:characters_to_list(Chomped,{utf16,little}), -		BrokenPart = iolist_to_binary(DeepBrokenPart2) -	    end || X <- lists:seq(1,OKLen) ] -      end || N <- lists:seq(1,16,3) ], -    ok. +    ex_binaries_errors_utf16(little). +  ex_binaries_errors_utf16_big(Config) when is_list(Config) -> -    BrokenPart = << <<X:16/big>> || X <- lists:seq(16#DC00,16#DFFF) >>, +    ex_binaries_errors_utf16(big). + +ex_binaries_errors_utf16(Endian) -> +    BrokenSeq = lists:seq(16#DC00, 16#DFFF), +    BrokenPart = case Endian of +		     little -> +			 << <<X:16/little>> || X <- BrokenSeq >>; +		     big -> +			 << <<X:16/big>> || X <- BrokenSeq >> +		 end,      BrokenSz = byte_size(BrokenPart), +    Seq255 = lists:seq(1, 255),      [ begin -	  OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))), -	  OKBin = unicode:characters_to_binary(OKList,unicode,{utf16,big}), -	  OKLen = length(OKList), -	  %% Copy to avoid that the binary get's writable -	  PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>), +	  OKList = lists:append(lists:duplicate(N, Seq255)), +	  OKBin = unicode:characters_to_binary(OKList, unicode, {utf16,Endian}), +	  PartlyBroken = iolist_to_binary([OKBin,BrokenPart]),  	  PBSz = byte_size(PartlyBroken),  	  {error,OKList,DeepBrokenPart} =  -	      unicode:characters_to_list(PartlyBroken,{utf16,big}), +	      unicode:characters_to_list(PartlyBroken, {utf16,Endian}),  	  BrokenPart = iolist_to_binary(DeepBrokenPart), -	  [ begin -		NewList = lists:nthtail(X, OKList), -		NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf16,big})) +  -		    BrokenSz, -		Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz), -		true = (binary:referenced_byte_size(Chomped) =:= PBSz), -		{error,NewList,DeepBrokenPart2} =   -		    unicode:characters_to_list(Chomped,{utf16,big}), -		BrokenPart = iolist_to_binary(DeepBrokenPart2) -	    end || X <- lists:seq(1,OKLen) ] -      end || N <- lists:seq(1,16,3) ], +	  utf16_inner_loop(OKList, BrokenPart, BrokenSz, +			   PartlyBroken, PBSz, Endian) +      end || N <- lists:seq(1, 16, 3) ], +    ok. + +utf16_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) -> +    Sz = length(List)*2 + BrokenSz, +    Chomped = binary:part(PartlyBroken, PBSz - Sz, Sz), +    true = binary:referenced_byte_size(Chomped) =:= PBSz, +    {error,List,DeepBrokenPart} = +	unicode:characters_to_list(Chomped, {utf16,Endian}), +    BrokenPart = iolist_to_binary(DeepBrokenPart), +    utf16_inner_loop(List, BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian); +utf16_inner_loop([], _, _, _, _, _) ->      ok.  ex_binaries_errors_utf32_big(Config) when is_list(Config) -> -    BrokenPart = << <<X:32/big>> || X <- lists:seq(16#DC00,16#DFFF) >>, -    BrokenSz = byte_size(BrokenPart), -    [ begin -	  OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))), -	  OKBin = unicode:characters_to_binary(OKList,unicode,{utf32,big}), -	  OKLen = length(OKList), -	  %% Copy to avoid that the binary get's writable -	  PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>), -	  PBSz = byte_size(PartlyBroken), -	  {error,OKList,DeepBrokenPart} =  -	      unicode:characters_to_list(PartlyBroken,{utf32,big}), -	  BrokenPart = iolist_to_binary(DeepBrokenPart), -	  [ begin -		NewList = lists:nthtail(X, OKList), -		NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf32,big})) +  -		    BrokenSz, -		Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz), -		true = (binary:referenced_byte_size(Chomped) =:= PBSz), -		{error,NewList,DeepBrokenPart2} =   -		    unicode:characters_to_list(Chomped,{utf32,big}), -		BrokenPart = iolist_to_binary(DeepBrokenPart2) -	    end || X <- lists:seq(1,OKLen) ] -      end || N <- lists:seq(1,16,3) ], -    ok. +    ex_binaries_errors_utf32(big).  ex_binaries_errors_utf32_little(Config) when is_list(Config) -> -    BrokenPart = << <<X:32/little>> || X <- lists:seq(16#DC00,16#DFFF) >>, +    ex_binaries_errors_utf32(little). + +ex_binaries_errors_utf32(Endian) -> +    BrokenSeq = lists:seq(16#DC00, 16#DFFF), +    BrokenPart = case Endian of +		     little -> +			 << <<X:32/little>> || X <- BrokenSeq >>; +		     big -> +			 << <<X:32/big>> || X <- BrokenSeq >> +		 end,      BrokenSz = byte_size(BrokenPart), +    Seq255 = lists:seq(1, 255),      [ begin -	  OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))), -	  OKBin = unicode:characters_to_binary(OKList,unicode,{utf32,little}), -	  OKLen = length(OKList), -	  %% Copy to avoid that the binary get's writable -	  PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>), +	  OKList = lists:append(lists:duplicate(N, Seq255)), +	  OKBin = unicode:characters_to_binary(OKList, unicode, {utf32,Endian}), +	  PartlyBroken = iolist_to_binary([OKBin,BrokenPart]),  	  PBSz = byte_size(PartlyBroken),  	  {error,OKList,DeepBrokenPart} =  -	      unicode:characters_to_list(PartlyBroken,{utf32,little}), +	      unicode:characters_to_list(PartlyBroken, {utf32,Endian}),  	  BrokenPart = iolist_to_binary(DeepBrokenPart), -	  [ begin -		NewList = lists:nthtail(X, OKList), -		NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf32,little})) +  -		    BrokenSz, -		Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz), -		true = (binary:referenced_byte_size(Chomped) =:= PBSz), -		{error,NewList,DeepBrokenPart2} =   -		    unicode:characters_to_list(Chomped,{utf32,little}), -		BrokenPart = iolist_to_binary(DeepBrokenPart2) -	    end || X <- lists:seq(1,OKLen) ] -      end || N <- lists:seq(1,16,3) ], +	  utf32_inner_loop(OKList, BrokenPart, BrokenSz, +			   PartlyBroken, PBSz, Endian) +      end || N <- lists:seq(1, 16, 3) ],      ok. - +utf32_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) -> +    Sz = length(List)*4 + BrokenSz, +    Chomped = binary:part(PartlyBroken, PBSz - Sz, Sz), +    true = binary:referenced_byte_size(Chomped) =:= PBSz, +    {error,List,DeepBrokenPart} = +	unicode:characters_to_list(Chomped, {utf32,Endian}), +    BrokenPart = iolist_to_binary(DeepBrokenPart), +    utf32_inner_loop(List, BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian); +utf32_inner_loop([], _, _, _, _, _) -> +    ok.  exceptions(Config) when is_list(Config) ->      setlimit(10), diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index d168a9d9bc..08243f7c4f 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -84,7 +84,7 @@ borderline_test(Size, TempDir) ->      io:format("Testing size ~p", [Size]),      %% Create a file and archive it. -    {_, _, X0} = erlang:now(), +    {_, _, X0} = erlang:timestamp(),      file:write_file(Name, random_byte_list(X0, Size)),      {ok, Archive} = zip:zip(Archive, [Name]),      ok = file:delete(Name), @@ -606,7 +606,7 @@ zip_to_binary(Config) when is_list(Config) ->  aliases(doc) ->      ["Test using the aliases, extract/2, table/2 and create/3"];  aliases(Config) when is_list(Config) -> -    {_, _, X0} = erlang:now(), +    {_, _, X0} = erlang:timestamp(),      Size = 100,      B = list_to_binary(random_byte_list(X0, Size)),      %% create | 
