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

« back to all changes in this revision

Viewing changes to lib/kernel/src/file.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 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-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(file).
36
36
%% Specialized
37
37
-export([ipread_s32bu_p32bu/3]).
38
38
%% Generic file contents.
39
 
-export([open/2, close/1, 
 
39
-export([open/2, close/1, advise/4,
40
40
         read/2, write/2, 
41
41
         pread/2, pread/3, pwrite/2, pwrite/3,
42
42
         read_line/1,
43
 
         position/2, truncate/1, sync/1,
 
43
         position/2, truncate/1, datasync/1, sync/1,
44
44
         copy/2, copy/3]).
45
45
%% High level operations
46
46
-export([consult/1, path_consult/2]).
61
61
 
62
62
-export([ipread_s32bu_p32bu_int/3]).
63
63
 
 
64
%% Types that can be used from other modules -- alphabetically ordered.
 
65
-export_type([date_time/0, fd/0, file_info/0, filename/0, io_device/0,
 
66
              name/0, posix/0]).
64
67
 
65
68
%%% Includes and defines
66
69
-include("file.hrl").
72
75
-define(RAM_FILE, ram_file).           % Module
73
76
 
74
77
%% data types
75
 
-type filename()  :: string().
76
 
-type io_device() :: pid() | #file_descriptor{}.
 
78
-type filename()  :: string() | binary().
 
79
-type file_info() :: #file_info{}.
 
80
-type fd()        :: #file_descriptor{}.
 
81
-type io_device() :: pid() | fd().
77
82
-type location()  :: integer() | {'bof', integer()} | {'cur', integer()}
78
83
                   | {'eof', integer()} | 'bof' | 'cur' | 'eof'.
79
 
-type mode()      :: 'read' | 'write' | 'append' | 'raw' | 'binary' | 
80
 
                     {'delayed_write', non_neg_integer(), non_neg_integer()} | 
81
 
                     'delayed_write' | {'read_ahead', pos_integer()} | 
82
 
                     'read_ahead' | 'compressed'.
 
84
-type mode()      :: 'read' | 'write' | 'append'
 
85
                   | 'exclusive' | 'raw' | 'binary'
 
86
                   | {'delayed_write', non_neg_integer(), non_neg_integer()}
 
87
                   | 'delayed_write' | {'read_ahead', pos_integer()}
 
88
                   | 'read_ahead' | 'compressed'
 
89
                   | {'encoding', unicode:encoding()}.
 
90
-type name()      :: string() | atom() | [name()] | binary().
 
91
-type posix()     :: 'eacces'  | 'eagain'  | 'ebadf'   | 'ebusy'  | 'edquot'
 
92
                   | 'eexist'  | 'efault'  | 'efbig'   | 'eintr'  | 'einval'
 
93
                   | 'eio'     | 'eisdir'  | 'eloop'   | 'emfile' | 'emlink'
 
94
                   | 'enametoolong'
 
95
                   | 'enfile'  | 'enodev'  | 'enoent'  | 'enomem' | 'enospc'
 
96
                   | 'enotblk' | 'enotdir' | 'enotsup' | 'enxio'  | 'eperm'
 
97
                   | 'epipe'   | 'erofs'   | 'espipe'  | 'esrch'  | 'estale'
 
98
                   | 'exdev'.
83
99
-type bindings()  :: any().
84
100
 
 
101
-type date()      :: {pos_integer(), pos_integer(), pos_integer()}.
 
102
-type time()      :: {non_neg_integer(), non_neg_integer(), non_neg_integer()}.
 
103
-type date_time() :: {date(), time()}.
 
104
-type posix_file_advise() :: 'normal' | 'sequential' | 'random'
 
105
                           | 'no_reuse' | 'will_need' | 'dont_need'.
 
106
 
85
107
%%%-----------------------------------------------------------------
86
108
%%% General functions
87
109
 
161
183
del_dir(Name) ->
162
184
    check_and_call(del_dir, [file_name(Name)]).
163
185
 
164
 
-spec read_file_info(Name :: name()) -> {'ok', #file_info{}} | {'error', posix()}.
 
186
-spec read_file_info(Name :: name()) -> {'ok', file_info()} | {'error', posix()}.
165
187
 
166
188
read_file_info(Name) ->
167
189
    check_and_call(read_file_info, [file_name(Name)]).
171
193
altname(Name) ->
172
194
    check_and_call(altname, [file_name(Name)]).
173
195
 
174
 
-spec read_link_info(Name :: name()) -> {'ok', #file_info{}} | {'error', posix()}.
 
196
-spec read_link_info(Name :: name()) -> {'ok', file_info()} | {'error', posix()}.
175
197
 
176
198
read_link_info(Name) ->
177
199
    check_and_call(read_link_info, [file_name(Name)]).
181
203
read_link(Name) ->
182
204
    check_and_call(read_link, [file_name(Name)]).
183
205
 
184
 
-spec write_file_info(Name :: name(), Info :: #file_info{}) ->
 
206
-spec write_file_info(Name :: name(), Info :: file_info()) ->
185
207
        'ok' | {'error', posix()}.
186
208
 
187
209
write_file_info(Name, Info = #file_info{}) ->
192
214
list_dir(Name) ->
193
215
    check_and_call(list_dir, [file_name(Name)]).
194
216
 
195
 
-spec read_file(Name :: name()) -> {'ok', binary()} | {'error', posix()}.
 
217
-spec read_file(Name :: name()) ->
 
218
        {'ok', binary()} | {'error', posix() | 'terminated' | 'system_limit'}.
196
219
 
197
220
read_file(Name) ->
198
221
    check_and_call(read_file, [file_name(Name)]).
207
230
make_symlink(Old, New) ->
208
231
    check_and_call(make_symlink, [file_name(Old), file_name(New)]).
209
232
 
210
 
-spec write_file(Name :: name(), Bin :: binary()) -> 'ok' | {'error', posix()}.
 
233
-spec write_file(Name :: name(), Bin :: iodata()) ->
 
234
        'ok' | {'error', posix() | 'terminated' | 'system_limit'}.
211
235
 
212
236
write_file(Name, Bin) ->
213
237
    check_and_call(write_file, [file_name(Name), make_binary(Bin)]).
214
238
 
215
239
%% This whole operation should be moved to the file_server and prim_file
216
240
%% when it is time to change file server protocol again.
217
 
%% Meanwhile, it is implemented here, slihtly less efficient.
218
 
%%
 
241
%% Meanwhile, it is implemented here, slightly less efficient.
219
242
 
220
 
-spec write_file(Name :: name(), Bin :: binary(), Modes :: [mode()]) -> 
 
243
-spec write_file(Name :: name(), Bin :: iodata(), Modes :: [mode()]) ->
221
244
        'ok' | {'error', posix()}.
222
245
 
223
246
write_file(Name, Bin, ModeList) when is_list(ModeList) ->
273
296
%% Contemporary mode specification - list of options
274
297
 
275
298
-spec open(Name :: name(), Modes :: [mode()]) ->
276
 
        {'ok', io_device()} | {'error', posix()}.
 
299
        {'ok', io_device()} | {'error', posix() | 'system_limit'}.
277
300
 
278
301
open(Item, ModeList) when is_list(ModeList) ->
279
302
    case lists:member(raw, ModeList) of
326
349
%%% The File argument must be either a Pid or a handle 
327
350
%%% returned from ?PRIM_FILE:open.
328
351
 
329
 
-spec close(File :: io_device()) -> 'ok' | {'error', posix()}.
 
352
-spec close(File :: io_device()) -> 'ok' | {'error', posix() | 'terminated'}.
330
353
 
331
354
close(File) when is_pid(File) ->
332
355
    R = file_request(File, close),
344
367
close(_) ->
345
368
    {error, badarg}.
346
369
 
347
 
-spec read(File :: io_device(), Size :: non_neg_integer()) ->
 
370
-spec advise(File :: io_device(), Offset :: integer(),
 
371
             Length :: integer(), Advise :: posix_file_advise()) ->
 
372
        'ok' | {'error', posix()}.
 
373
 
 
374
advise(File, Offset, Length, Advise) when is_pid(File) ->
 
375
    R = file_request(File, {advise, Offset, Length, Advise}),
 
376
    wait_file_reply(File, R);
 
377
advise(#file_descriptor{module = Module} = Handle, Offset, Length, Advise) ->
 
378
    Module:advise(Handle, Offset, Length, Advise);
 
379
advise(_, _, _, _) ->
 
380
    {error, badarg}.
 
381
 
 
382
-spec read(File :: io_device() | atom(), Size :: non_neg_integer()) ->
348
383
        'eof' | {'ok', [char()] | binary()} | {'error', posix()}.
349
384
 
350
 
read(File, Sz) when is_pid(File), is_integer(Sz), Sz >= 0 ->
 
385
read(File, Sz) when (is_pid(File) orelse is_atom(File)), is_integer(Sz), Sz >= 0 ->
351
386
    case io:request(File, {get_chars, '', Sz}) of
352
387
        Data when is_list(Data); is_binary(Data) ->
353
388
            {ok, Data};
360
395
read(_, _) ->
361
396
    {error, badarg}.
362
397
 
363
 
-spec read_line(File :: io_device()) ->
 
398
-spec read_line(File :: io_device() | atom()) ->
364
399
        'eof' | {'ok', [char()] | binary()} | {'error', posix()}.
365
400
 
366
 
read_line(File) when is_pid(File) ->
 
401
read_line(File) when (is_pid(File) orelse is_atom(File)) ->
367
402
    case io:request(File, {get_line, ''}) of
368
403
        Data when is_list(Data); is_binary(Data) ->
369
404
            {ok, Data};
414
449
pread(_, _, _) ->
415
450
    {error, badarg}.
416
451
 
417
 
-spec write(File :: io_device(), Byte :: iodata()) ->
418
 
        'ok' | {'error', posix()}.
 
452
-spec write(File :: io_device() | atom(), Byte :: iodata()) ->
 
453
        'ok' | {'error', posix() | 'terminated'}.
419
454
 
420
 
write(File, Bytes) when is_pid(File) ->
 
455
write(File, Bytes) when (is_pid(File) orelse is_atom(File)) ->
421
456
    case make_binary(Bytes) of
422
457
        Bin when is_binary(Bin) ->
423
458
            io:request(File, {put_chars,Bin});
464
499
pwrite(_, _, _) ->
465
500
    {error, badarg}.
466
501
 
 
502
-spec datasync(File :: io_device()) -> 'ok' | {'error', posix()}.
 
503
 
 
504
datasync(File) when is_pid(File) ->
 
505
    R = file_request(File, datasync),
 
506
    wait_file_reply(File, R);
 
507
datasync(#file_descriptor{module = Module} = Handle) ->
 
508
    Module:datasync(Handle);
 
509
datasync(_) ->
 
510
    {error, badarg}.
 
511
 
467
512
-spec sync(File :: io_device()) -> 'ok' | {'error', posix()}.
468
513
 
469
514
sync(File) when is_pid(File) ->
989
1034
%%      Generates a flat file name from a deep list of atoms and 
990
1035
%%      characters (integers).
991
1036
 
 
1037
file_name(N) when is_binary(N) ->
 
1038
    N;
992
1039
file_name(N) ->
993
1040
    try 
994
 
        file_name_1(N)
 
1041
        file_name_1(N,file:native_name_encoding())
995
1042
    catch Reason ->
996
1043
        {error, Reason}
997
1044
    end.
998
1045
 
999
 
file_name_1([C|T]) when is_integer(C), C > 0, C =< 255 ->
1000
 
    [C|file_name_1(T)];
1001
 
file_name_1([H|T]) ->
1002
 
    file_name_1(H) ++ file_name_1(T);
1003
 
file_name_1([]) ->
 
1046
file_name_1([C|T],latin1) when is_integer(C), C < 256->
 
1047
    [C|file_name_1(T,latin1)];
 
1048
file_name_1([C|T],utf8) when is_integer(C) ->
 
1049
    [C|file_name_1(T,utf8)];
 
1050
file_name_1([H|T],E) ->
 
1051
    file_name_1(H,E) ++ file_name_1(T,E);
 
1052
file_name_1([],_) ->
1004
1053
    [];
1005
 
file_name_1(N) when is_atom(N) ->
 
1054
file_name_1(N,_) when is_atom(N) ->
1006
1055
    atom_to_list(N);
1007
 
file_name_1(_) ->
 
1056
file_name_1(_,_) ->
1008
1057
    throw(badarg).
1009
1058
 
1010
1059
make_binary(Bin) when is_binary(Bin) ->