File 0580-crypto-Property-test-suite.patch of Package erlang

From cf802020f0c4c95c04978ac4a53d3588e1fd0056 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Tue, 22 Oct 2019 12:46:03 +0200
Subject: [PATCH] crypto: Property test suite

---
 lib/crypto/test/Makefile                        |   2 +
 lib/crypto/test/crypto_property_test_SUITE.erl  |  44 +++++++++
 lib/crypto/test/property_test/crypto_ng_api.erl | 121 ++++++++++++++++++++++++
 3 files changed, 167 insertions(+)
 create mode 100644 lib/crypto/test/crypto_property_test_SUITE.erl
 create mode 100644 lib/crypto/test/property_test/crypto_ng_api.erl

diff --git a/lib/crypto/test/Makefile b/lib/crypto/test/Makefile
index 988d95a8bc..bc3d25585a 100644
--- a/lib/crypto/test/Makefile
+++ b/lib/crypto/test/Makefile
@@ -8,6 +8,7 @@ include $(ERL_TOP)/make/$(TARGET)/otp.mk
 MODULES = \
 	crypto_bench_SUITE \
 	crypto_SUITE \
+	crypto_property_test_SUITE \
 	engine_SUITE
 
 ERL_FILES= $(MODULES:%=%.erl)
@@ -80,6 +81,7 @@ release_tests_spec: $(TEST_TARGET)
 	$(INSTALL_DATA) crypto.spec crypto_bench.spec crypto.cover $(RELTEST_FILES) "$(RELSYSDIR)"
 	@tar cfh - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -)
 	chmod -R u+w "$(RELSYSDIR)"
+	@tar cf - *_SUITE_data property_test | (cd "$(RELSYSDIR)"; tar xf -)	
 
 release_docs_spec:
 
diff --git a/lib/crypto/test/crypto_property_test_SUITE.erl b/lib/crypto/test/crypto_property_test_SUITE.erl
new file mode 100644
index 0000000000..392976b765
--- /dev/null
+++ b/lib/crypto/test/crypto_property_test_SUITE.erl
@@ -0,0 +1,44 @@
+%%
+%% %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_property_test_SUITE).
+
+-compile(export_all).
+
+-include_lib("common_test/include/ct.hrl").
+
+all() -> [encrypt_decrypt__crypto_one_time
+         ].
+
+%%% First prepare Config and compile the property tests for the found tool:
+init_per_suite(Config) ->
+    ct_property_test:init_per_suite(Config).
+
+end_per_suite(Config) ->
+    Config.
+
+%%%================================================================
+%%% Test suites
+%%%
+encrypt_decrypt__crypto_one_time(Config) ->
+    ct_property_test:quickcheck(
+      crypto_ng_api:prop__crypto_one_time(),
+      Config
+     ).
diff --git a/lib/crypto/test/property_test/crypto_ng_api.erl b/lib/crypto/test/property_test/crypto_ng_api.erl
new file mode 100644
index 0000000000..85e48d231e
--- /dev/null
+++ b/lib/crypto/test/property_test/crypto_ng_api.erl
@@ -0,0 +1,121 @@
+%%
+%% %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_ng_api).
+
+-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.
+
+
+%%% Properties:
+
+prop__crypto_one_time() ->
+    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_one_time(Cipher, Key, IV, TextPlain))
+                    )
+            ).
+
+%%% 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;
+equal(F, Tp, Td) ->
+    ct:pal("Full:  ~p~n"
+           "Block: ~p~n"
+           "Decr:  ~p~n",
+           [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).
+
+    
+full_blocks(TextPlain, Cipher) ->
+    TextPlainBin = iolist_to_binary(TextPlain),
+    {Head,_Tail} = split_binary(TextPlainBin, (size(TextPlainBin) - num_rest_bytes(TextPlainBin,Cipher))),
+    Head.
+
+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)).
-- 
2.16.4

openSUSE Build Service is sponsored by