~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/public_key/test/pkits_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
 
 
20
-module(pkits_SUITE).
 
21
 
 
22
-compile(export_all).
 
23
 
 
24
%%-include_lib("public_key/include/public_key.hrl").
 
25
-include("public_key.hrl").
 
26
 
 
27
-define(error(Format,Args), error(Format,Args,?FILE,?LINE)).
 
28
 
 
29
-define(CERTS, "pkits/certs").
 
30
-define(MIME,  "pkits/smime").
 
31
-define(CONV,  "pkits/smime-pem").
 
32
 
 
33
-define(NIST1, "2.16.840.1.101.3.2.1.48.1").
 
34
-define(NIST2, "2.16.840.1.101.3.2.1.48.2").
 
35
-define(NIST3, "2.16.840.1.101.3.2.1.48.3").
 
36
-define(NIST4, "2.16.840.1.101.3.2.1.48.4").
 
37
-define(NIST5, "2.16.840.1.101.3.2.1.48.5").
 
38
-define(NIST6, "2.16.840.1.101.3.2.1.48.6").
 
39
 
 
40
%%
 
41
all(doc) ->
 
42
    ["PKITS tests for RFC3280 compliance"];
 
43
all(suite) ->    
 
44
    [signature_verification,
 
45
     validity_periods,
 
46
     verifying_name_chaining,
 
47
     %% basic_certificate_revocation_tests,
 
48
     verifying_paths_with_self_issued_certificates,
 
49
     verifying_basic_constraints,
 
50
     key_usage,
 
51
%%      certificate_policies,
 
52
%%      require_explicit_policy,
 
53
%%      policy_mappings,
 
54
%%      inhibit_policy_mapping,
 
55
%%      inhibit_any_policy,
 
56
     name_constraints,       
 
57
%%      distribution_points,
 
58
%%      delta_crls,
 
59
     private_certificate_extensions].
 
60
 
 
61
signature_verification(doc) ->    [""];
 
62
signature_verification(suite) -> [];
 
63
signature_verification(Config) when is_list(Config) ->
 
64
    run(signature_verification()).
 
65
validity_periods(doc) ->    [""];
 
66
validity_periods(suite) -> [];
 
67
validity_periods(Config) when is_list(Config) ->
 
68
    run(validity_periods()).
 
69
verifying_name_chaining(doc) ->    [""];
 
70
verifying_name_chaining(suite) -> [];
 
71
verifying_name_chaining(Config) when is_list(Config) ->
 
72
    run(verifying_name_chaining()).
 
73
basic_certificate_revocation_tests(doc) ->    [""];
 
74
basic_certificate_revocation_tests(suite) -> [];
 
75
basic_certificate_revocation_tests(Config) when is_list(Config) ->
 
76
    run(basic_certificate_revocation_tests()).
 
77
verifying_paths_with_self_issued_certificates(doc) ->    [""];
 
78
verifying_paths_with_self_issued_certificates(suite) -> [];
 
79
verifying_paths_with_self_issued_certificates(Config) when is_list(Config) ->
 
80
    run(verifying_paths_with_self_issued_certificates()).
 
81
verifying_basic_constraints(doc) ->    [""];
 
82
verifying_basic_constraints(suite) -> [];
 
83
verifying_basic_constraints(Config) when is_list(Config) ->
 
84
    run(verifying_basic_constraints()).
 
85
key_usage(doc) ->    [""];
 
86
key_usage(suite) -> [];
 
87
key_usage(Config) when is_list(Config) ->
 
88
    run(key_usage()).
 
89
certificate_policies(doc) ->    [""];
 
90
certificate_policies(suite) -> [];
 
91
certificate_policies(Config) when is_list(Config) ->
 
92
    run(certificate_policies()).
 
93
require_explicit_policy(doc) ->    [""];
 
94
require_explicit_policy(suite) -> [];
 
95
require_explicit_policy(Config) when is_list(Config) ->
 
96
    run(require_explicit_policy()).
 
97
policy_mappings(doc) ->     [""];
 
98
policy_mappings(suite) -> [];
 
99
policy_mappings(Config) when is_list(Config) ->
 
100
    run(policy_mappings()).
 
101
inhibit_policy_mapping(doc) ->    [""];
 
102
inhibit_policy_mapping(suite) -> [];
 
103
inhibit_policy_mapping(Config) when is_list(Config) ->
 
104
    run(inhibit_policy_mapping()).
 
105
inhibit_any_policy(doc) ->    [""];
 
106
inhibit_any_policy(suite) -> [];
 
107
inhibit_any_policy(Config) when is_list(Config) ->
 
108
    run(inhibit_any_policy()).
 
109
name_constraints(doc) ->    [""];
 
110
name_constraints(suite) -> [];
 
111
name_constraints(Config) when is_list(Config) ->
 
112
    run(name_constraints()).
 
113
distribution_points(doc) ->    [""];
 
114
distribution_points(suite) -> [];
 
115
distribution_points(Config) when is_list(Config) ->
 
116
    run(distribution_points()).
 
117
delta_crls(doc) ->    [""];
 
118
delta_crls(suite) -> [];
 
119
delta_crls(Config) when is_list(Config) ->
 
120
    run(delta_crls()).
 
121
private_certificate_extensions(doc) ->    [""];
 
122
private_certificate_extensions(suite) -> [];
 
123
private_certificate_extensions(Config) when is_list(Config) ->
 
