Skip to content

Commit 8df6f90

Browse files
committed
extract EC group from private key for explicit curves
Going though the curve NID or name only works for standardized curves. However, explicit curves can use parameters that that deviate from the named curves. The public key generation would in that case fail to extract the group parameters from the key. Instead extract all parameters explicitly and build the group from that. fixes #9723
1 parent f958028 commit 8df6f90

File tree

2 files changed

+130
-32
lines changed

2 files changed

+130
-32
lines changed

lib/crypto/c_src/ec.c

+110-31
Original file line numberDiff line numberDiff line change
@@ -439,45 +439,125 @@ ERL_NIF_TERM ec_generate_key_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
439439
return ret;
440440
}
441441

442+
/*
443+
* Function to extract explicit EC params and construct an EC_GROUP
444+
* Returns a NEWLY ALLOCATED EC_GROUP on success (caller must free), NULL on failure.
445+
*/
446+
static EC_GROUP* extract_and_build_ec_group_from_ctx(EVP_PKEY *pkey) {
447+
EC_GROUP *new_group = NULL;
448+
BN_CTX *bn_ctx = NULL;
449+
EC_POINT *gen_point = NULL;
450+
451+
BIGNUM *bn_p = NULL, *bn_a = NULL, *bn_b = NULL, *bn_n = NULL, *bn_h = NULL;
452+
unsigned char *gen_buf = NULL;
453+
size_t gen_len_needed = 0;
454+
size_t gen_len_written = 0;
455+
char field_type_buf[64] = {0};
456+
size_t field_type_len_written = 0;
457+
size_t field_type_buf_len;
458+
459+
if (!EVP_PKEY_is_a(pkey, "EC"))
460+
return NULL;
461+
462+
field_type_buf_len = sizeof(field_type_buf);
463+
if (!EVP_PKEY_get_utf8_string_param(pkey, OSSL_PKEY_PARAM_EC_FIELD_TYPE,
464+
field_type_buf, field_type_buf_len, &field_type_len_written)) {
465+
ERR_clear_error();
466+
/* Assuming prime field is okay for EC_GROUP_new_curve_GFp */
467+
} else {
468+
/* We currently only support prime field construction below */
469+
if (strcmp(field_type_buf, SN_X9_62_prime_field) != 0) {
470+
goto cleanup;
471+
}
472+
}
473+
474+
/* P, A, B, Order N (Mandatory for construction) */
475+
if (!EVP_PKEY_get_bn_param(pkey, OSSL_PKEY_PARAM_EC_P, &bn_p) ||
476+
!EVP_PKEY_get_bn_param(pkey, OSSL_PKEY_PARAM_EC_A, &bn_a) ||
477+
!EVP_PKEY_get_bn_param(pkey, OSSL_PKEY_PARAM_EC_B, &bn_b) ||
478+
!EVP_PKEY_get_bn_param(pkey, OSSL_PKEY_PARAM_EC_ORDER, &bn_n))
479+
goto cleanup;
480+
481+
/* Cofactor H (Optional for construction, but good to get if available) */
482+
if (!EVP_PKEY_get_bn_param(pkey, OSSL_PKEY_PARAM_EC_COFACTOR, &bn_h))
483+
/* try to continue without Cofactor */
484+
ERR_clear_error();
485+
486+
/* Generator G (Mandatory for construction) */
487+
if (!EVP_PKEY_get_octet_string_param(pkey, OSSL_PKEY_PARAM_EC_GENERATOR,
488+
NULL, 0, &gen_len_needed) || gen_len_needed == 0)
489+
goto cleanup;
490+
491+
gen_buf = OPENSSL_malloc(gen_len_needed);
492+
if (!gen_buf)
493+
goto cleanup;
494+
495+
if (!EVP_PKEY_get_octet_string_param(pkey, OSSL_PKEY_PARAM_EC_GENERATOR,
496+
gen_buf, gen_len_needed, &gen_len_written) ||
497+
gen_len_written != gen_len_needed)
498+
goto cleanup;
499+
500+
/* 4. Construct the EC_GROUP */
501+
bn_ctx = BN_CTX_new();
502+
if (!bn_ctx)
503+
goto cleanup;
504+
505+
/* Create group structure with p, a, b */
506+
new_group = EC_GROUP_new_curve_GFp(bn_p, bn_a, bn_b, bn_ctx);
507+
if (!new_group)
508+
goto cleanup;
509+
510+
/* Create and set the generator point */
511+
gen_point = EC_POINT_new(new_group);
512+
if (!gen_point)
513+
goto cleanup;
514+
515+
/* Convert octet string generator to point object */
516+
if (!EC_POINT_oct2point(new_group, gen_point, gen_buf, gen_len_written, bn_ctx))
517+
goto cleanup;
518+
519+
/* Set generator, order (n), and cofactor (h)
520+
EC_GROUP_set_generator takes ownership of bn_n and bn_h if they are non-NULL.
521+
We pass bn_h which might be NULL if extraction failed - this is okay. */
522+
if (!EC_GROUP_set_generator(new_group, gen_point, bn_n, bn_h))
523+
goto cleanup;
524+
525+
/* Construction successful! Set return pointer and prevent cleanup from freeing inputs. */
526+
EC_POINT_free(gen_point);
527+
BN_CTX_free(bn_ctx);
528+
529+
if (bn_p) BN_free(bn_p);
530+
if (bn_a) BN_free(bn_a);
531+
if (bn_b) BN_free(bn_b);
532+
if (bn_n) BN_free(bn_n);
533+
if (bn_h) BN_free(bn_h);
534+
OPENSSL_free(gen_buf);
535+
536+
return new_group;
537+
538+
cleanup:
539+
if (bn_p) BN_free(bn_p);
540+
if (bn_a) BN_free(bn_a);
541+
if (bn_b) BN_free(bn_b);
542+
if (bn_n) BN_free(bn_n);
543+
if (bn_h) BN_free(bn_h);
544+
OPENSSL_free(gen_buf);
545+
EC_POINT_free(gen_point);
546+
EC_GROUP_free(new_group);
547+
BN_CTX_free(bn_ctx);
548+
return NULL;
549+
}
550+
442551
static int mk_pub_key_binary(ErlNifEnv* env, EVP_PKEY *peer_pkey,
443552
ErlNifBinary *pubkey_bin, ERL_NIF_TERM *ret)
444553
{
445554
size_t pub_key_size = 0;
446-
size_t group_name_size = 0;
447-
char group_name_buf[20];
448-
char* group_name = group_name_buf;
449-
int group_nid;
450555
EC_GROUP* ec_group = NULL;
451556
EC_POINT* pub_key = NULL;
452557
BIGNUM* priv_bn = NULL;
453558
int ok = 0;
454559

455-
/* This code was inspired by
456-
* https://github.com/openssl/openssl/issues/18437
457-
* which first tried to get public key directly with
458-
* EVP_PKEY_get_octet_string_param(peer_pkey, OSSL_PKEY_PARAM_PUB_KEY,..)
459-
*
460-
* I removed that since I don't know what key format that will produce
461-
* if it succeeds. That is, we go directly to the "fallback" and calculate
462-
* the public key.
463-
*/
464-
465-
if (!EVP_PKEY_get_utf8_string_param(peer_pkey, OSSL_PKEY_PARAM_GROUP_NAME,
466-
NULL, 0, &group_name_size))
467-
assign_goto(*ret, err, EXCP_ERROR(env, "Couldn't get EC group name size"));
468-
469-
if (group_name_size >= sizeof(group_name_buf))
470-
group_name = enif_alloc(group_name_size + 1);
471-
if (!EVP_PKEY_get_utf8_string_param(peer_pkey, OSSL_PKEY_PARAM_GROUP_NAME,
472-
group_name, group_name_size+1,
473-
NULL))
474-
assign_goto(*ret, err, EXCP_ERROR(env, "Couldn't get EC group name"));
475-
476-
group_nid = OBJ_sn2nid(group_name);
477-
if (group_nid == NID_undef)
478-
assign_goto(*ret, err, EXCP_ERROR(env, "Couldn't get EC group nid"));
479-
480-
ec_group = EC_GROUP_new_by_curve_name(group_nid);
560+
ec_group = extract_and_build_ec_group_from_ctx(peer_pkey);
481561
if (ec_group == NULL)
482562
assign_goto(*ret, err, EXCP_ERROR(env, "Couldn't get EC_GROUP"));
483563

@@ -508,7 +588,6 @@ static int mk_pub_key_binary(ErlNifEnv* env, EVP_PKEY *peer_pkey,
508588
ok = 1;
509589

510590
err:
511-
if (group_name != group_name_buf) enif_free(group_name);
512591
if (pub_key) EC_POINT_free(pub_key);
513592
if (ec_group) EC_GROUP_free(ec_group);
514593
if (priv_bn) BN_free(priv_bn);

lib/crypto/test/crypto_SUITE.erl

+20-1
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,7 @@
129129
use_all_ec_sign_verify/1,
130130
use_all_ecdh_generate_compute/1,
131131
use_all_eddh_generate_compute/1,
132+
ecdh_generate_explicit_curve/1,
132133
pbkdf2_hmac/0,
133134
pbkdf2_hmac/1,
134135
pbkdf2_hmac_invalid_input/0,
@@ -424,7 +425,8 @@ groups() ->
424425
generate
425426
]},
426427
{dh, [], [generate_compute, compute_bug]},
427-
{ecdh, [], [compute, generate, use_all_ecdh_generate_compute]},
428+
{ecdh, [], [compute, generate, use_all_ecdh_generate_compute,
429+
ecdh_generate_explicit_curve]},
428430
{eddh, [], [compute, generate, use_all_eddh_generate_compute]},
429431
{srp, [], [generate_compute]},
430432
{des_cbc, [], [api_ng, api_ng_one_shot, cmac, cmac_update]},
@@ -1305,6 +1307,23 @@ use_all_ec_sign_verify(_Config) ->
13051307
ct:fail("Bad curve(s)",[])
13061308
end.
13071309

1310+
%%--------------------------------------------------------------------
1311+
ecdh_generate_explicit_curve(_Config) ->
1312+
{Generator, _} = crypto:generate_key(ecdh, secp256k1, 2),
1313+
1314+
%% use the secp256k1 curve parameter, but move the generator to 2*G
1315+
Curve = {{prime_field,
1316+
<<255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,254,255,255,252,47>>},
1317+
{<<0>>,<<7>>,none},
1318+
Generator,
1319+
<<255,255,255,255,255,255,255,255,255,255,255,255,255,255,255,254,186,174,220,230,175,72,160,59,191,210,94,140,208,54,65,65>>,
1320+
<<1>>},
1321+
1322+
{Generator, <<1:256>>} = crypto:generate_key(ecdh, Curve, 1),
1323+
{Point2, _} = crypto:generate_key(ecdh, secp256k1, 4),
1324+
{Point2, <<2:256>>} = crypto:generate_key(ecdh, Curve, 2),
1325+
ok.
1326+
13081327
%%--------------------------------------------------------------------
13091328
use_all_ecdh_generate_compute(Config) ->
13101329
SkipCurves0 = [ed25519, ed448, x25519, x448],

0 commit comments

Comments
 (0)