Skip to content

Commit

Permalink
Merge pull request #7220 from jdamanalo/kernel/file-read-file-raw
Browse files Browse the repository at this point in the history
kernel/file: Add read_file/2

OTP-18589
OTP-18590
  • Loading branch information
jhogberg committed May 22, 2023
2 parents 4ab57f7 + 039a3bd commit 7df46d0
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 5 deletions.
3 changes: 3 additions & 0 deletions lib/kernel/doc/src/file.xml
Original file line number Diff line number Diff line change
Expand Up @@ -1413,13 +1413,16 @@ f.txt: {person, "kalle", 25}.
</func>
<func>
<name name="read_file" arity="1" since=""/>
<name name="read_file" arity="2" since=""/>
<fsummary>Read a file.</fsummary>
<type name="read_file_option"/>
<desc>
<p>Returns <c>{ok, <anno>Binary</anno>}</c>, where
<c><anno>Binary</anno></c> is a binary
data object that contains the contents of
<c><anno>Filename</anno></c>, or
<c>{error, <anno>Reason</anno>}</c> if an error occurs.</p>
<p>If the option <c>raw</c> is set, the file server is not called.</p>
<p>Typical error reasons:</p>
<taglist>
<tag><c>enoent</c></tag>
Expand Down
31 changes: 26 additions & 5 deletions lib/kernel/src/file.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@
read_link_info/1, read_link_info/2,
read_link/1, read_link_all/1,
make_link/2, make_symlink/2,
read_file/1, write_file/2, write_file/3]).
read_file/1, read_file/2,
write_file/2, write_file/3]).
%% Specialized
-export([ipread_s32bu_p32bu/3]).
%% Generic file contents.
Expand Down Expand Up @@ -125,6 +126,7 @@
-type posix_file_advise() :: 'normal' | 'sequential' | 'random'
| 'no_reuse' | 'will_need' | 'dont_need'.
-type delete_option() :: 'raw'.
-type read_file_option() :: 'raw'.
-type sendfile_option() :: {chunk_size, non_neg_integer()}
| {use_threads, boolean()}.
-type file_info_option() :: {'time', 'local'} | {'time', 'universal'}
Expand Down Expand Up @@ -218,15 +220,14 @@ delete(Name) ->
Reason :: posix() | badarg.

delete(Name, Opts) when is_list(Opts) ->
Args = [file_name(Name), Opts],
case check_args(Args) of
FileName = file_name(Name),
case check_args(Opts) of
ok ->
case lists:member(raw, Opts) of
true ->
[FileName|_] = Args,
?PRIM_FILE:delete(FileName);
false ->
call(delete, Args)
call(delete, [FileName])
end;
Error ->
Error
Expand Down Expand Up @@ -418,6 +419,26 @@ list_dir_all(Name) ->
read_file(Name) ->
check_and_call(read_file, [file_name(Name)]).

-spec read_file(Filename, Opts) -> {ok, Binary} | {error, Reason} when
Filename :: name_all(),
Opts :: [read_file_option()],
Binary :: binary(),
Reason :: posix() | badarg | terminated | system_limit.

read_file(Name, Opts) when is_list(Opts) ->
FileName = file_name(Name),
case check_args(Opts) of
ok ->
case lists:member(raw, Opts) of
true ->
?PRIM_FILE:read_file(FileName);
false ->
call(read_file, [FileName])
end;
Error ->
Error
end.

-spec make_link(Existing, New) -> ok | {error, Reason} when
Existing :: name_all(),
New :: name_all(),
Expand Down
23 changes: 23 additions & 0 deletions lib/kernel/test/file_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -535,6 +535,9 @@ read_write_file(Config) when is_list(Config) ->
{error, enoent} = ?FILE_MODULE:read_file(Name2),
{error, enoent} = ?FILE_MODULE:read_file(""),
{error, enoent} = ?FILE_MODULE:read_file(''),
{error, enoent} = ?FILE_MODULE:read_file(Name2, [raw]),
{error, enoent} = ?FILE_MODULE:read_file("", [raw]),
{error, enoent} = ?FILE_MODULE:read_file('', [raw]),

%% Try writing to a bad filename
{error, enoent} = do_read_write_file("", Bin2),
Expand All @@ -559,12 +562,15 @@ do_read_write_file(Name, Data) ->
ok ->
BinData = iolist_to_binary(Data),
{ok,BinData} = ?FILE_MODULE:read_file(Name),
{ok,BinData} = ?FILE_MODULE:read_file(Name, [raw]),

ok = ?FILE_MODULE:write_file(Name, Data, []),
{ok,BinData} = ?FILE_MODULE:read_file(Name),
{ok,BinData} = ?FILE_MODULE:read_file(Name, [raw]),

ok = ?FILE_MODULE:write_file(Name, Data, [raw]),
{ok,BinData} = ?FILE_MODULE:read_file(Name),
{ok,BinData} = ?FILE_MODULE:read_file(Name, [raw]),

ok;
{error,_}=Res ->
Expand Down Expand Up @@ -2333,6 +2339,23 @@ delete(Config) when is_list(Config) ->
{error, _} = ?FILE_MODULE:open(Name2, read),
%% Try deleting a nonexistent file with the raw option
{error, enoent} = ?FILE_MODULE:delete(Name2, [raw]),

Name3 = filename:join(RootDir,
atom_to_list(?MODULE)
++"_delete_3.fil"),
{ok, Fd5} = ?FILE_MODULE:open(Name3, write),
io:format(Fd5,"ok.\n",[]),
ok = ?FILE_MODULE:close(Fd5),
%% Check that the file is readable
{ok, Fd6} = ?FILE_MODULE:open(Name3, read),
ok = ?FILE_MODULE:close(Fd6),
%% Try deleting with no option, should be equivalent to delete/1
ok = ?FILE_MODULE:delete(Name3, []),
%% Check that the file is not readable anymore
{error, _} = ?FILE_MODULE:open(Name3, read),
%% Try deleting a nonexistent file with no option
{error, enoent} = ?FILE_MODULE:delete(Name3, []),

[] = flush(),
ok.

Expand Down

0 comments on commit 7df46d0

Please sign in to comment.