Skip to content

Commit 93cddfa

Browse files
committed
Whitespace: using spaces in modified lines
1 parent 6745aa9 commit 93cddfa

File tree

3 files changed

+24
-24
lines changed

3 files changed

+24
-24
lines changed

lib/inets/examples/httpd_load_test/hdlt_ctrl.erl

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,9 @@
5151
-define(SSH_CONNECT_TIMEOUT, 5000).
5252
-define(NODE_START_TIMEOUT, 5000).
5353
-define(LOCAL_PROXY_START_TIMEOUT, ?NODE_START_TIMEOUT * 4).
54-
-define(DEFAULT_DEBUGS,
55-
[{ctrl, info}, {follower, silence}, {proxy, silence}, {client, silence}]).
54+
-define(DEBUGS_OPTION_KEYS, [ctrl, proxy, follower, client]).
55+
-define(DEBUGS_OPTION_VALUES, [silence, info, log, debug]).
56+
-define(DEFAULT_DEBUGS, lists:zip(?DEBUGS_OPTION_KEYS, ?DEBUGS_OPTION_VALUES)).
5657
-define(DEFAULT_WORK_SIM, 10000).
5758
-define(DEFAULT_DATA_SIZE_START, 500).
5859
-define(DEFAULT_DATA_SIZE_END, 1500).
@@ -504,7 +505,7 @@ local_follower_module() ->
504505
Path when is_list(Path) ->
505506
Path;
506507
_ ->
507-
exit({follower_module_not_found, Mod})
508+
exit({follower_module_not_found, Mod})
508509
end.
509510

