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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/filelib.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 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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
-module(filelib).
20
20
 
21
21
%% File utilities.
22
22
 
 
23
%% Avoid warning for local function error/1 clashing with autoimported BIF.
 
24
-compile({no_auto_import,[error/1]}).
23
25
-export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1, 
24
26
         compile_wildcard/1]).
25
27
-export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1]).
40
42
 
41
43
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
42
44
 
43
 
-spec wildcard(name()) -> [file:filename()].
 
45
-spec wildcard(file:name()) -> [file:filename()].
44
46
wildcard(Pattern) when is_list(Pattern) ->
45
47
    ?HANDLE_ERROR(do_wildcard(Pattern, file)).
46
48
 
47
 
-spec wildcard(name(), name() | atom()) -> [file:filename()].
48
 
wildcard(Pattern, Cwd) when is_list(Pattern), is_list(Cwd) ->
 
49
-spec wildcard(file:name(), file:name() | atom()) -> [file:filename()].
 
50
wildcard(Pattern, Cwd) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) ->
49
51
    ?HANDLE_ERROR(do_wildcard(Pattern, Cwd, file));
50
52
wildcard(Pattern, Mod) when is_list(Pattern), is_atom(Mod) ->
51
53
    ?HANDLE_ERROR(do_wildcard(Pattern, Mod)).
52
54
 
53
 
-spec wildcard(name(), name(), atom()) -> [file:filename()].
 
55
-spec wildcard(file:name(), file:name(), atom()) -> [file:filename()].
54
56
wildcard(Pattern, Cwd, Mod)
55
 
  when is_list(Pattern), is_list(Cwd), is_atom(Mod) ->
 
57
  when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)), is_atom(Mod) ->
56
58
    ?HANDLE_ERROR(do_wildcard(Pattern, Cwd, Mod)).
57
59
 
58
 
-spec is_dir(name()) -> boolean().
 
60
-spec is_dir(file:name()) -> boolean().
59
61
is_dir(Dir) ->
60
62
    do_is_dir(Dir, file).
61
63
 
62
 
-spec is_dir(name(), atom()) -> boolean().
 
64
-spec is_dir(file:name(), atom()) -> boolean().
63
65
is_dir(Dir, Mod) when is_atom(Mod) ->
64
66
    do_is_dir(Dir, Mod).
65
67
 
66
 
-spec is_file(name()) -> boolean().
 
68
-spec is_file(file:name()) -> boolean().
67
69
is_file(File) ->
68
70
    do_is_file(File, file).
69
71
 
70
 
-spec is_file(name(), atom()) -> boolean().
 
72
-spec is_file(file:name(), atom()) -> boolean().
71
73
is_file(File, Mod) when is_atom(Mod) ->
72
74
    do_is_file(File, Mod).
73
75
 
74
 
-spec is_regular(name()) -> boolean().
 
76
-spec is_regular(file:name()) -> boolean().
75
77
is_regular(File) ->
76
78
    do_is_regular(File, file).
77
79
    
78
 
-spec is_regular(name(), atom()) -> boolean().
 
80
-spec is_regular(file:name(), atom()) -> boolean().
79
81
is_regular(File, Mod) when is_atom(Mod) ->
80
82
    do_is_regular(File, Mod).
81
83
    
82
 
-spec fold_files(name(), string(), boolean(), fun((_,_) -> _), _) -> _.
 
84
-spec fold_files(file:name(), string(), boolean(), fun((_,_) -> _), _) -> _.
83
85
fold_files(Dir, RegExp, Recursive, Fun, Acc) ->
84
86
    do_fold_files(Dir, RegExp, Recursive, Fun, Acc, file).
85
87
 
86
 
-spec fold_files(name(), string(), boolean(), fun((_,_) -> _), _, atom()) -> _.
 
88
-spec fold_files(file:name(), string(), boolean(), fun((_,_) -> _), _, atom()) -> _.
87
89
fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod) when is_atom(Mod) ->
88
90
    do_fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod).
