File 2272-crypto-Curves-cache.patch of Package erlang
From 99a2ea0b8db9e3e66e65d3dfe17716f6f52cf343 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Thu, 2 Apr 2020 10:02:52 +0200
Subject: [PATCH 2/2] crypto: Curves cache
Currently un-supported curves must be removed from the crypto:supports
result.
It is very slow on some machines (no hw-accel?) so we keep a cache once
the list is filtered. If FIPS mode is supported, the list must be changed
each time the mode is changed.
The list is rebuilt:
  - first call to start() or first call of crypto:supports
  - each state change of the FIPS mode
---
 lib/crypto/src/crypto.erl | 89 +++++++++++++++++++++++++++++++++++++++++------
 1 file changed, 79 insertions(+), 10 deletions(-)
diff --git a/lib/crypto/src/crypto.erl b/lib/crypto/src/crypto.erl
index 34f59300a6..2d6efbfd79 100644
--- a/lib/crypto/src/crypto.erl
+++ b/lib/crypto/src/crypto.erl
@@ -646,7 +646,13 @@ version() -> ?CRYPTO_VSN.
 
 -spec start() -> ok | {error, Reason::term()}.
 start() ->
-    application:start(crypto).
+    case application:start(crypto) of
+        ok ->
+            _ = supports(curves), % Build curves cache if needed
+            ok;
+        Error ->
+            Error
+    end.
 
 -spec stop() -> ok | {error, Reason::term()}.
 stop() ->
@@ -666,12 +672,13 @@ stop() ->
                              Curves :: [ec_named_curve() | edwards_curve_dh() | edwards_curve_ed()],
                              RSAopts :: [rsa_sign_verify_opt() | rsa_opt()] .
 supports() ->
-     [{hashs, hash_algorithms()},
-      {ciphers, prepend_old_aliases( cipher_algorithms())},
-      {public_keys, pubkey_algorithms()},
-      {macs, mac_algorithms()},
-      {curves, curve_algorithms()},
-      {rsa_opts, rsa_opts_algorithms()}
+     [{hashs,       supports(hashs)},
+      {ciphers,     prepend_old_aliases(supports(ciphers))}
+      | [{T,supports(T)} || T <- [public_keys,
+                                  macs,
+                                  curves,
+                                  rsa_opts]
+        ]
      ].
 
 
@@ -695,11 +702,13 @@ supports() ->
                              Curves :: [ec_named_curve() | edwards_curve_dh() | edwards_curve_ed()],
                              RSAopts :: [rsa_sign_verify_opt() | rsa_opt()] .
 
+-define(CURVES, '$curves$').
+
 supports(hashs)       -> hash_algorithms();
 supports(public_keys) -> pubkey_algorithms();
 supports(ciphers)     -> cipher_algorithms();
 supports(macs)        -> mac_algorithms();
-supports(curves)      -> curve_algorithms();
+supports(curves)      -> cached_curve_algorithms();
 supports(rsa_opts)    -> rsa_opts_algorithms().
 
 
@@ -715,9 +724,49 @@ info_fips() -> ?nif_stub.
 -spec enable_fips_mode(Enable) -> Result when Enable :: boolean(),
                                               Result :: boolean().
 enable_fips_mode(Enable) ->
-    enable_fips_mode_nif(Enable).
+    OldState = info_fips(),
+    Result = enable_fips_mode_nif(Enable),
+    case info_fips() of
+        OldState ->
+            %% No state change, so no need to touch the curve's cache
+            Result;
+        NewState ->
+            %% State change (not_enabled -> enabled  or  enabled -> not_enabled)
+            NewCurves =
+                case application:get_env(?MODULE, var_name(NewState)) of
+                    {ok,Cs} when is_list(Cs) ->
+                        %% We have been in this state before, and saved the
+                        %% list for that state.
+                        Cs;
+                    _ ->
+                        %% We have not been in this state before. Rebuild and save.
+                        %% But first maintain the local enable_fips_mode_nif cache:
+                        case application:get_env(?MODULE, var_name(OldState)) of
+                            undefined ->
+                                %% Make the next state change fast:
+                                OldCs = application:get_env(?MODULE,?CURVES), 
+                                application:set_env(?MODULE, var_name(OldState), OldCs);
+                            _ ->
+                                ok
+                        end,
+                        %% Now rebuild the list by hard work:
+                        application:unset_env(?MODULE, ?CURVES), % This will force a re-build
+                        %% Re-build curves cache. Not strictly needed here.
+                        Cs = supports(curves),
+                        %% We came here because var(NewState) wasn't set, so make the
+                        %% next state change fast:
+                        application:set_env(?MODULE, var_name(NewState), Cs),
+                        Cs
+                end,
+            application:set_env(?MODULE, ?CURVES, NewCurves), % So the call to supports(curves) will be fast
+            Result
+    end.
 
-enable_fips_mode_nif(Enable) -> ?nif_stub.
+var_name(enabled) -> '$curves-fips-enabled$';
+var_name(not_enabled) -> '$curves-fips-not_enabled$'.
+
+
+enable_fips_mode_nif(_) -> ?nif_stub.
 
 %%%================================================================
 %%%
@@ -2780,6 +2829,26 @@ exor(Data1, Data2, _Size, MaxByts, Acc) ->
 
 do_exor(_A, _B) -> ?nif_stub.
 
+cached_curve_algorithms() ->
+    case application:get_env(?MODULE, ?CURVES) of
+        undefined ->
+            Cs = remove_unavailable_curves(curve_algorithms()),
+            application:set_env(?MODULE, ?CURVES, Cs),
+            Cs;
+        {ok,Cs} ->
+            Cs
+    end.
+
+remove_unavailable_curves(Cs) ->
+    [C || C <- Cs,
+          lists:member(C,[ed25519,ed448,x25519,x448])
+              orelse try
+                         crypto:generate_key(ecdh,C)
+                     of _-> true
+                     catch _:_-> false
+                     end
+    ].
+
 hash_algorithms() -> ?nif_stub.
 pubkey_algorithms() -> ?nif_stub.
 cipher_algorithms() -> ?nif_stub.
-- 
2.16.4