File 0628-crypto-New-common-libfile-for-property-tests-in-cryp.patch of Package erlang

From 0c893dec80003245be9ed488477aec9aee904836 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Thu, 21 Nov 2019 12:51:41 +0100
Subject: [PATCH 1/2] crypto: New common libfile for property tests in crypto

---
 lib/crypto/test/property_test/crypto_ng_api.erl    | 31 +-------
 .../test/property_test/crypto_prop_generators.erl  | 93 ++++++++++++++++++++++
 .../test/property_test/crypto_prop_generators.hrl  | 36 +++++++++
 3 files changed, 130 insertions(+), 30 deletions(-)
 create mode 100644 lib/crypto/test/property_test/crypto_prop_generators.erl
 create mode 100644 lib/crypto/test/property_test/crypto_prop_generators.hrl

diff --git a/lib/crypto/test/property_test/crypto_ng_api.erl b/lib/crypto/test/property_test/crypto_ng_api.erl
index 85e48d231e..0319811b07 100644
--- a/lib/crypto/test/property_test/crypto_ng_api.erl
+++ b/lib/crypto/test/property_test/crypto_ng_api.erl
@@ -53,6 +53,7 @@
 -endif.
 -endif.
 
+-include("crypto_prop_generators.hrl").
 
 %%% Properties:
 
@@ -66,23 +67,6 @@ prop__crypto_one_time() ->
                     )
             ).
 
-%%% Generators
-text_plain() -> iolist().
-
-cipher() -> oneof( non_aead_ciphers() -- [aes_ige256] ).
-
-key(Cipher) ->
-    %% Can't be shrinked
-    crypto:strong_rand_bytes( key_length(Cipher) ).
-    
-iv(Cipher) ->
-    %% Can't be shrinked
-    crypto:strong_rand_bytes( iv_length(Cipher) ).
-
-iolist() -> oneof([list( oneof([list(byte()), binary(), list(binary())])),
-                   binary(1056)
-                  ]).
-    
 %%% Lib
 
 equal(_, T, T) -> true;
@@ -94,14 +78,6 @@ equal(F, Tp, Td) ->
     false.
 
 
-non_aead_ciphers() ->
-    [C || C <- crypto:supports(ciphers),
-          C =/= chacha20_poly1305,
-          begin
-              #{mode := Mode} = crypto:cipher_info(C),
-              not lists:member(Mode, [ccm_mode, gcm_mode])
-          end].
-
 decrypt_encrypt_one_time(Cipher, Key, IV, TextPlain) ->
     TextCrypto = crypto:crypto_one_time(Cipher, Key, IV, TextPlain, true),
     crypto:crypto_one_time(Cipher, Key, IV, TextCrypto, false).
@@ -114,8 +90,3 @@ full_blocks(TextPlain, Cipher) ->
 
 num_rest_bytes(Bin, Cipher) -> size(Bin) rem block_size(Cipher).
 
-block_size(Cipher) -> maps:get(block_size, crypto:cipher_info(Cipher)).
-
-key_length(Cipher) -> maps:get(key_length, crypto:cipher_info(Cipher)).
-
-iv_length(Cipher)  -> maps:get(iv_length, crypto:cipher_info(Cipher)).
diff --git a/lib/crypto/test/property_test/crypto_prop_generators.erl b/lib/crypto/test/property_test/crypto_prop_generators.erl
new file mode 100644
index 0000000000..5a53a000f0
--- /dev/null
+++ b/lib/crypto/test/property_test/crypto_prop_generators.erl
@@ -0,0 +1,93 @@
+%%
+%% %CopyrightBegin%
+%% 
+%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%% 
+%% %CopyrightEnd%
+%%
+%%
+
+-module(crypto_prop_generators).
+
+-compile(export_all).
+
+-proptest(eqc).
+-proptest([triq,proper]).
+
+-ifndef(EQC).
+-ifndef(PROPER).
+-ifndef(TRIQ).
+%%-define(EQC,true).
+-define(PROPER,true).
+%%-define(TRIQ,true).
+-endif.
+-endif.
+-endif.
+
+-ifdef(EQC).
+-include_lib("eqc/include/eqc.hrl").
+-define(MOD_eqc,eqc).
+
+-else.
+-ifdef(PROPER).
+-include_lib("proper/include/proper.hrl").
+-define(MOD_eqc,proper).
+-else.
+-ifdef(TRIQ).
+-define(MOD_eqc,triq).
+-include_lib("triq/include/triq.hrl").
+
+-endif.
+-endif.
+-endif.
+
+%%%================================================================
+%%% Generators
+
+text_plain() -> iolist().
+
+cipher() -> oneof( non_aead_ciphers() -- [aes_ige256] ).
+
+key(Cipher) ->
+    %% Can't be shrinked
+    crypto:strong_rand_bytes( key_length(Cipher) ).
+    
+iv(Cipher) ->
+    %% Can't be shrinked
+    crypto:strong_rand_bytes( iv_length(Cipher) ).
+
+iolist() -> frequency([{5, list( oneof([list(byte()),
+                                        binary(),
+                                        list(binary())]))},
+                       {1, mybinary(50000)}
+                      ]).
+
+mybinary(MaxSize) -> ?LET(Sz, integer(0,MaxSize), binary(Sz)).
+
+
+%%%================================================================
+non_aead_ciphers() ->
+    [C || C <- crypto:supports(ciphers),
+          C =/= chacha20_poly1305,
+          begin
+              #{mode := Mode} = crypto:cipher_info(C),
+              not lists:member(Mode, [ccm_mode, gcm_mode])
+          end].
+
+block_size(Cipher) -> maps:get(block_size, crypto:cipher_info(Cipher)).
+
+key_length(Cipher) -> maps:get(key_length, crypto:cipher_info(Cipher)).
+
+iv_length(Cipher)  -> maps:get(iv_length, crypto:cipher_info(Cipher)).
diff --git a/lib/crypto/test/property_test/crypto_prop_generators.hrl b/lib/crypto/test/property_test/crypto_prop_generators.hrl
new file mode 100644
index 0000000000..56a762e651
--- /dev/null
+++ b/lib/crypto/test/property_test/crypto_prop_generators.hrl
@@ -0,0 +1,36 @@
+%%%
+%%% %CopyrightBegin%
+%%% 
+%%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
+%%% 
+%%% Licensed under the Apache License, Version 2.0 (the "License");
+%%% you may not use this file except in compliance with the License.
+%%% You may obtain a copy of the License at
+%%%
+%%%     http://www.apache.org/licenses/LICENSE-2.0
+%%%
+%%% Unless required by applicable law or agreed to in writing, software
+%%% distributed under the License is distributed on an "AS IS" BASIS,
+%%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%%% See the License for the specific language governing permissions and
+%%% limitations under the License.
+%%% 
+%%% %CopyrightEnd%
+%%%
+%%%
+
+
+-import(crypto_prop_generators,
+        [
+         text_plain/0,
+         cipher/0,
+         key/1,
+         iv/1,
+         iolist/0,
+         mybinary/1,
+
+         non_aead_ciphers/0,
+         block_size/1,
+         key_length/1,
+         iv_length/1
+        ]).
-- 
2.16.4

openSUSE Build Service is sponsored by