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

« back to all changes in this revision

Viewing changes to lib/kernel/test/prim_file_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
 
%% 
4
 
%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2000-2011. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(prim_file_SUITE).
20
 
-export([all/1,
21
 
        init/1, fini/1,
22
 
        read_write_file/1, dirs/1, files/1]).
 
20
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
21
         init_per_group/2,end_per_group/2,
 
22
         read_write_file/1]).
23
23
-export([cur_dir_0a/1, cur_dir_0b/1, 
24
24
         cur_dir_1a/1, cur_dir_1b/1, 
25
25
         make_del_dir_a/1, make_del_dir_b/1,
26
 
         pos/1, pos1/1, pos2/1]).
 
26
         pos1/1, pos2/1]).
27
27
-export([close/1, 
28
28
         delete_a/1, delete_b/1]).
29
 
-export([open/1, open1/1, modes/1]).
30
 
-export([file_info/1, 
31
 
         file_info_basic_file_a/1, file_info_basic_file_b/1,
32
 
         file_info_basic_directory_a/1, file_info_basic_directory_b/1,
33
 
         file_info_bad_a/1, file_info_bad_b/1, 
34
 
         file_info_times_a/1, file_info_times_b/1, 
35
 
         file_write_file_info_a/1, file_write_file_info_b/1]).
 
29
-export([ open1/1, modes/1]).
 
30
-export([ 
 
31
          file_info_basic_file_a/1, file_info_basic_file_b/1,
 
32
          file_info_basic_directory_a/1, file_info_basic_directory_b/1,
 
33
          file_info_bad_a/1, file_info_bad_b/1, 
 
34
          file_info_times_a/1, file_info_times_b/1, 
 
35
          file_write_file_info_a/1, file_write_file_info_b/1]).
36
36
-export([rename_a/1, rename_b/1, 
37
 
         access/1, truncate/1, sync/1,
38
 
         read_write/1, pread_write/1, append/1]).
39
 
-export([errors/1, e_delete/1, e_rename/1, e_make_dir/1, e_del_dir/1]).
40
 
 
41
 
-export([compression/1, read_not_really_compressed/1,
42
 
         read_compressed/1, write_compressed/1,
43
 
         compress_errors/1]).
44
 
 
45
 
-export([links/1, 
46
 
         make_link_a/1, make_link_b/1,
47
 
         read_link_info_for_non_link/1, 
48
 
         symlinks_a/1, symlinks_b/1,
49
 
         list_dir_limit/1]).
50
 
 
51
 
-include("test_server.hrl").
 
37
         access/1, truncate/1, datasync/1, sync/1,
 
38
         read_write/1, pread_write/1, append/1, exclusive/1]).
 
39
-export([ e_delete/1, e_rename/1, e_make_dir/1, e_del_dir/1]).
 
40
 
 
41
-export([ read_not_really_compressed/1,
 
42
          read_compressed/1, write_compressed/1,
 
43
          compress_errors/1]).
 
44
 
 
45
-export([ 
 
46
          make_link_a/1, make_link_b/1,
 
47
          read_link_info_for_non_link/1, 
 
48
          symlinks_a/1, symlinks_b/1,
 
49
          list_dir_limit/1]).
 
50
 
 
51
-export([advise/1]).
 
52
 
 
53
-include_lib("test_server/include/test_server.hrl").
52
54
-include_lib("kernel/include/file.hrl").
53
55
 
54
56
-define(PRIM_FILE, prim_file).
65
67
            _ ->  apply(?PRIM_FILE, F, [H | A])
66
68
        end).
67
69
 
68
 
all(suite) -> {req, [kernel],
69
 
               {conf, init,
70
 
                [read_write_file, dirs, files, 
71
 
                 delete_a, delete_b, rename_a, rename_b, errors,
72
 
                 compression, links, list_dir_limit],
73
 
                fini}}.
74
 
 
75
 
init(Config) when is_list(Config) ->
 
70
suite() -> [{ct_hooks,[ts_install_cth]}].
 
71
 
 
72
all() -> 
 
73
    [read_write_file, {group, dirs}, {group, files},
 
74
     delete_a, delete_b, rename_a, rename_b, {group, errors},
 
75
     {group, compression}, {group, links}, list_dir_limit].
 
76
 
 
77
groups() -> 
 
