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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2005-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2005-2010. 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
 
21
21
 
22
22
-export([all/1,init_per_testcase/2,fin_per_testcase/2,
23
23
         wildcard_one/1,wildcard_two/1,wildcard_errors/1,
24
 
         fold_files/1,otp_5960/1]).
 
24
         fold_files/1,otp_5960/1,ensure_dir_eexist/1]).
25
25
 
26
26
-import(lists, [foreach/2]).
27
27
 
38
38
    ok.
39
39
 
40
40
all(suite) ->
41
 
    [wildcard_one,wildcard_two,wildcard_errors,fold_files,otp_5960].
 
41
    [wildcard_one,wildcard_two,wildcard_errors,fold_files,otp_5960,
 
42
     ensure_dir_eexist].
42
43
 
43
44
wildcard_one(Config) when is_list(Config) ->
44
45
    ?line {ok,OldCwd} = file:get_cwd(),
223
224
    ?line Name1 = filename:join(Dir, name1),
224
225
    ?line Name2 = filename:join(Dir, name2),
225
226
    ?line ok = filelib:ensure_dir(Name1), % parent is created
 
227
    ?line ok = filelib:ensure_dir(Name1), % repeating it should be OK
226
228
    ?line ok = filelib:ensure_dir(Name2), % parent already exists
 
229
    ?line ok = filelib:ensure_dir(Name2), % repeating it should be OK
227
230
    ?line Name3 = filename:join(Name1, name3),
228
231
    ?line {ok, FileInfo} = file:read_file_info(Dir),
229
232
    case os:type() of
239
242
            ?line ok = file:write_file_info(Dir, #file_info{mode=Mode}),
240
243
            ok
241
244
    end.
 
245
 
 
246
ensure_dir_eexist(Config) when is_list(Config) ->
 
247
    ?line PrivDir = ?config(priv_dir, Config),
 
248
    ?line Dir = filename:join(PrivDir, ensure_dir_eexist),
 
249
    ?line Name = filename:join(Dir, "same_name_as_file_and_dir"),
 
250
    ?line ok = filelib:ensure_dir(Name),
 
251
    ?line ok = file:write_file(Name, <<"some string\n">>),
 
252
 
 
253
    %% There already is a file with the name of the directory
 
254
    %% we want to create.
 
255
    ?line NeedFile = filename:join(Name, "file"),
 
256
    ?line {error, eexist} = filelib:ensure_dir(NeedFile),
 
257
    ok.