Skip to content

Commit a730c16

Browse files
committed
Merge branch 'lars/test_case_bugs'
* lars/test_case_bugs: Fix failing test cases
2 parents fc1cb16 + 68ecbe2 commit a730c16

File tree

6 files changed

+204
-143
lines changed

6 files changed

+204
-143
lines changed

lib/orber/test/Makefile

+1
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ IDL_FILES = \
4848
IDLOUTDIR = idl_output
4949

5050
MODULES = \
51+
cert_gen \
5152
cdrcoding_11_SUITE \
5253
cdrcoding_10_SUITE \
5354
cdrcoding_12_SUITE \

lib/orber/test/cert_gen.erl

+153
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,153 @@
1+
%%
2+
%% %CopyrightBegin%
3+
%%
4+
%% Copyright Ericsson AB 2017-2023. All Rights Reserved.
5+
%%
6+
%% Licensed under the Apache License, Version 2.0 (the "License");
7+
%% you may not use this file except in compliance with the License.
8+
%% You may obtain a copy of the License at
9+
%%
10+
%% http://www.apache.org/licenses/LICENSE-2.0
11+
%%
12+
%% Unless required by applicable law or agreed to in writing, software
13+
%% distributed under the License is distributed on an "AS IS" BASIS,
14+
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15+
%% See the License for the specific language governing permissions and
16+
%% limitations under the License.
17+
%%
18+
%% %CopyrightEnd%
19+
%%
20+
21+
%%
22+
23+
-module(cert_gen).
24+
25+
-include_lib("public_key/include/public_key.hrl").
26+
27+
-export([cert_key_gen/0, cert_key_gen/1, extensions/1, gen_pem_config_files/3]).
28+
29+
-define(DEFAULT_CURVE, secp256r1).
30+
31+
cert_key_gen() ->
32+
cert_key_gen(".").
33+
34+
cert_key_gen(Path) ->
35+
CertChainConf = #{server_chain =>
36+
#{root => [{digest, sha256}, {key,hardcode_rsa_key(1)}],
37+
peer => [{digest, sha256}, {key,hardcode_rsa_key(2)}]},
38+
client_chain =>
39+
#{root => [{digest, sha256}, {key,hardcode_rsa_key(1)}],
40+
peer => [{digest, sha256}, {key,hardcode_rsa_key(2)}]}},
41+
GenCertData = public_key:pkix_test_data(CertChainConf),
42+
%io:format("GenCertData: ~p\n", [GenCertData]),
43+
gen_pem_config_files(GenCertData, Path ++ "/xcmtest", Path ++ "/xcmtest").
44+
45+
46+
gen_pem_config_files(#{server_config := ServerConf,
47+
client_config := ClientConf}, ClientBase, ServerBase) ->
48+
49+
ServerCaCertFile = ServerBase ++ "_server_cacerts.pem",
50+
ServerCertFile = ServerBase ++ "_server_cert.pem",
51+
ServerKeyFile = ServerBase ++ "_server_key.pem",
52+
53+
ClientCaCertFile = ClientBase ++ "_client_cacerts.pem",
54+
ClientCertFile = ClientBase ++ "_client_cert.pem",
55+
ClientKeyFile = ClientBase ++ "_client_key.pem",
56+
57+
do_gen_pem_config_files(ServerConf,
58+
ServerCertFile,
59+
ServerKeyFile,
60+
ServerCaCertFile),
61+
do_gen_pem_config_files(ClientConf,
62+
ClientCertFile,
63+
ClientKeyFile,
64+
ClientCaCertFile),
65+
[{server_config, [{certfile, ServerCertFile},
66+
{keyfile, ServerKeyFile}, {cacertfile, ServerCaCertFile}]},
67+
{client_config, [{certfile, ClientCertFile},
68+
{keyfile, ClientKeyFile}, {cacertfile, ClientCaCertFile}]}].
69+
extensions(Exts) ->
70+
[extension(Ext) || Ext <- Exts].
71+
72+
73+
do_gen_pem_config_files(Config, CertFile, KeyFile, CAFile) ->
74+
CAs = proplists:get_value(cacerts, Config),
75+
Cert = proplists:get_value(cert, Config),
76+
Key = proplists:get_value(key, Config),
77+
der_to_pem(CertFile, [cert_entry(Cert)]),
78+
der_to_pem(KeyFile, [key_entry(Key)]),
79+
der_to_pem(CAFile, ca_entries(CAs)).
80+
81+
cert_entry(Cert) ->
82+
{'Certificate', Cert, not_encrypted}.
83+
84+
key_entry({'RSAPrivateKey', DERKey}) ->
85+
{'RSAPrivateKey', DERKey, not_encrypted};
86+
key_entry({'DSAPrivateKey', DERKey}) ->
87+
{'DSAPrivateKey', DERKey, not_encrypted};
88+
key_entry({'ECPrivateKey', DERKey}) ->
89+
{'ECPrivateKey', DERKey, not_encrypted}.
90+
91+
ca_entries(CAs) ->
92+
[{'Certificate', CACert, not_encrypted} || CACert <- CAs].
93+
94+
extension({_, undefined}) ->
95+
[];
96+
extension({basic_constraints, Data}) ->
97+
case Data of
98+
default ->
99+
#'Extension'{extnID = ?'id-ce-basicConstraints',
100+
extnValue = #'BasicConstraints'{cA=true},
101+
critical=true};
102+
false ->
103+
[];
104+
Len when is_integer(Len) ->
105+
#'Extension'{extnID = ?'id-ce-basicConstraints',
106+
extnValue = #'BasicConstraints'{cA=true, pathLenConstraint = Len},
107+
critical = true};
108+
_ ->
109+
#'Extension'{extnID = ?'id-ce-basicConstraints',
110+
extnValue = Data}
111+
end;
112+
extension({key_usage, Value}) ->
113+
#'Extension'{extnID = ?'id-ce-keyUsage',
114+
extnValue = Value,
115+
critical = false};
116+
extension({subject_alt, Hostname}) ->
117+
#'Extension'{extnID = ?'id-ce-subjectAltName',
118+
extnValue = [{dNSName, Hostname}],
119+
critical = false};
120+
extension({Id, Data, Critical}) ->
121+
#'Extension'{extnID = Id, extnValue = Data, critical = Critical}.
122+
123+
der_to_pem(File, Entries) ->
124+
%%io:format("File: ~p\nEntries: ~p\n", [File, Entries]),
125+
PemBin = public_key:pem_encode(Entries),
126+
file:write_file(File, PemBin).
127+
128+
129+
hardcode_rsa_key(1) ->
130+
#'RSAPrivateKey'{
131+
version = 'two-prime',
132+
modulus = 23995666614853919027835084074500048897452890537492185072956789802729257783422306095699263934587064480357348855732149402060270996295002843755712064937715826848741191927820899197493902093529581182351132392364214171173881547273475904587683433713767834856230531387991145055273426806331200574039205571401702219159773947658558490957010003143162250693492642996408861265758000254664396313741422909188635443907373976005987612936763564996605457102336549804831742940035613780926178523017685712710473543251580072875247250504243621640157403744718833162626193206685233710319205099867303242759099560438381385658382486042995679707669,
133+
publicExponent = 17,
134+
privateExponent = 11292078406990079542510627799764728892919007311761028269626724613049062486316379339152594792746853873109340637991599718616598115903530750002688030558925094987642913848386305504703012749896273497577003478759630198199473669305165131570674557041773098755873191241407597673069847908861741446606684974777271632545629600685952292605647052193819136445675100211504432575554351515262198132231537860917084269870590492135731720141577986787033006338680118008484613510063003323516659048210893001173583018220214626635609151105287049126443102976056146630518124476470236027123782297108342869049542023328584384300970694412006494684657,
135+
prime1 = 169371138592582642967021557955633494538845517070305333860805485424261447791289944610138334410987654265476540480228705481960508520379619587635662291973699651583489223555422528867090299996446070521801757353675026048850480903160224210802452555900007597342687137394192939372218903554801584969667104937092080815197,
136+
prime2 = 141675062317286527042995673340952251894209529891636708844197799307963834958115010129693036021381525952081167155681637592199810112261679449166276939178032066869788822014115556349519329537177920752776047051833616197615329017439297361972726138285974555338480581117881706656603857310337984049152655480389797687577,
137+
exponent1 = 119556097830058336212015217380447172615655659108450823901745048534772786676204666783627059584226579481512852103690850928442711896738555003036938088452023283470698275450886490965004917644550167427154181661417665446247398284583687678213495921811770068712485038160606780733330990744565824684470897602653233516609,
138+
exponent2 = 41669135975672507953822256864985956439473391144599032012999352737636422046504414744027363535700448809435637398729893409470532385959317485048904982111185902020526124121798693043976273393287623750816484427009887116945685005129205106462566511260580751570141347387612266663707016855981760014456663376585234613993,
139+
coefficient = 76837684977089699359024365285678488693966186052769523357232308621548155587515525857011429902602352279058920284048929101483304120686557782043616693940283344235057989514310975192908256494992960578961614059245280827077951132083993754797053182279229469590276271658395444955906108899267024101096069475145863928441,
140+
otherPrimeInfos = asn1_NOVALUE};
141+
142+
hardcode_rsa_key(2) ->
143+
#'RSAPrivateKey'{
144+
version = 'two-prime',
145+
modulus = 25089040456112869869472694987833070928503703615633809313972554887193090845137746668197820419383804666271752525807484521370419854590682661809972833718476098189250708650325307850184923546875260207894844301992963978994451844985784504212035958130279304082438876764367292331581532569155681984449177635856426023931875082020262146075451989132180409962870105455517050416234175675478291534563995772675388370042873175344937421148321291640477650173765084699931690748536036544188863178325887393475703801759010864779559318631816411493486934507417755306337476945299570726975433250753415110141783026008347194577506976486290259135429,
146+
publicExponent = 17,
147+
privateExponent = 8854955455098659953931539407470495621824836570223697404931489960185796768872145882893348383311931058684147950284994536954265831032005645344696294253579799360912014817761873358888796545955974191021709753644575521998041827642041589721895044045980930852625485916835514940558187965584358347452650930302268008446431977397918214293502821599497633970075862760001650736520566952260001423171553461362588848929781360590057040212831994258783694027013289053834376791974167294527043946669963760259975273650548116897900664646809242902841107022557239712438496384819445301703021164043324282687280801738470244471443835900160721870265,
148+
prime1 = 171641816401041100605063917111691927706183918906535463031548413586331728772311589438043965564336865070070922328258143588739626712299625805650832695450270566547004154065267940032684307994238248203186986569945677705100224518137694769557564475390859269797990555863306972197736879644001860925483629009305104925823,
149+
prime2 =146170909759497809922264016492088453282310383272504533061020897155289106805616042710009332510822455269704884883705830985184223718261139908416790475825625309815234508695722132706422885088219618698987115562577878897003573425367881351537506046253616435685549396767356003663417208105346307649599145759863108910523,
150+
exponent1 = 60579464612132153154728441333538327425711971378777222246428851853999433684345266860486105493295364142377972586444050678378691780811632637288529186629507258781295583787741625893888579292084087601124818789392592131211843947578009918667375697196773859928702549128225990187436545756706539150170692591519448797349,
151+
exponent2 = 137572620950115585809189662580789132500998007785886619351549079675566218169991569609420548245479957900898715184664311515467504676010484619686391036071176762179044243478326713135456833024206699951987873470661533079532774988581535389682358631768109586527575902839864474036157372334443583670210960715165278974609,
152+
coefficient = 15068630434698373319269196003209754243798959461311186548759287649485250508074064775263867418602372588394608558985183294561315208336731894947137343239541687540387209051236354318837334154993136528453613256169847839789803932725339395739618592522865156272771578671216082079933457043120923342632744996962853951612,
153+
otherPrimeInfos = asn1_NOVALUE}.