89
91
 
90
 
-spec last_modified(name()) -> date_time() | 0.
 
92
-spec last_modified(file:name()) -> file:date_time() | 0.
91
93
last_modified(File) ->
92
94
    do_last_modified(File, file).
93
95
 
94
 
-spec last_modified(name(), atom()) -> date_time() | 0.
 
96
-spec last_modified(file:name(), atom()) -> file:date_time() | 0.
95
97
last_modified(File, Mod) when is_atom(Mod) ->
96
98
    do_last_modified(File, Mod).
97
99
 
98
 
-spec file_size(name()) -> non_neg_integer().
 
100
-spec file_size(file:name()) -> non_neg_integer().
99
101
file_size(File) ->
100
102
    do_file_size(File, file).
101
103
 
102
 
-spec file_size(name(), atom()) -> non_neg_integer().
 
104
-spec file_size(file:name(), atom()) -> non_neg_integer().
103
105
file_size(File, Mod) when is_atom(Mod) ->
104
106
    do_file_size(File, Mod).
105
107
 
116
118
do_wildcard_comp({compiled_wildcard,[Base|Rest]}, Mod) ->
117
119
    do_wildcard_1([Base], Rest, Mod).
118
120
 
119
 
do_wildcard(Pattern, Cwd, Mod) when is_list(Pattern), is_list(Cwd) ->
 
121
do_wildcard(Pattern, Cwd, Mod) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) ->
120
122
    do_wildcard_comp(do_compile_wildcard(Pattern), Cwd, Mod).
121
123
 
122
124
do_wildcard_comp({compiled_wildcard,{exists,File}}, Cwd, Mod) ->
125
127
        _ -> []
126
128
    end;
127
129
do_wildcard_comp({compiled_wildcard,[current|Rest]}, Cwd0, Mod) ->
128
 
    Cwd = filename:join([Cwd0]),                %Slash away redundant slashes.
129
 
    PrefixLen = length(Cwd)+1,
130
 
    [lists:nthtail(PrefixLen, N) || N <- do_wildcard_1([Cwd], Rest, Mod)];
 
130
    {Cwd,PrefixLen} = case filename:join([Cwd0]) of
 
131
              Bin when is_binary(Bin) -> {Bin,byte_size(Bin)+1};
 
132
              Other -> {Other,length(Other)+1}
 
133
          end,          %Slash away redundant slashes.
 
134
    [
 
135
     if 
 
136
         is_binary(N) ->
 
137
             <<_:PrefixLen/binary,Res/binary>> = N,
 
138
             Res;
 
139
         true ->
 
140
             lists:nthtail(PrefixLen, N)
 
141
     end || N <- do_wildcard_1([Cwd], Rest, Mod)];
131
142
do_wildcard_comp({compiled_wildcard,[Base|Rest]}, _Cwd, Mod) ->
132
143
    do_wildcard_1([Base], Rest, Mod).
133
144
 
164
175
%%   If <Recursive> is true all sub-directories to <Dir> are processed
165
176
 
166
177
do_fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod) ->
167
 
    {ok, Re1} = re:compile(RegExp),
168
 
    do_fold_files1(Dir, Re1, Recursive, Fun, Acc, Mod).
 
178
    {ok, Re1} = re:compile(RegExp,[unicode]),
 
179
    do_fold_files1(Dir, Re1, RegExp, Recursive, Fun, Acc, Mod).
169
180
 
170
 
do_fold_files1(Dir, RegExp, Recursive, Fun, Acc, Mod) ->
 
181
do_fold_files1(Dir, RegExp, OrigRE, Recursive, Fun, Acc, Mod) ->
171
182
    case eval_list_dir(Dir, Mod) of
172
 
        {ok, Files} -> do_fold_files2(Files, Dir, RegExp, Recursive, Fun, Acc, Mod);
 