78
    [{dirs, [],
 
79
      [make_del_dir_a, make_del_dir_b, cur_dir_0a, cur_dir_0b,
 
80
       cur_dir_1a, cur_dir_1b]},
 
81
     {files, [],
 
82
      [{group, open}, {group, pos}, {group, file_info},
 
83
       truncate, sync, datasync, advise]},
 
84
     {open, [],
 
85
      [open1, modes, close, access, read_write, pread_write,
 
86
       append, exclusive]},
 
87
     {pos, [], [pos1, pos2]},
 
88
     {file_info, [],
 
89
      [file_info_basic_file_a, file_info_basic_file_b,
 
90
       file_info_basic_directory_a,
 
91
       file_info_basic_directory_b, file_info_bad_a,
 
92
       file_info_bad_b, file_info_times_a, file_info_times_b,
 
93
       file_write_file_info_a, file_write_file_info_b]},
 
94
     {errors, [],
 
95
      [e_delete, e_rename, e_make_dir, e_del_dir]},
 
96
     {compression, [],
 
97
      [read_compressed, read_not_really_compressed,
 
98
       write_compressed, compress_errors]},
 
99
     {links, [],
 
100
      [make_link_a, make_link_b, read_link_info_for_non_link,
 
101
       symlinks_a, symlinks_b]}].
 
102
 
 
103
init_per_group(_GroupName, Config) ->
 
104
    Config.
 
105
 
 
106
end_per_group(_GroupName, Config) ->
 
107
    Config.
 
108
 
 
109
 
 
110
init_per_suite(Config) when is_list(Config) ->
76
111
    case os:type() of
77
112
        {win32, _} ->
78
113
            Priv = ?config(priv_dir, Config),
89
124
            Config
90
125
    end.
91
126
 
92
 
fini(Config) when is_list(Config) ->
 
127
end_per_suite(Config) when is_list(Config) ->
93
128
    case os:type() of
94
129
        {win32, _} ->
95
130
            os:cmd("subst z: /d");
188
223
 
189
224
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
190
225
 
191
 
dirs(suite) -> [make_del_dir_a, make_del_dir_b, 
192
 
                cur_dir_0a, cur_dir_0b, 
193
 
                cur_dir_1a, cur_dir_1b].
194
226
 
195
227
make_del_dir_a(suite) -> [];
196
228
make_del_dir_a(doc) -> [];
243
275
    %% Try deleting some bad directories
244
276
    %% Deleting the parent directory to the current, sounds dangerous, huh?
245
277
    %% Don't worry ;-) the parent directory should never be empty, right?
246
 
    ?line {error, eexist} = ?PRIM_FILE_call(del_dir, Handle, [".."]),
 
278
    case ?PRIM_FILE_call(del_dir, Handle, [".."]) of
 
279
        {error, eexist} -> ok;
 
280
        {error, einval} -> ok           %FreeBSD
 
281
    end,
247
282
    ?line {error, enoent} = ?PRIM_FILE_call(del_dir, Handle, [""]),
248
283
    ?line {error, badarg} = ?PRIM_FILE_call(del_dir, Handle, [[3,2,1,{}]]),
249
284
 
377
412
 
378
413
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
379
414
 
380
 
files(suite) -> [open,pos,file_info,truncate,sync].
381
415
 
382
 
open(suite) -> [open1,modes,close,access,read_write,
383
 
               pread_write,append].
384
416
 
385
417
open1(suite) -> [];
386
418
open1(doc) -> [];
605
637
    ?line test_server:timetrap_cancel(Dog),
606
638
    ok.
607
639
 
 
640
exclusive(suite) -> [];
 
641
exclusive(doc) -> "Test exclusive access to a file.";
 
642
exclusive(Config) when is_list(Config) ->
 
643
    ?line Dog = test_server:timetrap(test_server:seconds(5)),
 
644
    ?line RootDir = ?config(priv_dir,Config),
 
645
    ?line NewDir = filename:join(RootDir,
 
646
                                 atom_to_list(?MODULE)
 
647
                                 ++"_exclusive"),
 
648
    ?line ok = ?PRIM_FILE:make_dir(NewDir),
 
649
    ?line Name = filename:join(NewDir, "ex_file.txt"),
 
650
    ?line {ok,Fd} = ?PRIM_FILE:open(Name, [write, exclusive]),
 
651
    ?line {error, eexist} = ?PRIM_FILE:open(Name, [write, exclusive]),
 
