File 0153-All-tests-pass-nginx.patch of Package erlang
From 0e0f5705887a704c78a380a83bb88505b9489c72 Mon Sep 17 00:00:00 2001
From: Dmytro Lytovchenko <dima.lytovchenko@ericsson.com>
Date: Thu, 4 Sep 2025 14:55:21 +0200
Subject: [PATCH 3/3] All tests pass + nginx Emacs formatting for changed
modules
---
lib/inets/test/httpd_bench_SUITE.erl | 490 ++++++++++++++-------------
lib/inets/test/httpd_bench_certs.erl | 88 ++---
2 files changed, 303 insertions(+), 275 deletions(-)
diff --git a/lib/inets/test/httpd_bench_SUITE.erl b/lib/inets/test/httpd_bench_SUITE.erl
index b81779df7c..181f66930b 100644
--- a/lib/inets/test/httpd_bench_SUITE.erl
+++ b/lib/inets/test/httpd_bench_SUITE.erl
@@ -18,9 +18,6 @@
%% limitations under the License.
%%
%% %CopyrightEnd%
-%%
-
-
%%
-module(httpd_bench_SUITE).
@@ -29,11 +26,10 @@
-include_lib("kernel/include/file.hrl").
-export([suite/0, all/0, groups/0, init_per_suite/1, end_per_suite/1, init_per_group/2, end_per_group/2,
- init_per_testcase/2, end_per_testcase/2, wget_small/1, erl_dummy_small/1, httpc_small/1, wget_big/1,
- erl_dummy_big/1, httpc_big/1]).
--export([httpc_client/1, httpc_client/2, httpd_lib_client/1, httpd_lib_client/2,
- wget_client/1, wget_client/2, wget/4]).
--export([handle_http_msg/3]).
+ init_per_testcase/2, end_per_testcase/2, wget_small/1, erl_dummy_small/1, httpc_small/1, wget_big/1,
+ erl_dummy_big/1, httpc_big/1]).
+-export([httpc_client/1, httpd_lib_client/1, wget_client/1, wget/4]).
+-export([handle_http_msg/3]). % httpd_test_lib callback
-define(remote_host, "NETMARKS_REMOTE_HOST").
-define(LF, [10]).
@@ -44,7 +40,7 @@
%% Common Test interface functions -----------------------------------
%%--------------------------------------------------------------------
suite() ->
- [{timetrap, {minutes, 1}}].
+ [{timetrap, {seconds, 10}}].
all() ->
[
@@ -114,7 +110,7 @@ init_per_group(Group, Config) when Group == http_dummy_keep_alive;
{http_headers, [{"connection", "keep-alive"}]},
{httpc_opts, [{keep_alive_timeout, 1500},
{max_keep_alive_length, ?config(iter, Config)}]}
- | Config]);
+ | Config]);
%% Init non-keepalive servers group
init_per_group(Group, Config) when Group == http_dummy;
Group == https_dummy;
@@ -130,7 +126,7 @@ init_per_group(Group, Config) when Group == http_dummy;
{http_headers, [{"connection", "close"}]},
{http_opts,[{version, Version}]},
{httpc_opts, [{keep_alive_timeout, 0}, {max_keep_alive_length, 0}]}
- | Config]);
+ | Config]);
init_per_group(_, Config) ->
@@ -154,6 +150,7 @@ end_per_testcase(TestCase, _Config) when TestCase == httpc_small;
ok = inets:stop(httpc, TestCase);
end_per_testcase(_TestCase, Config) ->
Config.
+
%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
@@ -195,12 +192,12 @@ notify({TestPerSec, _MBps}, Config, Suffix) ->
Name = lists:concat([?config(protocol,Config), " ",
server_name(Config, [dummy_pid, httpd_pid, nginx_port]),
"", Suffix]),
- ct:comment("~p tests/s", [TestPerSec]),
+ ct:comment("~p Req/s", [TestPerSec]),
ct_event:notify(#event{name = benchmark_data,
data=[{value, TestPerSec},
{suite, ?MODULE},
{name, Name}]}),
- ok.
+ ok.
%%--------------------------------------------------------------------
%% Setup erlang nodes ------------------------------------------------
%%--------------------------------------------------------------------
@@ -220,13 +217,11 @@ server_name(nginx_port) ->
server_name(dummy_pid) ->
"erlang".
-setup(_Config, nonode@nohost) ->
- exit(dist_not_enabled);
-setup(_Config, _LocalNode) ->
- Host = case os:getenv(?remote_host) of
- false -> net_adm:localhost();
- RemHost -> RemHost
- end,
+create_test_peer_opts() ->
+ {Host, IsRemote} = case os:getenv(?remote_host) of
+ false -> {net_adm:localhost(), false};
+ RemHost -> {RemHost, true}
+ end,
PeerArgs = case init:get_argument(pa) of
{ok, PaPaths} -> ["-pa"] ++ lists:concat(PaPaths);
_ -> []
@@ -236,25 +231,38 @@ setup(_Config, _LocalNode) ->
P -> P
end,
PeerOpts = #{
- name => inets_perf_server,
- args => PeerArgs,
- peer_down => crash,
- exec => Prog
- },
- ct:pal("about to start peer...", []),
- {ok, PeerPid, Node} = peer:start(PeerOpts),
- ct:pal("started peer ~0p", [Node]),
+ name => inets_perf_server,
+ args => PeerArgs,
+ peer_down => crash,
+ exec => Prog
+ },
+ PeerOpts1 = case IsRemote of
+ true -> PeerOpts#{host => Host};
+ false -> PeerOpts % on localhost do not specify 'host' in peer:start
+ end,
+ {PeerOpts1, Host}.
+
+setup_peers_after_start(Node) ->
Path = code:get_path(),
- true = rpc:call(Node, code, set_path, [Path]),
- [ensure_started(Node, App) || App <- [asn1, crypto, public_key, ssl, inets]],
+ (Node =/= node()) andalso
+ begin
+ true = rpc:call(Node, code, set_path, [Path]),
+ [ensure_started(Node, App) || App <- [asn1, crypto, public_key, ssl, inets]]
+ end,
[ensure_started(node(), App) || App <- [asn1, crypto, public_key, ssl, inets]],
- (Node =:= node()) andalso restrict_schedulers(client),
+ (Node =:= node()) andalso restrict_schedulers(client).
+
+setup(_Config, nonode@nohost) ->
+ exit(dist_not_enabled);
+setup(_Config, _LocalNode) ->
+ {PeerOpts, Host} = create_test_peer_opts(),
+ {ok, PeerPid, Node} = peer:start(PeerOpts),
+ setup_peers_after_start(Node),
%% Return also the pid for peer control
[{server_node, Node}, {server_host, Host}, {server_pid, PeerPid}].
ensure_started(Node, App) ->
- ok = rpc:call(Node, application, ensure_started, [App]).
-
+ ok = rpc:call(Node, application, ensure_started, [App]).
restrict_schedulers(Type) ->
%% We expect this to run on 8 core machine
@@ -268,9 +276,7 @@ restrict_schedulers(Type) ->
%%--------------------------------------------------------------------
init_ssl(Config) ->
-%% DDir = ?config(data_dir, Config),
PDir = ?config(priv_dir, Config),
-%% {ok, _} = make_certs:all(DDir, PDir).
httpd_bench_certs:make_cert_files(PDir).
cert_opts(Config) ->
@@ -278,11 +284,17 @@ cert_opts(Config) ->
ServerCaCertFile = filename:join([PrivDir, "server-cacerts.pem"]),
ServerCertFile = filename:join([PrivDir, "server-cert.pem"]),
ServerKeyFile = filename:join([PrivDir, "server-key.pem"]),
- [{server_verification_opts, [{cacertfile, ServerCaCertFile},
+ [
+ {server_verification_opts, [
+ {cacertfile, ServerCaCertFile},
{ciphers, ["ECDHE-RSA-AES256-GCM-SHA384", "TLS_AES_256_GCM_SHA384"]},
{certfile, ServerCertFile},
- {keyfile, ServerKeyFile}]},
- {client_verification_opts, [{cacertfile, ServerCaCertFile}]}].
+ {keyfile, ServerKeyFile}
+ ]},
+ {client_verification_opts, [
+ {cacertfile, ServerCaCertFile}
+ ]}
+ ].
%%--------------------------------------------------------------------
%% Run clients ------------------------------------------------
@@ -290,48 +302,47 @@ cert_opts(Config) ->
run_test(Client, File, Config) ->
Parent = self(),
- Pid = spawn(fun() ->
- receive
- go ->
- Parent ! {self(),
- do_runs(Client, [{file, File} | Config])}
- end
- end),
+ Pid = spawn(
+ fun() ->
+ receive
+ go ->
+ Parent ! {self(), do_runs(Client, [{file, File} | Config])}
+ end
+ end),
Pid ! go,
receive
- {Pid,{{tps, Tps}, {mbps, MBps}}} ->
- ct:log("Tps: ~p Bps~p", [Tps, MBps]),
- {ok, {Tps, MBps}}
+ {Pid, #{req_s := Tps, bytes_s := Bps}} ->
+ ct:log("Req/s=~p Bytes/s=~p", [Tps, Bps]),
+ {ok, {Tps, Bps}}
end.
+-type client_impl() :: fun(({create_args, Config :: proplists:proplist()}) -> map())
+ | fun(({init, map()}) -> ok)
+ | fun(({run, map(), N :: integer()}) -> ok).
+
+-spec do_runs(Client :: client_impl(), Config :: proplists:proplist()) ->
+ #{req_s => integer(), bytes_s => integer()}.
do_runs(Client, Config) ->
N = ?config(iter, Config),
DataDir = ?config(data_dir, Config),
File = ?config(file, Config),
Name = filename:join(DataDir, File),
- Args = ?MODULE:Client(Config),
+
+ Args = ?MODULE:Client({create_args, Config}),
?MODULE:Client({init, Args}),
- Run = fun() ->
- ok = ?MODULE:Client(Args, N)
- end,
+ Run = fun() -> ok = ?MODULE:Client({run, Args, N}) end,
+
{ok, Info} = file:read_file_info(Name, []),
Length = Info#file_info.size,
{TimeInMicro, _} = timer:tc(Run),
- ReqPerSecond = (1000000 * N) div TimeInMicro,
- BytesPerSecond = (1000000 * N * Length) div TimeInMicro,
- {{tps, ReqPerSecond}, {mbps, BytesPerSecond}}.
+ ReqPerSecond = (1_000_000 * N) div TimeInMicro,
+ BytesPerSecond = (1_000_000 * N * Length) div TimeInMicro,
+ #{req_s => ReqPerSecond, bytes_s => BytesPerSecond}.
%% Client handler for httpc-based test cases
-%% httpc_client/1 is called once with the config, to create args which will be then passed
-%% again into httpc_client/1 as {init, Args}.
-httpc_client({init, [_, Profile, URL, Headers, HTTPOpts]}) ->
- %% Make sure pipelining feature will kick in when appropriate.
- {ok, {{_ ,200, "OK"}, _,_}} = httpc:request(
- get,{URL, Headers}, HTTPOpts,
- [{body_format, binary}, {socket_opts, [{nodelay, true}]}],
- Profile),
- ct:sleep(1000);
-httpc_client(Config) ->
+%% httpc_client {create_args, Config} is called once with the config, to create args which will be then passed
+%% again into httpc_client with {init, Args}, which are then passed into httpc_client with {run, Args, N}.
+httpc_client({create_args, Config}) ->
File = ?config(file, Config),
Protocol = ?config(protocol, Config),
Profile = ?config(profile, Config),
@@ -339,40 +350,36 @@ httpc_client(Config) ->
Headers = ?config(http_headers, Config),
HTTPOpts = ?config(http_opts, Config)
++ case Protocol of
- "http" -> [];
- "https" -> % httpc would like to know more about certificates used in the test
- AllCertOpts = proplists:get_value(client_verification_opts, cert_opts(Config)),
- SSLOpts = [
- {verify, verify_peer}, % this is the default
- {cacertfile, proplists:get_value(cacertfile, AllCertOpts)}
- ],
- [{ssl, SSLOpts}]
- end,
- [Protocol, Profile, URL, Headers, HTTPOpts].
-
-%% This will receive arguments (Args, N) where N is iterations count,
-%% with Args produced by httpc_client/1 above.
-httpc_client(_,0) ->
+ "http" -> [];
+ "https" -> % httpc would like to know more about certificates used in the test
+ AllCertOpts = proplists:get_value(client_verification_opts, cert_opts(Config)),
+ SSLOpts = [
+ {verify, verify_peer}, % this is the default
+ {cacertfile, proplists:get_value(cacertfile, AllCertOpts)}
+ ],
+ [{ssl, SSLOpts}]
+ end,
+ #{protocol => Protocol, profile => Profile, url => URL, headers => Headers, http_opts => HTTPOpts};
+httpc_client({init, #{profile := Profile, url := URL, headers := Headers, http_opts := HTTPOpts}}) ->
+ %% Make sure pipelining feature will kick in when appropriate.
+ {ok, {{_ ,200, "OK"}, _,_}} = httpc:request(
+ get,{URL, Headers}, HTTPOpts,
+ [{body_format, binary}, {socket_opts, [{nodelay, true}]}],
+ Profile),
+ ct:sleep(1_000);
+httpc_client({run, _, 0}) ->
ok;
-httpc_client([Protocol, Profile, URL, Headers, HTTPOpts], N) ->
+httpc_client({run, Args = #{profile := Profile, url := URL, headers := Headers, http_opts := HTTPOpts}, N}) ->
{ok, {{_ ,200,"OK"}, _,_}} = httpc:request(
- get,{URL, Headers}, HTTPOpts,
- [{body_format, binary}, {socket_opts, [{nodelay, true}]}],
- Profile),
- httpc_client([Protocol, Profile, URL, Headers, HTTPOpts], N-1).
+ get,{URL, Headers}, HTTPOpts,
+ [{body_format, binary}, {socket_opts, [{nodelay, true}]}],
+ Profile),
+ httpc_client({run, Args, N-1}).
%% Client handler based on httpd_test_lib
-%% httpd_lib_client/1 is called once with the config, to create args which will be then passed
-%% again into httpd_lib_client/1 as {init, Args}.
-httpd_lib_client({init, [_, Type, Version, Request, Host, Port, Opts]}) ->
- ok = httpd_test_lib:verify_request(Type, Host,
- Port,
- Opts, node(),
- Request,
- [{statuscode, 200},
- {version, Version}], infinity),
- ct:sleep(1000);
-httpd_lib_client(Config) ->
+%% httpd_lib_client {create_args, Config} is called once with the config, to create args which will be then passed
+%% again into httpd_lib_client with {init, Args}, which are then passed into httpd_lib_client with {run, Args, N}.
+httpd_lib_client({create_args, Config}) ->
File = ?config(file, Config),
KeepAlive = ?config(keep_alive, Config),
Host = ?config(server_host, Config),
@@ -396,36 +403,37 @@ httpd_lib_client(Config) ->
http_request("GET /" ++ File ++ " ", Version, Host)
end,
- Args = [KeepAlive, Type, Version, Request, Host, Port, Opts],
- httpd_lib_client(Args, 1),
- Args.
-
-%% This will receive arguments (Args, N) where N is iterations count,
-%% with Args produced by httpd_lib_client/1 above.
-httpd_lib_client(_, 0) ->
- ok;
-httpd_lib_client([true, Type, Version, Request, Host, Port, Opts], N) ->
- ok = httpd_test_lib:verify_request_N(Type, Host,
- Port,
- Opts, node(),
- Request,
- [{statuscode, 200},
- {version, Version}], infinity, N);
-httpd_lib_client([false, Type, Version, Request, Host, Port, Opts] = List, N) ->
+ Args = #{keepalive => KeepAlive, type => Type, version => Version,
+ request => Request, host => Host, port => Port, opts => Opts},
+ httpd_lib_client({run, Args, 1}), % warm-up run,
+ Args;
+httpd_lib_client({init, #{type := Type, version := Version, request := Request, host := Host,
+ port := Port, opts := Opts}}) ->
ok = httpd_test_lib:verify_request(Type, Host,
Port,
Opts, node(),
Request,
- [{statuscode, 200},
- {version, Version}], infinity),
- httpd_lib_client(List, N-1).
+ [{statuscode, 200}, {version, Version}],
+ infinity),
+ ct:sleep(1_000);
+httpd_lib_client({run, _, 0}) ->
+ ok;
+httpd_lib_client({run, #{keepalive := true, type := Type, version := Version, request := Request,
+ host := Host, port := Port, opts := Opts}, N}) ->
+ ok = httpd_test_lib:verify_request_N(Type, Host,
+ Port, Opts, node(), Request,
+ [{statuscode, 200}, {version, Version}], infinity, N);
+httpd_lib_client({run, Args = #{keepalive := false, type := Type, version := Version, request := Request,
+ host := Host, port := Port, opts := Opts}, N}) ->
+ ok = httpd_test_lib:verify_request(Type, Host,
+ Port, Opts, node(), Request,
+ [{statuscode, 200}, {version, Version}], infinity),
+ httpd_lib_client({run, Args, N - 1}).
%% Client handler for wget-based test cases
-%% wget_client/1 is called once with the config, to create args which will be then passed
-%% again into wget_client/1 as {init, Args}.
-wget_client({init,_}) ->
- ok;
-wget_client(Config) ->
+%% wget_client {create_args, Config} is called once with the config, to create args which will be then passed
+%% again into wget_client with {init, Args}, which are then passed into wget_client with {run, Args, N}.
+wget_client({create_args, Config}) ->
File = ?config(file, Config),
URL = (?config(urlfun,Config))(File),
KeepAlive = ?config(keep_alive, Config),
@@ -434,15 +442,16 @@ wget_client(Config) ->
Iter = ?config(iter, Config),
FileName = filename:join(PrivDir, "wget_req"),
ProtocolOpts = case Protocol of
- "http" -> [];
- "https" -> proplists:get_value(client_verification_opts, cert_opts(Config))
+ "http" -> [];
+ "https" -> proplists:get_value(client_verification_opts, cert_opts(Config))
end,
wget_req_file(FileName,URL,Iter),
- [KeepAlive, FileName, URL, Protocol, ProtocolOpts, Iter].
-
-%% This will receive arguments (Args, N) where N is iterations count,
-%% with Args produced by wget_client/1 above.
-wget_client([KeepAlive, WgetFile, _URL, Protocol, ProtocolOpts, _], _Iter) ->
+ #{keepalive => KeepAlive, filename => FileName, url => URL, protocol => Protocol,
+ protocol_opts => ProtocolOpts, iter => Iter};
+wget_client({init, _}) ->
+ ok;
+wget_client({run, #{keepalive := KeepAlive, filename := WgetFile, protocol := Protocol,
+ protocol_opts := ProtocolOpts}, _N}) ->
process_flag(trap_exit, true),
Cmd = wget_N(KeepAlive, WgetFile, Protocol, ProtocolOpts),
%%ct:log("Wget cmd: ~p", [Cmd]),
@@ -455,44 +464,40 @@ wget_client([KeepAlive, WgetFile, _URL, Protocol, ProtocolOpts, _], _Iter) ->
%%--------------------------------------------------------------------
start_web_server(Group, Config) when Group == http_dummy;
Group == http_dummy_keep_alive ->
- start_dummy("http", Config);
+ start_http_test_lib_server("http", Config);
start_web_server(Group, Config) when Group == https_dummy;
Group == https_dummy_keep_alive ->
- start_dummy("https", Config);
+ start_http_test_lib_server("https", Config);
start_web_server(Group, Config) when Group == http_inets;
Group == http_inets_keep_alive ->
- start_inets("http", [], Config);
+ start_inets_server("http", [], Config);
start_web_server(Group, Config) when Group == https_inets;
Group == https_inets_keep_alive ->
Opts = proplists:get_value(server_verification_opts, cert_opts(Config)),
ReuseSessions = ?config(reuse_sessions, Config),
SSLConfHttpd = [{socket_type,
- {ssl, [{nodelay, true}, {reuse_sessions, ReuseSessions} | Opts]}
- }],
- start_inets("https", SSLConfHttpd, Config);
+ {ssl, [{nodelay, true}, {reuse_sessions, ReuseSessions} | Opts]}
+ }],
+ start_inets_server("https", SSLConfHttpd, Config);
start_web_server(Group, Config) when Group == http_nginx;
Group == http_nginx_keep_alive ->
case os:find_executable("nginx") of
- false ->
- {skip, "nginx not found"};
- _ ->
- start_nginx("http", Config)
+ false -> {skip, "nginx not found"};
+ _ -> start_nginx("http", Config)
end;
start_web_server(Group, Config) when Group == https_nginx;
Group == https_nginx_keep_alive ->
- case os:find_executable("nginx") of
- false ->
- {skip, "nginx not found"};
- _ ->
- start_nginx("https", cert_opts(Config) ++ Config)
- end.
-
-start_inets(Protocol, ConfHttpd, Config) ->
+ case os:find_executable("nginx") of
+ false -> {skip, "nginx not found"};
+ _ -> start_nginx("https", cert_opts(Config) ++ Config)
+ end.
+
+start_inets_server(Protocol, ConfHttpd, Config) ->
PrivDir = ?config(priv_dir, Config),
DataDir = ?config(data_dir, Config),
Node = ?config(server_node, Config),
@@ -506,15 +511,16 @@ start_inets(Protocol, ConfHttpd, Config) ->
{document_root, DataDir},
{keep_alive, ?config(keep_alive, Config)},
{keep_alive_timeout, 360}
- | ConfHttpd]],
+ | ConfHttpd]],
{ok, Pid} = rpc:call(Node, inets, start, Conf),
Port = proplists:get_value(port, rpc:call(Node, httpd, info, [Pid])),
F = fun(File) ->
- lists:concat([Protocol,"://",Host,":",Port,"/",File])
+ lists:concat([Protocol, "://", Host, ":", Port, "/", File])
end,
- [{httpd_pid,Pid},{urlfun,F},{protocol,Protocol},{port,Port} | Config].
+ %% Return CT config (init_per_group result)
+ [{httpd_pid, Pid}, {urlfun, F}, {protocol, Protocol}, {port, Port} | Config].
-start_dummy("http"= Protocol, Config) ->
+start_http_test_lib_server("http"= Protocol, Config) ->
HTTPVersion = ?config(http_version, Config),
Node = ?config(server_node, Config),
%%DataDir= ?config(data_dir, Config),
@@ -522,8 +528,8 @@ start_dummy("http"= Protocol, Config) ->
Conf = [
%%{big, filename:join(DataDir, "1M_file")},
%%{small, filename:join(DataDir, "1k_file")},
- {big, {gen, crypto:strong_rand_bytes(1000000)}},
- {small, {gen, crypto:strong_rand_bytes(1000)}},
+ {big, {gen, crypto:strong_rand_bytes(1_000_000)}},
+ {small, {gen, crypto:strong_rand_bytes(1_000)}},
{http_version, HTTPVersion},
{keep_alive, ?config(keep_alive, Config)}
],
@@ -531,9 +537,10 @@ start_dummy("http"= Protocol, Config) ->
F = fun(File) ->
lists:concat([Protocol,"://",Host,":",Port,"/",File])
end,
- [{dummy_pid,Pid},{urlfun,F},{protocol, Protocol},{port,Port} | Config];
+ %% Return CT config (init_per_group result)
+ [{dummy_pid, Pid}, {urlfun, F}, {protocol, Protocol}, {port, Port} | Config];
-start_dummy("https" = Protocol, Config) ->
+start_http_test_lib_server("https" = Protocol, Config) ->
HTTPVersion = ?config(http_version, Config),
Node = ?config(server_node, Config),
%% DataDir= ?config(data_dir, Config),
@@ -542,8 +549,8 @@ start_dummy("https" = Protocol, Config) ->
Opts = [{active, true}, {nodelay, true} | SSLOpts],
Conf = [%%{big, filename:join(DataDir, "1M_file")},
%%{small, filename:join(DataDir, "1k_file")},
- {big, {gen, crypto:strong_rand_bytes(1000000)}},
- {small, {gen, crypto:strong_rand_bytes(1000)}},
+ {big, {gen, crypto:strong_rand_bytes(1_000_000)}},
+ {small, {gen, crypto:strong_rand_bytes(1_000)}},
{http_version, HTTPVersion},
{keep_alive, ?config(keep_alive, Config)}
],
@@ -560,7 +567,7 @@ start_nginx(Protocol, Config) ->
Host = ?config(server_host, Config),
Port = inet_port(node()),
- ConfFile = filename:join(PrivDir, "nginx.conf"),
+ ConfFile = filename:join(PrivDir, "nginx-" ++ Protocol ++ ".conf"),
nginx_conf(ConfFile, [{port, Port}, {protocol, Protocol} | Config]),
Cmd = "nginx -c " ++ ConfFile,
NginxPort = open_port({spawn, Cmd}, [{cd, DataDir}, stderr_to_stdout]),
@@ -598,12 +605,10 @@ stop_web_server(Group, Config) when Group == http_nginx;
stop_nginx(Config).
stop_dummy_server(Config) ->
- case ?config(dummy_pid, Config) of
- Pid when is_pid(Pid) ->
- exit(Pid, kill);
- _ ->
- ok
- end.
+ case ?config(dummy_pid, Config) of
+ Pid when is_pid(Pid) -> exit(Pid, kill);
+ _ -> ok
+ end.
%%--------------------------------------------------------------------
%% Misc ------------------------------------------------
@@ -623,8 +628,8 @@ http_version(_) ->
inet_port(Node) ->
{Port, Socket} = do_inet_port(Node),
- rpc:call(Node, gen_tcp, close, [Socket]),
- Port.
+ rpc:call(Node, gen_tcp, close, [Socket]),
+ Port.
do_inet_port(Node) ->
{ok, Socket} = rpc:call(Node, gen_tcp, listen, [0, [{reuseaddr, true}]]),
@@ -663,16 +668,16 @@ do_handle_request(CB, S, {gen, Data}, Opts, KeepAlive) ->
send_file(CB, S, {gen, Data}) ->
CB:send(S, Data);
- %% ChunkSize = 64*1024,
- %% case byte_size(Data) of
- %% N when N > ChunkSize ->
- %% <<Chunk:N/binary, Rest/binary>> = Data,
- %% %%{Chunk, Rest} = lists:split(N, Data),
- %% CB:send(S, Chunk),
- %% send_file(CB, S, {gen, Rest});
- %% _ ->
- %% CB:send(S, Data)
- %% end;
+%% ChunkSize = 64*1024,
+%% case byte_size(Data) of
+%% N when N > ChunkSize ->
+%% <<Chunk:N/binary, Rest/binary>> = Data,
+%% %%{Chunk, Rest} = lists:split(N, Data),
+%% CB:send(S, Chunk),
+%% send_file(CB, S, {gen, Rest});
+%% _ ->
+%% CB:send(S, Data)
+%% end;
send_file(CB, S, FileDesc) ->
case file:read(FileDesc, 64*1024) of
@@ -696,13 +701,11 @@ keep_alive(false) ->
handle_http_msg({_Method, RelUri, _, {_, _Headers}, _Body}, Socket, Conf) ->
handle_request(connect_cb(Socket), Socket, RelUri, Conf),
case proplists:get_value(keep_alive, Conf) of
- true ->
- <<>>;
- false ->
- stop
+ true -> <<>>;
+ false -> stop
end.
-%% arity has increased in later versions of OTP, not arity 3 anymore
+%% #ssl_socket{} arity has increased in later versions of OTP, not arity 3 anymore
connect_cb(SSLSocket) when element(1, SSLSocket) =:= sslsocket ->
ssl;
connect_cb(_) ->
@@ -752,7 +755,7 @@ wget(KeepAlive, URL, "https", ProtocolOpts) ->
wget_keep_alive(true)->
"";
wget_keep_alive(false) ->
- "--no-http-keep-alive ".
+ "--no-http-keep-alive ".
wget_cacert(ProtocolOpts) ->
"--ca-certificate=" ++ proplists:get_value(cacertfile, ProtocolOpts) ++ " ".
@@ -762,85 +765,110 @@ wget_cacert(ProtocolOpts) ->
%%--------------------------------------------------------------------
nginx_conf(ConfFile, Config) ->
Protocol = ?config(protocol, Config),
- file:write_file(ConfFile,
- [format_nginx_conf(nginx_global(Config)),
- format_nginx_conf(nginx_events(Config)),
- format_nginx_conf(nginx_http(Protocol, Config))]).
-
-format_nginx_conf(Directives) ->
- lists:map(fun({Key, Value}) ->
- io_lib:format("~s ~s;\n", [Key, Value]);
- (Str) ->
- Str
- end, Directives).
-
-
+ ConfIodata = [
+ format_nginx_conf(nginx_global(Config), 0),
+ format_nginx_conf(nginx_events_section(Config), 0),
+ format_nginx_conf(nginx_httpserver_section(Protocol, Config), 0)
+ ],
+ ok = file:write_file(ConfFile, ConfIodata).
+
+%% Output keys or string values, terminated with semicolon and newline
+format_nginx_conf(Directives, Indent) when is_list(Directives) ->
+ lists:map(fun(D) -> format_nginx_conf(D, Indent) end, Directives);
+format_nginx_conf({section, Name, SubDirectives}, Indent) ->
+ IndentStr = [$\s || _ <- lists:seq(1, Indent)],
+ [IndentStr, Name, " {\n",
+ format_nginx_conf(SubDirectives, Indent + 4),
+ IndentStr, "}\n"];
+format_nginx_conf({Key, Value}, Indent) ->
+ IndentStr = [$\s || _ <- lists:seq(1, Indent)],
+ [IndentStr, Key, " ", Value, ";\n"].
+
+%% Nginx global section
nginx_global(Config) ->
PrivDir = ?config(priv_dir, Config),
- [{"pid", filename:join(PrivDir, "nginx.pid")},
- {"error_log", filename:join(PrivDir, "nginx.pid")},
- {"worker_processes", "1"}].
-
-nginx_events(_Config) ->
- ["events {\n",
- {"worker_connections", "1024"},
- "\n}"
+ [
+ {"pid", filename:join(PrivDir, "nginx.pid")},
+ {"error_log", filename:join(PrivDir, "nginx.pid")},
+ {"worker_processes", "1"}
].
-nginx_http("http", Config) ->
+nginx_events_section(_Config) ->
+ {section, "events", [
+ {"worker_connections", "1024"}
+ ]}.
+
+nginx_httpserver_section("http", Config) ->
PrivDir = ?config(priv_dir, Config),
DataDir = ?config(data_dir, Config),
Port = ?config(port, Config),
- ["http {\n" |
- nginx_defaults(PrivDir) ++
- [" server {",
- {root, DataDir},
- {listen, integer_to_list(Port)},
- " location / {\n try_files $uri $uri/ /index.html;\n}"
- "}\n", "}\n"
- ]
- ];
-
-nginx_http("https", Config) ->
+ {section, "http", nginx_defaults(PrivDir) ++ [
+ {section, "server", [
+ {"root", DataDir},
+ {"listen", integer_to_list(Port)},
+ {section, "location /", [
+ {"try_files", "$uri $uri/ /index.html"}
+ ]}
+ ]}
+ ]};
+nginx_httpserver_section("https", Config) ->
PrivDir = ?config(priv_dir, Config),
DataDir = ?config(data_dir, Config),
Port = ?config(port, Config),
SSLOpts = ?config(server_verification_opts, Config),
Ciphers = proplists:get_value(ciphers, SSLOpts),
ReuseSession = ?config(reuse_sessions, Config),
- ["http {" |
- nginx_defaults(PrivDir) ++
- [" server {",
- {"root", DataDir},
- {"listen", integer_to_list(Port) ++ " ssl"},
- {"ssl_certificate", ?config(certfile, SSLOpts)},
- {"ssl_certificate_key", ?config(keyfile, SSLOpts)},
- {"ssl_protocols", "TLSv1 TLSv1.1 TLSv1.2"},
- {"ssl_ciphers", Ciphers},
- {"ssl_session_cache", nginx_reuse_session(ReuseSession)},
- " location / {\n try_files $uri $uri/ /index.html;\n}"
- "}\n", "}\n"
- ]
- ].
+ {section, "http", nginx_defaults(PrivDir) ++
+ [{section, "server", [
+ {"root", DataDir},
+ {"listen", integer_to_list(Port) ++ " ssl"},
+ {"ssl_certificate", ?config(certfile, SSLOpts)},
+ {"ssl_certificate_key", ?config(keyfile, SSLOpts)},
+ {"ssl_protocols", "TLSv1 TLSv1.1 TLSv1.2"},
+ %% Nginx sends this string to OpenSSL in its format described here:
+ %% https://docs.openssl.org/3.0/man1/openssl-ciphers/#cipher-list-format
+ %% Ciphers list separated by ":" is a valid format
+ {"ssl_ciphers", string:join(Ciphers, ":")},
+ {"ssl_prefer_server_ciphers", "on"},
+ {"ssl_session_cache", nginx_reuse_session(ReuseSession)},
+ {section, "location /", [
+ {"try_files", "$uri $uri/ /index.html"}
+ ]}
+ ]}
+ ]}.
+
+%% Searches for a file in several directories, and returns the first found file path, or 'not_found'
+find_file(_, []) -> not_found;
+find_file(FileName, [Dir | Rest]) ->
+ TryThisFile = filename:join(Dir, FileName),
+ case filelib:is_file(TryThisFile) of
+ true -> TryThisFile;
+ false -> find_file(FileName, Rest)
+ end.
nginx_defaults(PrivDir) ->
+ SearchDirs = ["/etc/nginx", "/opt/Homebrew/etc/nginx", "/usr/local/etc/nginx"],
+ MimeTypes = case find_file("mime.types", SearchDirs) of
+ not_found -> erlang:throw({file_not_found, "mime.types", SearchDirs});
+ Filename -> Filename
+ end,
[
%% Set temp and cache file options that will otherwise default to
%% restricted locations accessible only to root.
{"client_body_temp_path", filename:join(PrivDir, "client_body")},
- {"fastcgi_temp_path", filename:join(PrivDir, "fastcgi_temp")},
+ {"fastcgi_temp_path", filename:join(PrivDir, "fastcgi_temp")},
{"proxy_temp_path", filename:join(PrivDir, "proxy_temp")},
{"scgi_temp_path", filename:join(PrivDir, "scgi_temp")},
{"uwsgi_temp_path", filename:join(PrivDir, "uwsgi_temp_path")},
- {"access_log", filename:join(PrivDir, "access.log")},
- {"error_log", filename:join(PrivDir, "error.log")},
+ {"access_log", filename:join(PrivDir, "access.log")},
+ {"error_log", filename:join(PrivDir, "error.log")},
%% Standard options
{"sendfile", "on"},
{"tcp_nopush", "on"},
{"tcp_nodelay", "on"},
- {"keepalive_timeout", "360"},
+ {"keepalive_timeout", "360"},
{"types_hash_max_size", "2048"},
- {"include", "/etc/nginx/mime.types"},
+ {"include", MimeTypes},
{"default_type", "application/octet-stream"}
].
diff --git a/lib/inets/test/httpd_bench_certs.erl b/lib/inets/test/httpd_bench_certs.erl
index 0c3940bfe8..02ff246cac 100644
--- a/lib/inets/test/httpd_bench_certs.erl
+++ b/lib/inets/test/httpd_bench_certs.erl
@@ -21,7 +21,7 @@
-module(httpd_bench_certs).
-export([hardcode_rsa_key/1, choose_sha_function/0, der_to_pem/2, cert_entry/1,
- key_entry/1, ca_entries/1, make_cert_files/1]).
+ key_entry/1, ca_entries/1, make_cert_files/1]).
-include_lib("public_key/include/public_key.hrl").
@@ -29,19 +29,19 @@
make_cert_files(Dir) ->
#{server_config := ServerConf,
client_config := _} = public_key:pkix_test_data(
- #{server_chain =>
- #{
- root => [{key, hardcode_rsa_key(1)}, {digest, choose_sha_function()}],
- intermediates => [[{key, hardcode_rsa_key(2)}, {digest, choose_sha_function()}]],
- peer => [{key, hardcode_rsa_key(3)}, {digest, choose_sha_function()}]
- },
- client_chain =>
- #{
- root => [{key, hardcode_rsa_key(1)}, {digest, choose_sha_function()}],
- intermediates => [[{key, hardcode_rsa_key(3)}, {digest, choose_sha_function()}]],
- peer => [{key, hardcode_rsa_key(2)}, {digest, choose_sha_function()}]
- }
- }),
+ #{server_chain =>
+ #{
+ root => [{key, hardcode_rsa_key(1)}, {digest, choose_sha_function()}],
+ intermediates => [[{key, hardcode_rsa_key(2)}, {digest, choose_sha_function()}]],
+ peer => [{key, hardcode_rsa_key(3)}, {digest, choose_sha_function()}]
+ },
+ client_chain =>
+ #{
+ root => [{key, hardcode_rsa_key(1)}, {digest, choose_sha_function()}],
+ intermediates => [[{key, hardcode_rsa_key(3)}, {digest, choose_sha_function()}]],
+ peer => [{key, hardcode_rsa_key(2)}, {digest, choose_sha_function()}]
+ }
+ }),
CaCertFile = filename:join([Dir, "server-cacerts.pem"]),
CertFile = filename:join([Dir, "server-cert.pem"]),
@@ -90,39 +90,39 @@ ca_entries(CAs) ->
hardcode_rsa_key(1) ->
#'RSAPrivateKey'{
- version = 'two-prime',
- modulus = 23995666614853919027835084074500048897452890537492185072956789802729257783422306095699263934587064480357348855732149402060270996295002843755712064937715826848741191927820899197493902093529581182351132392364214171173881547273475904587683433713767834856230531387991145055273426806331200574039205571401702219159773947658558490957010003143162250693492642996408861265758000254664396313741422909188635443907373976005987612936763564996605457102336549804831742940035613780926178523017685712710473543251580072875247250504243621640157403744718833162626193206685233710319205099867303242759099560438381385658382486042995679707669,
- publicExponent = 17,
- privateExponent = 11292078406990079542510627799764728892919007311761028269626724613049062486316379339152594792746853873109340637991599718616598115903530750002688030558925094987642913848386305504703012749896273497577003478759630198199473669305165131570674557041773098755873191241407597673069847908861741446606684974777271632545629600685952292605647052193819136445675100211504432575554351515262198132231537860917084269870590492135731720141577986787033006338680118008484613510063003323516659048210893001173583018220214626635609151105287049126443102976056146630518124476470236027123782297108342869049542023328584384300970694412006494684657,
- prime1 = 169371138592582642967021557955633494538845517070305333860805485424261447791289944610138334410987654265476540480228705481960508520379619587635662291973699651583489223555422528867090299996446070521801757353675026048850480903160224210802452555900007597342687137394192939372218903554801584969667104937092080815197,
- prime2 = 141675062317286527042995673340952251894209529891636708844197799307963834958115010129693036021381525952081167155681637592199810112261679449166276939178032066869788822014115556349519329537177920752776047051833616197615329017439297361972726138285974555338480581117881706656603857310337984049152655480389797687577,
- exponent1 = 119556097830058336212015217380447172615655659108450823901745048534772786676204666783627059584226579481512852103690850928442711896738555003036938088452023283470698275450886490965004917644550167427154181661417665446247398284583687678213495921811770068712485038160606780733330990744565824684470897602653233516609,
- exponent2 = 41669135975672507953822256864985956439473391144599032012999352737636422046504414744027363535700448809435637398729893409470532385959317485048904982111185902020526124121798693043976273393287623750816484427009887116945685005129205106462566511260580751570141347387612266663707016855981760014456663376585234613993,
- coefficient = 76837684977089699359024365285678488693966186052769523357232308621548155587515525857011429902602352279058920284048929101483304120686557782043616693940283344235057989514310975192908256494992960578961614059245280827077951132083993754797053182279229469590276271658395444955906108899267024101096069475145863928441,
- otherPrimeInfos = asn1_NOVALUE};
+ version = 'two-prime',
+ modulus = 23995666614853919027835084074500048897452890537492185072956789802729257783422306095699263934587064480357348855732149402060270996295002843755712064937715826848741191927820899197493902093529581182351132392364214171173881547273475904587683433713767834856230531387991145055273426806331200574039205571401702219159773947658558490957010003143162250693492642996408861265758000254664396313741422909188635443907373976005987612936763564996605457102336549804831742940035613780926178523017685712710473543251580072875247250504243621640157403744718833162626193206685233710319205099867303242759099560438381385658382486042995679707669,
+ publicExponent = 17,
+ privateExponent = 11292078406990079542510627799764728892919007311761028269626724613049062486316379339152594792746853873109340637991599718616598115903530750002688030558925094987642913848386305504703012749896273497577003478759630198199473669305165131570674557041773098755873191241407597673069847908861741446606684974777271632545629600685952292605647052193819136445675100211504432575554351515262198132231537860917084269870590492135731720141577986787033006338680118008484613510063003323516659048210893001173583018220214626635609151105287049126443102976056146630518124476470236027123782297108342869049542023328584384300970694412006494684657,
+ prime1 = 169371138592582642967021557955633494538845517070305333860805485424261447791289944610138334410987654265476540480228705481960508520379619587635662291973699651583489223555422528867090299996446070521801757353675026048850480903160224210802452555900007597342687137394192939372218903554801584969667104937092080815197,
+ prime2 = 141675062317286527042995673340952251894209529891636708844197799307963834958115010129693036021381525952081167155681637592199810112261679449166276939178032066869788822014115556349519329537177920752776047051833616197615329017439297361972726138285974555338480581117881706656603857310337984049152655480389797687577,
+ exponent1 = 119556097830058336212015217380447172615655659108450823901745048534772786676204666783627059584226579481512852103690850928442711896738555003036938088452023283470698275450886490965004917644550167427154181661417665446247398284583687678213495921811770068712485038160606780733330990744565824684470897602653233516609,
+ exponent2 = 41669135975672507953822256864985956439473391144599032012999352737636422046504414744027363535700448809435637398729893409470532385959317485048904982111185902020526124121798693043976273393287623750816484427009887116945685005129205106462566511260580751570141347387612266663707016855981760014456663376585234613993,
+ coefficient = 76837684977089699359024365285678488693966186052769523357232308621548155587515525857011429902602352279058920284048929101483304120686557782043616693940283344235057989514310975192908256494992960578961614059245280827077951132083993754797053182279229469590276271658395444955906108899267024101096069475145863928441,
+ otherPrimeInfos = asn1_NOVALUE};
hardcode_rsa_key(2) ->
#'RSAPrivateKey'{
- version = 'two-prime',
- modulus = 21343679768589700771839799834197557895311746244621307033143551583788179817796325695589283169969489517156931770973490560582341832744966317712674900833543896521418422508485833901274928542544381247956820115082240721897193055368570146764204557110415281995205343662628196075590438954399631753508888358737971039058298703003743872818150364935790613286541190842600031570570099801682794056444451081563070538409720109449780410837763602317050353477918147758267825417201591905091231778937606362076129350476690460157227101296599527319242747999737801698427160817755293383890373574621116766934110792127739174475029121017282777887777,
- publicExponent = 17,
- privateExponent = 18832658619343853622211588088997845201745658451136447382185486691577805721584993260814073385267196632785528033211903435807948675951440868570007265441362261636545666919252206383477878125774454042314841278013741813438699754736973658909592256273895837054592950290554290654932740253882028017801960316533503857992358685308186680144968293076156011747178275038098868263178095174694099811498968993700538293188879611375604635940554394589807673542938082281934965292051746326331046224291377703201248790910007232374006151098976879987912446997911775904329728563222485791845480864283470332826504617837402078265424772379987120023773,
- prime1 = 146807662748886761089048448970170315054939768171908279335181627815919052012991509112344782731265837727551849787333310044397991034789843793140419387740928103541736452627413492093463231242466386868459637115999163097726153692593711599245170083315894262154838974616739452594203727376460632750934355508361223110419,
- prime2 = 145385325050081892763917667176962991350872697916072592966410309213561884732628046256782356731057378829876640317801978404203665761131810712267778698468684631707642938779964806354584156202882543264893826268426566901882487709510744074274965029453915224310656287149777603803201831202222853023280023478269485417083,
- exponent1 = 51814469205489445090252393754177758254684624060673510353593515699736136004585238510239335081623236845018299924941168250963996835808180162284853901555621683602965806809675350150634081614988136541809283687999704622726877773856604093851236499993845033701707873394143336209718962603456693912094478414715725803677,
- exponent2 = 51312467664734785681382706062457526359131540440966797517556579722433606376221663384746714140373192528191755406283051201483646739222992016094510128871300458249756331334105225772206172777487956446433115153562317730076172132768497908567634716277852432109643395464627389577600646306666889302334125933506877206029,
- coefficient = 30504662229874176232343608562807118278893368758027179776313787938167236952567905398252901545019583024374163153775359371298239336609182249464886717948407152570850677549297935773605431024166978281486607154204888016179709037883348099374995148481968169438302456074511782717758301581202874062062542434218011141540,
- otherPrimeInfos = asn1_NOVALUE};
+ version = 'two-prime',
+ modulus = 21343679768589700771839799834197557895311746244621307033143551583788179817796325695589283169969489517156931770973490560582341832744966317712674900833543896521418422508485833901274928542544381247956820115082240721897193055368570146764204557110415281995205343662628196075590438954399631753508888358737971039058298703003743872818150364935790613286541190842600031570570099801682794056444451081563070538409720109449780410837763602317050353477918147758267825417201591905091231778937606362076129350476690460157227101296599527319242747999737801698427160817755293383890373574621116766934110792127739174475029121017282777887777,
+ publicExponent = 17,
+ privateExponent = 18832658619343853622211588088997845201745658451136447382185486691577805721584993260814073385267196632785528033211903435807948675951440868570007265441362261636545666919252206383477878125774454042314841278013741813438699754736973658909592256273895837054592950290554290654932740253882028017801960316533503857992358685308186680144968293076156011747178275038098868263178095174694099811498968993700538293188879611375604635940554394589807673542938082281934965292051746326331046224291377703201248790910007232374006151098976879987912446997911775904329728563222485791845480864283470332826504617837402078265424772379987120023773,
+ prime1 = 146807662748886761089048448970170315054939768171908279335181627815919052012991509112344782731265837727551849787333310044397991034789843793140419387740928103541736452627413492093463231242466386868459637115999163097726153692593711599245170083315894262154838974616739452594203727376460632750934355508361223110419,
+ prime2 = 145385325050081892763917667176962991350872697916072592966410309213561884732628046256782356731057378829876640317801978404203665761131810712267778698468684631707642938779964806354584156202882543264893826268426566901882487709510744074274965029453915224310656287149777603803201831202222853023280023478269485417083,
+ exponent1 = 51814469205489445090252393754177758254684624060673510353593515699736136004585238510239335081623236845018299924941168250963996835808180162284853901555621683602965806809675350150634081614988136541809283687999704622726877773856604093851236499993845033701707873394143336209718962603456693912094478414715725803677,
+ exponent2 = 51312467664734785681382706062457526359131540440966797517556579722433606376221663384746714140373192528191755406283051201483646739222992016094510128871300458249756331334105225772206172777487956446433115153562317730076172132768497908567634716277852432109643395464627389577600646306666889302334125933506877206029,
+ coefficient = 30504662229874176232343608562807118278893368758027179776313787938167236952567905398252901545019583024374163153775359371298239336609182249464886717948407152570850677549297935773605431024166978281486607154204888016179709037883348099374995148481968169438302456074511782717758301581202874062062542434218011141540,
+ otherPrimeInfos = asn1_NOVALUE};
hardcode_rsa_key(3) ->
#'RSAPrivateKey'{
- version = 'two-prime',
- modulus = 25089040456112869869472694987833070928503703615633809313972554887193090845137746668197820419383804666271752525807484521370419854590682661809972833718476098189250708650325307850184923546875260207894844301992963978994451844985784504212035958130279304082438876764367292331581532569155681984449177635856426023931875082020262146075451989132180409962870105455517050416234175675478291534563995772675388370042873175344937421148321291640477650173765084699931690748536036544188863178325887393475703801759010864779559318631816411493486934507417755306337476945299570726975433250753415110141783026008347194577506976486290259135429,
- publicExponent = 17,
- privateExponent = 8854955455098659953931539407470495621824836570223697404931489960185796768872145882893348383311931058684147950284994536954265831032005645344696294253579799360912014817761873358888796545955974191021709753644575521998041827642041589721895044045980930852625485916835514940558187965584358347452650930302268008446431977397918214293502821599497633970075862760001650736520566952260001423171553461362588848929781360590057040212831994258783694027013289053834376791974167294527043946669963760259975273650548116897900664646809242902841107022557239712438496384819445301703021164043324282687280801738470244471443835900160721870265,
- prime1 = 171641816401041100605063917111691927706183918906535463031548413586331728772311589438043965564336865070070922328258143588739626712299625805650832695450270566547004154065267940032684307994238248203186986569945677705100224518137694769557564475390859269797990555863306972197736879644001860925483629009305104925823,
- prime2 = 146170909759497809922264016492088453282310383272504533061020897155289106805616042710009332510822455269704884883705830985184223718261139908416790475825625309815234508695722132706422885088219618698987115562577878897003573425367881351537506046253616435685549396767356003663417208105346307649599145759863108910523,
- exponent1 = 60579464612132153154728441333538327425711971378777222246428851853999433684345266860486105493295364142377972586444050678378691780811632637288529186629507258781295583787741625893888579292084087601124818789392592131211843947578009918667375697196773859928702549128225990187436545756706539150170692591519448797349,
- exponent2 = 137572620950115585809189662580789132500998007785886619351549079675566218169991569609420548245479957900898715184664311515467504676010484619686391036071176762179044243478326713135456833024206699951987873470661533079532774988581535389682358631768109586527575902839864474036157372334443583670210960715165278974609,
- coefficient = 15068630434698373319269196003209754243798959461311186548759287649485250508074064775263867418602372588394608558985183294561315208336731894947137343239541687540387209051236354318837334154993136528453613256169847839789803932725339395739618592522865156272771578671216082079933457043120923342632744996962853951612,
- otherPrimeInfos = asn1_NOVALUE}.
+ version = 'two-prime',
+ modulus = 25089040456112869869472694987833070928503703615633809313972554887193090845137746668197820419383804666271752525807484521370419854590682661809972833718476098189250708650325307850184923546875260207894844301992963978994451844985784504212035958130279304082438876764367292331581532569155681984449177635856426023931875082020262146075451989132180409962870105455517050416234175675478291534563995772675388370042873175344937421148321291640477650173765084699931690748536036544188863178325887393475703801759010864779559318631816411493486934507417755306337476945299570726975433250753415110141783026008347194577506976486290259135429,
+ publicExponent = 17,
+ privateExponent = 8854955455098659953931539407470495621824836570223697404931489960185796768872145882893348383311931058684147950284994536954265831032005645344696294253579799360912014817761873358888796545955974191021709753644575521998041827642041589721895044045980930852625485916835514940558187965584358347452650930302268008446431977397918214293502821599497633970075862760001650736520566952260001423171553461362588848929781360590057040212831994258783694027013289053834376791974167294527043946669963760259975273650548116897900664646809242902841107022557239712438496384819445301703021164043324282687280801738470244471443835900160721870265,
+ prime1 = 171641816401041100605063917111691927706183918906535463031548413586331728772311589438043965564336865070070922328258143588739626712299625805650832695450270566547004154065267940032684307994238248203186986569945677705100224518137694769557564475390859269797990555863306972197736879644001860925483629009305104925823,
+ prime2 = 146170909759497809922264016492088453282310383272504533061020897155289106805616042710009332510822455269704884883705830985184223718261139908416790475825625309815234508695722132706422885088219618698987115562577878897003573425367881351537506046253616435685549396767356003663417208105346307649599145759863108910523,
+ exponent1 = 60579464612132153154728441333538327425711971378777222246428851853999433684345266860486105493295364142377972586444050678378691780811632637288529186629507258781295583787741625893888579292084087601124818789392592131211843947578009918667375697196773859928702549128225990187436545756706539150170692591519448797349,
+ exponent2 = 137572620950115585809189662580789132500998007785886619351549079675566218169991569609420548245479957900898715184664311515467504676010484619686391036071176762179044243478326713135456833024206699951987873470661533079532774988581535389682358631768109586527575902839864474036157372334443583670210960715165278974609,
+ coefficient = 15068630434698373319269196003209754243798959461311186548759287649485250508074064775263867418602372588394608558985183294561315208336731894947137343239541687540387209051236354318837334154993136528453613256169847839789803932725339395739618592522865156272771578671216082079933457043120923342632744996962853951612,
+ otherPrimeInfos = asn1_NOVALUE}.
--
2.51.0