124
    run(private_certificate_extensions()).
 
125
    
 
126
run() ->
 
127
    catch crypto:start(),
 
128
    Tests = 
 
129
        [signature_verification(),
 
130
         validity_periods(),
 
131
         verifying_name_chaining(),
 
132
         %%basic_certificate_revocation_tests(),
 
133
         verifying_paths_with_self_issued_certificates(),
 
134
         verifying_basic_constraints(),
 
135
         key_usage(),
 
136
         %%certificate_policies(),
 
137
         %%require_explicit_policy(),
 
138
         %%policy_mappings(),
 
139
         %%inhibit_policy_mapping(),
 
140
         %%inhibit_any_policy(),
 
141
         name_constraints(),         
 
142
         %distribution_points(),
 
143
         %delta_crls(),
 
144
         private_certificate_extensions()
 
145
        ],
 
146
    run(lists:append(Tests)).
 
147
 
 
148
run(Tests) ->    
 
149
    File = file(?CERTS,"TrustAnchorRootCertificate.crt"),
 
150
    {ok, TA} = file:read_file(File),
 
151
    run(Tests, TA).
 
152
 
 
153
run({Chap, Test, Result}, TA) ->
 
154
    CertChain = sort_chain(read_certs(Test),TA, [], false),    
 
155
    try public_key:pkix_path_validation(TA, CertChain, []) of   
 
156
        {Result, _} -> ok;      
 
157
        {error,Result} when Result =/= ok ->
 
158
            ok;
 
159
        {error,Error} when Result =/= ok ->
 
160
            ?error("Warning in ~p~n  Got ~p expected ~p~n",[Test, Error, Result]);
 
161
        {error, Error}  ->
 
162
            ?error("ERROR in ~p ~p~n  Expected ~p got ~p ~n", [Chap, Test, Result, Error]),
 
163
            fail;
 
164
        {ok, _} when Result =/= ok ->
 
165
            ?error("ERROR in ~p ~p~n  Expected ~p got ~p ~n", [Chap, Test, Result, ok]),
 
166
            fail
 
167
    catch Type:Reason ->
 
168
            Stack = erlang:get_stacktrace(),
 
169
            io:format("Crash ~p:~p in ~p~n",[Type,Reason,Stack]),
 
170
            io:format("   ~p ~p Expected ~p ~n", [Chap, Test, Result]),
 
171
            exit(crash)
 
172
    end;
 
173
 
 
174
run([Test|Rest],TA) ->
 
175
    run(Test,TA),
 
176
    run(Rest,TA);
 
177
run([],_) -> ok.
 
178
 
 
179
 
 
180
read_certs(Test) ->
 
181
    File = test_file(Test),
 
182
    %% io:format("Read ~p ",[File]),
 
183
    {ok, Ders} = public_key:pem_to_der(File),
 
184
    %% io:format("Ders ~p ~n",[length(Ders)]),
 
185
    [Cert || {cert,Cert,not_encrypted} <- Ders].
 
186
 
 
187
test_file(Test) ->
 
188
    file(?CONV, lists:append(string:tokens(Test, " -")) ++ ".pem").
 
189
 
 
190
file(Sub,File) ->
 
191
    TestDir = case get(datadir) of
 
192
                  undefined -> "./pkits_SUITE_data";
 
193
                  Dir when is_list(Dir) ->
 
194
                      Dir
 
195
              end,
 
196
    AbsFile = filename:join([TestDir,Sub,File]),
 
197
    case filelib:is_file(AbsFile) of
 
198
        true -> ok;
 
199
        false ->
 
200
            ?error("Couldn't read data from ~p ~n",[AbsFile])
 
201
    end,
 
202
    AbsFile.
 
203
 
 
204
sort_chain([First|Certs], TA, Try, Found) -> 
 
205
    case public_key:pkix_is_issuer(First,TA) of
 
206
        true -> 
 
207
            [First|sort_chain(Certs,First,Try,true)];
 
208
        false ->
 
209
            sort_chain(Certs,TA,[First|Try],Found)
 
210
    end;
 
211
sort_chain([], _, [],_) -> [];
 
212
sort_chain([], Valid, Check, true) ->
 
213
    sort_chain(lists:reverse(Check), Valid, [], false);
 
214
sort_chain([], _Valid, Check, false) ->
 
215
    Check.
 
216
 
 
217
signature_verification() ->    
 
218
    %%  "4.1", "Signature Verification" ,
 
219
    [{ "4.1.1", "Valid Signatures Test1",                        ok},
 
220
     { "4.1.2", "Invalid CA Signature Test2",                    {bad_cert,invalid_signature}},
 
221
     { "4.1.3", "Invalid EE Signature Test3",                    {bad_cert,invalid_signature}},
 
222
     { "4.1.4", "Valid DSA Signatures Test4",                    ok},
 
223
     { "4.1.5", "Valid DSA Parameter Inheritance Test5",         ok},
 
224
     { "4.1.6", "Invalid DSA Signature Test6",                   {bad_cert,invalid_signature}}].
 
225
validity_periods() ->
 
226
    %% { "4.2",   "Validity Periods" },
 
