diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 1 | ||||
-rw-r--r-- | lib/stdlib/test/edlin_expand_SUITE.erl | 11 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 20 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 113 | ||||
-rw-r--r-- | lib/stdlib/test/gen_statem_SUITE.erl | 190 | ||||
-rw-r--r-- | lib/stdlib/test/io_proto_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/math_SUITE.erl | 92 | ||||
-rw-r--r-- | lib/stdlib/test/ms_transform_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 21 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/test/timer_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/timer_simple_SUITE.erl | 2 |
13 files changed, 398 insertions, 75 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index 28c35aed55..deac04aa66 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -52,6 +52,7 @@ MODULES= \ io_proto_SUITE \ lists_SUITE \ log_mf_h_SUITE \ + math_SUITE \ ms_transform_SUITE \ proc_lib_SUITE \ qlc_SUITE \ diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl index ccffa2e244..718d91c6a3 100644 --- a/lib/stdlib/test/edlin_expand_SUITE.erl +++ b/lib/stdlib/test/edlin_expand_SUITE.erl @@ -21,7 +21,7 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_testcase/2, end_per_testcase/2, init_per_group/2,end_per_group/2]). --export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1]). +-export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1, erl_1152/1]). -include_lib("common_test/include/ct.hrl"). @@ -36,7 +36,7 @@ suite() -> {timetrap,{minutes,1}}]. all() -> - [normal, quoted_fun, quoted_module, quoted_both]. + [normal, quoted_fun, quoted_module, quoted_both, erl_1152]. groups() -> []. @@ -149,5 +149,12 @@ quoted_both(Config) when is_list(Config) -> {yes,"weird-fun-name'()",[]} = do_expand("'ExpandTestCaps1':'#"), ok. +erl_1152(Config) when is_list(Config) -> + "\n"++"foo"++" "++[1089]++_ = do_format(["foo",[1089]]), + ok. + do_expand(String) -> edlin_expand:expand(lists:reverse(String)). + +do_format(StringList) -> + lists:flatten(edlin_expand:format_matches(StringList)). diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index d916eb3eef..4ee3950882 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -1554,7 +1554,15 @@ guard(Config) when is_list(Config) -> [], {errors,[{1,erl_lint,illegal_guard_expr}, {2,erl_lint,illegal_guard_expr}], - []}} + []}}, + {guard10, + <<"is_port(_) -> false. + t(P) when port(P) -> ok. + ">>, + [], + {error, + [{2,erl_lint,{obsolete_guard_overridden,port}}], + [{2,erl_lint,{obsolete_guard,{port,1}}}]}} ], [] = run(Config, Ts1), ok. diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index a103f6dc53..13c5662741 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -1166,19 +1166,21 @@ compile(Config, Tests) -> lists:foldl(F, [], Tests). compile_file(Config, Test0) -> - case compile_file(Config, Test0, ['E']) of + Test = ["-module(erl_pp_test).\n", + "-compile(export_all).\n", + Test0], + case compile_file(Config, Test, ['E']) of {ok, RootFile} -> File = RootFile ++ ".E", {ok, Bin0} = file:read_file(File), - Bin = strip_module_info(Bin0), %% A very simple check: just try to compile the output. - case compile_file(Config, Bin, []) of + case compile_file(Config, Bin0, []) of {ok, RootFile2} -> File2 = RootFile2 ++ ".E", {ok, Bin1} = file:read_file(File2), case Bin0 =:= Bin1 of true -> - test_max_line(binary_to_list(Bin)); + test_max_line(binary_to_list(Bin0)); false -> {error, file_contents_modified, {Bin0, Bin1}} end; @@ -1189,11 +1191,8 @@ compile_file(Config, Test0) -> Error end. -compile_file(Config, Test0, Opts0) -> +compile_file(Config, Test, Opts0) -> FileName = filename('erl_pp_test.erl', Config), - Test = list_to_binary(["-module(erl_pp_test). " - "-compile(export_all). ", - Test0]), Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir} | Opts0], ok = file:write_file(FileName, Test), case compile:file(FileName, Opts) of @@ -1202,11 +1201,6 @@ compile_file(Config, Test0, Opts0) -> Error -> Error end. -strip_module_info(Bin) -> - {match, [{Start,_Len}|_]} = re:run(Bin, "module_info"), - <<R:Start/binary,_/binary>> = Bin, - R. - flat_expr1(Expr0) -> Expr = erl_parse:new_anno(Expr0), lists:flatten(erl_pp:expr(Expr)). diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index b02d17bdb6..9a14c7014c 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -218,7 +218,7 @@ memory_check_summary(_Config) -> receive {get_failed_memchecks, FailedMemchecks} -> ok end, io:format("Failed memchecks: ~p\n",[FailedMemchecks]), NoFailedMemchecks = length(FailedMemchecks), - if NoFailedMemchecks > 3 -> + if NoFailedMemchecks > 1 -> ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]); true -> ok @@ -591,12 +591,6 @@ select_fail_do(Opts) -> -define(S(T),ets:info(T,memory)). --define(TAB_STRUCT_SZ, erts_debug:get_internal_state('DbTable_words')). -%%-define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap -%% -%% The hardcoded expected memory sizes (in words) are the ones we expect on: -%% SunOS5.8, 32-bit, non smp, private heap -%% %% Whitebox test of ets:info(X, memory). memory(Config) when is_list(Config) -> @@ -607,11 +601,11 @@ memory(Config) when is_list(Config) -> memory_do(Opts) -> L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts), XR1 = case mem_mode(T1) of - {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078}; - {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278}; - {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286} + {normal,_} -> {13836, 15346, 15346, 15346+6}; + {compressed,4} -> {11041, 12551, 12551, 12551+1}; + {compressed,8} -> {10050, 11560, 11560, 11560} end, - XRes1 = adjust_xmem(L, XR1), + XRes1 = adjust_xmem(L, XR1, 1), Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)}, lists:foreach(fun(T) -> Before = ets:info(T,size), @@ -623,11 +617,11 @@ memory_do(Opts) -> end, L), XR2 = case mem_mode(T1) of - {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060}; - {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260}; - {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268} + {normal,_} -> {13826, 15337, 15337-9, 15337-3}; + {compressed,4} -> {11031, 12542, 12542-9, 12542-8}; + {compressed,8} -> {10040, 11551, 11551-9, 11551-9} end, - XRes2 = adjust_xmem(L, XR2), + XRes2 = adjust_xmem(L, XR2, 1), Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)}, lists:foreach(fun(T) -> Before = ets:info(T,size), @@ -639,17 +633,17 @@ memory_do(Opts) -> end, L), XR3 = case mem_mode(T1) of - {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042}; - {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242}; - {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250} + {normal,_} -> {13816, 15328, 15328-18, 15328-12}; + {compressed,4} -> {11021, 12533, 12533-18, 12533-17}; + {compressed,8} -> {10030, 11542, 11542-18, 11542-18} end, - XRes3 = adjust_xmem(L, XR3), + XRes3 = adjust_xmem(L, XR3, 1), Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)}, lists:foreach(fun(T) -> ets:delete_all_objects(T) end, L), - XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}), + XRes4 = adjust_xmem(L, {50, 256, 256, 256}, 0), Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)}, lists:foreach(fun(T) -> ets:delete(T) @@ -660,7 +654,7 @@ memory_do(Opts) -> ets:select_delete(T,[{'_',[],[true]}]) end, L2), - XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}), + XRes5 = adjust_xmem(L2, {50, 256, 256, 256}, 0), Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)}, io:format("XRes1 = ~p~n" " Res1 = ~p~n~n" @@ -698,15 +692,15 @@ chk_normal_tab_struct_size() -> erlang:system_info(smp_support), erlang:system_info(heap_type)}, io:format("System = ~p~n", [System]), - io:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]), ok. -adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0) -> +adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0, EstCnt) -> %% Adjust for 64-bit, smp, and os: %% Table struct size may differ. - TabDiff = ?TAB_STRUCT_SZ, - {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}. + {TabSz, EstSz} = erts_debug:get_internal_state('DbTable_words'), + HTabSz = TabSz + EstCnt*EstSz, + {A0+TabSz, B0+HTabSz, C0+HTabSz, D0+HTabSz}. %% Misc. whitebox tests t_whitebox(Config) when is_list(Config) -> @@ -1908,7 +1902,7 @@ evil_counter(I,Opts) -> end, Start = Start0 + rand:uniform(100000), ets:insert(T, {dracula,Start}), - Iter = 40000, + Iter = 40000 div syrup_factor(), End = Start + Iter, End = evil_counter_1(Iter, T), ets:delete(T). @@ -3302,7 +3296,8 @@ evil_delete_owner(Name, Flags, Data, Fix) -> exit_large_table_owner(Config) when is_list(Config) -> %%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)], - FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok}; + Laps = 500000 div syrup_factor(), + FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok}; (I) -> Do({erlang:phash2(I, 16#ffffff),I}), {true, I+1} end, 1) @@ -3318,7 +3313,8 @@ exit_large_table_owner_do(Opts,{FEData,Config}) -> exit_many_large_table_owner(Config) when is_list(Config) -> ct:timetrap({minutes,30}), %% valgrind needs a lot %%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)], - FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok}; + Laps = 500000 div syrup_factor(), + FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok}; (I) -> Do({erlang:phash2(I, 16#ffffff),I}), {true, I+1} end, 1) @@ -4271,7 +4267,8 @@ heavy_lookup_element_do(Opts) -> Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]), ok = fill_tab2(Tab, 0, 7000), %% lookup ALL elements 50 times - _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, 50)], + Laps = 50 div syrup_factor(), + _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, Laps)], true = ets:delete(Tab), verify_etsmem(EtsMem). @@ -4295,6 +4292,7 @@ heavy_concurrent(Config) when is_list(Config) -> do_heavy_concurrent(Opts) -> Size = 10000, + Laps = 10000 div syrup_factor(), EtsMem = etsmem(), Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]), ok = fill_tab2(Tab, 0, Size), @@ -4302,7 +4300,7 @@ do_heavy_concurrent(Opts) -> fun (N) -> my_spawn_link( fun () -> - do_heavy_concurrent_proc(Tab, Size, N) + do_heavy_concurrent_proc(Tab, Laps, N) end) end, lists:seq(1, 500)), @@ -4448,15 +4446,15 @@ build_table2(L1,L2,Num) -> T. time_match_object(Tab,Match, Res) -> - T1 = erlang:monotonic_time(micro_seconds), + T1 = erlang:monotonic_time(microsecond), Res = ets:match_object(Tab,Match), - T2 = erlang:monotonic_time(micro_seconds), + T2 = erlang:monotonic_time(microsecond), T2 - T1. time_match(Tab,Match) -> - T1 = erlang:monotonic_time(micro_seconds), + T1 = erlang:monotonic_time(microsecond), ets:match(Tab,Match), - T2 = erlang:monotonic_time(micro_seconds), + T2 = erlang:monotonic_time(microsecond), T2 - T1. seventyfive_percent_success(_,S,Fa,0) -> @@ -5363,12 +5361,12 @@ verify_table_load(T) -> Stats = ets:info(T,stats), {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats, ok = if - AvgLen > 7 -> + AvgLen > 1.2 -> io:format("Table overloaded: Stats=~p\n~p\n", [Stats, ets:info(T)]), false; - Buckets>256, AvgLen < 6 -> + Buckets>256, AvgLen < 0.47 -> io:format("Table underloaded: Stats=~p\n~p\n", [Stats, ets:info(T)]), false; @@ -5442,7 +5440,8 @@ smp_select_delete(Config) when is_list(Config) -> Eq+1 end, 0, TotCnts), - verify_table_load(T), + %% May fail as select_delete does not shrink table (enough) + %%verify_table_load(T), LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]), 0 = ets:info(T,size), false = ets:info(T,fixed), @@ -5718,27 +5717,45 @@ etsmem() -> {Bl0+Bl,BlSz0+BlSz} end, {0,0}, CS) end}, - {Mem,AllTabs}. + {Mem,AllTabs, erts_debug:get_internal_state('DbTable_meta')}. -verify_etsmem({MemInfo,AllTabs}) -> +verify_etsmem(EtsMem) -> wait_for_test_procs(), + verify_etsmem(EtsMem, false). + +verify_etsmem({MemInfo,AllTabs,MetaState}=EtsMem, Adjusted) -> case etsmem() of - {MemInfo,_} -> + {MemInfo,_,_} -> io:format("Ets mem info: ~p", [MemInfo]), case MemInfo of {ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined -> %% Use 'erl +Mea max' to do more complete memory leak testing. {comment,"Incomplete or no mem leak testing"}; _ -> - ok + case Adjusted of + true -> + {comment, "Meta state adjusted"}; + false -> + ok + end end; - {MemInfo2, AllTabs2} -> + + {MemInfo2, AllTabs2, MetaState2} -> io:format("Expected: ~p", [MemInfo]), io:format("Actual: ~p", [MemInfo2]), io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]), io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]), - ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')}, - {comment, "Failed memory check"} + io:format("Meta state before: ~p\n", [MetaState]), + io:format("Meta state after: ~p\n", [MetaState2]), + case {MetaState =:= MetaState2, Adjusted} of + {false, false} -> + io:format("Adjust meta state and retry...\n\n",[]), + {ok,ok} = erts_debug:set_internal_state('DbTable_meta', MetaState), + verify_etsmem(EtsMem, true); + _ -> + ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')}, + {comment, "Failed memory check"} + end end. @@ -6259,5 +6276,11 @@ do_tc(Do, Report) -> T1 = erlang:monotonic_time(), Do(), T2 = erlang:monotonic_time(), - Elapsed = erlang:convert_time_unit(T2 - T1, native, milli_seconds), + Elapsed = erlang:convert_time_unit(T2 - T1, native, millisecond), Report(Elapsed). + +syrup_factor() -> + case erlang:system_info(build_type) of + valgrind -> 20; + _ -> 1 + end. diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 1d1417c2e6..28f9ab81fe 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -37,7 +37,8 @@ all() -> {group, stop_handle_event}, {group, abnormal}, {group, abnormal_handle_event}, - shutdown, stop_and_reply, event_order, code_change, + shutdown, stop_and_reply, state_enter, event_order, + state_timeout, code_change, {group, sys}, hibernate, enter_loop]. @@ -57,7 +58,7 @@ tcs(start) -> tcs(stop) -> [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]; tcs(abnormal) -> - [abnormal1, abnormal2]; + [abnormal1, abnormal1clean, abnormal1dirty, abnormal2]; tcs(sys) -> [sys1, call_format_status, error_format_status, terminate_crash_format, @@ -451,8 +452,52 @@ abnormal1(Config) -> gen_statem:call(Name, {delayed_answer,1000}, 10), Reason), ok = gen_statem:stop(Name), + ?t:sleep(1100), ok = verify_empty_msgq(). +%% Check that time outs in calls work +abnormal1clean(Config) -> + Name = abnormal1clean, + LocalSTM = {local,Name}, + + {ok, _Pid} = + gen_statem:start(LocalSTM, ?MODULE, start_arg(Config, []), []), + + %% timeout call. + delayed = + gen_statem:call(Name, {delayed_answer,1}, {clean_timeout,100}), + {timeout,_} = + ?EXPECT_FAILURE( + gen_statem:call( + Name, {delayed_answer,1000}, {clean_timeout,10}), + Reason), + ok = gen_statem:stop(Name), + ?t:sleep(1100), + ok = verify_empty_msgq(). + +%% Check that time outs in calls work +abnormal1dirty(Config) -> + Name = abnormal1dirty, + LocalSTM = {local,Name}, + + {ok, _Pid} = + gen_statem:start(LocalSTM, ?MODULE, start_arg(Config, []), []), + + %% timeout call. + delayed = + gen_statem:call(Name, {delayed_answer,1}, {dirty_timeout,100}), + {timeout,_} = + ?EXPECT_FAILURE( + gen_statem:call( + Name, {delayed_answer,1000}, {dirty_timeout,10}), + Reason), + ok = gen_statem:stop(Name), + ?t:sleep(1100), + case flush() of + [{Ref,delayed}] when is_reference(Ref) -> + ok + end. + %% Check that bad return values makes the stm crash. Note that we must %% trap exit since we must link to get the real bad_return_ error abnormal2(Config) -> @@ -512,7 +557,8 @@ stop_and_reply(_Config) -> {stop_and_reply,Reason, [R1,{reply,From2,Reply2}]} end}, - {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine}, []), + {ok,STM} = + gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []), Self = self(), Tag1 = make_ref(), @@ -537,6 +583,61 @@ stop_and_reply(_Config) -> +state_enter(_Config) -> + process_flag(trap_exit, true), + Self = self(), + + Machine = + %% Abusing the internal format of From... + #{init => + fun () -> + {ok,start,1} + end, + start => + fun (enter, Prev, N) -> + Self ! {enter,start,Prev,N}, + {keep_state,N + 1}; + (internal, Prev, N) -> + Self ! {internal,start,Prev,N}, + {keep_state,N + 1}; + ({call,From}, echo, N) -> + {next_state,wait,N + 1,{reply,From,{echo,start,N}}}; + ({call,From}, {stop,Reason}, N) -> + {stop_and_reply,Reason,[{reply,From,{stop,N}}],N + 1} + end, + wait => + fun (enter, Prev, N) -> + Self ! {enter,wait,Prev,N}, + {keep_state,N + 1}; + ({call,From}, echo, N) -> + {next_state,start,N + 1, + [{next_event,internal,wait}, + {reply,From,{echo,wait,N}}]} + end}, + {ok,STM} = + gen_statem:start_link( + ?MODULE, {map_statem,Machine,[state_enter]}, []), + + [{enter,start,start,1}] = flush(), + {echo,start,2} = gen_statem:call(STM, echo), + [{enter,wait,start,3}] = flush(), + {wait,[4|_]} = sys:get_state(STM), + {echo,wait,4} = gen_statem:call(STM, echo), + [{enter,start,wait,5},{internal,start,wait,6}] = flush(), + {stop,7} = gen_statem:call(STM, {stop,bye}), + [{'EXIT',STM,bye}] = flush(), + + {noproc,_} = + ?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason), + case flush() of + [] -> + ok; + Other2 -> + ct:fail({unexpected,Other2}) + end. + + + event_order(_Config) -> process_flag(trap_exit, true), @@ -579,7 +680,7 @@ event_order(_Config) -> Result end}, - {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine}, []), + {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []), Self = self(), Tag1 = make_ref(), gen_statem:cast(STM, {reply,{Self,Tag1},ok1}), @@ -609,6 +710,83 @@ event_order(_Config) -> +state_timeout(_Config) -> + process_flag(trap_exit, true), + + Machine = + #{init => + fun () -> + {ok,start,0} + end, + start => + fun + ({call,From}, {go,Time}, 0) -> + self() ! message_to_self, + {next_state, state1, {Time,From}, + %% Verify that internal events goes before external + [{state_timeout,Time,1}, + {next_event,internal,1}]} + end, + state1 => + fun + (internal, 1, Data) -> + %% Verify that a state change cancels timeout 1 + {next_state, state2, Data, + [{timeout,0,2}, + {state_timeout,0,2}, + {next_event,internal,2}]} + end, + state2 => + fun + (internal, 2, Data) -> + %% Verify that {state_timeout,0,_} + %% comes after next_event and that + %% {timeout,0,_} is cancelled by + %% {state_timeout,0,_} + {keep_state, {ok,2,Data}, + [{timeout,0,3}]}; + (state_timeout, 2, {ok,2,{Time,From}}) -> + {next_state, state3, 3, + [{reply,From,ok}, + {state_timeout,Time,3}]} + end, + state3 => + fun + (info, message_to_self, 3) -> + {keep_state, '3'}; + ({call,From}, check, '3') -> + {keep_state, From}; + (state_timeout, 3, From) -> + {stop_and_reply, normal, + {reply,From,ok}} + end}, + + {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []), + TRef = erlang:start_timer(1000, self(), kull), + ok = gen_statem:call(STM, {go,500}), + ok = gen_statem:call(STM, check), + receive + {timeout,TRef,kull} -> + ct:fail(late_timeout) + after 0 -> + receive + {timeout,TRef,kull} -> + ok + after 1000 -> + ct:fail(no_check_timeout) + end + end, + receive + {'EXIT',STM,normal} -> + ok + after 500 -> + ct:fail(did_not_stop) + end, + + verify_empty_msgq(). + + + sys1(Config) -> {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []), {status, Pid, {module,gen_statem}, _} = sys:get_status(Pid), @@ -1271,9 +1449,9 @@ init({callback_mode,CallbackMode,Arg}) -> ets:new(?MODULE, [named_table,private]), ets:insert(?MODULE, {callback_mode,CallbackMode}), init(Arg); -init({map_statem,#{init := Init}=Machine}) -> +init({map_statem,#{init := Init}=Machine,Modes}) -> ets:new(?MODULE, [named_table,private]), - ets:insert(?MODULE, {callback_mode,handle_event_function}), + ets:insert(?MODULE, {callback_mode,[handle_event_function|Modes]}), case Init() of {ok,State,Data,Ops} -> {ok,State,[Data|Machine],Ops}; diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index 1e286a9306..db321d7490 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -1715,7 +1715,7 @@ toerl_loop(Port,Acc) -> end. millistamp() -> - erlang:monotonic_time(milli_seconds). + erlang:monotonic_time(millisecond). get_data_within(Port, X, Acc) when X =< 0 -> ?dbg({get_data_within, X, Acc, ?LINE}), diff --git a/lib/stdlib/test/math_SUITE.erl b/lib/stdlib/test/math_SUITE.erl new file mode 100644 index 0000000000..2b29e44228 --- /dev/null +++ b/lib/stdlib/test/math_SUITE.erl @@ -0,0 +1,92 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2007-2016. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% + +-module(math_SUITE). + +-include_lib("common_test/include/ct.hrl"). + +%% Test server specific exports +-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, + init_per_group/2,end_per_group/2, + init_per_testcase/2, end_per_testcase/2]). + +%% Test cases +-export([floor_ceil/1]). + + +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,1}}]. + +all() -> + [floor_ceil]. + +groups() -> + []. + +init_per_suite(Config) -> + Config. + +end_per_suite(_Config) -> + ok. + +init_per_group(_GroupName, Config) -> + Config. + +end_per_group(_GroupName, Config) -> + Config. + + +init_per_testcase(_Case, Config) -> + Config. + +end_per_testcase(_Case, _Config) -> + ok. + +floor_ceil(_Config) -> + MinusZero = 0.0/(-1.0), + -43.0 = do_floor_ceil(-42.1), + -43.0 = do_floor_ceil(-42.7), + 0.0 = do_floor_ceil(MinusZero), + 10.0 = do_floor_ceil(10.1), + 10.0 = do_floor_ceil(10.9), + + -533.0 = do_floor_ceil(-533.0), + 453555.0 = do_floor_ceil(453555.0), + + -58.0 = do_floor_ceil(-58), + 777.0 = do_floor_ceil(777), + + ok. + +do_floor_ceil(Val) -> + Floor = math:floor(Val), + Ceil = math:ceil(Val), + + true = is_float(Floor), + true = is_float(Ceil), + + if + Floor =:= Ceil -> + Floor; + true -> + 1.0 = Ceil - Floor, + Floor + end. diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index 1c5faa960b..f35013b1b2 100644 --- a/lib/stdlib/test/ms_transform_SUITE.erl +++ b/lib/stdlib/test/ms_transform_SUITE.erl @@ -296,6 +296,8 @@ basic_dbg(Config) when is_list(Config) -> compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> bindings() end)">>), [{['$1','$2'],[],['$_']}] = compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> object() end)">>), + [{[],[],[{return_trace}]}] = + compile_and_run(<<"dbg:fun2ms(fun([]) -> return_trace() end)">>), ok. %% Test calling of ets/dbg:fun2ms from the shell. diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 2bd940020c..8c7d5a5fcf 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -58,7 +58,7 @@ -export([ badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1, filter_var/1, single/1, exported_var/1, generator_vars/1, - nomatch/1, errors/1, pattern/1, + nomatch/1, errors/1, pattern/1, overridden_bif/1, eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1, evaluator/1, string_to_handle/1, table/1, process_dies/1, @@ -126,7 +126,7 @@ groups() -> [{parse_transform, [], [badarg, nested_qlc, unused_var, lc, fun_clauses, filter_var, single, exported_var, generator_vars, - nomatch, errors, pattern]}, + nomatch, errors, pattern, overridden_bif]}, {evaluation, [], [eval, cursor, fold, eval_unique, eval_cache, append, evaluator, string_to_handle, table, process_dies, sort, @@ -468,6 +468,23 @@ pattern(Config) when is_list(Config) -> -record(k, {t,v}).\n">>, Ts), ok. +%% Override a guard BIF with an imported or local function. +overridden_bif(Config) -> + Ts = [ + <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])), + [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12], + (is_reference(P) andalso P > 5)])), + Empty = gb_sets:empty(), Single = gb_sets:singleton(42), + GbSets = [Empty,Single], + [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0])) + ">> + ], + run(Config, "-import(gb_sets, [size/1]). + -compile({no_auto_import, [size/1, is_reference/1]}). + port(N) -> N rem 2 =:= 0. + is_reference(N) -> N rem 10 =:= 0.\n", Ts), + ok. + %% eval/2 eval(Config) when is_list(Config) -> diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index c409a6949b..07eb6772db 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -573,7 +573,7 @@ otp_5327(Config) when is_list(Config) -> (catch evaluate(<<"<<32/unit:8>>.">>, [])), ok. -%% OTP-5435. sys_pre_expand not in the path. +%% OTP-5435. compiler application not in the path. otp_5435(Config) when is_list(Config) -> true = <<103133:64/float>> =:= evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []), @@ -591,8 +591,9 @@ start_node(Name) -> otp_5435_2() -> true = code:del_path(compiler), - %% sys_pre_expand can no longer be found - %% OTP-5876. But erl_expand_records can! + %% Make sure record evaluation is not dependent on the compiler + %% application being in the path. + %% OTP-5876. [{attribute,_,record,{bar,_}},ok] = scan(<<"rd(foo,{bar}), rd(bar,{foo = (#foo{})#foo.bar}), diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl index 5fc95b16a6..9062cbae80 100644 --- a/lib/stdlib/test/timer_SUITE.erl +++ b/lib/stdlib/test/timer_SUITE.erl @@ -353,7 +353,7 @@ res_combine({error,Es}, [{error,E}|T]) -> system_time() -> - erlang:monotonic_time(milli_seconds). + erlang:monotonic_time(millisecond). %% ------------------------------------------------------- %% diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl index ff5116b8b6..1a582ae95a 100644 --- a/lib/stdlib/test/timer_simple_SUITE.erl +++ b/lib/stdlib/test/timer_simple_SUITE.erl @@ -457,7 +457,7 @@ append([],X) -> X. system_time() -> - erlang:monotonic_time(micro_seconds). + erlang:monotonic_time(microsecond). %% ------------------------------------------------------- %% |