Skip to content

Commit

Permalink
Merge pull request #177 from r-lib/fix/faster-fs-info
Browse files Browse the repository at this point in the history
Speed up ps_fs_info()
  • Loading branch information
gaborcsardi authored Sep 6, 2024
2 parents fc500ca + 518edad commit 3b8417f
Show file tree
Hide file tree
Showing 7 changed files with 37 additions and 118 deletions.
3 changes: 2 additions & 1 deletion R/disk.R
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,8 @@ ps__disk_io_counters_macos <- function() {
ps_fs_info <- function(paths = "/") {
assert_character(paths)
abspaths <- normalizePath(paths, mustWork = TRUE)
res <- .Call(ps__fs_info, paths, abspaths)
mps <- ps_fs_mount_point(paths)
res <- .Call(ps__fs_info, paths, abspaths, mps)
df <- as_data_frame(res)

# this should not happen in practice, but just in case
Expand Down
109 changes: 18 additions & 91 deletions src/api-linux.c
Original file line number Diff line number Diff line change
Expand Up @@ -1654,41 +1654,14 @@ SEXP ps__disk_partitions(SEXP all) {
#define ST_RELATIME 0x1000 /* update atime relative to mtime/ctime */
#define ST_NOSYMFOLLOW 0x2000 /* do not follow symlinks */

SEXP ps__fs_info(SEXP path, SEXP abspath) {
SEXP ps__fs_info(SEXP path, SEXP abspath, SEXP mps) {
struct statfs sfs;
R_xlen_t i, j, len = Rf_xlength(path);
int ret;

// Need to query all partitions and look up their
// fs id, because struct statfs does not contain the
// directory or the device of the file systems. So we'll
// run statfs for the directory of all partitions as well,
// to match the input paths to device names.

// Need to query all partitions to get the device name and fs type.
SEXP partitions = PROTECT(ps__disk_partitions(Rf_ScalarLogical(1)));
R_xlen_t num_parts = Rf_xlength(partitions);
SEXP rfsid = PROTECT(Rf_allocVector(RAWSXP, num_parts * sizeof(fsid_t)));
fsid_t *fsid = (fsid_t *) RAW(rfsid);
memset(fsid, 0, num_parts * sizeof(fsid_t));
for (i = 0; i < num_parts; i++) {
if (isNull(VECTOR_ELT(partitions, i))) {
num_parts = i;
break;
}
const char *mp = CHAR(STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, i), 1), 0));
ret = statfs(mp, &sfs);
// Skip the ones that fail, those are zeroed out,
// we assume the zeros do not match any real fs id.
if (ret == 0) {
memcpy(&fsid[i], &sfs.f_fsid, sizeof(fsid_t));
}
}

// Some files and partitions do not have a proper fsid, but it is just
// all zeros. For these we try to match dirnam() to a mount point
// recursively.
fsid_t zerofsid;
memset(&zerofsid, 0, sizeof(fsid_t));

const char *nms[] = {
"path",
Expand Down Expand Up @@ -1762,68 +1735,22 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
SET_STRING_ELT(VECTOR_ELT(res, 2), i, NA_STRING);
SET_STRING_ELT(VECTOR_ELT(res, 3), i, NA_STRING);

// match to partition, either with fsid, or matching a parent
// directory to a mount point
int found_part = 0;
if (0 != memcmp(&sfs.f_fsid, &zerofsid, sizeof(fsid_t))) {
for (j = 0; j < num_parts; j++) {
if (0 == memcmp(&fsid[j], &sfs.f_fsid, sizeof(fsid_t))) {
SET_STRING_ELT(
VECTOR_ELT(res, 1), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 1), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 2), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 0), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 3), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 2), 0));
found_part = 1;
break;
}
}
}
if (!found_part) {
char *dn = strdup(CHAR(STRING_ELT(abspath, i)));
while (!found_part) {
for (j = 0; j < num_parts; j++) {
const char *mp = CHAR(STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 1), 0));
if (0 == strcmp(dn, mp)) {
SET_STRING_ELT(
VECTOR_ELT(res, 1), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 1), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 2), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 0), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 3), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 2), 0));
found_part = 1;
break;
}
}
// quit asap, to avoid the dirname() mess
if (found_part) {
break;
}
// we didn't even find /??? wow
if (0 == strcmp("/", dn)) {
break;
}
// Get parent. dirname() might modify dn and return the
// same pointer (!!!). So need to copy both input and output.
char *orig = strdup(dn);
char *ddn = strdup(dirname(dn));
// This might happen if dn has no /. (Should not happen here,
// because we use the absolute file name, but just in case.)
if (0 == strcmp(orig, ddn)) {
free(orig);
free(ddn);
break;
}
free(orig);
dn = ddn;
// match the mount point to the partitions
const char *mpi = CHAR(STRING_ELT(mps, i));
for (j = 0; j < num_parts; j++) {
const char *mpp = CHAR(STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 1), 0));
if (0 == strcmp(mpi, mpp)) {
SET_STRING_ELT(
VECTOR_ELT(res, 1), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 1), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 2), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 0), 0));
SET_STRING_ELT(
VECTOR_ELT(res, 3), i,
STRING_ELT(VECTOR_ELT(VECTOR_ELT(partitions, j), 2), 0));
break;
}
free(dn);
}