lib/orber/test/csiv2_SUITE.erl

+3-1
Original file line numberDiff line numberDiff line change
@@ -361,9 +361,11 @@ end_per_testcase(_Case, Config) ->
361361
ok.
362362

363363
init_per_suite(Config) ->
364+
Dir = filename:dirname(code:which(?MODULE)),
365+
cert_gen:cert_key_gen(Dir), %% Generate cert and keyfiles
364366
try crypto:start() of
365367
ok ->
366-
case orber_test_lib:ssl_version() of
368+
case orber_test_lib:ssl_available() of
367369
no_ssl ->
368370
{skip, "SSL is not installed!"};
369371
_ ->

lib/orber/test/multi_ORB_SUITE.erl

+3-105
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,6 @@
5555
init_per_suite/1, end_per_suite/1, basic_PI_api/1, multi_orber_api/1,
5656
init_per_testcase/2, end_per_testcase/2, multi_pseudo_orber_api/1,
5757
light_orber_api/1, light_orber2_api/1,
58-
ssl_1_multi_orber_api/1, ssl_2_multi_orber_api/1, ssl_reconfigure_api/1,
5958
iiop_timeout_api/1, iiop_timeout_added_api/1, setup_connection_timeout_api/1,
6059
setup_multi_connection_timeout_api/1, setup_multi_connection_timeout_random_api/1,
6160
setup_multi_connection_timeout_attempts_api/1,
@@ -139,28 +138,21 @@ cases() ->
139138
ssl_2_multi_orber_generation_3_api,
140139
ssl_reconfigure_generation_3_api].
141140

