Skip to content

Commit 58da2c0

Browse files
committed
Merge branch 'raimo/ssl/dist-test-zero-fault' into maint
* raimo/ssl/dist-test-zero-fault: Limit the number of spawned nodes Handle more "normal" socket errors Add test for early double call of local fun Remove redundant export Improve test case diagnostics Fix Cryptcookie test crypto distribution bugs
2 parents 0b5fdd2 + 77b497d commit 58da2c0

7 files changed

+143
-63
lines changed

lib/ssl/test/cryptcookie.erl

Lines changed: 18 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -462,9 +462,13 @@ encrypt_and_send_chunk(
462462
Chunk, Size) ->
463463
%%
464464
Timestamp = timestamp(),
465+
Seq_1 = Seq + 1,
465466
if
466-
RekeyCount =< Seq;
467-
RekeyTimestamp + RekeyTime =< Timestamp ->
467+
Seq_1 < RekeyCount,
468+
Timestamp < RekeyTimestamp + RekeyTime ->
469+
{encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, Size),
470+
[Seq_1 | Params]};
471+
true ->
468472
{OutStream_1, Params_1} =
469473
encrypt_and_send_rekey_chunk(
470474
OutStream, Seq, Params, Timestamp),
@@ -475,15 +479,12 @@ encrypt_and_send_chunk(
475479
{encrypt_and_send_chunk(
476480
OutStream_1, 0, Params_1, Chunk, Size),
477481
[1 | Params_1]}
478-
end;
479-
true ->
480-
{encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, Size),
481-
[Seq + 1 | Params]}
482+
end
482483
end.
483484

484485
encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, 0) -> % Tick
485486
<<>> = Chunk, % ASSERT
486-
%% A ticks are sent as a somewhat random size block
487+
%% A tick is sent as a somewhat random size block
487488
%% to make it less obvious to spot
488489
<<S:8>> = crypto:strong_rand_bytes(1),
489490
TickSize = 8 + (S band 63),
@@ -565,8 +566,8 @@ recv_and_decrypt_chunk(InStream, SeqParams = [Seq | Params]) ->
565566
{[DataChunk | InStream_1], [Seq + 1 | Params]};
566567
<<?TICK_CHUNK, _/binary>> ->
567568
{[<<>> | InStream_1], [Seq + 1 | Params]};
568-
<<?REKEY_CHUNK, RekeyChunk>> ->
569-
case decrypt_rekey(Params, RekeyChunk) of
569+
<<?REKEY_CHUNK, RekeyChunk/binary>> ->
570+
case decrypt_rekey(Seq, Params, RekeyChunk) of
570571
Params_1 = #params{} ->
571572
recv_and_decrypt_chunk(
572573
InStream_1, [0 | Params_1]);
@@ -644,24 +645,26 @@ decrypt_block(
644645
end.
645646

646647
decrypt_rekey(
648+
Seq,
647649
Params =
648650
#params{
649-
iv = IV,
651+
iv = {IVSalt, IVNo},
650652
key = Key,
651653
rekey_key = #keypair{public = PubKeyA} = KeyPair,
652-
hmac_algorithm = HmacAlgorithm},
654+
hmac_algorithm = HmacAlgo},
653655
RekeyChunk) ->
654656
%%
655657
PubKeyLen = byte_size(PubKeyA),
656658
case RekeyChunk of
657659
<<PubKeyB:PubKeyLen/binary>> ->
658-
SharedSecret = compute_shared_secret(KeyPair, PubKeyB),
659660
KeyLen = byte_size(Key),
660-
IVLen = byte_size(IV),
661-
IVSaltLen = IVLen - 6,
661+
IVSaltLen = byte_size(IVSalt),
662+
SharedSecret = compute_shared_secret(KeyPair, PubKeyB),
663+
IV = <<(IVNo + Seq):48>>,
662664
{Key_1, <<IVSalt_1:IVSaltLen/binary, IVNo_1:48>>} =
663665
hmac_key_iv(
664-
HmacAlgorithm, SharedSecret, [Key, IV], KeyLen, IVLen),
666+
HmacAlgo, SharedSecret, [Key, IVSalt, IV],
667+
KeyLen, IVSaltLen + 6),
665668
Params#params{
666669
iv = {IVSalt_1, IVNo_1},
667670
key = Key_1 };

