~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/test/base64_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
18
18
%%
19
19
 
20
20
-module(base64_SUITE).
21
 
-author('jakob@erix.ericsson.se').
22
21
 
23
 
-include("test_server.hrl").
 
22
-include_lib("common_test/include/ct.hrl").
24
23
-include("test_server_line.hrl").
25
24
 
26
25
%% Test server specific exports
27
 
-export([all/1, init_per_testcase/2, end_per_testcase/2]).
 
26
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
27
         init_per_group/2,end_per_group/2, 
 
28
         init_per_testcase/2, end_per_testcase/2]).
28
29
 
29
30
%% Test cases must be exported.
30
31
-export([base64_encode/1, base64_decode/1, base64_otp_5635/1,
31
32
         base64_otp_6279/1, big/1, illegal/1, mime_decode/1,
32
 
         roundtrip/1]).
 
33
         mime_decode_to_string/1, roundtrip/1]).
33
34
 
34
35
init_per_testcase(_, Config) ->
35
36
    Dog = test_server:timetrap(?t:minutes(2)),
44
45
%%-------------------------------------------------------------------------
45
46
%% Test cases starts here.
46
47
%%-------------------------------------------------------------------------
47
 
all(doc) ->
48
 
    ["Test library functions for base64 encode and decode "
49
 
     "(taken from inets/test/http_format_SUITE)"];
50
 
all(suite) ->
 
48
suite() -> [{ct_hooks,[ts_install_cth]}].
 
49
 
 
50
all() -> 
51
51
    [base64_encode, base64_decode, base64_otp_5635,
52
 
     base64_otp_6279, big, illegal, mime_decode,
 
52
     base64_otp_6279, big, illegal, mime_decode, mime_decode_to_string,
53
53
     roundtrip].
54
54
 
 
55
groups() -> 
 
56
    [].
 
57
 
 
58
init_per_suite(Config) ->
 
59
    Config.
 
60
 
 
61
end_per_suite(_Config) ->
 
62
    ok.
 
63
 
 
64
init_per_group(_GroupName, Config) ->
 
65
    Config.
 
66
 
 
67
end_per_group(_GroupName, Config) ->
 
68
    Config.
 
69
 
 
70
 
55
71
 
56
72
%%-------------------------------------------------------------------------
57
73
base64_encode(doc) ->
59
75
base64_encode(suite) ->
60
76
    [];
61
77
base64_encode(Config) when is_list(Config) ->
62
 
    %% Two pads 
 
78
    %% Two pads
63
79
    <<"QWxhZGRpbjpvcGVuIHNlc2FtZQ==">> =
64
80
        base64:encode("Aladdin:open sesame"),
65
81
    %% One pad
77
93
base64_decode(suite) ->
78
94
    [];
79
95
base64_decode(Config) when is_list(Config) ->
80
 
    %% Two pads 
81
 
    <<"Aladdin:open sesame">> = 
 
96
    %% Two pads
 
97
    <<"Aladdin:open sesame">> =
82
98
        base64:decode("QWxhZGRpbjpvcGVuIHNlc2FtZQ=="),
83
99
    %% One pad
84
100
    <<"Hello World">> = base64:decode(<<"SGVsbG8gV29ybGQ=">>),
138
154
    {'EXIT',{function_clause, _}} = (catch base64:decode("()")),
139
155
    ok.
140
156
%%-------------------------------------------------------------------------
 
157
%% mime_decode and mime_decode_to_string have different implementations
 
158
%% so test both with the same input separately. Both functions have
 
159
%% the same implementation for binary/string arguments.
141
160
mime_decode(doc) ->
142
161
    ["Test base64:mime_decode/1."];
143
162
mime_decode(suite) ->
144
163
    [];
145
164
mime_decode(Config) when is_list(Config) ->
146
 
    %% Two pads 
147
 
    <<"Aladdin:open sesame">> = 
 
165
    %% Test correct padding
 
166
    <<"one">> = base64:mime_decode(<<"b25l">>),
 
167
    <<"on">>  = base64:mime_decode(<<"b24=">>),
 
168
    <<"o">>   = base64:mime_decode(<<"bw==">>),
 
169
    %% Test 1 extra padding
 
170
    <<"one">> = base64:mime_decode(<<"b25l= =">>),
 
171
    <<"on">>  = base64:mime_decode(<<"b24== =">>),
 
172
    <<"o">>   = base64:mime_decode(<<"bw=== =">>),
 
173
    %% Test 2 extra padding
 
174
    <<"one">> = base64:mime_decode(<<"b25l===">>),
 
175
    <<"on">>  = base64:mime_decode(<<"b24====">>),
 
176
    <<"o">>   = base64:mime_decode(<<"bw=====">>),
 