227
    [{ "4.2.1", "Invalid CA notBefore Date Test1",               {bad_cert, cert_expired}},
 
228
     { "4.2.2", "Invalid EE notBefore Date Test2",               {bad_cert, cert_expired}},
 
229
     { "4.2.3", "Valid pre2000 UTC notBefore Date Test3",        ok},
 
230
     { "4.2.4", "Valid GeneralizedTime notBefore Date Test4",    ok},
 
231
     { "4.2.5", "Invalid CA notAfter Date Test5",                {bad_cert, cert_expired}},
 
232
     { "4.2.6", "Invalid EE notAfter Date Test6",                {bad_cert, cert_expired}},
 
233
     { "4.2.7", "Invalid pre2000 UTC EE notAfter Date Test7",    {bad_cert, cert_expired}},
 
234
     { "4.2.8", "Valid GeneralizedTime notAfter Date Test8",     ok}].
 
235
verifying_name_chaining() ->
 
236
    %%{ "4.3",   "Verifying Name Chaining" },
 
237
    [{ "4.3.1", "Invalid Name Chaining EE Test1",                {bad_cert, invalid_issuer}},
 
238
     { "4.3.2", "Invalid Name Chaining Order Test2",             {bad_cert, invalid_issuer}},
 
239
     { "4.3.3", "Valid Name Chaining Whitespace Test3",          ok},
 
240
     { "4.3.4", "Valid Name Chaining Whitespace Test4",          ok},
 
241
     { "4.3.5", "Valid Name Chaining Capitalization Test5",      ok},
 
242
     { "4.3.6", "Valid Name Chaining UIDs Test6",                ok},
 
243
     { "4.3.7", "Valid RFC3280 Mandatory Attribute Types Test7", ok},
 
244
     { "4.3.8", "Valid RFC3280 Optional Attribute Types Test8",  ok},
 
245
     { "4.3.9", "Valid UTF8String Encoded Names Test9",          ok},
 
246
     { "4.3.10", "Valid Rollover from PrintableString to UTF8String Test10", ok},
 
247
     { "4.3.11", "Valid UTF8String Case Insensitive Match Test11",           ok}].
 
248
basic_certificate_revocation_tests() ->
 
249
    %%{ "4.4",    "Basic Certificate Revocation Tests" },
 
250
    [{ "4.4.1",  "Missing CRL Test1",                 3 },
 
251
     { "4.4.2", "Invalid Revoked CA Test2",          23 },
 
252
     { "4.4.3", "Invalid Revoked EE Test3",          23 },
 
253
     { "4.4.4", "Invalid Bad CRL Signature Test4",   8 },
 
254
     { "4.4.5", "Invalid Bad CRL Issuer Name Test5", 3 },
 
255
     { "4.4.6", "Invalid Wrong CRL Test6",           3 },
 
256
     { "4.4.7", "Valid Two CRLs Test7",              ok},
 
257
 
 
258
     %% The test document suggests these should return certificate revoked...
 
259
     %% Subsquent discussion has concluded they should not due to unhandle
 
260
     %% critical CRL extensions.
 
261
     { "4.4.8", "Invalid Unknown CRL Entry Extension Test8", 36 },
 
262
     { "4.4.9", "Invalid Unknown CRL Extension Test9",       36 },
 
263
 
 
264
     { "4.4.10", "Invalid Unknown CRL Extension Test10",             36 },
 
265
     { "4.4.11", "Invalid Old CRL nextUpdate Test11",                12 },
 
266
     { "4.4.12", "Invalid pre2000 CRL nextUpdate Test12",            12 },
 
267
     { "4.4.13", "Valid GeneralizedTime CRL nextUpdate Test13",      ok},
 
268
     { "4.4.14", "Valid Negative Serial Number Test14",              ok},
 
269
     { "4.4.15", "Invalid Negative Serial Number Test15",            23 },
 
270
     { "4.4.16", "Valid Long Serial Number Test16",                  ok},
 
271
     { "4.4.17", "Valid Long Serial Number Test17",                  ok},
 
272
     { "4.4.18", "Invalid Long Serial Number Test18",                23 },
 
273
     { "4.4.19", "Valid Separate Certificate and CRL Keys Test19",   ok},
 
274
     { "4.4.20", "Invalid Separate Certificate and CRL Keys Test20", 23 },
 
275
 
 
276
     %% CRL path is revoked so get a CRL path validation error
 
277
     { "4.4.21", "Invalid Separate Certificate and CRL Keys Test21",      54 }].
 
278
verifying_paths_with_self_issued_certificates() ->
 
279
    %%{ "4.5",    "Verifying Paths with Self-Issued Certificates" },
 
280
    [{ "4.5.1",  "Valid Basic Self-Issued Old With New Test1",            ok},
 
281
     { "4.5.2",  "Invalid Basic Self-Issued Old With New Test2",          23 },
 
282
     { "4.5.3",  "Valid Basic Self-Issued New With Old Test3",            ok},
 
283
     { "4.5.4",  "Valid Basic Self-Issued New With Old Test4",            ok},
 
284
     { "4.5.5",  "Invalid Basic Self-Issued New With Old Test5",          23 },
 
285
     { "4.5.6",  "Valid Basic Self-Issued CRL Signing Key Test6",         ok},
 
286
     { "4.5.7",  "Invalid Basic Self-Issued CRL Signing Key Test7",       23 },
 
287
     { "4.5.8",  "Invalid Basic Self-Issued CRL Signing Key Test8",       {bad_cert,invalid_key_usage} }].
 
288
verifying_basic_constraints() ->
 