183
        {ok, Files} -> do_fold_files2(Files, Dir, RegExp, OrigRE,
 
184
                                      Recursive, Fun, Acc, Mod);
173
185
        {error, _}  -> Acc
174
186
    end.
175
187
 
176
 
do_fold_files2([], _Dir, _RegExp, _Recursive, _Fun, Acc, _Mod) -> 
 
188
%% OrigRE is not to be compiled as it's for non conforming filenames,
 
189
%% i.e. for filenames that does not comply to the current encoding, which should
 
190
%% be very rare. We use it only in those cases and do not want to precompile.
 
191
do_fold_files2([], _Dir, _RegExp, _OrigRE, _Recursive, _Fun, Acc, _Mod) -> 
177
192
    Acc;
178
 
do_fold_files2([File|T], Dir, RegExp, Recursive, Fun, Acc0, Mod) ->
 
193
do_fold_files2([File|T], Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod) ->
179
194
    FullName = filename:join(Dir, File),
180
195
    case do_is_regular(FullName, Mod) of
181
196
        true  ->
182
 
            case re:run(File, RegExp, [{capture,none}]) of
 
197
            case (catch re:run(File, if is_binary(File) -> OrigRE; 
 
198
                                        true -> RegExp end, 
 
199
                               [{capture,none}])) of
183
200
                match  -> 
184
201
                    Acc = Fun(FullName, Acc0),
185
 
                    do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc, Mod);
 
202
                    do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc, Mod);
 
203
                {'EXIT',_} ->
 
204
                    do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod);
186
205
                nomatch ->
187
 
                    do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc0, Mod)
 
206
                    do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod)
188
207
            end;
189
208
        false ->
190
209
            case Recursive andalso do_is_dir(FullName, Mod) of
191
210
                true ->
192
 
                    Acc1 = do_fold_files1(FullName, RegExp, Recursive,
 
211
                    Acc1 = do_fold_files1(FullName, RegExp, OrigRE, Recursive,
193
212
                                          Fun, Acc0, Mod),
194
 
                    do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc1, Mod);
 
213
                    do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc1, Mod);
195
214
                false ->
196
 
                    do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc0, Mod)
 
215
                    do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod)
197
216
            end
198
217
    end.
199
218
 
218
237
%% +type X = filename() | dirname()
219
238
%% ensures that the directory name required to create D exists
220
239
 
221
 
-spec ensure_dir(name()) -> 'ok' | {'error', posix()}.
 
240
-spec ensure_dir(file:name()) -> 'ok' | {'error', file:posix()}.
222
241
ensure_dir("/") ->
223
242
    ok;
224
243
ensure_dir(F) ->
228
247
            ok;
229
248
        false ->
230
249
            ensure_dir(Dir),
231
 
            file:make_dir(Dir)
 
250
            case file:make_dir(Dir) of
 
251
                {error,eexist}=EExist ->
 
252
                    case do_is_dir(Dir, file) of
 
253
                        true ->
 
254
                            ok;
 
255
                        false ->
 
256
                            EExist
 
257
                    end;
 
258
                Err ->
 
259
                    Err
 
260
            end
232
261
    end.
233
262
 
234
263
 
256
285
do_wildcard_3(Base, [], Result, _Mod) ->
257
286
    [Base|Result].
258
287
 
 
288
wildcard_4(Pattern, [File|Rest], Base, Result) when is_binary(File) ->
 
289
    case wildcard_5(Pattern, binary_to_list(File)) of
 
290
        true ->
 
291
            wildcard_4(Pattern, Rest, Base, [join(Base, File)|Result]);
 
292
        false ->
 
293
            wildcard_4(Pattern, Rest, Base, Result)
 
294
    end;
259
295
wildcard_4(Pattern, [File|Rest], Base, Result) ->
260
296
    case wildcard_5(Pattern, File) of
261
297
        true ->