142-
% ssl_1_multi_orber_api,ssl_2_multi_orber_api,ssl_reconfigure_api,
143-
144141
%%-----------------------------------------------------------------
145142
%% Init and cleanup functions.
146143
%%-----------------------------------------------------------------
147-
init_per_testcase(TC,Config)
148-
when TC =:= ssl_1_multi_orber_api;
149-
TC =:= ssl_2_multi_orber_api;
150-
TC =:= ssl_reconfigure_api ->
151-
init_ssl(Config);
152144
init_per_testcase(TC,Config)
153145
when TC =:= ssl_1_multi_orber_generation_3_api;
154146
TC =:= ssl_2_multi_orber_generation_3_api;
155147
TC =:= ssl_reconfigure_generation_3_api ->
156-
init_ssl_3(Config);
148+
init_ssl(Config);
157149
init_per_testcase(_Case, Config) ->
158150
init_all(Config).
159151

160152
init_ssl(Config) ->
161-
case proplists:get_value(crypto_started, Config) of
153+
case proplists:get_value(crypto_started, Config) of
162154
true ->
163-
case orber_test_lib:ssl_version() of
155+
case orber_test_lib:ssl_available() of
164156
no_ssl ->
165157
{skip, "SSL is not installed!"};
166158
_ ->
@@ -170,21 +162,6 @@ init_ssl(Config) ->
170162
{skip, "Crypto did not start"}
171163
end.
172164

