Hooray, PULSE things look stable; remove debugging verbose cruft
This commit is contained in:
parent
c10200138c
commit
b4d9ac5fe0
9 changed files with 12 additions and 89 deletions
|
@ -1,7 +1,7 @@
|
|||
{application, machi, [
|
||||
{description, "A village of write-once files."},
|
||||
{vsn, "0.0.0"},
|
||||
{applications, [kernel, stdlib, sasl, crypto]},
|
||||
{applications, [kernel, stdlib, crypto]},
|
||||
{mod,{machi_app,[]}},
|
||||
{registered, []},
|
||||
{env, [
|
||||
|
|
|
@ -36,7 +36,6 @@
|
|||
-export([start/2, stop/1]).
|
||||
|
||||
start(_StartType, _StartArgs) ->
|
||||
erlang:display({machi_app,self()}),
|
||||
case machi_sup:start_link() of
|
||||
{ok, Pid} ->
|
||||
{ok, Pid};
|
||||
|
|
|
@ -751,10 +751,8 @@ run_middleworker_job(Fun, ArgList, WTimeout) ->
|
|||
Parent = self(),
|
||||
MiddleWorker =
|
||||
spawn(fun() ->
|
||||
?V("Goo1-~w,", [self()]),
|
||||
PidsMons =
|
||||
[spawn_monitor(fun() ->
|
||||
?V("Goo1-~w,", [self()]),
|
||||
Res = (catch Fun(Arg)),
|
||||
exit(Res)
|
||||
end) || Arg <- ArgList],
|
||||
|
|
|
@ -142,7 +142,6 @@ ets_table_name(FluName) when is_atom(FluName) ->
|
|||
%% list_to_atom(binary_to_list(FluName) ++ "_epoch").
|
||||
|
||||
main2(FluName, TcpPort, DataDir, Rest) ->
|
||||
?V("flu-~w,", [self()]),
|
||||
{Props, DbgProps} = case proplists:get_value(dbg, Rest) of
|
||||
undefined ->
|
||||
{Rest, []};
|
||||
|
@ -223,7 +222,6 @@ start_append_server(S, AckPid) ->
|
|||
%% spawn_link(fun() -> run_projection_server(S) end).
|
||||
|
||||
run_listen_server(#state{flu_name=FluName, tcp_port=TcpPort}=S) ->
|
||||
?V("listen-~w,", [self()]),
|
||||
register(make_listener_regname(FluName), self()),
|
||||
SockOpts = ?PB_PACKET_OPTS ++
|
||||
[{reuseaddr, true}, {mode, binary}, {active, false}],
|
||||
|
@ -239,7 +237,6 @@ run_listen_server(#state{flu_name=FluName, tcp_port=TcpPort}=S) ->
|
|||
|
||||
run_append_server(FluPid, AckPid, #state{flu_name=Name,
|
||||
wedged=Wedged_p,epoch_id=EpochId}=S) ->
|
||||
?V("append-~w,", [self()]),
|
||||
%% Reminder: Name is the "main" name of the FLU, i.e., no suffix
|
||||
register(Name, self()),
|
||||
TID = ets:new(ets_table_name(Name),
|
||||
|
@ -252,7 +249,7 @@ run_append_server(FluPid, AckPid, #state{flu_name=Name,
|
|||
|
||||
listen_server_loop(LSock, S) ->
|
||||
{ok, Sock} = gen_tcp:accept(LSock),
|
||||
spawn_link(fun() -> ?V("net_server-~w,", [self()]), net_server_loop(Sock, S) end),
|
||||
spawn_link(fun() -> net_server_loop(Sock, S) end),
|
||||
listen_server_loop(LSock, S).
|
||||
|
||||
append_server_loop(FluPid, #state{data_dir=DataDir,wedged=Wedged_p,
|
||||
|
@ -263,7 +260,7 @@ append_server_loop(FluPid, #state{data_dir=DataDir,wedged=Wedged_p,
|
|||
From ! wedged,
|
||||
append_server_loop(FluPid, S);
|
||||
{seq_append, From, Prefix, Chunk, CSum, Extra} ->
|
||||
spawn(fun() -> ?V("appendX-~w,", [self()]), append_server_dispatch(From, Prefix,
|
||||
spawn(fun() -> append_server_dispatch(From, Prefix,
|
||||
Chunk, CSum, Extra,
|
||||
DataDir, AppendServerPid) end),
|
||||
append_server_loop(FluPid, S);
|
||||
|
@ -297,36 +294,22 @@ append_server_loop(FluPid, #state{data_dir=DataDir,wedged=Wedged_p,
|
|||
end.
|
||||
|
||||
net_server_loop(Sock, S) ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
case gen_tcp:recv(Sock, 0, ?SERVER_CMD_READ_TIMEOUT) of
|
||||
{ok, Bin} ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{RespBin, S2} =
|
||||
case machi_pb:decode_mpb_ll_request(Bin) of
|
||||
LL_req when LL_req#mpb_ll_request.do_not_alter == 2 ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
ZARF = (catch do_pb_ll_request(LL_req, S)),
|
||||
%% ?V("~w ~w ~p,", [self(), ?LINE, ZARF]),
|
||||
{R, NewS} = ZARF,
|
||||
%% {R, NewS} = do_pb_ll_request(LL_req, S),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{R, NewS} = do_pb_ll_request(LL_req, S),
|
||||
{machi_pb:encode_mpb_ll_response(R), mode(low, NewS)};
|
||||
_ ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
HL_req = machi_pb:decode_mpb_request(Bin),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
1 = HL_req#mpb_request.do_not_alter,
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{R, NewS} = do_pb_hl_request(HL_req, make_high_clnt(S)),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{machi_pb:encode_mpb_response(R), mode(high, NewS)}
|
||||
end,
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
ok = gen_tcp:send(Sock, RespBin),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
net_server_loop(Sock, S2);
|
||||
{error, SockError} ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
Msg = io_lib:format("Socket error ~w", [SockError]),
|
||||
R = #mpb_ll_response{req_id= <<>>,
|
||||
generic=#mpb_errorresp{code=1, msg=Msg}},
|
||||
|
@ -356,13 +339,10 @@ make_high_clnt(S) ->
|
|||
S.
|
||||
|
||||
do_pb_ll_request(#mpb_ll_request{req_id=ReqID}, #state{pb_mode=high}=S) ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
Result = {high_error, 41, "Low protocol request while in high mode"},
|
||||
{machi_pb_translate:to_pb_response(ReqID, unused, Result), S};
|
||||
do_pb_ll_request(PB_request, S) ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
Req = machi_pb_translate:from_pb_request(PB_request),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{ReqID, Cmd, Result, S2} =
|
||||
case Req of
|
||||
{RqID, {LowCmd, _}=CMD}
|
||||
|
@ -370,19 +350,13 @@ do_pb_ll_request(PB_request, S) ->
|
|||
LowCmd == low_wedge_status; LowCmd == low_list_files ->
|
||||
%% Skip wedge check for projection commands!
|
||||
%% Skip wedge check for these unprivileged commands
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{Rs, NewS} = do_pb_ll_request3(CMD, S),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{RqID, CMD, Rs, NewS};
|
||||
{RqID, CMD} ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
EpochID = element(2, CMD), % by common convention
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{Rs, NewS} = do_pb_ll_request2(EpochID, CMD, S),
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{RqID, CMD, Rs, NewS}
|
||||
end,
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{machi_pb_translate:to_pb_response(ReqID, Cmd, Result), S2}.
|
||||
|
||||
do_pb_ll_request2(EpochID, CMD, S) ->
|
||||
|
@ -432,7 +406,6 @@ do_pb_ll_request3({low_delete_migration, _EpochID, File}, S) ->
|
|||
do_pb_ll_request3({low_trunc_hack, _EpochID, File}, S) ->
|
||||
{do_server_trunc_hack(File, S), S};
|
||||
do_pb_ll_request3({low_proj, PCMD}, S) ->
|
||||
?V("~w ~w,", [self(), ?LINE]),
|
||||
{do_server_proj_request(PCMD, S), S}.
|
||||
|
||||
do_pb_hl_request(#mpb_request{req_id=ReqID}, #state{pb_mode=low}=S) ->
|
||||
|
@ -746,7 +719,6 @@ write_server_find_pid(Prefix) ->
|
|||
|
||||
start_seq_append_server(Prefix, DataDir, AppendServerPid) ->
|
||||
proc_lib:spawn_link(fun() ->
|
||||
?V("appendY-~w,", [self()]),
|
||||
%% The following is only necessary to
|
||||
%% make nice process relationships in
|
||||
%% 'appmon' and related tools.
|
||||
|
|
|
@ -102,7 +102,6 @@ start_link(FluName, TcpPort, DataDir, Props) ->
|
|||
[FluName, TcpPort, DataDir, Props]).
|
||||
|
||||
init([FluName, TcpPort, DataDir, Props0]) ->
|
||||
erlang:display({flu_psup,self()}),
|
||||
RestartStrategy = one_for_all,
|
||||
MaxRestarts = 1000,
|
||||
MaxSecondsBetweenRestarts = 3600,
|
||||
|
|
|
@ -50,7 +50,6 @@ start_link() ->
|
|||
supervisor:start_link({local, ?SERVER}, ?MODULE, []).
|
||||
|
||||
init([]) ->
|
||||
erlang:display({flu_sup,self()}),
|
||||
RestartStrategy = one_for_one,
|
||||
MaxRestarts = 1000,
|
||||
MaxSecondsBetweenRestarts = 3600,
|
||||
|
|
|
@ -108,7 +108,6 @@ read_latest_projection(PidSpec, ProjType) ->
|
|||
|
||||
read_latest_projection(PidSpec, ProjType, Timeout)
|
||||
when ProjType == 'public' orelse ProjType == 'private' ->
|
||||
?V("~w ~w ~w,", [self(), ?MODULE, ?LINE]),
|
||||
g_call(PidSpec, {read_latest_projection, ProjType}, Timeout).
|
||||
|
||||
%% @doc Fetch the projection record type `ProjType' for epoch number `Epoch' .
|
||||
|
@ -173,7 +172,6 @@ g_call(PidSpec, Arg, Timeout) ->
|
|||
%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
init([DataDir, NotifyWedgeStateChanges]) ->
|
||||
?V("pstore-~w,", [self()]),
|
||||
lclock_init(),
|
||||
PublicDir = machi_util:make_projection_filename(DataDir, "public"),
|
||||
PrivateDir = machi_util:make_projection_filename(DataDir, "private"),
|
||||
|
@ -201,9 +199,7 @@ handle_call({{read_latest_projection, ProjType}, LC1}, _From, S) ->
|
|||
{EpochNum, _CSum} = if ProjType == public -> S#state.max_public_epochid;
|
||||
ProjType == private -> S#state.max_private_epochid
|
||||
end,
|
||||
?V("~w ~w ~w,", [self(), ?MODULE, ?LINE]),
|
||||
{Reply, NewS} = do_proj_read(ProjType, EpochNum, S),
|
||||
?V("~w ~w ~w,", [self(), ?MODULE, ?LINE]),
|
||||
{reply, {Reply, LC2}, NewS};
|
||||
handle_call({{read, ProjType, Epoch}, LC1}, _From, S) ->
|
||||
LC2 = lclock_update(LC1),
|
||||
|
|
|
@ -47,11 +47,8 @@ start_link() ->
|
|||
supervisor:start_link({local, ?SERVER}, ?MODULE, []).
|
||||
|
||||
init([]) ->
|
||||
erlang:display({flu_sup,?LINE,self()}),
|
||||
{_, Ps} = process_info(self(), links),
|
||||
erlang:display({flu_sup,self(), links, Ps}),
|
||||
[unlink(P) || P <- Ps],
|
||||
erlang:display({flu_sup,?LINE,self()}),
|
||||
%% {_, Ps} = process_info(self(), links),
|
||||
%% [unlink(P) || P <- Ps],
|
||||
RestartStrategy = one_for_one,
|
||||
MaxRestarts = 1000,
|
||||
MaxSecondsBetweenRestarts = 3600,
|
||||
|
|
|
@ -171,7 +171,7 @@ all_list() ->
|
|||
[P#p_srvr.name || {P, _Dir} <- all_list_extra()].
|
||||
|
||||
setup(Num, Seed) ->
|
||||
?V("\nsetup(~w,~w", [self(), Num]),
|
||||
?V("\nsetup(~w", [Num]),
|
||||
All_list = lists:sublist(all_list(), Num),
|
||||
All_listE = lists:sublist(all_list_extra(), Num),
|
||||
%% shutdown_hard() has taken care of killing all relevant procs.
|
||||
|
@ -183,18 +183,14 @@ setup(Num, Seed) ->
|
|||
|
||||
%% GRRR, not PULSE: {ok, _} = application:ensure_all_started(machi),
|
||||
[begin
|
||||
?V(",z~w,~w", [?LINE,App]),
|
||||
_QQ = (catch application:start(App)),
|
||||
erlang:display({app_start,App,_QQ})
|
||||
_QQ = (catch application:start(App))
|
||||
end || App <- [machi] ],
|
||||
?V(",z~w", [?LINE]),
|
||||
|
||||
SimSpec = {part_sim, {machi_partition_simulator, start_link,
|
||||
[{0,0,0}, 0, 100]},
|
||||
permanent, 500, worker, []},
|
||||
?V(",z~w", [?LINE]),
|
||||
{ok, PSimPid} = supervisor:start_child(machi_sup, SimSpec),
|
||||
?V(",z~w", [?LINE]),
|
||||
ok = machi_partition_simulator:set_seed(Seed),
|
||||
_Partitions = machi_partition_simulator:get(All_list),
|
||||
?V(",z~w", [?LINE]),
|
||||
|
@ -207,9 +203,9 @@ setup(Num, Seed) ->
|
|||
end || {P, Dir} <- All_listE],
|
||||
%% Set up the chain
|
||||
Dict = orddict:from_list([{P#p_srvr.name, P} || {P, _Dir} <- All_listE]),
|
||||
?V(",z~w", [?LINE]),
|
||||
[machi_chain_manager1:set_chain_members(get_chmgr(P), Dict) ||
|
||||
{P, _Dir} <- All_listE],
|
||||
?V(",z~w", [?LINE]),
|
||||
|
||||
%% Trigger some environment reactions for humming consensus: first
|
||||
%% do all the same server first, then round-robin evenly across
|
||||
|
@ -217,7 +213,6 @@ setup(Num, Seed) ->
|
|||
[begin
|
||||
_QQa = machi_chain_manager1:test_react_to_env(get_chmgr(P))
|
||||
end || {P, _Dir} <- All_listE, _I <- lists:seq(1,20), _Repeat <- [1,2]],
|
||||
?V(",z~w", [?LINE]),
|
||||
[begin
|
||||
_QQa = machi_chain_manager1:test_react_to_env(get_chmgr(P))
|
||||
end || _I <- lists:seq(1,20), {P, _Dir} <- All_listE, _Repeat <- [1,2]],
|
||||
|
@ -307,10 +302,7 @@ dump_state() ->
|
|||
[P || P <- Ps,
|
||||
P#projection_v1.epoch_number /= 0]
|
||||
end} || {Name, Proxy} <- ProxiesDict],
|
||||
?V("~w,", [ [{X,whereis(X)} || X <- [machi_sup, machi_flu_sup, machi_partition_simulator]] ]),
|
||||
?V("~w,", [catch application:stop(machi)]),
|
||||
[?V("~w,", [timer:sleep(10)]) || _ <- lists:seq(1,50)],
|
||||
?V("~w,", [ [{X,whereis(X)} || X <- [machi_sup, machi_flu_sup, machi_partition_simulator]] ]),
|
||||
?V("~w", [catch application:stop(machi)]),
|
||||
?V(")", []),
|
||||
Diag1 = Diag2 = "skip_diags",
|
||||
{Report, PrivProjs, lists:flatten([Diag1, Diag2])}
|
||||
|
@ -325,14 +317,11 @@ prop_pulse() ->
|
|||
prop_pulse(new).
|
||||
|
||||
prop_pulse(Style) when Style == new; Style == regression ->
|
||||
_ = application:start(sasl),
|
||||
_ = application:start(crypto),
|
||||
?FORALL({Cmds0, Seed}, {gen_commands(Style), pulse:seed()},
|
||||
?IMPLIES(1 < length(Cmds0) andalso length(Cmds0) < 11,
|
||||
begin
|
||||
erlang:display({prop,?MODULE,?LINE,self()}),
|
||||
ok = shutdown_hard(),
|
||||
erlang:display({prop,?MODULE,?LINE,self()}),
|
||||
%% PULSE can be really unfair, of course, including having exec_ticks
|
||||
%% run where all of FLU a does its ticks then FLU b. Such a situation
|
||||
%% doesn't always allow unanimous private projection store values:
|
||||
|
@ -355,14 +344,9 @@ erlang:display({prop,?MODULE,?LINE,self()}),
|
|||
pulse:verbose([format]),
|
||||
{_H2, S2, Res} = pulse:run(
|
||||
fun() ->
|
||||
?V("PROP-~w,", [self()]),
|
||||
%% {_H, _S, _R} = run_commands(?MODULE, Cmds)
|
||||
_QAQA = run_commands(?MODULE, Cmds)
|
||||
, erlang:display({prop,?MODULE,?LINE,self()}), _QAQA
|
||||
%% ,?V("pid681=~p", [process_info(list_to_pid("<0.681.0>"))]), _QAQA
|
||||
{_H, _S, _R} = run_commands(?MODULE, Cmds)
|
||||
end, [{seed, Seed},
|
||||
{strategy, unfair}]),
|
||||
erlang:display({prop,?MODULE,?LINE,self()}),
|
||||
ok = shutdown_hard(),
|
||||
{Report, PrivProjs, Diag} = S2#state.dump_state,
|
||||
|
||||
|
@ -479,37 +463,16 @@ get_do_shrink() ->
|
|||
end.
|
||||
|
||||
shutdown_hard() ->
|
||||
erlang:display({hard,?MODULE,?LINE,self()}),
|
||||
%% HANG: [catch machi_flu_psup:stop_flu_package(FLU) || FLU <- all_list()],
|
||||
erlang:display({apps,?LINE,application:which_applications()}),
|
||||
%%erlang:display({apps,?LINE,application:which_applications()}),
|
||||
[begin
|
||||
erlang:display({hard,?MODULE,?LINE,self()}),
|
||||
_STOP = application:stop(App),
|
||||
erlang:display({stop, App, _STOP})
|
||||
_STOP = application:stop(App)
|
||||
end || App <- [machi] ],
|
||||
timer:sleep(100),
|
||||
|
||||
(catch unlink(whereis(machi_partition_simulator))),
|
||||
[begin
|
||||
Pid = whereis(X),
|
||||
erlang:display({hard,?MODULE,?LINE,self(),X,Pid}),
|
||||
okokokokokokwhaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
||||
%% %%%%%%DELME deadlock source? spawn(fun() -> ?QC_FMT("shutdown-~w,", [self()]), (catch X:stop()) end),
|
||||
%% timer:sleep(50),
|
||||
%% timer:sleep(10),
|
||||
%% (catch exit(Pid, shutdown)),
|
||||
%% timer:sleep(1),
|
||||
%% (catch exit(Pid, kill))
|
||||
%% end || X <- [machi_partition_simulator] ],
|
||||
end || X <- [machi_partition_simulator, machi_flu_sup, machi_sup] ],
|
||||
timer:sleep(100),
|
||||
ok.
|
||||
|
||||
exec_ticks(Num, All_listE) ->
|
||||
Parent = self(),
|
||||
Pids = [spawn_link(fun() ->
|
||||
?V("tick-~w,", [self()]),
|
||||
[begin
|
||||
M_name = P#p_srvr.name,
|
||||
%% Max = 10,
|
||||
|
|
Loading…
Reference in a new issue