652
    ?line ok = ?PRIM_FILE:close(Fd),
 
653
    ?line test_server:timetrap_cancel(Dog),
 
654
    ok.
 
655
 
608
656
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
609
657
 
610
 
pos(suite) -> [pos1,pos2].
611
658
 
612
659
pos1(suite) -> [];
613
660
pos1(doc) -> [];
695
742
    ?line test_server:timetrap_cancel(Dog),
696
743
    ok.
697
744
 
698
 
file_info(suite) -> [file_info_basic_file_a, file_info_basic_file_b,
699
 
                     file_info_basic_directory_a, 
700
 
                     file_info_basic_directory_b,
701
 
                     file_info_bad_a, file_info_bad_b, 
702
 
                     file_info_times_a, file_info_times_b, 
703
 
                     file_write_file_info_a, file_write_file_info_b].
704
745
 
705
746
file_info_basic_file_a(suite) -> [];
706
747
file_info_basic_file_a(doc) -> [];
1061
1102
    ok.
1062
1103
 
1063
1104
 
 
1105
datasync(suite) -> [];
 
1106
datasync(doc) -> "Tests that ?PRIM_FILE:datasync/1 at least doesn't crash.";
 
1107
datasync(Config) when is_list(Config) ->
 
1108
    ?line Dog = test_server:timetrap(test_server:seconds(5)),
 
1109
    ?line PrivDir = ?config(priv_dir, Config),
 
1110
    ?line Sync = filename:join(PrivDir,
 
1111
                               atom_to_list(?MODULE)
 
1112
                               ++"_sync.fil"),
 
1113
 
 
1114
    %% Raw open.
 
1115
    ?line {ok, Fd} = ?PRIM_FILE:open(Sync, [write]),
 
1116
    ?line ok = ?PRIM_FILE:datasync(Fd),
 
1117
    ?line ok = ?PRIM_FILE:close(Fd),
 
1118
 
 
1119
    ?line test_server:timetrap_cancel(Dog),
 
1120
    ok.
 
1121
 
 
1122
 
1064
1123
sync(suite) -> [];
1065
1124
sync(doc) -> "Tests that ?PRIM_FILE:sync/1 at least doesn't crash.";
1066
1125
sync(Config) when is_list(Config) ->
1079
1138
    ok.
1080
1139
 
1081
1140
 
 
1141
advise(suite) -> [];
 
1142
advise(doc) -> "Tests that ?PRIM_FILE:advise/4 at least doesn't crash.";
 
1143
advise(Config) when is_list(Config) ->
 
1144
    ?line Dog = test_server:timetrap(test_server:seconds(5)),
 
1145
    ?line PrivDir = ?config(priv_dir, Config),
 
1146
    ?line Advise = filename:join(PrivDir,
 
1147
                               atom_to_list(?MODULE)
 
1148
                               ++"_advise.fil"),
 
1149
 
 
1150
    Line1 = "Hello\n",
 
1151
    Line2 = "World!\n",
 
1152
 
 
1153
    ?line {ok, Fd} = ?PRIM_FILE:open(Advise, [write]),
 
1154
    ?line ok = ?PRIM_FILE:advise(Fd, 0, 0, normal),
 
1155
    ?line ok = ?PRIM_FILE:write(Fd, Line1),
 
1156
    ?line ok = ?PRIM_FILE:write(Fd, Line2),
 
1157
    ?line ok = ?PRIM_FILE:close(Fd),
 
1158
 
 
1159
    ?line {ok, Fd2} = ?PRIM_FILE:open(Advise, [write]),
 
1160
    ?line ok = ?PRIM_FILE:advise(Fd2, 0, 0, random),
 
1161
    ?line ok = ?PRIM_FILE:write(Fd2, Line1),
 
1162
    ?line ok = ?PRIM_FILE:write(Fd2, Line2),
 
1163
    ?line ok = ?PRIM_FILE:close(Fd2),
 
1164
 
 
1165
    ?line {ok, Fd3} = ?PRIM_FILE:open(Advise, [write]),
 
1166
    ?line ok = ?PRIM_FILE:advise(Fd3, 0, 0, sequential),
 
1167
    ?line ok = ?PRIM_FILE:write(Fd3, Line1),
 
1168
    ?line ok = ?PRIM_FILE:write(Fd3, Line2),
 