289
    [%%{ "4.6",    "Verifying Basic Constraints" },
 
290
     { "4.6.1",  "Invalid Missing basicConstraints Test1",                
 
291
       {bad_cert, missing_basic_constraint} },
 
292
     { "4.6.2",  "Invalid cA False Test2",                                {bad_cert, missing_basic_constraint}},
 
293
     { "4.6.3",  "Invalid cA False Test3",                                {bad_cert, missing_basic_constraint}},
 
294
     { "4.6.4",  "Valid basicConstraints Not Critical Test4",             ok},
 
295
     { "4.6.5",  "Invalid pathLenConstraint Test5",                       {bad_cert, max_path_length_reached}},
 
296
     { "4.6.6",  "Invalid pathLenConstraint Test6",                       {bad_cert, max_path_length_reached}},
 
297
     { "4.6.7",  "Valid pathLenConstraint Test7",                         ok},
 
298
     { "4.6.8",  "Valid pathLenConstraint Test8",                         ok},
 
299
     { "4.6.9",  "Invalid pathLenConstraint Test9",                       {bad_cert, max_path_length_reached}},
 
300
     { "4.6.10", "Invalid pathLenConstraint Test10",                      {bad_cert, max_path_length_reached}},
 
301
     { "4.6.11", "Invalid pathLenConstraint Test11",                      {bad_cert, max_path_length_reached}},
 
302
     { "4.6.12", "Invalid pathLenConstraint Test12",                      {bad_cert, max_path_length_reached}},
 
303
     { "4.6.13", "Valid pathLenConstraint Test13",                        ok},
 
304
     { "4.6.14", "Valid pathLenConstraint Test14",                        ok},
 
305
     { "4.6.15", "Valid Self-Issued pathLenConstraint Test15",            ok},
 
306
     { "4.6.16", "Invalid Self-Issued pathLenConstraint Test16",          {bad_cert, max_path_length_reached}},
 
307
     { "4.6.17", "Valid Self-Issued pathLenConstraint Test17",            ok}].
 
308
key_usage() ->
 
309
    %%{ "4.7",    "Key Usage" },
 
310
    [{ "4.7.1",  "Invalid keyUsage Critical keyCertSign False Test1",     {bad_cert,invalid_key_usage} },
 
311
     { "4.7.2",  "Invalid keyUsage Not Critical keyCertSign False Test2", {bad_cert,invalid_key_usage} },
 
312
     { "4.7.3",  "Valid keyUsage Not Critical Test3",                     ok},
 
313
     { "4.7.4",  "Invalid keyUsage Critical cRLSign False Test4",         35 },
 
314
     { "4.7.5",  "Invalid keyUsage Not Critical cRLSign False Test5",     35 }].
 
315
 
 
316
%% Certificate policy tests need special handling. They can have several
 
317
%% sub tests and we need to check the outputs are correct.
 
318
 
 
319
certificate_policies() ->
 
320
    %%{ "4.8", "Certificate Policies" },
 