177
    %% Test misc embedded padding
 
178
    <<"one">> = base64:mime_decode(<<"b2=5l===">>),
 
179
    <<"on">>  = base64:mime_decode(<<"b=24====">>),
 
180
    <<"o">>   = base64:mime_decode(<<"b=w=====">>),
 
181
    %% Test misc white space and illegals with embedded padding
 
182
    <<"one">> = base64:mime_decode(<<" b~2=\r\n5()l===">>),
 
183
    <<"on">>  = base64:mime_decode(<<"\tb =2\"�4=�=   ==">>),
 
184
    <<"o">>   = base64:mime_decode(<<"\nb=w=====">>),
 
185
    %% Two pads
 
186
    <<"Aladdin:open sesame">> =
148
187
        base64:mime_decode("QWxhZGRpbjpvc()GVuIHNlc2FtZQ=="),
149
 
    %% One pad, followed by ignored text
150
 
    <<"Hello World">> = base64:mime_decode(<<"SGVsb)(G8gV29ybGQ=apa">>),
 
188
    %% One pad to ignore, followed by more text
 
189
    <<"Hello World!!">> = base64:mime_decode(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
 
190
    %% No pad
 
191
    <<"Aladdin:open sesam">> =
 
192
        base64:mime_decode("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
 
193
    %% Encoded base 64 strings may be divided by non base 64 chars.
 
194
    %% In this cases whitespaces.
 
195
    <<"0123456789!@#0^&*();:<>,. []{}">> =
 
196
        base64:mime_decode(
 
197
          <<"MDEy MzQ1Njc4 \tOSFAIzBeJ \nio)(oKTs6 PD4sLi \r\nBbXXt9">>),
 
198
    ok.
 
199
 
 
200
%%-------------------------------------------------------------------------
 
201
 
 
202
%% Repeat of mime_decode() tests
 
203
mime_decode_to_string(doc) ->
 
204
    ["Test base64:mime_decode_to_string/1."];
 
205
mime_decode_to_string(suite) ->
 
206
    [];
 
207
mime_decode_to_string(Config) when is_list(Config) ->
 
208
    %% Test correct padding
 
209
    "one" = base64:mime_decode_to_string(<<"b25l">>),
 
210
    "on"  = base64:mime_decode_to_string(<<"b24=">>),
 
211
    "o"   = base64:mime_decode_to_string(<<"bw==">>),
 
212
    %% Test 1 extra padding
 
213
    "one" = base64:mime_decode_to_string(<<"b25l= =">>),
 
214
    "on"  = base64:mime_decode_to_string(<<"b24== =">>),
 
215
    "o"   = base64:mime_decode_to_string(<<"bw=== =">>),
 
216
    %% Test 2 extra padding
 
217
    "one" = base64:mime_decode_to_string(<<"b25l===">>),
 
218
    "on"  = base64:mime_decode_to_string(<<"b24====">>),
 
219
    "o"   = base64:mime_decode_to_string(<<"bw=====">>),
 
220
    %% Test misc embedded padding
 
221
    "one" = base64:mime_decode_to_string(<<"b2=5l===">>),
 
222
    "on"  = base64:mime_decode_to_string(<<"b=24====">>),
 
223
    "o"   = base64:mime_decode_to_string(<<"b=w=====">>),
 
224
    %% Test misc white space and illegals with embedded padding
 
225
    "one" = base64:mime_decode_to_string(<<" b~2=\r\n5()l===">>),
 
226
    "on"  = base64:mime_decode_to_string(<<"\tb =2\"�4=�=   ==">>),
 
227
    "o"   = base64:mime_decode_to_string(<<"\nb=w=====">>),
 
228
    %% Two pads
 
229
    "Aladdin:open sesame" =
 
230
        base64:mime_decode_to_string("QWxhZGRpbjpvc()GVuIHNlc2FtZQ=="),
 
231
    %% One pad to ignore, followed by more text
 
232
    "Hello World!!" = base64:mime_decode_to_string(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
151
233
    %% No pad
152
234
    "Aladdin:open sesam" = 
153
235
        base64:mime_decode_to_string("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
154
 
 
155
236
    %% Encoded base 64 strings may be divided by non base 64 chars.
156
237
    %% In this cases whitespaces.
157
238
    "0123456789!@#0^&*();:<>,. []{}" =
159
240
          <<"MDEy MzQ1Njc4 \tOSFAIzBeJ \nio)(oKTs6 PD4sLi \r\nBbXXt9">>),
160
241
    ok.
161
242
 
 
243
%%-------------------------------------------------------------------------
162
244
 
163
245
roundtrip(Config) when is_list(Config) ->
164
246
    Sizes = lists:seq(1, 255) ++ lists:seq(2400-5, 2440),