1169
    ?line ok = ?PRIM_FILE:close(Fd3),
 
1170
 
 
1171
    ?line {ok, Fd4} = ?PRIM_FILE:open(Advise, [write]),
 
1172
    ?line ok = ?PRIM_FILE:advise(Fd4, 0, 0, will_need),
 
1173
    ?line ok = ?PRIM_FILE:write(Fd4, Line1),
 
1174
    ?line ok = ?PRIM_FILE:write(Fd4, Line2),
 
1175
    ?line ok = ?PRIM_FILE:close(Fd4),
 
1176
 
 
1177
    ?line {ok, Fd5} = ?PRIM_FILE:open(Advise, [write]),
 
1178
    ?line ok = ?PRIM_FILE:advise(Fd5, 0, 0, dont_need),
 
1179
    ?line ok = ?PRIM_FILE:write(Fd5, Line1),
 
1180
    ?line ok = ?PRIM_FILE:write(Fd5, Line2),
 
1181
    ?line ok = ?PRIM_FILE:close(Fd5),
 
1182
 
 
1183
    ?line {ok, Fd6} = ?PRIM_FILE:open(Advise, [write]),
 
1184
    ?line ok = ?PRIM_FILE:advise(Fd6, 0, 0, no_reuse),
 
1185
    ?line ok = ?PRIM_FILE:write(Fd6, Line1),
 
1186
    ?line ok = ?PRIM_FILE:write(Fd6, Line2),
 
1187
    ?line ok = ?PRIM_FILE:close(Fd6),
 
1188
 
 
1189
    ?line {ok, Fd7} = ?PRIM_FILE:open(Advise, [write]),
 
1190
    ?line {error, einval} = ?PRIM_FILE:advise(Fd7, 0, 0, bad_advise),
 
1191
    ?line ok = ?PRIM_FILE:close(Fd7),
 
1192
 
 
1193
    %% test write without advise, then a read after an advise
 
1194
    ?line {ok, Fd8} = ?PRIM_FILE:open(Advise, [write]),
 
1195
    ?line ok = ?PRIM_FILE:write(Fd8, Line1),
 
1196
    ?line ok = ?PRIM_FILE:write(Fd8, Line2),
 
1197
    ?line ok = ?PRIM_FILE:close(Fd8),
 
1198
    ?line {ok, Fd9} = ?PRIM_FILE:open(Advise, [read]),
 
1199
    Offset = 0,
 
1200
    %% same as a 0 length in some implementations
 
1201
    Length = length(Line1) + length(Line2),
 
1202
    ?line ok = ?PRIM_FILE:advise(Fd9, Offset, Length, sequential),
 
1203
    ?line {ok, Line1} = ?PRIM_FILE:read_line(Fd9),
 
1204
    ?line {ok, Line2} = ?PRIM_FILE:read_line(Fd9),
 
1205
    ?line eof = ?PRIM_FILE:read_line(Fd9),
 
1206
    ?line ok = ?PRIM_FILE:close(Fd9),
 
1207
 
 
1208
    ?line test_server:timetrap_cancel(Dog),
 
1209
    ok.
 
1210
 
 
1211
 
1082
1212
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1083
1213
 
1084
1214
delete_a(suite) -> [];
1188
1318
 
1189
1319
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1190
1320
 
1191
 
errors(suite) -> [e_delete, e_rename, e_make_dir, e_del_dir].
1192
1321
 
1193
1322
e_delete(suite) -> [];
1194
1323
e_delete(doc) -> [];
1440
1569
    ?line test_server:timetrap_cancel(Dog),
1441
1570
    ok.
1442
1571
 
1443
 
compression(suite) -> [read_compressed, read_not_really_compressed,
1444
 
                       write_compressed, compress_errors].
1445
1572
 
1446
1573
%% Trying reading and positioning from a compressed file.
1447
1574
 
1594
1721
    ?line test_server:timetrap_cancel(Dog),
1595
1722
    ok.
1596
1723
 
1597
 
links(doc) -> "Test the link functions.";
1598
 
links(suite) -> 
1599
 
    [make_link_a, make_link_b, 
1600
 
     read_link_info_for_non_link, 
1601
 
     symlinks_a, symlinks_b].
1602
1724
 
1603
1725
make_link_a(doc) -> "Test creating a hard link.";
1604
1726
make_link_a(suite) -> [];