Skip to content

Commit

Permalink
file: copy_file_range
Browse files Browse the repository at this point in the history
  • Loading branch information
RomaniukVadim committed Nov 29, 2023
1 parent 3348e03 commit 91b4350
Show file tree
Hide file tree
Showing 8 changed files with 130 additions and 5 deletions.
82 changes: 82 additions & 0 deletions erts/emulator/nifs/common/prim_file_nif.c
Original file line number Diff line number Diff line change
Expand Up @@ -102,6 +102,9 @@ static ERL_NIF_TERM read_file_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM a
static ERL_NIF_TERM open_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM close_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM argv[]);

static ERL_NIF_TERM copy_file_range_available_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM copy_file_range_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM argv[]);

static ERL_NIF_TERM file_desc_to_ref_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM argv[]);

/* Internal ops */
Expand Down Expand Up @@ -185,6 +188,8 @@ static ErlNifFunc nif_funcs[] = {
{"allocate_nif", 3, allocate_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"advise_nif", 4, advise_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"read_handle_info_nif", 1, read_handle_info_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"copy_file_range_available_nif", 0, copy_file_range_available_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"copy_file_range_nif", 3, copy_file_range_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},

/* Filesystem ops */
{"make_hard_link_nif", 2, make_hard_link_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
Expand Down Expand Up @@ -1399,3 +1404,80 @@ static ERL_NIF_TERM altname_nif(ErlNifEnv *env, int argc, const ERL_NIF_TERM arg

return enif_make_tuple2(env, am_ok, result);
}

static ERL_NIF_TERM copy_file_range_available_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
off64_t ret;

ret = syscall(SYS_copy_file_range, -1, NULL, -1, NULL, 0, 0);

if (ret == -1 && errno == ENOSYS) {
return enif_make_atom(env, "false");
} else {
return enif_make_atom(env, "true");
}
}

static ERL_NIF_TERM copy_file_range_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
posix_errno_t posix_errno, ignored;
efile_data_t *d_in, *d_out;
off64_t ret = 0, len;
efile_fileinfo_t info = {0};
efile_path_t file_path_in, file_path_out;
char atom_name[256];

ASSERT(argc == 3);

if ((posix_errno = efile_marshal_path(env, argv[0], &file_path_in))) {
return posix_error_to_tuple(env, posix_errno);
}

if ((posix_errno = efile_marshal_path(env, argv[1], &file_path_out))) {
return posix_error_to_tuple(env, posix_errno);
}

// Check if the third argument is an atom
if (enif_get_atom(env, argv[2], atom_name, sizeof(atom_name), ERL_NIF_LATIN1)) {
if (strcmp(atom_name, "infinity") == 0) {
if ((posix_errno = efile_open(&file_path_in, EFILE_MODE_READ, efile_resource_type, &d_in))) {
return posix_error_to_tuple(env, posix_errno);
}

if ((posix_errno = efile_read_handle_info(d_in, &info))) {
return posix_error_to_tuple(env, posix_errno);
}

len = (off64_t)info.size;
efile_close(d_in, &ignored);
}
}
// Check if the third argument is an integer
else if (!enif_get_int64(env, argv[2], &len)) {
return enif_make_tuple2(env, enif_make_atom(env, "error"), enif_make_atom(env, "badarg"));
}

if (len < 0) {
return enif_make_badarg(env);
}

if ((posix_errno = efile_open(&file_path_in, EFILE_MODE_READ, efile_resource_type, &d_in))) {
return posix_error_to_tuple(env, posix_errno);
}

if ((posix_errno = efile_open(&file_path_out, EFILE_MODE_WRITE, efile_resource_type, &d_out))) {
efile_close(d_in, &ignored);
return posix_error_to_tuple(env, posix_errno);
}

// Copy file contents using SYS_copy_file_range syscall
if (posix_errno = efile_copy_file_range(d_in, d_out, len, &ret)) {
efile_close(d_in, &ignored);
efile_close(d_out, &ignored);
return posix_error_to_tuple(env, posix_errno);
}

// Close file descriptors
efile_close(d_in, &ignored);
efile_close(d_out, &ignored);

return enif_make_tuple2(env, enif_make_atom(env, "ok"), enif_make_uint(env, (unsigned int)ret));
}
2 changes: 2 additions & 0 deletions erts/emulator/nifs/common/prim_file_nif.h
Original file line number Diff line number Diff line change
Expand Up @@ -177,6 +177,8 @@ posix_errno_t efile_from_fd(int fd,
ErlNifResourceType *nif_type,
efile_data_t **d);

posix_errno_t efile_copy_file_range(efile_data_t *d_in, efile_data_t *d_out, off64_t length, off64_t *result);