173-
init_ssl_3(Config) ->
174-
case proplists:get_value(crypto_started, Config) of
175-
true ->
176-
case orber_test_lib:ssl_version() of
177-
3 ->
178-
init_all(Config);
179-
2 ->
180-
{skip, "Could not find the correct SSL version!"};
181-
no_ssl ->
182-
{skip, "SSL is not installed!"}
183-
end;
184-
false ->
185-
{skip, "Crypto did not start"}
186-
end.
187-
188165
init_all(Config) ->
189166
Path = code:which(?MODULE),
190167
code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
@@ -1554,19 +1531,6 @@ basic_PI_api(_Config) ->
15541531
%%-----------------------------------------------------------------
15551532
%% API tests for ORB to ORB, ssl security depth 1
15561533
%%-----------------------------------------------------------------
1557-
1558-
%% SECURE MULTI ORB API tests (SSL depth 1)
1559-
%% This case set up two secure orbs and test if they can
1560-
%% communicate. The case also test to access one of the
1561-
%% secure orbs which must raise a NO_PERMISSION exception.
1562-
ssl_1_multi_orber_api(_Config) ->
1563-
ServerOptions = orber_test_lib:get_options_old(iiop_ssl, server,
1564-
1, [{iiop_ssl_port, 0}]),
1565-
ClientOptions = orber_test_lib:get_options_old(iiop_ssl, client,
1566-
1, [{iiop_ssl_port, 0}]),
1567-
ssl_suite(ServerOptions, ClientOptions).
1568-
1569-
15701534
%% SECURE MULTI ORB API tests (SSL depth 1)
15711535
%% This case set up two secure orbs and test if they can
15721536
%% communicate. The case also test to access one of the
@@ -1589,14 +1553,6 @@ ssl_1_multi_orber_generation_3_api(_Config) ->
15891553
%% These case set up two secure orbs and test if they can
15901554
%% communicate. They also test to access one of the
15911555
%% secure orbs which must raise a NO_PERMISSION exception.
1592-
ssl_2_multi_orber_api(_Config) ->
1593-
1594-
ServerOptions = orber_test_lib:get_options_old(iiop_ssl, server,
1595-
2, [{iiop_ssl_port, 0}]),
1596-
ClientOptions = orber_test_lib:get_options_old(iiop_ssl, client,
1597-
2, [{iiop_ssl_port, 0}]),
1598-
ssl_suite(ServerOptions, ClientOptions).
1599-
16001556
ssl_2_multi_orber_generation_3_api(_Config) ->
16011557

