Skip to content

Commit cd2cf74

Browse files
committed
ssh: cleanup in property_test
- explicit exports - unused code commented out
1 parent 68cad02 commit cd2cf74

File tree

3 files changed

+78
-47
lines changed

3 files changed

+78
-47
lines changed

lib/ssh/test/property_test/ssh_eqc_client_info_timing.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@
2323

2424
-module(ssh_eqc_client_info_timing).
2525

26-
-compile(export_all).
26+
-export([prop_seq/1]).
2727

2828
-include_lib("common_test/include/ct_property_test.hrl").
2929

lib/ssh/test/property_test/ssh_eqc_client_server.erl

Lines changed: 67 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,36 @@
2222
%%
2323

2424
-module(ssh_eqc_client_server).
25+
-compile(nowarn_unused_function).
26+
-export([
27+
prop_seq/0,
28+
prop_seq/1,
29+
do_prop_seq/2,
30+
prop_parallel/0,
31+
prop_parallel/1,
32+
initial_state/0,
33+
initial_state/1,
34+
command/1,
35+
initial_state_pre/1,
36+
initial_state_args/1,
37+
initial_state_next/3,
38+
ssh_server/3,
39+
ssh_server_pre/1,
40+
ssh_server_args/1,
41+
ssh_client/0,
42+
ssh_client_pre/1,
43+
ssh_client_args/1,
44+
ssh_open_connection_pre/1,
45+
ssh_close_connection_pre/1,
46+
ssh_open_channel_pre/1,
47+
ssh_close_channel_pre/1,
48+
ssh_start_subsyst_pre/1,
49+
ssh_send_pre/1,
50+
precondition/2,
51+
next_state/3,
52+
postcondition/3
53+
]).
2554

26-
-compile(export_all).
27-
2855
-ifndef(PROPER).
2956
-else.
3057
%% Only use proper
@@ -164,7 +191,7 @@ initial_state() ->
164191
#state{}.
165192

166193
%%% called when using commands/2
167-
initial_state(DataDir) ->
194+
initial_state(_DataDir) ->
168195
application:stop(ssh),
169196
ssh:start().
170197

@@ -260,11 +287,11 @@ ssh_server(IP0, DataDir, ExtraOptions) ->
260287
Other
261288
end.
262289