REAL(VECTOR_ELT(res, 4))[i] = sfs.f_bsize;
Expand Down Expand Up @@ -1851,7 +1778,7 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
LOGICAL(VECTOR_ELT(res, 24))[i] = sfs.f_flags & ST_NOSYMFOLLOW;
}

UNPROTECT(3);
UNPROTECT(2);
return res;
}

Expand Down
7 changes: 3 additions & 4 deletions src/api-macos.c
Original file line number Diff line number Diff line change
Expand Up @@ -1130,13 +1130,13 @@ SEXP ps__disk_partitions(SEXP all) {
return R_NilValue;
}

SEXP ps__fs_info(SEXP path, SEXP abspath) {
SEXP ps__fs_info(SEXP path, SEXP abspath, SEXP mps) {
struct statfs sfs;
R_xlen_t i, len = Rf_xlength(path);

const char *nms[] = {
"path", // 0
"mountpoint", // 1
"mountpoint", // 1
"name", // 2
"type", // 3
"block_size", // 4
Expand Down Expand Up @@ -1218,8 +1218,7 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
);
ps__throw_error();
}
SET_STRING_ELT(VECTOR_ELT(res, 1), i,
Rf_mkCharCE(sfs.f_mntonname, CE_UTF8));
SET_STRING_ELT(VECTOR_ELT(res, 1), i, STRING_ELT(mps, i));
SET_STRING_ELT(VECTOR_ELT(res, 2), i,
Rf_mkCharCE(sfs.f_mntfromname, CE_UTF8));
SET_STRING_ELT(VECTOR_ELT(res, 3), i,
Expand Down
30 changes: 11 additions & 19 deletions src/api-windows.c
Original file line number Diff line number Diff line change
Expand Up @@ -1373,7 +1373,7 @@ SEXP ps__disk_usage(SEXP paths) {
#define FILE_SUPPORTS_GHOSTING 0x40000000
#endif

SEXP ps__fs_info(SEXP path, SEXP abspath) {
SEXP ps__fs_info(SEXP path, SEXP abspath, SEXP mps) {
R_xlen_t i, len = Rf_xlength(path);

const char *nms[] = {
Expand Down Expand Up @@ -1476,26 +1476,18 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
ps__throw_error();
}

// look up mount point
wchar_t volume[MAX_PATH + 1];
BOOL ok = GetVolumePathNameW(
wpath,
volume,
sizeof(volume)/sizeof(wchar_t) - 1
);
if (!ok) {
ps__set_error_from_windows_error(0);
// we already have the mount point, convert to UTF-16
wchar_t *wmp;
iret = ps__utf8_to_utf16(CHAR(STRING_ELT(mps, i)), &wmp);
if (iret) {
ps__throw_error();
}
SET_STRING_ELT(
VECTOR_ELT(res, 1), i,
ps__utf16_to_charsxp(volume, -1)
);
SET_STRING_ELT(VECTOR_ELT(res, 1), i, STRING_ELT(mps, i));

// name of the volume
wchar_t volname[1024];
ok = GetVolumeNameForVolumeMountPointW(
volume,
BOOL ok = GetVolumeNameForVolumeMountPointW(
wmp,
volname,
sizeof(volname)/sizeof(wchar_t) - 1
);
Expand All @@ -1511,7 +1503,7 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
DWORD sn, mcl, flags;
wchar_t type[MAX_PATH + 1];
ok = GetVolumeInformationW(
volume, NULL, 0, &sn, &mcl, &flags, type,
wmp, NULL, 0, &sn, &mcl, &flags, type,
sizeof(type)/sizeof(wchar_t) - 1);
if (!ok) {
ps__set_error_from_windows_error(0);
Expand All @@ -1524,7 +1516,7 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
);

DWORD spc, bps, freec, totalc;
ok = GetDiskFreeSpaceW(volume, &spc, &bps, &freec, &totalc);
ok = GetDiskFreeSpaceW(wmp, &spc, &bps, &freec, &totalc);
if (!ok) {
ps__set_error_from_windows_error(0);
ps__throw_error();
Expand All @@ -1533,7 +1525,7 @@ SEXP ps__fs_info(SEXP path, SEXP abspath) {
REAL(VECTOR_ELT(res, 5))[i] = bps * spc;

ULARGE_INTEGER freeuser, total, freeroot;
ok = GetDiskFreeSpaceExW(volume, &freeuser, &total, &freeroot);
ok = GetDiskFreeSpaceExW(wmp, &freeuser, &total, &freeroot);
if (!ok) {
ps__set_error_from_windows_error(0);
ps__throw_error();
Expand Down
2 changes: 1 addition & 1 deletion src/dummy.c
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ SEXP ps__tty_size(void) { return ps__dummy("ps_tty_size"); }
SEXP ps__disk_partitions(SEXP x) { return ps__dummy("ps_disk_partitions"); }
SEXP ps__disk_io_counters(void) { return ps__dummy("ps__get_disk_io_counters"); }
SEXP ps__disk_usage(void) { return ps__dummy("ps_disk_usage"); }
SEXP ps__fs_info(SEXP x, SEXP y) { return ps__dummy("ps_fs_info"); }
SEXP ps__fs_info(SEXP x, SEXP y, SEXP z) { return ps__dummy("ps_fs_info"); }
SEXP ps__system_cpu_times(void) { return ps__dummy("ps_system_cpu_times"); }
SEXP ps__system_memory(void) { return ps__dummy("ps_system_memory"); }
SEXP ps__system_swap(void) { return ps__dummy("ps_system_swap"); }
Expand Down
2 changes: 1 addition & 1 deletion src/init.c
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ static const R_CallMethodDef callMethods[] = {
{ "ps__disk_partitions", (DL_FUNC) ps__disk_partitions, 1 },
{ "ps__disk_usage", (DL_FUNC) ps__disk_usage, 1 },
{ "ps__disk_io_counters", (DL_FUNC) ps__disk_io_counters, 0 },
{ "ps__fs_info", (DL_FUNC) ps__fs_info, 2 },
{ "ps__fs_info", (DL_FUNC) ps__fs_info, 3 },
{ "ps__system_memory", (DL_FUNC) ps__system_memory, 0 },
{ "ps__system_swap", (DL_FUNC) ps__system_swap, 0 },
{ "ps__list_apps", (DL_FUNC) ps__list_apps, 0 },
Expand Down
2 changes: 1 addition & 1 deletion src/ps.h
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ SEXP ps__tty_size(void);
SEXP ps__disk_partitions(SEXP all);
SEXP ps__disk_usage(SEXP paths);
SEXP ps__disk_io_counters(void);
SEXP ps__fs_info(SEXP path, SEXP abspath);
SEXP ps__fs_info(SEXP path, SEXP abspath, SEXP mps);
SEXP ps__system_memory(void);
SEXP ps__system_swap(void);
SEXP ps__loadavg(SEXP counter_name);
Expand Down

0 comments on commit 3b8417f

Please sign in to comment.