16021558
ServerOptions = orber_test_lib:get_options(iiop_ssl, server,
@@ -1609,71 +1565,13 @@ ssl_2_multi_orber_generation_3_api(_Config) ->
16091565
%%-----------------------------------------------------------------
16101566
%% API tests for ORB to ORB, ssl security depth 2
16111567
%%-----------------------------------------------------------------
1612-
16131568
%% SECURE MULTI ORB API tests (SSL depth 2)
16141569
%% These case set up two secure orbs and test if they can
16151570
%% communicate. They also test to access one of the
16161571
%% secure orbs which must raise a NO_PERMISSION exception.
1617-
ssl_reconfigure_api(_Config) ->
1618-
ssl_reconfigure_old([]).
1619-
1620-
1621-
% ssl_reconfigure_generation_3_api_old(_Config) ->
1622-
% ssl_reconfigure_old([{ssl_generation, 3}]).
1623-
1624-
ssl_reconfigure_old(ExtraSSLOptions) ->
1625-
1626-
IP = orber_test_lib:get_host(),
1627-
Loopback = orber_test_lib:get_loopback_interface(),
1628-
{ok, ServerNode, _ServerHost} =
1629-
?match({ok,_,_},
1630-
orber_test_lib:js_node([{iiop_port, 0},
1631-
{flags, ?ORB_ENV_LOCAL_INTERFACE},
1632-
{ip_address, IP}|ExtraSSLOptions])),
1633-
orber_test_lib:remote_apply(ServerNode, ssl, start, []),
1634-
orber_test_lib:remote_apply(ServerNode, crypto, start, []),
1635-
?match(ok, orber_test_lib:remote_apply(ServerNode, orber_test_lib,
1636-
install_test_data,
1637-
[ssl])),
1638-
?match({ok, _},
1639-
orber_test_lib:remote_apply(ServerNode, orber,
1640-
add_listen_interface,
1641-
[Loopback, normal, [{iiop_port, 5648},
1642-
{iiop_ssl_port, 5649},
1643-
{interceptors, {native, [orber_iiop_tracer_silent]}}|ExtraSSLOptions]])),
1644-
ServerOptions = orber_test_lib:get_options_old(iiop_ssl, server,
1645-
2, [{flags, ?ORB_ENV_LOCAL_INTERFACE},
1646-
{iiop_port, 5648},
1647-
{iiop_ssl_port, 5649},
1648-
{interceptors, {native, [orber_iiop_tracer_silent]}}|ExtraSSLOptions]),
1649-
?match({ok, _},
1650-
orber_test_lib:remote_apply(ServerNode, orber,
1651-
add_listen_interface,
1652-
[Loopback, ssl, ServerOptions])),
1653-
1654-
ClientOptions = orber_test_lib:get_options_old(iiop_ssl, client,
1655-
2, [{iiop_ssl_port, 0}|ExtraSSLOptions]),
1656-
{ok, ClientNode, _ClientHost} =
1657-
?match({ok,_,_}, orber_test_lib:js_node(ClientOptions)),
1658-
1659-
?match(ok, orber_test_lib:remote_apply(ClientNode, orber_test_lib,
1660-
install_test_data,
1661-
[ssl])),
1662-
orber_test_lib:remote_apply(ClientNode, ssl, start, []),
1663-
orber_test_lib:remote_apply(ServerNode, crypto, start, []),
1664-
Obj = ?match(#'IOP_IOR'{},
1665-
orber_test_lib:remote_apply(ClientNode, corba,
1666-
string_to_object, ["corbaname:iiop:1.1@"++Loopback++":5648/NameService#mamba",
1667-
[{context, [#'IOP_ServiceContext'{context_id=?ORBER_GENERIC_CTX_ID,
1668-
context_data = {configuration, ClientOptions}}]}]])),
1669-
?match(ok, orber_test_lib:remote_apply(ClientNode, orber_test_server,
1670-
print, [Obj])).
1671-
1672-
16731572
ssl_reconfigure_generation_3_api(_Config) ->
16741573
ssl_reconfigure([{ssl_generation, 3}]).
16751574

1676-
16771575
ssl_reconfigure(ExtraSSLOptions) ->
16781576

16791577
IP = orber_test_lib:get_host(),

lib/orber/test/orber_nat_SUITE.erl

+1-1
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ init_per_testcase(TC, Config)
104104
TC =:= nat_iiop_ssl_port_local ->
105105
case proplists:get_value(crypto_started, Config) of
106106
true ->
107-
case orber_test_lib:ssl_version() of
107+
case orber_test_lib:ssl_available() of
108108
no_ssl ->
109109
{skip,"SSL not installed!"};
110110
_ ->

0 commit comments

Comments
 (0)