lib/ssl/test/dist_cryptcookie.erl

Lines changed: 32 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -293,33 +293,36 @@ output_handler_data(OutStream, EncryptState, CS_DH) ->
293293
erlang:dist_ctrl_get_data_notification(tl(CS_DH)),
294294
output_handler(OutStream_1, EncryptState_1, CS_DH).
295295

296-
%% Get outbound data from VM; encrypt and send,
296+
%% Transfer outbound data from VM; encrypt and send,
297297
%% until the VM has no more
298298
%%
299299
%% Front,Size,Rear is an Okasaki queue of binaries with total byte Size
300300
%%
301301
output_handler_xfer(
302-
OutStream, EncryptState, CS_DH, Front, Size, Rear)
303-
when hd(CS_DH) =< Size ->
302+
OutStream, EncryptState, [ChunkSize|_] = CS_DH, Front, Size, Rear)
303+
when ChunkSize =< Size ->
304+
%%
305+
%% We have a full chunk or more -> collect chunks and send
304306
%%
305-
%% We have a full chunk or more
306-
%% -> collect one chunk or less and send
307307
output_handler_collect(
308308
OutStream, EncryptState, CS_DH, Front, Size, Rear);
309309
output_handler_xfer(
310-
OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
311-
%% when Size < hd(CS_DH) ->
310+
OutStream, EncryptState, [_|DistHandle] = CS_DH, Front, Size, Rear) ->
311+
%% when Size < ChunkSize ->
312312
%%
313313
%% We do not have a full chunk -> try to fetch more from VM
314-
case erlang:dist_ctrl_get_data(tl(CS_DH)) of
314+
%%
315+
case erlang:dist_ctrl_get_data(DistHandle) of
315316
none ->
316317
if
317318
Size =:= 0 ->
318319
%% No more data from VM, nothing buffered
319320
%% -> done, for now
321+
%%
320322
{OutStream, EncryptState};
321323
true ->
322324
%% The VM had no more -> send what we have
325+
%%
323326
output_handler_collect(
324327
OutStream, EncryptState, CS_DH, Front, Size, Rear)
325328
end;
@@ -330,49 +333,50 @@ output_handler_xfer(
330333
Iov)
331334
end.
332335

