22
22
% %
23
23
24
24
-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
+ ]).
25
54
26
- -compile (export_all ).
27
-
28
55
-ifndef (PROPER ).
29
56
-else .
30
57
% % Only use proper
@@ -164,7 +191,7 @@ initial_state() ->
164
191
# state {}.
165
192
166
193
% %% called when using commands/2
167
- initial_state (DataDir ) ->
194
+ initial_state (_DataDir ) ->
168
195
application :stop (ssh ),
169
196
ssh :start ().
170
197
@@ -260,11 +287,11 @@ ssh_server(IP0, DataDir, ExtraOptions) ->
260
287
Other
261
288
end .
262
289
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.
265
292
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]}.
268
295
269
296
% %%----------------
270
297
% %% Start a new client
@@ -277,7 +304,7 @@ ssh_client_args(_S) -> [].
277
304
278
305
ssh_client () -> spawn (fun client_init /0 ).
279
306
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]}.
281
308
282
309
283
310
client_init () -> client_loop ().
@@ -305,44 +332,44 @@ do(Pid, Fun, Timeout) when is_function(Fun,0) ->
305
332
306
333
ssh_open_connection_pre (S ) -> S # state .servers /= [].
307
334
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}].
309
336
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)).
318
345
319
- ssh_open_connection_post (_S , _Args , Result ) -> is_ok (Result ).
346
+ % % ssh_open_connection_post(_S, _Args, Result) -> is_ok(Result).
320
347
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]}.
322
349
323
350
% %%----------------
324
351
% %% Stop a new connection
325
352
% %% Precondition: connection exists
326
353
327
354
ssh_close_connection_pre (S ) -> S # state .connections /= [].
328
355
329
- ssh_close_connection_args (S ) -> [oneof (S # state .connections )].
356
+ % % ssh_close_connection_args(S) -> [oneof(S#state.connections)].
330
357
331
- ssh_close_connection (ConnectionRef ) -> ssh :close (ConnectionRef ).
358
+ % % ssh_close_connection(ConnectionRef) -> ssh:close(ConnectionRef).
332
359
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
+ % % }.
338
365
339
366
% %%----------------
340
367
% %% Start a new channel without a sub system
341
368
% %% Precondition: connection exists
342
369
343
370
ssh_open_channel_pre (S ) -> S # state .connections /= [].
344
371
345
- ssh_open_channel_args (S ) -> [oneof (S # state .connections )].
372
+ % % ssh_open_channel_args(S) -> [oneof(S#state.connections)].
346
373
347
374
% %% For re-arrangement in parallel tests.
348
375
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,
432
459
end
433
460
end ).
434
461
435
- ssh_send_blocking (_S , _Args ) ->
436
- true .
462
+ % % ssh_send_blocking(_S, _Args) ->
463
+ % % true.
437
464
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;
444
471
445
- ssh_send_post (_S , _Args , Response ) ->
446
- {error ,Response }.
472
+ % % ssh_send_post(_S, _Args, Response) ->
473
+ % % {error,Response}.
447
474
448
475
449
476
modify_msg (_ , <<>>) -> <<>>;
@@ -472,8 +499,8 @@ ok({error,Err}) -> {error,Err}.
472
499
is_ok ({error ,_ }) -> false ;
473
500
is_ok (_ ) -> true .
474
501
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.
477
504
478
505
% %%================================================================
479
506
% %% The rest is taken and modified from ssh_test_lib.erl
@@ -486,7 +513,7 @@ setup_rsa(Dir) ->
486
513
[Dir ,data_dir (Dir ),system_dir (Dir ),user_dir (Dir )]),
487
514
ssh_test_lib :setup_all_user_host_keys ( data_dir (Dir ), user_dir (Dir ), system_dir (Dir )).
488
515
489
- data_dir (Dir , File ) -> filename :join (Dir , File ).
516
+ % % data_dir(Dir, File) -> filename:join(Dir, File).
490
517
system_dir (Dir , File ) -> filename :join ([Dir , " system" , File ]).
491
518
user_dir (Dir , File ) -> filename :join ([Dir , " user" , File ]).
492
519
0 commit comments