/** @brief Closes a file. The file must have entered the CLOSED state prior to
* calling this to prevent double close.
*
Expand Down
24 changes: 24 additions & 0 deletions erts/emulator/nifs/unix/unix_prim_file.c
Original file line number Diff line number Diff line change
Expand Up @@ -1085,3 +1085,27 @@ posix_errno_t efile_altname(ErlNifEnv *env, const efile_path_t *path, ERL_NIF_TE

return ENOTSUP;
}


posix_errno_t efile_copy_file_range(efile_data_t *d_in, efile_data_t *d_out, off64_t length, off64_t *result) {
efile_unix_t *u_in = (efile_unix_t*)d_in;
efile_unix_t *u_out = (efile_unix_t*)d_out;

if (!u_in || !u_out || u_in->fd < 0 || u_out->fd < 0) {
return EINVAL; // or appropriate error code
}

// Perform the copy file range operation
off64_t ret = syscall(SYS_copy_file_range, u_in->fd, NULL, u_out->fd, NULL, length, 0);

if (ret < 0) {
return errno; // Return errno if syscall fails
}

// Assign the result to the pointer passed
if (result != NULL) {
(*result) = ret;
}

return 0;
}
Binary file modified erts/preloaded/ebin/prim_file.beam
Binary file not shown.
17 changes: 15 additions & 2 deletions erts/preloaded/src/prim_file.erl
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,8 @@
-export([open/2, close/1,
sync/1, datasync/1, truncate/1, advise/4, allocate/3,
read_line/1, read/2, write/2, position/2,
pread/2, pread/3, pwrite/2, pwrite/3]).
pread/2, pread/3, pwrite/2, pwrite/3,
copy_file_range_available/0, copy_file_range/3]).

%% OTP internal.

Expand Down Expand Up @@ -73,7 +74,8 @@
del_dir_nif/1, get_device_cwd_nif/1, set_cwd_nif/1, get_cwd_nif/0,
ipread_s32bu_p32bu_nif/3, read_file_nif/1,
get_handle_nif/1, delayed_close_nif/1, altname_nif/1,
file_desc_to_ref_nif/1]).
file_desc_to_ref_nif/1, copy_file_range_available_nif/0,
copy_file_range_nif/3]).

-type prim_file_name() :: string() | unicode:unicode_binary().
-type prim_file_name_error() :: 'error' | 'ignore' | 'warning'.
Expand Down Expand Up @@ -126,6 +128,13 @@ copy(#file_descriptor{module = ?MODULE} = Source,
%% XXX Should be moved down to the driver for optimization.
file:copy_opened(Source, Dest, Length).

%% Returns {error, Reason} | {ok, BytesCopied}
%% Using unix syscall copy_file_range(3)
copy_file_range(Source, Destination, ByteCount) ->
copy_file_range_nif(encode_path(Source), encode_path(Destination), ByteCount).
copy_file_range_available() ->
copy_file_range_available_nif().

open(Name, Modes) ->
%% The try/catch pattern seen here is used throughout the file to adhere to
%% the public file interface, which has leaked through for ages because of
Expand Down Expand Up @@ -529,6 +538,10 @@ delayed_close_nif(_FileRef) ->
erlang:nif_error(undef).
read_handle_info_nif(_FileRef) ->
erlang:nif_error(undef).
copy_file_range_available_nif() ->
erlang:nif_error(undef).
copy_file_range_nif(_Name,_Dest,_Size) ->
erlang:nif_error(undef).

%%
%% Quality-of-life helpers
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ MODULES = \
raw_file_io_deflate \
raw_file_io_delayed \
raw_file_io_list \
wrap_log_reader
wrap_log_reader

HRL_FILES= ../include/file.hrl ../include/inet.hrl ../include/inet_sctp.hrl \
../include/dist.hrl ../include/dist_util.hrl \
Expand Down
5 changes: 4 additions & 1 deletion lib/kernel/src/file.erl
Original file line number Diff line number Diff line change
Expand Up @@ -907,7 +907,10 @@ copy_int(Source, {_DestName, DestOpts} = Dest, Length)
%% Both must be bare filenames. If they are not,
%% the filename check in the copy operation will yell.
copy_int(Source, Dest, Length) ->
copy_int({Source, []}, {Dest, []}, Length).
case ?PRIM_FILE:copy_file_range_available() of
true -> ?PRIM_FILE:copy_file_range(Source, Dest, Length);
false -> copy_int({Source, []}, {Dest, []}, Length)
end.



Expand Down
3 changes: 2 additions & 1 deletion lib/kernel/src/kernel.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,8 @@
seq_trace,
socket,
standard_error,
wrap_log_reader]},
wrap_log_reader,
file_nif]},
{registered, [application_controller,
erl_reply,
auth,
Expand Down

0 comments on commit 91b4350

Please sign in to comment.