321
    [{"4.8.1.1", "All Certificates Same Policy Test1", "-policy anyPolicy -explicit_policy", "True", ?NIST1, ?NIST1, 0},
 
322
     {"4.8.1.2", "All Certificates Same Policy Test1", "-policy ?NIST1 -explicit_policy", "True", ?NIST1, ?NIST1, 0},
 
323
     {"4.8.1.3", "All Certificates Same Policy Test1", "-policy ?NIST2 -explicit_policy", "True", ?NIST1, "<empty>", 43},
 
324
     {"4.8.1.4", "All Certificates Same Policy Test1", "-policy ?NIST1 -policy ?NIST2 -explicit_policy", "True", ?NIST1, ?NIST1, 0},
 
325
     {"4.8.2.1", "All Certificates No Policies Test2", "-policy anyPolicy", "False", "<empty>", "<empty>", 0},
 
326
     {"4.8.2.2", "All Certificates No Policies Test2", "-policy anyPolicy -explicit_policy", "True", "<empty>", "<empty>", 43},
 
327
     {"4.8.3.1", "Different Policies Test3", "-policy anyPolicy", "False", "<empty>", "<empty>", 0},
 
328
    {"4.8.3.2", "Different Policies Test3", "-policy anyPolicy -explicit_policy", "True", "<empty>", "<empty>", 43},
 
329
     {"4.8.3.3", "Different Policies Test3", "-policy ?NIST1 -policy ?NIST2 -explicit_policy", "True", "<empty>", "<empty>", 43},
 
330
     {"4.8.4", "Different Policies Test4", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
331
     {"4.8.5", "Different Policies Test5", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
332
     {"4.8.6.1", "Overlapping Policies Test6", "-policy anyPolicy", "True", ?NIST1, ?NIST1, 0},
 
333
     {"4.8.6.2", "Overlapping Policies Test6", "-policy ?NIST1", "True", ?NIST1, ?NIST1, 0},
 
334
     {"4.8.6.3", "Overlapping Policies Test6", "-policy ?NIST2", "True", ?NIST1, "<empty>", 43},
 
335
     {"4.8.7", "Different Policies Test7", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
336
     {"4.8.8", "Different Policies Test8", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
337
     {"4.8.9", "Different Policies Test9", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
338
     {"4.8.10.1", "All Certificates Same Policies Test10", "-policy ?NIST1", "True", "?NIST1:?NIST2", "?NIST1", 0},
 
339
     {"4.8.10.2", "All Certificates Same Policies Test10", "-policy ?NIST2", "True", "?NIST1:?NIST2", "?NIST2", 0},
 
340
     {"4.8.10.3", "All Certificates Same Policies Test10", "-policy anyPolicy", "True", "?NIST1:?NIST2", "?NIST1:?NIST2", 0},
 
341
     {"4.8.11.1", "All Certificates AnyPolicy Test11", "-policy anyPolicy", "True", "$apolicy", "$apolicy", 0},
 
342
    {"4.8.11.2", "All Certificates AnyPolicy Test11", "-policy ?NIST1", "True", "$apolicy", "?NIST1", 0},
 
343
     {"4.8.12", "Different Policies Test12", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
344
     {"4.8.13.1", "All Certificates Same Policies Test13", "-policy ?NIST1", "True", "?NIST1:?NIST2:?NIST3", "?NIST1", 0},
 
345
     {"4.8.13.2", "All Certificates Same Policies Test13", "-policy ?NIST2", "True", "?NIST1:?NIST2:?NIST3", "?NIST2", 0},
 
346
     {"4.8.13.3", "All Certificates Same Policies Test13", "-policy ?NIST3", "True", "?NIST1:?NIST2:?NIST3", "?NIST3", 0},
 
347
     {"4.8.14.1",       "AnyPolicy Test14", "-policy ?NIST1", "True", "?NIST1",         "?NIST1", 0},
 
348
     {"4.8.14.2",       "AnyPolicy Test14", "-policy ?NIST2", "True", "?NIST1",         "<empty>", 43},
 
349
     {"4.8.15", "User Notice Qualifier Test15", "-policy anyPolicy", "False", "?NIST1", "?NIST1", 0},
 
350
     {"4.8.16", "User Notice Qualifier Test16", "-policy anyPolicy", "False", "?NIST1", "?NIST1", 0},
 
351
    {"4.8.17", "User Notice Qualifier Test17", "-policy anyPolicy", "False", "?NIST1", "?NIST1", 0},
 
352
     {"4.8.18.1", "User Notice Qualifier Test18", "-policy ?NIST1", "True", "?NIST1:?NIST2", "?NIST1", 0},
 
353
     {"4.8.18.2", "User Notice Qualifier Test18", "-policy ?NIST2", "True", "?NIST1:?NIST2", "?NIST2", 0},
 
354
     {"4.8.19", "User Notice Qualifier Test19", "-policy anyPolicy", "False", "?NIST1", "?NIST1", 0},
 
355
     {"4.8.20", "CPS Pointer Qualifier Test20", "-policy anyPolicy -explicit_policy", "True", "?NIST1", "?NIST1", 0}].
 
356
require_explicit_policy() ->
 
357
    %%{ "4.9", "Require Explicit Policy" },
 
358
    [{"4.9.1", "Valid RequireExplicitPolicy Test1", "-policy anyPolicy", "False", "<empty>", "<empty>", 0},
 
359
     {"4.9.2", "Valid RequireExplicitPolicy Test2", "-policy anyPolicy", "False", "<empty>", "<empty>", 0},
 
360
     {"4.9.3", "Invalid RequireExplicitPolicy Test3", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
361
     {"4.9.4", "Valid RequireExplicitPolicy Test4", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
362
     {"4.9.5", "Invalid RequireExplicitPolicy Test5", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
363
     {"4.9.6", "Valid Self-Issued requireExplicitPolicy Test6", "-policy anyPolicy", "False", "<empty>", "<empty>", 0},
 
364
     {"4.9.7", "Invalid Self-Issued requireExplicitPolicy Test7", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
365
     {"4.9.8", "Invalid Self-Issued requireExplicitPolicy Test8", "-policy anyPolicy", "True", "<empty>", "<empty>", 43}].
 
366
policy_mappings() ->
 
367
    %%{ "4.10", "Policy Mappings" },
 
368
    [{"4.10.1.1", "Valid Policy Mapping Test1", "-policy ?NIST1", "True", "?NIST1", "?NIST1", 0},
 
369
     {"4.10.1.2", "Valid Policy Mapping Test1", "-policy ?NIST2", "True", "?NIST1", "<empty>", 43},
 
370
     {"4.10.1.3", "Valid Policy Mapping Test1", "-policy anyPolicy -inhibit_map", "True", "<empty>", "<empty>", 43},
 
371
     {"4.10.2.1", "Invalid Policy Mapping Test2", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
372
     {"4.10.2.2", "Invalid Policy Mapping Test2", "-policy anyPolicy -inhibit_map", "True", "<empty>", "<empty>", 43},
 
373
     {"4.10.3.1", "Valid Policy Mapping Test3", "-policy ?NIST1", "True", "?NIST2", "<empty>", 43},
 
374
     {"4.10.3.2", "Valid Policy Mapping Test3", "-policy ?NIST2", "True", "?NIST2", "?NIST2", 0},
 
375
     {"4.10.4", "Invalid Policy Mapping Test4", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
376
     {"4.10.5.1", "Valid Policy Mapping Test5", "-policy ?NIST1", "True", "?NIST1", "?NIST1", 0},
 
377
     {"4.10.5.2", "Valid Policy Mapping Test5", "-policy ?NIST6", "True", "?NIST1", "<empty>", 43},
 
378
     {"4.10.6.1", "Valid Policy Mapping Test6", "-policy ?NIST1", "True", "?NIST1", "?NIST1", 0},
 
379
     {"4.10.6.2", "Valid Policy Mapping Test6", "-policy ?NIST6", "True", "?NIST1", "<empty>", 43},
 
380
     { "4.10.7", "Invalid Mapping From anyPolicy Test7", 42 },
 
381
     { "4.10.8", "Invalid Mapping To anyPolicy Test8",   42 },
 
382
     {"4.10.9", "Valid Policy Mapping Test9", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
383
     {"4.10.10", "Invalid Policy Mapping Test10", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
384
     {"4.10.11", "Valid Policy Mapping Test11", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
385
 
 
386
     %% TODO: check notice display
 
387
     {"4.10.12.1", "Valid Policy Mapping Test12", "-policy ?NIST1", "True", "?NIST1:?NIST2", "?NIST1", 0},
 
388
 
 
389
     %% TODO: check notice display
 
390
     {"4.10.12.2", "Valid Policy Mapping Test12", "-policy ?NIST2", "True", "?NIST1:?NIST2", "?NIST2", 0},
 
391
     {"4.10.13", "Valid Policy Mapping Test13", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
392
 
 
393
     %% TODO: check notice display
 
394
     {"4.10.14", "Valid Policy Mapping Test14", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0}].
 
395
 
 
396
inhibit_policy_mapping() ->
 
397
    %%{ "4.11", "Inhibit Policy Mapping" },
 
398
    [{"4.11.1", "Invalid inhibitPolicyMapping Test1", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
399
     {"4.11.2", "Valid inhibitPolicyMapping Test2", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
400
     {"4.11.3", "Invalid inhibitPolicyMapping Test3", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
401
     {"4.11.4", "Valid inhibitPolicyMapping Test4", "-policy anyPolicy", "True", "?NIST2", "?NIST2", 0},
 
402
     {"4.11.5", "Invalid inhibitPolicyMapping Test5", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
403
     {"4.11.6", "Invalid inhibitPolicyMapping Test6", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
404
     {"4.11.7", "Valid Self-Issued inhibitPolicyMapping Test7", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
405
     {"4.11.8", "Invalid Self-Issued inhibitPolicyMapping Test8", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
406
     {"4.11.9", "Invalid Self-Issued inhibitPolicyMapping Test9", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
407
     {"4.11.10", "Invalid Self-Issued inhibitPolicyMapping Test10", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
408
     {"4.11.11", "Invalid Self-Issued inhibitPolicyMapping Test11", "-policy anyPolicy", "True", "<empty>", "<empty>", 43}].
 
409
inhibit_any_policy() ->
 
410
    %%{ "4.12", "Inhibit Any Policy" },
 
411
    [{"4.12.1", "Invalid inhibitAnyPolicy Test1", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
412
     {"4.12.2", "Valid inhibitAnyPolicy Test2", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
413
     {"4.12.3.1", "inhibitAnyPolicy Test3", "-policy anyPolicy", "True", "?NIST1", "?NIST1", 0},
 
414
     {"4.12.3.2", "inhibitAnyPolicy Test3", "-policy anyPolicy -inhibit_any", "True", "<empty>", "<empty>", 43},
 
415
     {"4.12.4", "Invalid inhibitAnyPolicy Test4", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
416
     {"4.12.5", "Invalid inhibitAnyPolicy Test5", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
417
     {"4.12.6", "Invalid inhibitAnyPolicy Test6", "-policy anyPolicy", "True", "<empty>", "<empty>", 43},
 
418
     {"4.12.7",  "Valid Self-Issued inhibitAnyPolicy Test7",      ok},
 
419
     {"4.12.8",  "Invalid Self-Issued inhibitAnyPolicy Test8",    43 },
 
420
     {"4.12.9",  "Valid Self-Issued inhibitAnyPolicy Test9",      ok},
 
421
     {"4.12.10", "Invalid Self-Issued inhibitAnyPolicy Test10",   43 }].
 
422
 
 
423
name_constraints() ->
 
424
    %%{ "4.13",    "Name Constraints" },
 
425
    [{ "4.13.1",  "Valid DN nameConstraints Test1",                ok},
 
426
     { "4.13.2",  "Invalid DN nameConstraints Test2",              {bad_cert, name_not_permitted}},
 
427
     { "4.13.3",  "Invalid DN nameConstraints Test3",              {bad_cert, name_not_permitted}},
 
428
     { "4.13.4",  "Valid DN nameConstraints Test4",                ok},
 
429
     { "4.13.5",  "Valid DN nameConstraints Test5",                ok},
 
430
     { "4.13.6",  "Valid DN nameConstraints Test6",                ok},
 
431
     { "4.13.7",  "Invalid DN nameConstraints Test7",              {bad_cert, name_not_permitted}},
 
432
     { "4.13.8",  "Invalid DN nameConstraints Test8",              {bad_cert, name_not_permitted}},
 
433
     { "4.13.9",  "Invalid DN nameConstraints Test9",              {bad_cert, name_not_permitted}},
 
434
     { "4.13.10", "Invalid DN nameConstraints Test10",             {bad_cert, name_not_permitted}},
 
435
     { "4.13.11", "Valid DN nameConstraints Test11",               ok},
 
436
     { "4.13.12", "Invalid DN nameConstraints Test12",             {bad_cert, name_not_permitted}},
 
437
     { "4.13.13", "Invalid DN nameConstraints Test13",             {bad_cert, name_not_permitted}},
 
438
     { "4.13.14", "Valid DN nameConstraints Test14",               ok},
 
439
     { "4.13.15", "Invalid DN nameConstraints Test15",             {bad_cert, name_not_permitted}},
 
440
     { "4.13.16", "Invalid DN nameConstraints Test16",             {bad_cert, name_not_permitted}},
 
441
     { "4.13.17", "Invalid DN nameConstraints Test17",             {bad_cert, name_not_permitted}},
 
442
     { "4.13.18", "Valid DN nameConstraints Test18",               ok},
 
443
     { "4.13.19", "Valid Self-Issued DN nameConstraints Test19",   ok},
 
444
     { "4.13.20", "Invalid Self-Issued DN nameConstraints Test20", {bad_cert, name_not_permitted} },
 
445
     { "4.13.21", "Valid RFC822 nameConstraints Test21",           ok},
 
446
     { "4.13.22", "Invalid RFC822 nameConstraints Test22",         {bad_cert, name_not_permitted} },
 
447
     { "4.13.23", "Valid RFC822 nameConstraints Test23",           ok},
 
448
     { "4.13.24", "Invalid RFC822 nameConstraints Test24",         {bad_cert, name_not_permitted} },
 
449
     { "4.13.25", "Valid RFC822 nameConstraints Test25",           ok},
 
450
     { "4.13.26", "Invalid RFC822 nameConstraints Test26",         {bad_cert, name_not_permitted}},
 
451
     { "4.13.27", "Valid DN and RFC822 nameConstraints Test27",    ok},
 
452
     { "4.13.28", "Invalid DN and RFC822 nameConstraints Test28",  {bad_cert, name_not_permitted} },
 
453
     { "4.13.29", "Invalid DN and RFC822 nameConstraints Test29",  {bad_cert, name_not_permitted} },
 
454
     { "4.13.30", "Valid DNS nameConstraints Test30",              ok},
 
455
     { "4.13.31", "Invalid DNS nameConstraints Test31",            {bad_cert, name_not_permitted} },
 
456
     { "4.13.32", "Valid DNS nameConstraints Test32",              ok},
 
457
     { "4.13.33", "Invalid DNS nameConstraints Test33",            {bad_cert, name_not_permitted}},
 
458
     { "4.13.34", "Valid URI nameConstraints Test34",              ok},
 
459
     { "4.13.35", "Invalid URI nameConstraints Test35",            {bad_cert, name_not_permitted} },
 
460
     { "4.13.36", "Valid URI nameConstraints Test36",              ok},
 
461
     { "4.13.37", "Invalid URI nameConstraints Test37",            {bad_cert, name_not_permitted}},
 
462
     { "4.13.38", "Invalid DNS nameConstraints Test38",            {bad_cert, name_not_permitted} }].
 
463
distribution_points() ->
 
464
     %%{ "4.14",    "Distribution Points" },
 
465
    [{ "4.14.1",  "Valid distributionPoint Test1",                 ok},
 
466
     { "4.14.2",  "Invalid distributionPoint Test2",               23 },
 
467
     { "4.14.3",  "Invalid distributionPoint Test3",               44 },
 
468
     { "4.14.4",  "Valid distributionPoint Test4",                 ok},
 
469
     { "4.14.5",  "Valid distributionPoint Test5",                 ok},
 
470
     { "4.14.6",  "Invalid distributionPoint Test6",               23 },
 
471
     { "4.14.7",  "Valid distributionPoint Test7",                 ok},
 
472
     { "4.14.8",  "Invalid distributionPoint Test8",               44 },
 
473
     { "4.14.9",  "Invalid distributionPoint Test9",               44 },
 
474
     { "4.14.10", "Valid No issuingDistributionPoint Test10",      ok},
 
475
     { "4.14.11", "Invalid onlyContainsUserCerts CRL Test11",      44 },
 
476
     { "4.14.12", "Invalid onlyContainsCACerts CRL Test12",        44 },
 
477
     { "4.14.13", "Valid onlyContainsCACerts CRL Test13",          ok},
 
478
     { "4.14.14", "Invalid onlyContainsAttributeCerts Test14",     44 },
 
479
     { "4.14.15", "Invalid onlySomeReasons Test15",                23 },
 
480
     { "4.14.16", "Invalid onlySomeReasons Test16",                23 },
 
481
     { "4.14.17", "Invalid onlySomeReasons Test17",                3 },
 
482
     { "4.14.18", "Valid onlySomeReasons Test18",                  ok},
 
483
     { "4.14.19", "Valid onlySomeReasons Test19",                  ok},
 
484
     { "4.14.20", "Invalid onlySomeReasons Test20",                23 },
 
485
     { "4.14.21", "Invalid onlySomeReasons Test21",                23 },
 
486
     { "4.14.22", "Valid IDP with indirectCRL Test22",             ok},
 
487
     { "4.14.23", "Invalid IDP with indirectCRL Test23",           23 },
 
488
     { "4.14.24", "Valid IDP with indirectCRL Test24",             ok},
 
489
     { "4.14.25", "Valid IDP with indirectCRL Test25",             ok},
 
490
     { "4.14.26", "Invalid IDP with indirectCRL Test26",           44 },
 
491
     { "4.14.27", "Invalid cRLIssuer Test27",                      3 },
 
492
     { "4.14.28", "Valid cRLIssuer Test28",                        ok},
 
493
     { "4.14.29", "Valid cRLIssuer Test29",                        ok},
 
494
 
 
495
     %% Although this test is valid it has a circular dependency. As a result
 
496
     %% an attempt is made to reursively checks a CRL path and rejected due to
 
497
     %% a CRL path validation error. PKITS notes suggest this test does not
 
498
     %% need to be run due to this issue.
 
499
     { "4.14.30", "Valid cRLIssuer Test30",                                 54 },
 
500
     { "4.14.31", "Invalid cRLIssuer Test31",                               23 },
 
501
     { "4.14.32", "Invalid cRLIssuer Test32",                               23 },
 
502
     { "4.14.33", "Valid cRLIssuer Test33",                                 ok},
 
503
     { "4.14.34", "Invalid cRLIssuer Test34",                               23 },
 
504
     { "4.14.35", "Invalid cRLIssuer Test35",                               44 }].
 
505
delta_crls() ->
 
506
    %%{ "4.15",    "Delta-CRLs" },
 
507
    [{ "4.15.1",  "Invalid deltaCRLIndicator No Base Test1",                3 },
 
508
     { "4.15.2",  "Valid delta-CRL Test2",                                  ok},
 
509
     { "4.15.3",  "Invalid delta-CRL Test3",                                23 },
 
510
     { "4.15.4",  "Invalid delta-CRL Test4",                                23 },
 
511
     { "4.15.5",  "Valid delta-CRL Test5",                                  ok},
 
512
     { "4.15.6",  "Invalid delta-CRL Test6",                                23 },
 
513
     { "4.15.7",  "Valid delta-CRL Test7",                                  ok},
 
514
     { "4.15.8",  "Valid delta-CRL Test8",                                  ok},
 
515
     { "4.15.9",  "Invalid delta-CRL Test9",                                23 },
 
516
     { "4.15.10", "Invalid delta-CRL Test10",                               12 }].
 
517
private_certificate_extensions() ->
 
518
    %%{ "4.16",    "Private Certificate Extensions" },
 
519
    [{ "4.16.1",  "Valid Unknown Not Critical Certificate Extension Test1", ok},
 
520
     { "4.16.2",  "Invalid Unknown Critical Certificate Extension Test2",   
 
521
       {bad_cert,unknown_critical_extension}}].
 
522
 
 
523
 
 
524
convert() ->
 
525
    Tests = [signature_verification(),
 
526
             validity_periods(),
 
527
             verifying_name_chaining(),
 
528
             basic_certificate_revocation_tests(),
 
529
             verifying_paths_with_self_issued_certificates(),
 
530
             verifying_basic_constraints(),
 
531
             key_usage(),
 
532
             certificate_policies(),
 
533
             require_explicit_policy(),
 
534
             policy_mappings(),
 
535
             inhibit_policy_mapping(),
 
536
             inhibit_any_policy(),
 
537
             name_constraints(),             
 
538
             distribution_points(),
 
539
             delta_crls(),
 
540
             private_certificate_extensions()],    
 
541
    [convert(Test) || Test <- lists:flatten(Tests)].
 
542
 
 
543
convert({_,Test,_}) ->
 
544
    convert1(Test);
 
545
convert({_,Test,_,_,_,_,_}) ->
 
546
    convert1(Test).
 
547
 
 
548
convert1(Test) ->
 
549
    FName = lists:append(string:tokens(Test, " -")),
 
550
    File = filename:join(?MIME, "Signed" ++ FName ++ ".eml"),
 
551
    io:format("Convert ~p~n",[File]),
 
552
    {ok, Mail} = file:read_file(File),
 
553
    Base64  = skip_lines(Mail),
 
554
    %%io:format("~s",[Base64]),
 
555
    Tmp = base64:mime_decode(Base64),
 
556
    file:write_file("pkits/smime-pem/tmp-pkcs7.der", Tmp),
 
557
    Cmd = "openssl pkcs7 -inform der -in pkits/smime-pem/tmp-pkcs7.der"
 
558
        " -print_certs -out pkits/smime-pem/" ++ FName ++ ".pem",
 
559
    case os:cmd(Cmd) of
 
560
        "" -> ok;
 
561
        Err -> 
 
562
            io:format("~s",[Err]),
 
563
            erlang:error(bad_cmd)
 
564
    end.
 
565
 
 
566
skip_lines(<<"\r\n\r\n", Rest/binary>>) -> Rest;
 
567
skip_lines(<<"\n\n", Rest/binary>>) -> Rest;
 
568
skip_lines(<<_:8, Rest/binary>>) ->
 
569
    skip_lines(Rest).
 
570
 
 
571
init_per_testcase(_Func, Config) ->    
 
572
    Datadir = proplists:get_value(data_dir, Config),
 
573
    put(datadir, Datadir),
 
574
    Config.
 
575
 
 
576
fin_per_testcase(_Func, Config) ->
 
577
    %% Nodes = select_nodes(all, Config, ?FILE, ?LINE),
 
578
    %% rpc:multicall(Nodes, mnesia, lkill, []),
 
579
    Config.
 
580
 
 
581
init_per_suite(Config) ->
 
582
    crypto:start(),
 
583
    Config.
 
584
 
 
585
end_per_suite(_Config) ->
 
586
    crypto:stop().
 
587
 
 
588
error(Format, Args, File0, Line) ->
 
589
    File = filename:basename(File0),
 
590
    Pid = group_leader(),
 
591
    Pid ! {failed, File, Line},
 
592
    io:format(Pid, "~s(~p): "++Format, [File,Line|Args]).