File 1301-crypto-Break-out-aead_one_time-to-2-functions.patch of Package erlang
From 05efc8b7c634693104a6ab2ceaace4119be80897 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Wed, 30 Oct 2024 09:31:25 +0100
Subject: [PATCH] crypto: Break out aead_one_time to 2 functions
To allow ssl send fewer arguments to and re-use the initialization.
While at it change the crypto:crypto_one_time_aead[_init]/4 to
automatically, append or, use the tag at the end data.
---
lib/crypto/c_src/aead.c | 312 ++++++++++++++++++++++++-------
lib/crypto/c_src/aead.h | 3 +
lib/crypto/c_src/crypto.c | 6 +
lib/crypto/src/crypto.erl | 57 +++++-
lib/crypto/test/crypto_SUITE.erl | 30 ++-
5 files changed, 328 insertions(+), 80 deletions(-)
diff --git a/lib/crypto/c_src/aead.c b/lib/crypto/c_src/aead.c
index 01957c486b..310d71e3b1 100644
--- a/lib/crypto/c_src/aead.c
+++ b/lib/crypto/c_src/aead.c
@@ -21,37 +21,69 @@
#include "aead.h"
#include "aes.h"
#include "cipher.h"
+#include "info.h"
+ErlNifResourceType* aead_cipher_ctx_rtype;
-ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
+struct aead_cipher_ctx {
+ const struct cipher_type_t *cipherp;
+ EVP_CIPHER_CTX *ctx;
+
+ ERL_NIF_TERM key;
+
+ int encflg;
+ unsigned int tag_len;
+ ErlNifEnv *env;
+};
+
+static void aead_cipher_ctx_dtor(ErlNifEnv* env, struct aead_cipher_ctx* ctx) {
+ enif_free_env(ctx->env);
+ if (ctx->ctx)
+ EVP_CIPHER_CTX_free(ctx->ctx);
+
+ return;
+}
+
+int init_aead_cipher_ctx(ErlNifEnv *env, ErlNifBinary* rt_buf) {
+ aead_cipher_ctx_rtype = enif_open_resource_type(env, NULL,
+ resource_name("AEAD_CIPHER_CTX", rt_buf),
+ (ErlNifResourceDtor*) aead_cipher_ctx_dtor,
+ ERL_NIF_RT_CREATE|ERL_NIF_RT_TAKEOVER,
+ NULL);
+ if (aead_cipher_ctx_rtype == NULL)
+ goto err;
+
+ return 1;
+
+ err:
+ PRINTF_ERR0("CRYPTO: Could not open resource type 'AEAD_CIPHER_CTX'");
+ return 0;
+}
+
+ERL_NIF_TERM aead_cipher_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
{/*
- (Type,Key,Iv,AAD,In,TagLen,true)
- (Type,Key,Iv,AAD,In,Tag,false)
+ (Type,Key,TagLen,DoEncode)
*/
#if defined(HAVE_AEAD)
- const struct cipher_type_t *cipherp;
- EVP_CIPHER_CTX *ctx = NULL;
- const EVP_CIPHER *cipher = NULL;
- ErlNifBinary key, iv, aad, in, tag;
- unsigned int tag_len;
- unsigned char *outp, *tagp, *tag_data;
- ERL_NIF_TERM type, out, out_tag, ret, encflg_arg;
- int len, encflg;
+ struct aead_cipher_ctx *ctx_res = NULL;
+ ERL_NIF_TERM ret, encflg_arg, type;
+ ErlNifBinary key;
+
+ if ((ctx_res = enif_alloc_resource(aead_cipher_ctx_rtype, sizeof(struct aead_cipher_ctx))) == NULL)
+ return EXCP_ERROR(env, "Can't allocate resource");
- encflg_arg = argv[6];
+ ctx_res->env = enif_alloc_env();
+ encflg_arg = argv[3];
/* Fetch the flag telling if we are going to encrypt (=true) or decrypt (=false) */
if (encflg_arg == atom_true)
- encflg = 1;
+ ctx_res->encflg = 1;
else if (encflg_arg == atom_false)
- encflg = 0;
- else if (encflg_arg == atom_undefined)
- /* For compat funcs in crypto.erl */
- encflg = -1;
+ ctx_res->encflg = 0;
else
{
- ret = EXCP_BADARG_N(env, 6, "Bad enc flag");
+ ret = EXCP_BADARG_N(env, 3, "Bad enc flag");
goto done;
}
@@ -59,54 +91,176 @@ ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
if (!enif_is_atom(env, type))
{ret = EXCP_BADARG_N(env, 0, "non-atom cipher type"); goto done;}
- if (!enif_inspect_iolist_as_binary(env, argv[1], &key))
+
+ if (!enif_inspect_binary(env, argv[1], &key))
{ret = EXCP_BADARG_N(env, 1, "non-binary key"); goto done;}
- if (!enif_inspect_iolist_as_binary(env, argv[2], &iv))
- {ret = EXCP_BADARG_N(env, 2, "non-binary iv"); goto done;}
- if (!enif_inspect_iolist_as_binary(env, argv[3], &in))
- {ret = EXCP_BADARG_N(env, 3, "non-binary text"); goto done;}
- if (!enif_inspect_iolist_as_binary(env, argv[4], &aad))
- {ret = EXCP_BADARG_N(env, 4, "non-binary AAD"); goto done;}
-
- if (encflg) {
- if (!enif_get_uint(env, argv[5], &tag_len))
- {ret = EXCP_BADARG_N(env, 5, "Bad Tag length"); goto done;}
- tag_data = NULL;
- } else {
- if (!enif_inspect_iolist_as_binary(env, argv[5], &tag))
- {ret = EXCP_BADARG_N(env, 5, "non-binary Tag"); goto done;}
- tag_len = tag.size;
- tag_data = tag.data;
- }
+ ctx_res->key = enif_make_copy(ctx_res->env, argv[1]);
- if (tag_len > INT_MAX
- || key.size > INT_MAX
- || iv.size > INT_MAX
- || in.size > INT_MAX
- || aad.size > INT_MAX)
- {ret = EXCP_BADARG_N(env, 5, "binary too long"); goto done;}
+ if (!enif_get_uint(env, argv[2], &ctx_res->tag_len))
+ {ret = EXCP_BADARG_N(env, 2, "Bad Tag length"); goto done;}
- if ((cipherp = get_cipher_type(type, key.size)) == NULL)
+ if (ctx_res->tag_len > INT_MAX
+ || key.size > INT_MAX)
+ {ret = EXCP_BADARG_N(env, 1, "key or tag too long"); goto done;}
+
+ if ((ctx_res->cipherp = get_cipher_type(type, key.size)) == NULL)
{ret = EXCP_BADARG_N(env, 0, "Unknown cipher or invalid key size"); goto done;}
- if (cipherp->flags & NON_EVP_CIPHER)
+ if (ctx_res->cipherp->flags & NON_EVP_CIPHER)
{ret = EXCP_BADARG_N(env, 0, "Bad cipher"); goto done;}
- if (! (cipherp->flags & AEAD_CIPHER) )
+ if (! (ctx_res->cipherp->flags & AEAD_CIPHER) )
{ret = EXCP_BADARG_N(env, 0, "Not aead cipher"); goto done;}
- if (CIPHER_FORBIDDEN_IN_FIPS(cipherp))
+ if (CIPHER_FORBIDDEN_IN_FIPS(ctx_res->cipherp))
{ret = EXCP_NOTSUP_N(env, 0, "Forbidden in FIPS"); goto done;}
- if ((cipher = cipherp->cipher.p) == NULL)
- {ret = EXCP_NOTSUP_N(env, 0, "The cipher is not supported in this libcrypto version"); goto done;}
#if defined(HAVE_GCM_EVP_DECRYPT_BUG)
- if ( !encflg && (cipherp->flags & GCM_MODE))
- return aes_gcm_decrypt_NO_EVP(env, argc, argv);
+ if ( !ctx_res->encflg && (ctx_res->cipherp->flags & GCM_MODE)) {
+ {ret = EXCP_NOTSUP_N(env, 0, "HAVE_GCM_EVP_DECRYPT_BUG with init aead not supported, update ssl version"); goto done;}
+ }
#endif
- if ((ctx = EVP_CIPHER_CTX_new()) == NULL)
- {ret = EXCP_ERROR(env, "Can't allocate ctx"); goto done;}
+ if (ctx_res->cipherp->cipher.p == NULL)
+ {ret = EXCP_NOTSUP_N(env, 0, "The cipher is not supported in this libcrypto version"); goto done;}
- if (EVP_CipherInit_ex(ctx, cipher, NULL, NULL, NULL, encflg) != 1)
+ if ((ctx_res->ctx = EVP_CIPHER_CTX_new()) == NULL)
+ {ret = EXCP_ERROR(env, "Can't allocate ctx"); goto done;}
+ if (EVP_CipherInit_ex(ctx_res->ctx, ctx_res->cipherp->cipher.p, NULL, NULL, NULL, ctx_res->encflg) != 1)
{ret = EXCP_ERROR(env, "CipherInit failed"); goto done;}
+
+ ret = enif_make_resource(env, ctx_res);
+
+done:
+ if(ctx_res) enif_release_resource(ctx_res);
+ return ret;
+#else
+ return EXCP_NOTSUP_N(env, 0, "Unsupported Cipher");
+#endif
+}
+
+ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
+{
+#if defined(HAVE_AEAD)
+ const struct cipher_type_t *cipherp;
+ EVP_CIPHER_CTX *ctx = NULL;
+ const EVP_CIPHER *cipher = NULL;
+ ErlNifBinary key, iv, aad, in, tag;
+ unsigned int tag_len;
+ unsigned char *outp, *tagp, *tag_data, *in_data;
+ ERL_NIF_TERM type, out, out_tag, ret, encflg_arg;
+ int len, encflg, in_len;
+
+ if(argc == 7) {
+ /*
+ (Type,Key,Iv,In,AAD,TagLen,true)
+ (Type,Key,Iv,In,AAD,Tag,false)
+ */
+ encflg_arg = argv[6];
+
+ /* Fetch the flag telling if we are going to encrypt (=true) or decrypt (=false) */
+ if (encflg_arg == atom_true)
+ encflg = 1;
+ else if (encflg_arg == atom_false)
+ encflg = 0;
+ else if (encflg_arg == atom_undefined)
+ /* For compat funcs in crypto.erl */
+ encflg = -1;
+ else
+ {
+ ret = EXCP_BADARG_N(env, 6, "Bad enc flag");
+ goto done;
+ }
+
+ type = argv[0];
+
+ if (!enif_is_atom(env, type))
+ {ret = EXCP_BADARG_N(env, 0, "non-atom cipher type"); goto done;}
+ if (!enif_inspect_iolist_as_binary(env, argv[1], &key))
+ {ret = EXCP_BADARG_N(env, 1, "non-binary key"); goto done;}
+ if (!enif_inspect_iolist_as_binary(env, argv[2], &iv))
+ {ret = EXCP_BADARG_N(env, 2, "non-binary iv"); goto done;}
+ if (!enif_inspect_iolist_as_binary(env, argv[3], &in))
+ {ret = EXCP_BADARG_N(env, 3, "non-binary text"); goto done;}
+ in_data = in.data;
+ in_len = in.size;
+ if (!enif_inspect_iolist_as_binary(env, argv[4], &aad))
+ {ret = EXCP_BADARG_N(env, 4, "non-binary AAD"); goto done;}
+
+ if (encflg) {
+ if (!enif_get_uint(env, argv[5], &tag_len))
+ {ret = EXCP_BADARG_N(env, 5, "Bad Tag length"); goto done;}
+ tag_data = NULL;
+ } else {
+ if (!enif_inspect_iolist_as_binary(env, argv[5], &tag))
+ {ret = EXCP_BADARG_N(env, 5, "non-binary Tag"); goto done;}
+ tag_len = tag.size;
+ tag_data = tag.data;
+ }
+
+ if (tag_len > INT_MAX
+ || key.size > INT_MAX
+ || iv.size > INT_MAX
+ || in.size > INT_MAX
+ || aad.size > INT_MAX)
+ {ret = EXCP_BADARG_N(env, 5, "binary too long"); goto done;}
+
+ if ((cipherp = get_cipher_type(type, key.size)) == NULL)
+ {ret = EXCP_BADARG_N(env, 0, "Unknown cipher or invalid key size"); goto done;}
+ if (cipherp->flags & NON_EVP_CIPHER)
+ {ret = EXCP_BADARG_N(env, 0, "Bad cipher"); goto done;}
+ if (! (cipherp->flags & AEAD_CIPHER) )
+ {ret = EXCP_BADARG_N(env, 0, "Not aead cipher"); goto done;}
+ if (CIPHER_FORBIDDEN_IN_FIPS(cipherp))
+ {ret = EXCP_NOTSUP_N(env, 0, "Forbidden in FIPS"); goto done;}
+
+#if defined(HAVE_GCM_EVP_DECRYPT_BUG)
+ if ( !encflg && (cipherp->flags & GCM_MODE)) {
+ return aes_gcm_decrypt_NO_EVP(env, argc, argv);
+ }
+#endif
+ if ((cipher = cipherp->cipher.p) == NULL)
+ {ret = EXCP_NOTSUP_N(env, 0, "The cipher is not supported in this libcrypto version"); goto done;}
+
+ if ((ctx = EVP_CIPHER_CTX_new()) == NULL)
+ {ret = EXCP_ERROR(env, "Can't allocate ctx"); goto done;}
+ if (EVP_CipherInit_ex(ctx, cipher, NULL, NULL, NULL, encflg) != 1)
+ {ret = EXCP_ERROR(env, "CipherInit failed"); goto done;}
+
+ } else {
+ /* argc = 4 {state, IV, InData, AAD } */
+ struct aead_cipher_ctx *ctx_res = NULL;
+ if (!enif_get_resource(env, argv[0], aead_cipher_ctx_rtype, (void**)&ctx_res))
+ {ret = EXCP_BADARG_N(env, 0, "Bad State"); goto done;}
+ if (!enif_inspect_iolist_as_binary(env, argv[1], &iv))
+ {ret = EXCP_BADARG_N(env, 1, "non-binary iv"); goto done;}
+ if (!enif_inspect_iolist_as_binary(env, argv[2], &in))
+ {ret = EXCP_BADARG_N(env, 2, "non-binary text"); goto done;}
+ in_data = in.data;
+ in_len = in.size;
+
+ if (!enif_inspect_iolist_as_binary(env, argv[3], &aad))
+ {ret = EXCP_BADARG_N(env, 3, "non-binary AAD"); goto done;}
+
+ if (!enif_inspect_binary(env, ctx_res->key, &key))
+ {ret = EXCP_BADARG_N(env, 0, "Bad State key"); goto done;}
+
+ encflg = ctx_res->encflg;
+
+ if(ctx_res->encflg) {
+ tag_len = ctx_res->tag_len;
+ tag_data = NULL;
+ } else {
+ tag_len = ctx_res->tag_len;
+ in_len = in_len - tag_len;
+ if (in_len < 0)
+ {ret = EXCP_ERROR(env, "Bad in data"); goto done;}
+ tag_data = in_data + in_len;
+ }
+
+ cipherp = ctx_res->cipherp;
+ cipher = cipherp->cipher.p;
+ ctx = ctx_res->ctx;
+ }
+ /* Init done */
+
if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_set_ivlen, (int)iv.size, NULL) != 1)
{ret = EXCP_BADARG_N(env, 2, "Bad IV length"); goto done;}
@@ -116,7 +270,7 @@ ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
{ret = EXCP_BADARG_N(env, 5, "Can't set tag"); goto done;}
if (EVP_CipherInit_ex(ctx, NULL, NULL, key.data, iv.data, -1) != 1)
{ret = EXCP_ERROR(env, "Can't set key or iv"); goto done;}
- if (EVP_CipherUpdate(ctx, NULL, &len, NULL, (int)in.size) != 1)
+ if (EVP_CipherUpdate(ctx, NULL, &len, NULL, (int)in_len) != 1)
{ret = EXCP_ERROR(env, "Can't set text size"); goto done;}
} else
#endif
@@ -131,9 +285,15 @@ ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
{ret = EXCP_BADARG_N(env, 4, "Can't set AAD"); goto done;}
/* Set the plain text and get the crypto text (or vice versa :) ) */
- if ((outp = enif_make_new_binary(env, in.size, &out)) == NULL)
+ if (encflg && argc == 4)
+ len = in_len+tag_len;
+ else
+ len = in_len;
+
+ if ((outp = enif_make_new_binary(env, len, &out)) == NULL)
{ret = EXCP_ERROR(env, "Can't make 'Out' binary"); goto done;}
- if (EVP_CipherUpdate(ctx, outp, &len, in.data, (int)in.size) != 1)
+
+ if (EVP_CipherUpdate(ctx, outp, &len, in_data, in_len) != 1)
{
if (encflg)
ret = EXCP_BADARG_N(env, 3, "Can't set in-text");
@@ -142,28 +302,37 @@ ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
ret = atom_error;
goto done;
}
-
if (encflg)
{
- /* Finalize the encrypted text */
- if (EVP_CipherFinal_ex(ctx, outp, &len) != 1)
- {ret = EXCP_ERROR(env, "Encrypt error"); goto done;}
-
- /* Get the tag */
- if ((tagp = enif_make_new_binary(env, tag_len, &out_tag)) == NULL)
- {ret = EXCP_ERROR(env, "Can't make 'Out' binary"); goto done;}
- if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_get_tag, (int)tag_len, tagp) != 1)
- {ret = EXCP_ERROR(env, "Can't get Tag"); goto done;}
-
- /* Make the return value (the tuple with binary crypto text and the tag) */
- ret = enif_make_tuple2(env, out, out_tag);
+ if (argc == 7) {
+ /* Finalize the encrypted text */
+ if (EVP_CipherFinal_ex(ctx, outp, &len) != 1)
+ {ret = EXCP_ERROR(env, "Encrypt error"); goto done;}
+
+ /* Get the tag */
+ if ((tagp = enif_make_new_binary(env, tag_len, &out_tag)) == NULL)
+ {ret = EXCP_ERROR(env, "Can't make 'Out' binary"); goto done;}
+ if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_get_tag, (int)tag_len, tagp) != 1)
+ {ret = EXCP_ERROR(env, "Can't get Tag"); goto done;}
+
+ /* Make the return value (the tuple with binary crypto text and the tag) */
+ ret = enif_make_tuple2(env, out, out_tag);
+ } else {
+ if (EVP_CipherFinal_ex(ctx, outp, &len) != 1)
+ {ret = EXCP_ERROR(env, "Encrypt error"); goto done;}
+ /* Add tag to output end */
+ tagp = outp + in_len;
+ if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_get_tag, (int)tag_len, tagp) != 1)
+ {ret = EXCP_ERROR(env, "Can't get Tag"); goto done;}
+ ret = out;
+ }
}
else /* Decrypting. The plain text is already pointed to by 'out' */
{
#if defined(HAVE_GCM) || defined(HAVE_CHACHA20_POLY1305)
/* Check the Tag before returning. CCM_MODE does this previously. */
if (!(cipherp->flags & CCM_MODE)) { /* That is, CHACHA20_POLY1305 or GCM_MODE */
- if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_set_tag, (int)tag_len, tag.data) != 1)
+ if (EVP_CIPHER_CTX_ctrl(ctx, cipherp->extra.aead.ctx_ctrl_set_tag, (int)tag_len, tag_data) != 1)
/* Decrypt error */
{ret = atom_error; goto done;}
/* CCM dislikes EVP_DecryptFinal_ex on decrypting for pre 1.1.1, so we do it only here */
@@ -179,7 +348,7 @@ ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
CONSUME_REDS(env, in);
done:
- if (ctx)
+ if (ctx && argc == 7 )
EVP_CIPHER_CTX_free(ctx);
return ret;
@@ -188,4 +357,3 @@ done:
#endif
}
-
diff --git a/lib/crypto/c_src/aead.h b/lib/crypto/c_src/aead.h
index f2fad17743..bed3816c53 100644
--- a/lib/crypto/c_src/aead.h
+++ b/lib/crypto/c_src/aead.h
@@ -23,6 +23,9 @@
#include "common.h"
+int init_aead_cipher_ctx(ErlNifEnv *env, ErlNifBinary* rt_buf);
+
+ERL_NIF_TERM aead_cipher_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
ERL_NIF_TERM aead_cipher_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
#endif /* E_AEAD_H__ */
diff --git a/lib/crypto/c_src/crypto.c b/lib/crypto/c_src/crypto.c
index dc10b190f8..343bd30fff 100644
--- a/lib/crypto/c_src/crypto.c
+++ b/lib/crypto/c_src/crypto.c
@@ -118,6 +118,8 @@ static ErlNifFunc nif_funcs[] = {
{"rand_seed_nif", 1, rand_seed_nif, 0},
{"aead_cipher_nif", 7, aead_cipher_nif, 0},
+ {"aead_cipher_nif", 4, aead_cipher_nif, 0},
+ {"aead_cipher_init_nif", 4, aead_cipher_init_nif, 0},
{"engine_by_id_nif", 1, engine_by_id_nif, 0},
{"engine_init_nif", 1, engine_init_nif, 0},
@@ -224,6 +226,10 @@ static int initialize(ErlNifEnv* env, ERL_NIF_TERM load_info)
if (!init_cipher_ctx(env, &rt_buf)) {
ret = __LINE__; goto done;
}
+ if (!init_aead_cipher_ctx(env, &rt_buf)) {
+ ret = __LINE__; goto done;
+ }
+
if (!init_engine_ctx(env, &rt_buf)) {
ret = __LINE__; goto done;
}
diff --git a/lib/crypto/src/crypto.erl b/lib/crypto/src/crypto.erl
index 385f5f9df2..5b24800e8e 100644
--- a/lib/crypto/src/crypto.erl
+++ b/lib/crypto/src/crypto.erl
@@ -147,6 +147,7 @@ try crypto:crypto_init(Ciph, Key, IV, true)
end
```
""".
+
-moduledoc(#{titles =>
[{function,<<"Cipher API">>},
{function,<<"Hash API">>},
@@ -247,6 +248,7 @@ end
crypto_one_time/4, crypto_one_time/5,
crypto_one_time_aead/6, crypto_one_time_aead/7,
+ crypto_one_time_aead_init/4, crypto_one_time_aead/4,
crypto_final/1,
crypto_get_data/1,
@@ -297,7 +299,8 @@ end
evp_compute_key_nif/3, evp_generate_key_nif/2, privkey_to_pubkey_nif/2,
srp_value_B_nif/5, srp_user_secret_nif/7, srp_host_secret_nif/5,
ec_generate_key_nif/2, ecdh_compute_key_nif/3, rand_seed_nif/1,
- aead_cipher_nif/7, engine_by_id_nif/1, engine_init_nif/1,
+ aead_cipher_nif/7, aead_cipher_init_nif/4, aead_cipher_nif/4,
+ engine_by_id_nif/1, engine_init_nif/1,
engine_free_nif/1, engine_load_dynamic_nif/0,
engine_ctrl_cmd_strings_nif/3, engine_register_nif/2,
engine_unregister_nif/2, engine_add_nif/1, engine_remove_nif/1,
@@ -1752,7 +1755,6 @@ crypto_one_time_aead(Cipher, Key, IV, PlainText, AAD, true) ->
{1,2,3,4,5,-1,6}
).
-
-doc """
Do a complete encrypt or decrypt with an AEAD cipher of the full text.
@@ -1816,6 +1818,53 @@ aead_tag_len(sm4_ccm) -> 16;
aead_tag_len(_) ->
error({badarg, "Not an AEAD cipher"}).
+
+
+-doc("""
+Initializes AEAD cipher.
+
+Similar to 'crypto_one_time_aead/7' but only does the initialization part,
+returns a handle that can be used with 'crypto_one_time_aead/4' serveral times.
+
+""").
+-doc(#{title => <<"Cipher API">>,
+ since => <<"OTP 28.0">>}).
+-spec crypto_one_time_aead_init(Cipher, Key, TagLength, EncFlag) -> Result
+ when Cipher :: cipher_aead(),
+ Key :: iodata(),
+ TagLength :: non_neg_integer(), % or pos_integer() 1..
+ EncFlag :: boolean(),
+ Result :: crypto_state().
+
+crypto_one_time_aead_init(Cipher, Key, Length, Encode) when is_integer(Length) ->
+ ?nif_call(aead_cipher_init_nif(alias(Cipher,Key), iolist_to_binary(Key), Length, Encode),
+ [Cipher, Key, Length, Encode],
+ {}
+ ).
+
+-doc("""
+Do a complete encrypt or decrypt with an AEAD cipher of the full text.
+
+Similar to 'crypto_one_time_aead/7' but uses the handle from 'crypto_one_time_aead_init/4'.
+
+Appends the tag of the specified 'TagLength' to the end of the encrypted data, when doing encryption.
+Strips the tag from the end of 'InText' and verifies it when doing decryption.
+""").
+-doc(#{title => <<"Cipher API">>,
+ since => <<"OTP 28.0">>}).
+-spec crypto_one_time_aead(State, IV, InText, AAD) ->
+ Result
+ when State :: crypto_state(),
+ IV :: iodata(),
+ InText :: iodata(),
+ AAD :: iodata(),
+ Result :: EncryptResult | DecryptResult,
+ EncryptResult :: binary(),
+ DecryptResult :: binary() | error.
+crypto_one_time_aead(State, IV, InText, AAD) ->
+ ?nif_call(aead_cipher_nif(State, IV, InText, AAD)).
+
+
%%%----------------------------------------------------------------
%%% Cipher NIFs
@@ -1831,6 +1880,10 @@ ng_crypto_one_time_nif(_Cipher, _Key, _IVec, _Data, _OptionsMap) -> ?nif_stub.
aead_cipher_nif(_Type, _Key, _Ivec, _AAD, _In, _TagOrTagLength, _EncFlg) -> ?nif_stub.
+aead_cipher_init_nif(_Type, _Key, _TagOrTagLength, _EncFlg) -> ?nif_stub.
+
+aead_cipher_nif(_State, _IV, _InText, _AA) -> ?nif_stub.
+
cipher_info_nif(_Type) -> ?nif_stub.
%%%----------------------------------------------------------------
diff --git a/lib/crypto/test/crypto_SUITE.erl b/lib/crypto/test/crypto_SUITE.erl
index 89c6343e85..dda90b0b7c 100644
--- a/lib/crypto/test/crypto_SUITE.erl
+++ b/lib/crypto/test/crypto_SUITE.erl
@@ -1648,11 +1648,29 @@ aead_cipher_ng({Type, Key, PlainText, IV, AAD, CipherText, CipherTag, _Info}=T)
aead_cipher_ng({Type, Key, PlainText, IV, AAD, CipherText, CipherTag, TagLen, _Info}=T) ->
<<TruncatedCipherTag:TagLen/binary, _/binary>> = CipherTag,
Plain = iolist_to_binary(PlainText),
- cipher_test(T,
- fun() -> crypto:crypto_one_time_aead(Type, Key, IV, PlainText, AAD, TagLen, true) end,
- {CipherText, TruncatedCipherTag},
- fun() -> crypto:crypto_one_time_aead(Type, Key, IV, CipherText, AAD, TruncatedCipherTag, false) end,
- Plain).
+ T1 = cipher_test(T,
+ fun() -> crypto:crypto_one_time_aead(Type, Key, IV, PlainText, AAD, TagLen, true) end,
+ {CipherText, TruncatedCipherTag},
+ fun() -> crypto:crypto_one_time_aead(Type, Key, IV, CipherText, AAD, TruncatedCipherTag, false) end,
+ Plain),
+ case T1 == ok of
+ false ->
+ T1;
+ true ->
+ %% ok
+ CipherTextCipherTag = <<CipherText/binary, TruncatedCipherTag/binary>>,
+ cipher_test(T,
+ fun() ->
+ Handle = crypto:crypto_one_time_aead_init(Type, Key, TagLen, true),
+ crypto:crypto_one_time_aead(Handle, IV, PlainText, AAD)
+ end,
+ CipherTextCipherTag,
+ fun() ->
+ Handle = crypto:crypto_one_time_aead_init(Type, Key, TagLen, false),
+ crypto:crypto_one_time_aead(Handle, IV, CipherTextCipherTag, AAD)
+ end,
+ Plain)
+ end.
aead_cipher_bad_tag({Type, Key, _PlainText, IV, AAD, CipherText, CipherTag, _Info}=T) ->
BadTag = mk_bad_tag(CipherTag),
@@ -1708,7 +1726,7 @@ do_cipher_tests(F, TestVectors) when is_function(F,1) ->
[] ->
ct:comment("All ~p passed", [length(Passed)]);
_ ->
- ct:log("~p",[hd(Failed)]),
+ ct:log("~p", [hd(Failed)]),
ct:comment("Passed: ~p, BothFailed: ~p OnlyOneFailed: ~p",
[length(Passed), length(BothFailed), length(Failed)-length(BothFailed)]),
ct:fail("Failed", [])
--
2.43.0