File 0629-crypto-Add-prop__crypto_init_update-to-property-test.patch of Package erlang

From 78241111e38a29934936ae11d37cebb308413b1a Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Tue, 19 Nov 2019 13:51:58 +0100
Subject: [PATCH 2/2] crypto: Add prop__crypto_init_update to property tests

---
 lib/crypto/test/crypto_property_test_SUITE.erl  |  8 ++++-
 lib/crypto/test/property_test/crypto_ng_api.erl | 46 +++++++++++++++++++++++--
 2 files changed, 51 insertions(+), 3 deletions(-)

diff --git a/lib/crypto/test/crypto_property_test_SUITE.erl b/lib/crypto/test/crypto_property_test_SUITE.erl
index 392976b765..75a3d4872f 100644
--- a/lib/crypto/test/crypto_property_test_SUITE.erl
+++ b/lib/crypto/test/crypto_property_test_SUITE.erl
@@ -24,7 +24,8 @@
 
 -include_lib("common_test/include/ct.hrl").
 
-all() -> [encrypt_decrypt__crypto_one_time
+all() -> [encrypt_decrypt__crypto_one_time,
+          prop__crypto_init_update
          ].
 
 %%% First prepare Config and compile the property tests for the found tool:
@@ -42,3 +43,8 @@ encrypt_decrypt__crypto_one_time(Config) ->
       crypto_ng_api:prop__crypto_one_time(),
       Config
      ).
+prop__crypto_init_update(Config) ->
+    ct_property_test:quickcheck(
+      crypto_ng_api:prop__crypto_init_update(),
+      Config
+     ).
diff --git a/lib/crypto/test/property_test/crypto_ng_api.erl b/lib/crypto/test/property_test/crypto_ng_api.erl
index 0319811b07..c3a21b0804 100644
--- a/lib/crypto/test/property_test/crypto_ng_api.erl
+++ b/lib/crypto/test/property_test/crypto_ng_api.erl
@@ -55,6 +55,7 @@
 
 -include("crypto_prop_generators.hrl").
 
+%%%================================================================
 %%% Properties:
 
 prop__crypto_one_time() ->
@@ -67,6 +68,17 @@ prop__crypto_one_time() ->
                     )
             ).
 
+prop__crypto_init_update() ->
+    numtests(10000,
+             ?FORALL({TextPlain, Cipher, Key, IV}, ?LET(Ciph,cipher(),
+                                                                 {text_plain(), Ciph, key(Ciph), iv(Ciph)}),
+                     equal(TextPlain,
+                           full_blocks(TextPlain, Cipher),
+                           decrypt_encrypt_init_update(Cipher, Key, IV, TextPlain))
+                    )
+            ).
+
+%%%================================================================
 %%% Lib
 
 equal(_, T, T) -> true;
@@ -79,14 +91,44 @@ equal(F, Tp, Td) ->
 
 
 decrypt_encrypt_one_time(Cipher, Key, IV, TextPlain) ->
+    io:format("~p:~p Cipher: ~p, BlockSize: ~p, Key: ~p, IV: ~p, TextPlain: ~p (~p chunks)",
+              [?MODULE,?LINE, Cipher, block_size(Cipher), size(Key), size(IV), size(iolist_to_binary(TextPlain)),
+               num_chunks(TextPlain)]),
     TextCrypto = crypto:crypto_one_time(Cipher, Key, IV, TextPlain, true),
-    crypto:crypto_one_time(Cipher, Key, IV, TextCrypto, false).
-
+    io:format("~p:~p TextCrypto: ~p", [?MODULE,?LINE, size(TextCrypto)]),
+    TextDecrypt = crypto:crypto_one_time(Cipher, Key, IV, TextCrypto, false),
+    io:format("~p:~p TextDecrypt: ~p", [?MODULE,?LINE, size(TextDecrypt)]),
+    TextDecrypt.
+
+
+decrypt_encrypt_init_update(Cipher, Key, IV, TextPlain) when is_binary(TextPlain) ->
+    decrypt_encrypt_init_update(Cipher, Key, IV, [TextPlain]);
+
+decrypt_encrypt_init_update(Cipher, Key, IV, TextPlain) ->
+    io:format("~p:~p Cipher: ~p, BlockSize: ~p, Key: ~p, IV: ~p, TextPlain: ~p (~p chunks)",
+              [?MODULE,?LINE, Cipher, block_size(Cipher), size(Key), size(IV), size(iolist_to_binary(TextPlain)),
+               num_chunks(TextPlain)]),
+    Cenc = crypto:crypto_init(Cipher, Key, IV, true),
+    TextOut = lists:foldl(fun(TextIn, TextOutAcc) ->
+                                  [crypto:crypto_update(Cenc,TextIn) | TextOutAcc]
+                          end, [], TextPlain),
+    TextCrypto = lists:reverse(TextOut),
+    io:format("~p:~p TextCrypto: ~p",
+              [?MODULE,?LINE, size(iolist_to_binary(TextCrypto))]),
     
+    Cdec = crypto:crypto_init(Cipher, Key, IV, false),
+    TextDec = lists:foldl(fun(TextC, TextDecAcc) ->
+                                  [crypto:crypto_update(Cdec,TextC) | TextDecAcc]
+                          end, [], TextCrypto),
+    iolist_to_binary(lists:reverse(TextDec)).
+
 full_blocks(TextPlain, Cipher) ->
     TextPlainBin = iolist_to_binary(TextPlain),
     {Head,_Tail} = split_binary(TextPlainBin, (size(TextPlainBin) - num_rest_bytes(TextPlainBin,Cipher))),
     Head.
 
+num_chunks(B) when is_binary(B) -> 1;
+num_chunks(L) when is_list(L) -> length(L).
+
 num_rest_bytes(Bin, Cipher) -> size(Bin) rem block_size(Cipher).
 
-- 
2.16.4

openSUSE Build Service is sponsored by