Skip to content

Commit

Permalink
Use faccessat instead of custom permission check
Browse files Browse the repository at this point in the history
Unix.access uses RUID and RGID, which is not correct when doing a
PATH-search. The faccessat function is able to check permissions using
EUID and EGID instead. opam's hand-rolled check_permissions function is
therefore replaced with a binding for faccessat.

This simultaneously fixes two other things:
- Platforms (such as Cygwin) which use ACLs no longer need special
  support, because their implementations of faccessat already take ACLs
  into account
- We no longer use Unix.getgroups which means that we work around a
  problem with binaries built using musl libc and then used on systems
  where a user belongs to more than 32 groups
  (cf. https://www.openwall.com/lists/musl/2021/07/03/1)
  • Loading branch information
kit-ty-kate committed Sep 17, 2024
1 parent 56ef9b6 commit b16317b
Show file tree
Hide file tree
Showing 7 changed files with 84 additions and 28 deletions.
2 changes: 1 addition & 1 deletion configure

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion configure.ac
Original file line number Diff line number Diff line change
Expand Up @@ -342,7 +342,7 @@ AS_IF([test "${enable_static}" = yes],[
],[
unix_lib_name=unixnat
])
echo "(-noautolink -cclib -l${unix_lib_name} -cclib -lmccs_stubs -cclib -lmccs_glpk_stubs -cclib -lsha_stubs ${platform_dependent_stuff})" > src/client/linking.sexp
echo "(-noautolink -cclib -l${unix_lib_name} -cclib -lmccs_stubs -cclib -lmccs_glpk_stubs -cclib -lsha_stubs -cclib -lopam_core_stubs ${platform_dependent_stuff})" > src/client/linking.sexp
AC_MSG_RESULT([static])
],[
AC_MSG_RESULT([shared])
Expand Down
4 changes: 3 additions & 1 deletion master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ users)
* Reduce allocations in OpamVersionCompare [#6144 @talex5]
* Speedup OpamVersionCompare by 25% by removing the unused handling of epoch [#5518 @kit-ty-kate]
* Fix error in `OpamSystem.transform_patch` - patches were only applied when debugging [#6182 @dra27 regression since #3449]
* Remove --with-acl option (reverts a Cygwin fix in #4265) [#5381 @kit-ty-kate - fix #5373]
* Remove `--with-acl` option from the configure script and its related C stubs (reverts a Cygwin fix in #4265) [#5381 @kit-ty-kate - fix #5373]

## Internal: Windows

Expand Down Expand Up @@ -272,3 +272,5 @@ users)
* `OpamHash`: export `compare_kind` [#5561 @rjbou]
* `OpamFilename`: add `might_escape` to check if a path is escapable, ie contains `<sep>..<sep>` [#5561 @rjbou]
* Add `OpamStd.Sys.getconf` [#5950 @kit-ty-kate]
* Fix opam unable to find executables on systems where users belong to more than 32 groups when opam is built using musl libc [#5381 @kit-ty-kate - fix #5373]
* `OpamACL`: remove module [#5381 @kit-ty-kate]
11 changes: 11 additions & 0 deletions src/core/dune
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,14 @@
(:include ../ocaml-flags-standard.sexp)
(:include ../ocaml-flags-configure.sexp)
(:include ../ocaml-context-flags.sexp)))
(foreign_stubs
(language c)
(names opamCommonStubs)
(flags :standard
-DUNICODE -D_UNICODE -DCAML_NAME_SPACE
(:include ../stubs/c-flags.sexp)))
(c_library_flags (:standard
(:include c-libraries.sexp)))
(wrapped false))

(rule
Expand Down Expand Up @@ -41,3 +49,6 @@
(targets developer)
(mode fallback)
(action (with-stdout-to %{targets} (echo ""))))

(rule
(with-stdout-to c-libraries.sexp (run ocaml %{dep:../../shell/context_flags.ml} clibs)))
60 changes: 60 additions & 0 deletions src/core/opamCommonStubs.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
/**************************************************************************/
/* */
/* Copyright 2024 Kate Deplaix */
/* */
/* All rights reserved. This file is distributed under the terms of the */
/* GNU Lesser General Public License version 2.1, with the special */
/* exception on linking described in the file LICENSE. */
/* */
/**************************************************************************/

/* Needed for the Windows string conversion functions on older OCaml */
#define CAML_INTERNALS

#include <caml/mlvalues.h>
#include <caml/alloc.h>
#include <caml/memory.h>
#include <caml/signals.h>
#include <caml/osdeps.h>
#include <caml/unixsupport.h>
#include <caml/version.h>

#ifndef _WIN32

#include <fcntl.h>
#include <unistd.h>

#else

#include <io.h>

/* mingw-w64 defines R_OK */
#ifndef R_OK
#define R_OK 4
#endif

#endif

#if OCAML_VERSION < 50000
#define caml_unix_access unix_access
#endif

CAMLprim value opam_is_executable(value path)
{
CAMLparam1(path);
char_os * p;
int ret;

caml_unix_check_path(path, "faccessat");
p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section();
#ifdef _WIN32
/* No execute bit on Windows */
ret = _waccess(p, R_OK);
#else
ret = faccessat(AT_FDCWD, p, X_OK, AT_EACCESS);
#endif
caml_leave_blocking_section();
caml_stat_free(p);
CAMLreturn(Val_bool(ret == 0));
}
28 changes: 3 additions & 25 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1249,33 +1249,11 @@ module OpamSys = struct
(* OCaml 4.05.0 no longer follows the updated PATH to resolve commands. This
makes unqualified commands absolute as a workaround. *)
let resolve_command =
let check_perms =
if Sys.win32 then fun f ->
try (Unix.stat f).Unix.st_kind = Unix.S_REG
with e -> fatal e; false
else fun f ->
try
let {Unix.st_uid; st_gid; st_perm; st_kind; _} = Unix.stat f in
if st_kind <> Unix.S_REG then false else
let groups =
Unix.getegid () :: Array.to_list (Unix.getgroups ())
in
let mask =
if Unix.geteuid () = (st_uid : int) then
0o100
else if List.mem st_gid groups then
0o010
else
0o001
in
(st_perm land mask) <> 0
with e -> fatal e; false
in
let resolve ?dir env name =
if not (Filename.is_relative name) then begin
(* absolute path *)
if not (Sys.file_exists name) then `Not_found
else if not (check_perms name) then `Denied
else if not (OpamStubs.is_executable name) then `Denied
else `Cmd name
end else if is_external_cmd name then begin
(* relative path *)
Expand All @@ -1284,7 +1262,7 @@ module OpamSys = struct
| Some d -> Filename.concat d name
in
if not (Sys.file_exists cmd) then `Not_found
else if not (check_perms cmd) then `Denied
else if not (OpamStubs.is_executable cmd) then `Denied
else `Cmd cmd
end else
(* bare command, lookup in PATH *)
Expand All @@ -1298,7 +1276,7 @@ module OpamSys = struct
expected name but not the right permissions are skipped silently.
Therefore, only two outcomes are possible in that case, [`Cmd ..] or
[`Not_found]. *)
match List.find check_perms possibles with
match List.find OpamStubs.is_executable possibles with
| cmdname -> `Cmd cmdname
| exception Not_found ->
if possibles = [] then
Expand Down
5 changes: 5 additions & 0 deletions src/core/opamStubsTypes.ml
Original file line number Diff line number Diff line change
Expand Up @@ -113,3 +113,8 @@ type win32_version_info = {
strings: ((int * int) * win32_non_fixed_version_info) list;
(** Non-fixed string table. First field is a pair of Language and Codepage ID. *)
}

external is_executable : string -> bool = "opam_is_executable"
(** faccessat on Unix; _waccess on Windows. Checks whether a path is executable
for the current process. On Unix, unlike Unix.access, this is checked using
the EUID/EGID rather than RUID/RGID. *)

0 comments on commit b16317b

Please sign in to comment.