263-
ssh_server_post(_S, _Args, #srvr{port=Port}) -> (0 < Port) andalso (Port < 65536);
264-
ssh_server_post(_S, _Args, _) -> false.
290+
%% ssh_server_post(_S, _Args, #srvr{port=Port}) -> (0 < Port) andalso (Port < 65536);
291+
%% ssh_server_post(_S, _Args, _) -> false.
265292

266-
ssh_server_next(S, Srvr, _) ->
267-
S#state{servers=[Srvr | S#state.servers]}.
293+
%% ssh_server_next(S, Srvr, _) ->
294+
%% S#state{servers=[Srvr | S#state.servers]}.
268295

269296
%%%----------------
270297
%%% Start a new client
@@ -277,7 +304,7 @@ ssh_client_args(_S) -> [].
277304

278305
ssh_client() -> spawn(fun client_init/0).
279306

280-
ssh_client_next(S, Pid, _) -> S#state{clients=[Pid|S#state.clients]}.
307+
%% ssh_client_next(S, Pid, _) -> S#state{clients=[Pid|S#state.clients]}.
281308

282309

283310
client_init() -> client_loop().
@@ -305,44 +332,44 @@ do(Pid, Fun, Timeout) when is_function(Fun,0) ->
305332

306333
ssh_open_connection_pre(S) -> S#state.servers /= [].
307334

308-
ssh_open_connection_args(S) -> [oneof(S#state.servers), {var,data_dir}].
335+
%% ssh_open_connection_args(S) -> [oneof(S#state.servers), {var,data_dir}].
309336

310-
ssh_open_connection(#srvr{address=Ip, port=Port}, DataDir) ->
311-
ok(ssh:connect(ensure_string(Ip), Port,
312-
[
313-
{silently_accept_hosts, true},
314-
{user_dir, user_dir(DataDir)},
315-
{user_interaction, false},
316-
{connect_timeout, 2000}
317-
], 2000)).
337+
%% ssh_open_connection(#srvr{address=Ip, port=Port}, DataDir) ->
338+
%% ok(ssh:connect(ensure_string(Ip), Port,
339+
%% [
340+
%% {silently_accept_hosts, true},
341+
%% {user_dir, user_dir(DataDir)},
342+
%% {user_interaction, false},
343+
%% {connect_timeout, 2000}
344+
%% ], 2000)).
318345

319-
ssh_open_connection_post(_S, _Args, Result) -> is_ok(Result).
346+
%% ssh_open_connection_post(_S, _Args, Result) -> is_ok(Result).
320347

321-
ssh_open_connection_next(S, ConnRef, [_,_]) -> S#state{connections=[ConnRef|S#state.connections]}.
348+
%% ssh_open_connection_next(S, ConnRef, [_,_]) -> S#state{connections=[ConnRef|S#state.connections]}.
322349

323350
%%%----------------
324351
%%% Stop a new connection
325352
%%% Precondition: connection exists
326353

327354
ssh_close_connection_pre(S) -> S#state.connections /= [].
328355

329-
ssh_close_connection_args(S) -> [oneof(S#state.connections)].
356+
%% ssh_close_connection_args(S) -> [oneof(S#state.connections)].
330357

331-
ssh_close_connection(ConnectionRef) -> ssh:close(ConnectionRef).
358+
%% ssh_close_connection(ConnectionRef) -> ssh:close(ConnectionRef).
332359

333-
ssh_close_connection_next(S, _, [ConnRef]) ->
334-
S#state{connections = S#state.connections--[ConnRef],
335-
channels = [C || C <- S#state.channels,
336-
C#chan.conn_ref /= ConnRef]
337-
}.
360+
%% ssh_close_connection_next(S, _, [ConnRef]) ->
361+
%% S#state{connections = S#state.connections--[ConnRef],
362+
%% channels = [C || C <- S#state.channels,
363+
%% C#chan.conn_ref /= ConnRef]
364+
%% }.
338365

339366
%%%----------------
340367
%%% Start a new channel without a sub system
341368
%%% Precondition: connection exists
342369

343370
ssh_open_channel_pre(S) -> S#state.connections /= [].
344371

345-
ssh_open_channel_args(S) -> [oneof(S#state.connections)].
372+
%% ssh_open_channel_args(S) -> [oneof(S#state.connections)].
346373

347374
%%% For re-arrangement in parallel tests.
348375
ssh_open_channel_pre(S,[C]) when is_record(S,state) -> lists:member(C,S#state.connections).
@@ -432,18 +459,18 @@ ssh_send(C=#chan{conn_ref=ConnectionRef, ref=ChannelRef, client_pid=Pid}, Type,
432459
end
433460
end).
434461

435-
ssh_send_blocking(_S, _Args) ->
436-
true.
462+
%% ssh_send_blocking(_S, _Args) ->
463+
%% true.
437464

438-
ssh_send_post(_S, [C,_,Msg], Response) when is_binary(Response) ->
439-
Expected = ssh_eqc_subsys:response(modify_msg(C,Msg), C#chan.subsystem),
440-
case Response of
441-
Expected -> true;
442-
_ -> {send_failed, size(Response), size(Expected)}
443-
end;
465+
%% ssh_send_post(_S, [C,_,Msg], Response) when is_binary(Response) ->
466+
%% Expected = ssh_eqc_subsys:response(modify_msg(C,Msg), C#chan.subsystem),
467+
%% case Response of
468+
%% Expected -> true;
469+
%% _ -> {send_failed, size(Response), size(Expected)}
470+
%% end;
444471

445-
ssh_send_post(_S, _Args, Response) ->
446-
{error,Response}.
472+
%% ssh_send_post(_S, _Args, Response) ->
473+
%% {error,Response}.
447474

448475

449476
modify_msg(_, <<>>) -> <<>>;
@@ -472,8 +499,8 @@ ok({error,Err}) -> {error,Err}.
472499
is_ok({error,_}) -> false;
473500
is_ok(_) -> true.
474501

475-
ensure_string({A,B,C,D}) -> lists:flatten(io_lib:format("~w.~w.~w.~w",[A,B,C,D]));
476-
ensure_string(X) -> X.
502+
%% ensure_string({A,B,C,D}) -> lists:flatten(io_lib:format("~w.~w.~w.~w",[A,B,C,D]));
503+
%% ensure_string(X) -> X.
477504

478505
%%%================================================================
479506
%%% The rest is taken and modified from ssh_test_lib.erl
@@ -486,7 +513,7 @@ setup_rsa(Dir) ->
486513
[Dir,data_dir(Dir),system_dir(Dir),user_dir(Dir)]),
487514
ssh_test_lib:setup_all_user_host_keys( data_dir(Dir), user_dir(Dir), system_dir(Dir)).
488515

489-
data_dir(Dir, File) -> filename:join(Dir, File).
516+
%% data_dir(Dir, File) -> filename:join(Dir, File).
490517
system_dir(Dir, File) -> filename:join([Dir, "system", File]).
491518
user_dir(Dir, File) -> filename:join([Dir, "user", File]).
492519

lib/ssh/test/property_test/ssh_eqc_encode_decode.erl

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,8 +23,9 @@
2323

2424
-module(ssh_eqc_encode_decode).
2525

26-
-compile(export_all).
27-
26+
-export([prop_ssh_decode/0,
27+
prop_ssh_decode_encode/0
28+
]).
2829
-include_lib("common_test/include/ct_property_test.hrl").
2930

3031
%% Public key records:
@@ -147,20 +148,20 @@ gen_boolean() -> choose(0,1).
147148

148149
gen_byte() -> choose(0,255).
149150

150-
gen_uint16() -> gen_byte(2).
151+
%% gen_uint16() -> gen_byte(2).
151152

152153
gen_uint32() -> gen_byte(4).
153154

154-
gen_uint64() -> gen_byte(8).
155+
%% gen_uint64() -> gen_byte(8).
155156

156157
gen_byte(N) when N>0 -> [gen_byte() || _ <- lists:seq(1,N)].
157158

158159
gen_char() -> choose($a,$z).
159160

160161
gen_mpint() -> ?LET(I, largeint(), ssh_bits:mpint(I)).
161162

162-
strip_0s([0|T]) -> strip_0s(T);
163-
strip_0s(X) -> X.
163+
%% strip_0s([0|T]) -> strip_0s(T);
164+
%% strip_0s(X) -> X.
164165

165166

166167
gen_string() ->
@@ -209,6 +210,7 @@ msg_code(Num) -> Name
209210
?MSG_CODE('SSH_MSG_USERAUTH_SUCCESS', 52);
210211
?MSG_CODE('SSH_MSG_USERAUTH_BANNER', 53);
211212
?MSG_CODE('SSH_MSG_USERAUTH_PK_OK', 60);
213+
%% FIXME Warning: this clause cannot match because a previous clause
212214
?MSG_CODE('SSH_MSG_USERAUTH_PASSWD_CHANGEREQ', 60);
213215
?MSG_CODE('SSH_MSG_DISCONNECT', 1);
214216
?MSG_CODE('SSH_MSG_IGNORE', 2);
@@ -236,12 +238,14 @@ msg_code(Num) -> Name
236238
?MSG_CODE('SSH_MSG_USERAUTH_INFO_RESPONSE', 61);
237239
?MSG_CODE('SSH_MSG_KEXDH_INIT', 30);
238240
?MSG_CODE('SSH_MSG_KEXDH_REPLY', 31);
241+
%% FIXME Warning: this clause cannot match because a previous clause
239242
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REQUEST_OLD', 30);
240243
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REQUEST', 34);
241244
?MSG_CODE('SSH_MSG_KEX_DH_GEX_GROUP', 31);
242245
?MSG_CODE('SSH_MSG_KEX_DH_GEX_INIT', 32);
243246
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REPLY', 33);
244247
?MSG_CODE('SSH_MSG_KEX_ECDH_INIT', 30);
248+
%% FIXME Warning: this clause cannot match because a previous clause
245249
?MSG_CODE('SSH_MSG_KEX_ECDH_REPLY', 31).
246250

247251
%%%====================================================

0 commit comments

Comments
 (0)