Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion lib/ssh/test/property_test/ssh_eqc_client_info_timing.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@

-module(ssh_eqc_client_info_timing).

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

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

Expand Down
107 changes: 67 additions & 40 deletions lib/ssh/test/property_test/ssh_eqc_client_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,36 @@
%%

-module(ssh_eqc_client_server).
-compile(nowarn_unused_function).
-export([
prop_seq/0,
prop_seq/1,
do_prop_seq/2,
prop_parallel/0,
prop_parallel/1,
initial_state/0,
initial_state/1,
command/1,
initial_state_pre/1,
initial_state_args/1,
initial_state_next/3,
ssh_server/3,
ssh_server_pre/1,
ssh_server_args/1,
ssh_client/0,
ssh_client_pre/1,
ssh_client_args/1,
ssh_open_connection_pre/1,
ssh_close_connection_pre/1,
ssh_open_channel_pre/1,
ssh_close_channel_pre/1,
ssh_start_subsyst_pre/1,
ssh_send_pre/1,
precondition/2,
next_state/3,
postcondition/3
]).

-compile(export_all).

-ifndef(PROPER).
-else.
%% Only use proper
Expand Down Expand Up @@ -164,7 +191,7 @@ initial_state() ->
#state{}.

%%% called when using commands/2
initial_state(DataDir) ->
initial_state(_DataDir) ->
application:stop(ssh),
ssh:start().

Expand Down Expand Up @@ -260,11 +287,11 @@ ssh_server(IP0, DataDir, ExtraOptions) ->
Other
end.

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

ssh_server_next(S, Srvr, _) ->
S#state{servers=[Srvr | S#state.servers]}.
%% ssh_server_next(S, Srvr, _) ->
%% S#state{servers=[Srvr | S#state.servers]}.

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

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

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


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

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

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

ssh_open_connection(#srvr{address=Ip, port=Port}, DataDir) ->
ok(ssh:connect(ensure_string(Ip), Port,
[
{silently_accept_hosts, true},
{user_dir, user_dir(DataDir)},
{user_interaction, false},
{connect_timeout, 2000}
], 2000)).
%% ssh_open_connection(#srvr{address=Ip, port=Port}, DataDir) ->
%% ok(ssh:connect(ensure_string(Ip), Port,
%% [
%% {silently_accept_hosts, true},
%% {user_dir, user_dir(DataDir)},
%% {user_interaction, false},
%% {connect_timeout, 2000}
%% ], 2000)).

ssh_open_connection_post(_S, _Args, Result) -> is_ok(Result).
%% ssh_open_connection_post(_S, _Args, Result) -> is_ok(Result).

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

%%%----------------
%%% Stop a new connection
%%% Precondition: connection exists

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

ssh_close_connection_args(S) -> [oneof(S#state.connections)].
%% ssh_close_connection_args(S) -> [oneof(S#state.connections)].

ssh_close_connection(ConnectionRef) -> ssh:close(ConnectionRef).
%% ssh_close_connection(ConnectionRef) -> ssh:close(ConnectionRef).

ssh_close_connection_next(S, _, [ConnRef]) ->
S#state{connections = S#state.connections--[ConnRef],
channels = [C || C <- S#state.channels,
C#chan.conn_ref /= ConnRef]
}.
%% ssh_close_connection_next(S, _, [ConnRef]) ->
%% S#state{connections = S#state.connections--[ConnRef],
%% channels = [C || C <- S#state.channels,
%% C#chan.conn_ref /= ConnRef]
%% }.

%%%----------------
%%% Start a new channel without a sub system
%%% Precondition: connection exists

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

ssh_open_channel_args(S) -> [oneof(S#state.connections)].
%% ssh_open_channel_args(S) -> [oneof(S#state.connections)].

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

ssh_send_blocking(_S, _Args) ->
true.
%% ssh_send_blocking(_S, _Args) ->
%% true.

ssh_send_post(_S, [C,_,Msg], Response) when is_binary(Response) ->
Expected = ssh_eqc_subsys:response(modify_msg(C,Msg), C#chan.subsystem),
case Response of
Expected -> true;
_ -> {send_failed, size(Response), size(Expected)}
end;
%% ssh_send_post(_S, [C,_,Msg], Response) when is_binary(Response) ->
%% Expected = ssh_eqc_subsys:response(modify_msg(C,Msg), C#chan.subsystem),
%% case Response of
%% Expected -> true;
%% _ -> {send_failed, size(Response), size(Expected)}
%% end;

ssh_send_post(_S, _Args, Response) ->
{error,Response}.
%% ssh_send_post(_S, _Args, Response) ->
%% {error,Response}.


modify_msg(_, <<>>) -> <<>>;
Expand Down Expand Up @@ -472,8 +499,8 @@ ok({error,Err}) -> {error,Err}.
is_ok({error,_}) -> false;
is_ok(_) -> true.

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

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

data_dir(Dir, File) -> filename:join(Dir, File).
%% data_dir(Dir, File) -> filename:join(Dir, File).
system_dir(Dir, File) -> filename:join([Dir, "system", File]).
user_dir(Dir, File) -> filename:join([Dir, "user", File]).

Expand Down
16 changes: 10 additions & 6 deletions lib/ssh/test/property_test/ssh_eqc_encode_decode.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,9 @@

-module(ssh_eqc_encode_decode).

-compile(export_all).

-export([prop_ssh_decode/0,
prop_ssh_decode_encode/0
]).
-include_lib("common_test/include/ct_property_test.hrl").

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

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

gen_uint16() -> gen_byte(2).
%% gen_uint16() -> gen_byte(2).

gen_uint32() -> gen_byte(4).

gen_uint64() -> gen_byte(8).
%% gen_uint64() -> gen_byte(8).

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

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

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

strip_0s([0|T]) -> strip_0s(T);
strip_0s(X) -> X.
%% strip_0s([0|T]) -> strip_0s(T);
%% strip_0s(X) -> X.


gen_string() ->
Expand Down Expand Up @@ -209,6 +210,7 @@ msg_code(Num) -> Name
?MSG_CODE('SSH_MSG_USERAUTH_SUCCESS', 52);
?MSG_CODE('SSH_MSG_USERAUTH_BANNER', 53);
?MSG_CODE('SSH_MSG_USERAUTH_PK_OK', 60);
%% FIXME Warning: this clause cannot match because a previous clause
?MSG_CODE('SSH_MSG_USERAUTH_PASSWD_CHANGEREQ', 60);
?MSG_CODE('SSH_MSG_DISCONNECT', 1);
?MSG_CODE('SSH_MSG_IGNORE', 2);
Expand Down Expand Up @@ -236,12 +238,14 @@ msg_code(Num) -> Name
?MSG_CODE('SSH_MSG_USERAUTH_INFO_RESPONSE', 61);
?MSG_CODE('SSH_MSG_KEXDH_INIT', 30);
?MSG_CODE('SSH_MSG_KEXDH_REPLY', 31);
%% FIXME Warning: this clause cannot match because a previous clause
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REQUEST_OLD', 30);
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REQUEST', 34);
?MSG_CODE('SSH_MSG_KEX_DH_GEX_GROUP', 31);
?MSG_CODE('SSH_MSG_KEX_DH_GEX_INIT', 32);
?MSG_CODE('SSH_MSG_KEX_DH_GEX_REPLY', 33);
?MSG_CODE('SSH_MSG_KEX_ECDH_INIT', 30);
%% FIXME Warning: this clause cannot match because a previous clause
?MSG_CODE('SSH_MSG_KEX_ECDH_REPLY', 31).

%%%====================================================
Expand Down
Loading