510511
follower_module() ->
@@ -725,7 +726,7 @@ proxy_loop(#proxy{mode = started,
725726
receive
726727
{proxy_request, Ref, From, {start_node, Debug}} ->
727728
?LOG("[starting] received start_node order", []),
728-
case hdlt_follower_node:start_link(Host, NodeName,
729+
case hdlt_follower_node:start_link(Host, NodeName,
729730
ErlPath, Paths, Args, Debug) of
730731
{ok, Node} ->
731732
?DEBUG("[starting] node ~p started - now monitor", [Node]),
@@ -1241,13 +1242,13 @@ verify_debugs([{Tag, Debug}|Debugs]) ->
12411242
verify_debugs(Debugs).
12421243

12431244
verify_debug(Tag, Debug) ->
1244-
case lists:member(Tag, [ctrl, proxy, follower, client]) of
1245+
case lists:member(Tag, ?DEBUGS_OPTION_KEYS) of
12451246
true ->
12461247
ok;
12471248
false ->
12481249
exit({bad_debug_tag, Tag})
12491250
end,
1250-
case lists:member(Debug, [silence, info, log, debug]) of
1251+
case lists:member(Debug, ?DEBUGS_OPTION_VALUES) of
12511252
true ->
12521253
ok;
12531254
false ->

lib/inets/examples/httpd_load_test/hdlt_follower_node.erl

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -114,17 +114,17 @@ wait_for_follower_node(Parent, Host, Name, Node, Paths, Args,
114114
case (catch mk_cmd(Host, Name, Paths, Args, Waiter, Prog)) of
115115
{ok, Cmd} ->
116116
?DEBUG("command generated: ~n~s", [Cmd]),
117-
case (catch ssh_follower_start(Host, Cmd)) of
117+
case (catch ssh_follower_start(Host, Cmd)) of
118118
{ok, Conn, _Chan} ->
119119
?DEBUG("ssh channel created", []),
120120
receive
121-
{FollowerPid, follower_started} ->
122-
?DEBUG("follower started: ~p", [FollowerPid]),
121+
{FollowerPid, follower_started} ->
122+
?DEBUG("follower started: ~p", [FollowerPid]),
123123
unregister(Waiter),
124-
follower_started(Parent, LinkTo, FollowerPid, Conn,
125-
DebugLevel)
124+
follower_started(Parent, LinkTo, FollowerPid, Conn,
125+
DebugLevel)
126126
after 32000 ->
127-
?INFO("follower node failed to report in on time",
127+
?INFO("follower node failed to report in on time",
128128
[]),
129129
%% If it seems that the node was partially started,
130130
%% try to kill it.
@@ -200,8 +200,8 @@ follower_started(ReplyTo, Master, Follower, Conn, Level)
200200
when is_pid(Master) andalso is_pid(Follower) ->
201201
process_flag(trap_exit, true),
202202
SName = lists:flatten(
203-
io_lib:format("HDLT FOLLOWER CTRL[~p,~p]",
204-
[self(), node(Follower)])),
203+
io_lib:format("HDLT FOLLOWER CTRL[~p,~p]",
204+
[self(), node(Follower)])),
205205
?SET_NAME(SName),
206206
?SET_LEVEL(Level),
207207
?LOG("initiating", []),
@@ -219,18 +219,18 @@ follower_running(Master, MasterRef, Follower, FollowerRef, Conn) ->
219219
receive
220220
{'DOWN', MasterRef, process, _Object, _Info} ->
221221
?LOG("received DOWN from master", []),
222-
erlang:demonitor(FollowerRef, [flush]),
223-
Follower ! {nodedown, node()},
222+
erlang:demonitor(FollowerRef, [flush]),
223+
Follower ! {nodedown, node()},
224224
ssh:close(Conn);
225225

226-
{'DOWN', FollowerRef, process, Object, _Info} ->
227-
?LOG("received DOWN from follower (~p)", [Object]),
226+
{'DOWN', FollowerRef, process, Object, _Info} ->
227+
?LOG("received DOWN from follower (~p)", [Object]),
228228
erlang:demonitor(MasterRef, [flush]),
229229
ssh:close(Conn);
230230

231231
Other ->
232232
?DEBUG("received unknown: ~n~p", [Other]),
233-
follower_running(Master, MasterRef, Follower, FollowerRef, Conn)
233+
follower_running(Master, MasterRef, Follower, FollowerRef, Conn)
234234

235235
end.
236236

@@ -255,7 +255,7 @@ mk_cmd(Host, Name, Paths, Args, Waiter, Prog) ->
255255
" -detached -nopinput ",
256256
Args, " ",
257257
" -sname ", Name, "@", Host,
258-
" -s ", ?MODULE, " follower_node_start ", node(),
258+
" -s ", ?MODULE, " follower_node_start ", node(),
259259
" ", Waiter,
260260
" ", PaPaths]))}.
261261

@@ -267,12 +267,12 @@ follower_node_start([Master, Waiter]) ->
267267
spawn(?MODULE, wait_for_master_to_die, [Master, Waiter, silence]);
268268
follower_node_start([Master, Waiter, Level]) ->
269269
spawn(?MODULE, wait_for_master_to_die, [Master, Waiter, Level]).
270-
270+
271271

272272
wait_for_master_to_die(Master, Waiter, Level) ->
273273
process_flag(trap_exit, true),
274274
SName = lists:flatten(
275-
io_lib:format("HDLT-FOLLOWER MASTER MONITOR[~p,~p,~p]",
275+
io_lib:format("HDLT-FOLLOWER MASTER MONITOR[~p,~p,~p]",
276276
[self(), node(), Master])),
277277
?SET_NAME(SName),
278278
?SET_LEVEL(Level),

lib/inets/test/httpd_bench_SUITE.erl

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -240,8 +240,7 @@ setup(_Config, _LocalNode) ->
240240
case net_adm:ping(Node) of
241241
pong -> ok;
242242
pang ->
243-
%% {ok, Node} = slave:start(Host, inets_perf_server, PeerArgs, no_link, Prog)
244-
{ok, Node} = peer:start(#{
243+
{ok, Node} = peer:start(#{
245244
host => Host,
246245
name => inets_perf_server,
247246
args => PeerArgs,

0 commit comments

Comments
 (0)