333-
%% Enqueue VM data while splitting large binaries into
334-
%% chunk size; hd(CS_DH)
336+
%% Enqueue VM data while splitting large binaries into max
337+
%% ChunkSize = hd(CS_DH)
335338
%%
336339
output_handler_enq(
337340
OutStream, EncryptState, CS_DH, Front, Size, Rear, []) ->
338341
output_handler_xfer(
339342
OutStream, EncryptState, CS_DH, Front, Size, Rear);
340343
output_handler_enq(
341344
OutStream, EncryptState, CS_DH, Front, Size, Rear, [Bin|Iov]) ->
342-
output_handler_enq(
345+
output_handler_split(
343346
OutStream, EncryptState, CS_DH, Front, Size, Rear, Iov, Bin).
344-
%%
345-
output_handler_enq(
346-
OutStream, EncryptState, CS_DH, Front, Size, Rear, Iov, Bin) ->
347-
BinSize = byte_size(Bin),
348-
ChunkSize = hd(CS_DH),
347+
348+
output_handler_split(
349+
OutStream, EncryptState, [ChunkSize|_] = CS_DH,
350+
Front, Size, Rear, Iov, Bin) ->
349351
if
350-
BinSize =< ChunkSize ->
352+
byte_size(Bin) =< ChunkSize ->
351353
output_handler_enq(
352354
OutStream, EncryptState, CS_DH, Front, Size, [Bin|Rear],
353355
Iov);
354356
true ->
355357
<<Bin1:ChunkSize/binary, Bin2/binary>> = Bin,
356-
output_handler_enq(
358+
output_handler_split(
357359
OutStream, EncryptState, CS_DH, Front, Size, [Bin1|Rear],
358360
Iov, Bin2)
359361
end.
360362

361363
%% Collect small binaries into chunks of at most
362-
%% chunk size; hd(CS_DH)
364+
%% ChunkSize = hd(CS_DH); encrypt and send them
363365
%%
364-
output_handler_collect(OutStream, EncryptState, CS_DH, [], Zero, []) ->
366+
output_handler_collect(
367+
OutStream, EncryptState, CS_DH, [], Zero, []) ->
365368
0 = Zero, % ASSERT
366-
%% No more enqueued -> try to get more form VM
369+
%% No more enqueued -> try to get more from VM
367370
output_handler_xfer(OutStream, EncryptState, CS_DH, [], Zero, []);
368-
output_handler_collect(OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
371+
output_handler_collect(
372+
OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
369373
output_handler_collect(
370374
OutStream, EncryptState, CS_DH, Front, Size, Rear, [], 0).
371375
%%
372376
output_handler_collect(
373377
OutStream, EncryptState, CS_DH, [], Zero, [], Acc, DataSize) ->
374378
0 = Zero, % ASSERT
375-
output_handler_chunk(
379+
output_handler_encrypt_and_send_chunk(
376380
OutStream, EncryptState, CS_DH, [], Zero, [], Acc, DataSize);
377381
output_handler_collect(
378382
OutStream, EncryptState, CS_DH, [], Size, Rear, Acc, DataSize) ->
@@ -381,15 +385,14 @@ output_handler_collect(
381385
OutStream, EncryptState, CS_DH, lists:reverse(Rear), Size, [],
382386
Acc, DataSize);
383387
output_handler_collect(
384-
OutStream, EncryptState, CS_DH, [Bin|Iov] = Front, Size, Rear,
385-
Acc, DataSize) ->
386-
ChunkSize = hd(CS_DH),
388+
OutStream, EncryptState, [ChunkSize|_] = CS_DH,
389+
[Bin|Iov] = Front, Size, Rear, Acc, DataSize) ->
387390
BinSize = byte_size(Bin),
388391
DataSize_1 = DataSize + BinSize,
389392
if
390393
ChunkSize < DataSize_1 ->
391394
%% Bin does not fit in chunk -> send Acc
392-
output_handler_chunk(
395+
output_handler_encrypt_and_send_chunk(
393396
OutStream, EncryptState, CS_DH, Front, Size, Rear,
394397
Acc, DataSize);
395398
DataSize_1 < ChunkSize ->
@@ -400,14 +403,12 @@ output_handler_collect(
400403
true -> % DataSize_1 == ChunkSize ->
401404
%% Optimize one iteration; Bin fits exactly
402405
%% -> accumulate and send
403-
output_handler_chunk(
406+
output_handler_encrypt_and_send_chunk(
404407
OutStream, EncryptState, CS_DH, Iov, Size - BinSize, Rear,
405408
[Bin|Acc], DataSize_1)
406409
end.
407410

408-
%% Encrypt and send a chunk
409-
%%
410-
output_handler_chunk(
411+
output_handler_encrypt_and_send_chunk(
411412
OutStream, EncryptState, CS_DH, Front, Size, Rear, Acc, DataSize) ->
412413
Data = lists:reverse(Acc),
413414
{OutStream_1, EncryptState_1} =

lib/ssl/test/inet_epmd_cryptcookie_inet_ktls.erl

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -179,7 +179,10 @@ stream_recv(InStream = [_ | Socket], Size) ->
179179
[Data | InStream];
180180
{error, timeout} ->
181181
[<<>> | InStream];
182-
{error, closed} ->
182+
{error, Reason}
183+
when Reason =:= closed;
184+
Reason =:= econnreset;
185+
Reason =:= epipe ->
183186
[closed | InStream];
184187
{error, Reason} ->
185188
erlang:error({?MODULE, ?FUNCTION_NAME, Reason})
@@ -192,7 +195,10 @@ stream_send(OutStream = [_ | Socket], Data) ->
192195
case ?DRIVER:send(Socket, Data) of
193196
ok ->
194197
OutStream;
195-
{error, closed} ->
198+
{error, Reason}
199+
when Reason =:= closed;
200+
Reason =:= econnreset;
201+
Reason =:= epipe ->
196202
[closed | OutStream];
197203
{error, Reason} ->
198204
erlang:error({?MODULE, ?FUNCTION_NAME, Reason, [OutStream, Data]})

lib/ssl/test/inet_epmd_cryptcookie_socket_ktls.erl

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -218,7 +218,8 @@ stream_recv(InStream = [_ | Socket], Size) ->
218218
stream_recv_error(InStream, Reason) ->
219219
if
220220
Reason =:= closed;
221-
Reason =:= econnreset ->
221+
Reason =:= econnreset;
222+
Reason =:= epipe ->
222223
[closed | InStream];
223224
true ->
224225
erlang:error({?MODULE, ?FUNCTION_NAME, Reason})
@@ -233,7 +234,10 @@ stream_send(OutStream = [_ | Socket], Data) ->
233234
case socket:sendmsg(Socket, #{ iov => Data }) of
234235
ok ->
235236
OutStream;
236-
{error, closed} ->
237+
{error, Reason}
238+
when Reason =:= closed;
239+
Reason =:= econnreset;
240+
Reason =:= epipe ->
237241
[closed | OutStream];
238242
{error, Reason} ->
239243
erlang:error({?MODULE, ?FUNCTION_NAME, Reason, [OutStream, Data]})

lib/ssl/test/inet_epmd_dist_cryptcookie_inet.erl

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,10 @@ stream_recv(InStream = [_ | Socket], Size) ->
168168
[Data | InStream];
169169
{error, timeout} ->
170170
[<<>> | InStream];
171-
{error, closed} ->
171+
{error, Reason}
172+
when Reason =:= closed;
173+
Reason =:= econnreset;
174+
Reason =:= epipe ->
172175
[closed | InStream];
173176
{error, Reason} ->
174177
erlang:error({?MODULE, ?FUNCTION_NAME, Reason})
@@ -181,7 +184,10 @@ stream_send(OutStream = [_ | Socket], Data) ->
181184
case ?DRIVER:send(Socket, Data) of
182185
ok ->
183186
OutStream;
184-
{error, closed} ->
187+
{error, Reason}
188+
when Reason =:= closed;
189+
Reason =:= econnreset;
190+
Reason =:= epipe ->
185191
[closed | OutStream];
186192
{error, Reason} ->
187193
erlang:error({?MODULE, ?FUNCTION_NAME, Reason, [OutStream, Data]})

lib/ssl/test/inet_epmd_dist_cryptcookie_socket.erl

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -204,7 +204,8 @@ stream_recv(InStream = [_ | Socket], Size) ->
204204
stream_recv_error(InStream, Reason) ->
205205
if
206206
Reason =:= closed;
207-
Reason =:= econnreset ->
207+
Reason =:= econnreset;
208+
Reason =:= epipe ->
208209
[closed | InStream];
209210
true ->
210211
erlang:error({?MODULE, ?FUNCTION_NAME, Reason})
@@ -219,7 +220,10 @@ stream_send(OutStream = [_ | Socket], Data) ->
219220
case socket:sendmsg(Socket, #{ iov => Data }) of
220221
ok ->
221222
OutStream;
222-
{error, closed} ->
223+
{error, Reason}
224+
when Reason =:= closed;
225+
Reason =:= econnreset;
226+
Reason =:= epipe ->
223227
[closed | OutStream];
224228
{error, Reason} ->
225229
erlang:error({?MODULE, ?FUNCTION_NAME, Reason, [OutStream, Data]})

0 commit comments

Comments
 (0)