|
75 | 75 | system_limit/1, |
76 | 76 | hopefull_data_encoding/1, |
77 | 77 | hopefull_export_fun_bug/1, |
78 | | - huge_iovec/1]). |
| 78 | + huge_iovec/1, |
| 79 | + creation_selection/1, |
| 80 | + creation_selection_test/1]). |
79 | 81 |
|
80 | 82 | %% Internal exports. |
81 | 83 | -export([sender/3, receiver2/2, dummy_waiter/0, dead_process/0, |
@@ -106,7 +108,7 @@ all() -> |
106 | 108 | {group, bad_dist}, {group, bad_dist_ext}, |
107 | 109 | start_epmd_false, epmd_module, system_limit, |
108 | 110 | hopefull_data_encoding, hopefull_export_fun_bug, |
109 | | - huge_iovec]. |
| 111 | + huge_iovec, creation_selection]. |
110 | 112 |
|
111 | 113 | groups() -> |
112 | 114 | [{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]}, |
@@ -2810,9 +2812,126 @@ mk_rand_bin(0, Data) -> |
2810 | 2812 | mk_rand_bin(N, Data) -> |
2811 | 2813 | mk_rand_bin(N-1, [rand:uniform(256) - 1 | Data]). |
2812 | 2814 |
|
| 2815 | +creation_selection(Config) when is_list(Config) -> |
| 2816 | + register(creation_selection_test_supervisor, self()), |
| 2817 | + Name = atom_to_list(?FUNCTION_NAME) ++ "-" |
| 2818 | + ++ integer_to_list(erlang:system_time()), |
| 2819 | + Host = hostname(), |
| 2820 | + Cmd = lists:append( |
| 2821 | + [ct:get_progname(), |
| 2822 | + " -noshell", |
| 2823 | + " -setcookie ", atom_to_list(erlang:get_cookie()), |
| 2824 | + " -pa ", filename:dirname(code:which(?MODULE)), |
| 2825 | + " -s ", atom_to_list(?MODULE), " ", |
| 2826 | + " creation_selection_test ", atom_to_list(node()), " ", |
| 2827 | + atom_to_list(net_kernel:longnames()), " ", Name, " ", Host]), |
| 2828 | + ct:pal("Node command: ~p~n", [Cmd]), |
| 2829 | + Port = open_port({spawn, Cmd}, [exit_status]), |
| 2830 | + Node = list_to_atom(lists:append([Name, "@", Host])), |
| 2831 | + ok = receive_creation_selection_info(Port, Node). |
| 2832 | + |
| 2833 | +receive_creation_selection_info(Port, Node) -> |
| 2834 | + receive |
| 2835 | + {creation_selection_test, Node, Creations, InvalidCreation, |
| 2836 | + ClashResolvedCreation} = Msg -> |
| 2837 | + ct:log("Test result: ~p~n", [Msg]), |
| 2838 | + %% Verify that creation values are created as expected. The |
| 2839 | + %% list of creations is in reverse start order... |
| 2840 | + MaxC = (1 bsl 32) - 1, |
| 2841 | + MinC = 4, |
| 2842 | + StartOrderCreations = lists:reverse(Creations), |
| 2843 | + InvalidCreation = lists:foldl(fun (C, C) when is_integer(C), |
| 2844 | + MinC =< C, |
| 2845 | + C =< MaxC -> |
| 2846 | + %% Return next expected |
| 2847 | + %% creation... |
| 2848 | + if C == MaxC -> MinC; |
| 2849 | + true -> C+1 |
| 2850 | + end |
| 2851 | + end, |
| 2852 | + hd(StartOrderCreations), |
| 2853 | + StartOrderCreations), |
| 2854 | + false = lists:member(ClashResolvedCreation, [InvalidCreation |
| 2855 | + | Creations]), |
| 2856 | + receive |
| 2857 | + {Port, {exit_status, 0}} -> |
| 2858 | + Port ! {self(), close}, |
| 2859 | + ok; |
| 2860 | + {Port, {exit_status, EStat}} -> |
| 2861 | + ct:fail({"node exited abnormally: ", EStat}) |
| 2862 | + end; |
| 2863 | + {Port, {exit_status, EStat}} -> |
| 2864 | + ct:fail({"node prematurely exited: ", EStat}); |
| 2865 | + {Port, {data, Data}} -> |
| 2866 | + ct:log("~ts", [Data]), |
| 2867 | + receive_creation_selection_info(Port, Node) |
| 2868 | + end, |
| 2869 | + ok. |
| 2870 | + |
| 2871 | +creation_selection_test([TestSupNode, LongNames, Name, Host]) -> |
| 2872 | + try |
| 2873 | + StartArgs = [Name, |
| 2874 | + case LongNames of |
| 2875 | + true -> longnames; |
| 2876 | + false -> shortnames |
| 2877 | + end], |
| 2878 | + Node = list_to_atom(lists:append([atom_to_list(Name), |
| 2879 | + "@", atom_to_list(Host)])), |
| 2880 | + GoDistributed = fun (F) -> |
| 2881 | + {ok, _} = net_kernel:start(StartArgs), |
| 2882 | + Node = node(), |
| 2883 | + Creation = erlang:system_info(creation), |
| 2884 | + _ = F(Creation), |
| 2885 | + net_kernel:stop(), |
| 2886 | + Creation |
| 2887 | + end, |
| 2888 | + %% We start multiple times to verify that the creation values |
| 2889 | + %% we get from epmd are delivered in sequence. This is a |
| 2890 | + %% must for the test case such as it is written now, but can be |
| 2891 | + %% changed. If changed, this test case must be updated... |
| 2892 | + {Creations, |
| 2893 | + LastCreation} = lists:foldl(fun (_, {Cs, _LC}) -> |
| 2894 | + CFun = fun (X) -> X end, |
| 2895 | + C = GoDistributed(CFun), |
| 2896 | + {[C|Cs], C} |
| 2897 | + end, {[], 0}, lists:seq(1, 5)), |
| 2898 | + %% We create a pid with the creation that epmd will offer us the next |
| 2899 | + %% time we start the distribution and then start the distribution |
| 2900 | + %% once more. The node should avoid this creation, since this would |
| 2901 | + %% cause external identifiers in the system with same |
| 2902 | + %% nodename/creation pair as used by the local node, which in turn |
| 2903 | + %% would cause these identifers not to work as expected. That is, the |
| 2904 | + %% node should silently reject this creation and chose another one when |
| 2905 | + %% starting the distribution. |
| 2906 | + InvalidCreation = LastCreation+1, |
| 2907 | + Pid = erts_test_utils:mk_ext_pid({Node, InvalidCreation}, 4711, 0), |
| 2908 | + true = erts_debug:size(Pid) > 0, %% External pid |
| 2909 | + ResultFun = fun (ClashResolvedCreation) -> |
| 2910 | + pong = net_adm:ping(TestSupNode), |
| 2911 | + Msg = {creation_selection_test, node(), Creations, |
| 2912 | + InvalidCreation, ClashResolvedCreation}, |
| 2913 | + {creation_selection_test_supervisor, TestSupNode} |
| 2914 | + ! Msg, |
| 2915 | + %% Wait a bit so the message have time to get |
| 2916 | + %% through before we take down the distribution... |
| 2917 | + receive after 500 -> ok end |
| 2918 | + end, |
| 2919 | + _ = GoDistributed(ResultFun), |
| 2920 | + %% Ensure Pid is not garbage collected before starting the |
| 2921 | + %% distribution... |
| 2922 | + _ = id(Pid), |
| 2923 | + erlang:halt(0) |
| 2924 | + catch |
| 2925 | + Class:Reason:StackTrace -> |
| 2926 | + erlang:display({Class, Reason, StackTrace}), |
| 2927 | + erlang:halt(17) |
| 2928 | + end. |
2813 | 2929 |
|
2814 | 2930 | %%% Utilities |
2815 | 2931 |
|
| 2932 | +id(X) -> |
| 2933 | + X. |
| 2934 | + |
2816 | 2935 | timestamp() -> |
2817 | 2936 | erlang:monotonic_time(millisecond). |
2818 | 2937 |
|
|
0 commit comments