Skip to content

Commit

Permalink
Rename Unix/Windows user types to ById/ByName
Browse files Browse the repository at this point in the history
  • Loading branch information
dustanddreams committed Aug 28, 2023
1 parent df2d3ad commit 6ea9db3
Show file tree
Hide file tree
Showing 15 changed files with 54 additions and 54 deletions.
4 changes: 2 additions & 2 deletions lib/btrfs_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -191,9 +191,9 @@ let cache ~user t name : (string * (unit -> unit Lwt.t)) Lwt.t =
let gen = cache.gen in
Btrfs.subvolume_snapshot `RW ~src:snapshot tmp >>= fun () ->
begin match user with
| `Unix { Obuilder_spec.uid; gid } ->
| `ById { Obuilder_spec.uid; gid } ->
Os.sudo ["chown"; Printf.sprintf "%d:%d" uid gid; tmp]
| `Windows _ -> assert false (* btrfs not supported on Windows*)
| `ByName _ -> assert false (* btrfs not supported on Windows*)
end >>= fun () ->
let release () =
Lwt_mutex.with_lock cache.lock @@ fun () ->
Expand Down
4 changes: 2 additions & 2 deletions lib/docker_sandbox.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,8 @@ module Docker_config = struct
let network = network |> List.concat_map (fun network -> ["--network"; network]) in
let user =
match user with
| `Unix { Obuilder_spec.uid; gid } when not Sys.win32 -> ["--user"; strf "%d:%d" uid gid]
| `Windows { name } when Sys.win32 -> ["--user"; name]
| `ById { Obuilder_spec.uid; gid } when not Sys.win32 -> ["--user"; strf "%d:%d" uid gid]
| `ByName { name } when Sys.win32 -> ["--user"; name]
| _ -> assert false
in
let mount_secrets =
Expand Down
4 changes: 2 additions & 2 deletions lib/docker_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -178,10 +178,10 @@ let cache ~user t name : (string * (unit -> unit Lwt.t)) Lwt.t =
let gen = cache.gen in
let* () = Cache.snapshot ~src:snapshot tmp in
let+ () = match user with
| `Unix { Obuilder_spec.uid; gid } ->
| `ById { Obuilder_spec.uid; gid } ->
let* tmp = Docker.Cmd.mount_point tmp in
Os.sudo ["chown"; strf "%d:%d" uid gid; tmp]
| `Windows _ -> Lwt.return_unit (* FIXME: does Windows need special treatment? *)
| `ByName _ -> Lwt.return_unit (* FIXME: does Windows need special treatment? *)
in
let release () =
Lwt_mutex.with_lock cache.lock @@ fun () ->
Expand Down
4 changes: 2 additions & 2 deletions lib/rsync_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -154,8 +154,8 @@ let cache ~user t name =
(* Create writeable clone. *)
let gen = cache.gen in
let { Obuilder_spec.uid; gid } = match user with
| `Unix user -> user
| `Windows _ -> assert false (* rsync not supported on Windows *)
| `ById user -> user
| `ByName _ -> assert false (* rsync not supported on Windows *)
in
(* rsync --chown not supported by the rsync that macOS ships with *)
Rsync.copy_children ~src:snapshot ~dst:tmp () >>= fun () ->
Expand Down
4 changes: 2 additions & 2 deletions lib/sandbox.jail.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,8 @@ type config = unit [@@deriving sexp]
Note that the gid is currently ignored. *)
let jail_username rootdir config =
match config.Config.user with
| `Windows w -> w.name
| `Unix { uid; _ } ->
| `ByName { name } -> name
| `ById { Obuilder_spec.uid; _ } ->
let pwdfile = rootdir / "etc" / "passwd" in
let uidstr = string_of_int uid in
let rec parse_line ch =
Expand Down
4 changes: 2 additions & 2 deletions lib/sandbox.runc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,8 +108,8 @@ module Json_config = struct
assert (entrypoint = None);
let user =
let { Obuilder_spec.uid; gid } = match user with
| `Unix user -> user
| `Windows _ -> assert false (* runc not supported on Windows *) in
| `ById user -> user
| `ByName _ -> assert false (* runc not supported on Windows *) in
`Assoc [
"uid", `Int uid;
"gid", `Int gid;
Expand Down
12 changes: 6 additions & 6 deletions lib/tar_transfer.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,12 +56,12 @@ let copy_to ~dst src =
aux ()

let get_ids = function
| `Unix user -> Some user.Obuilder_spec.uid, Some user.gid, None, None
| `Windows user when user.Obuilder_spec.name = "ContainerAdministrator" ->
| `ById user -> Some user.Obuilder_spec.uid, Some user.gid, None, None
| `ByName user when user.Obuilder_spec.name = "ContainerAdministrator" ->
(* https://cygwin.com/cygwin-ug-net/ntsec.html#ntsec-mapping *)
let x = 93 and rid = 1 in
Some (0x1000 * x + rid), Some (0x1000 * x + rid), Some user.name, Some user.name
| `Windows _ -> None, None, None, None
| `ByName _ -> None, None, None, None

let copy_file ~src ~dst ~to_untar ~user =
Lwt_unix.LargeFile.lstat src >>= fun stat ->
Expand Down Expand Up @@ -145,13 +145,13 @@ let transform ~user fname hdr =
(* Make a copy to erase unneeded data from the tar headers. *)
let hdr' = Tar.Header.(make ~file_mode:hdr.file_mode ~mod_time:hdr.mod_time hdr.file_name hdr.file_size) in
let hdr' = match user with
| `Unix user ->
| `ById user ->
{ hdr' with Tar.Header.user_id = user.Obuilder_spec.uid; group_id = user.gid; }
| `Windows user when user.Obuilder_spec.name = "ContainerAdministrator" ->
| `ByName user when user.Obuilder_spec.name = "ContainerAdministrator" ->
(* https://cygwin.com/cygwin-ug-net/ntsec.html#ntsec-mapping *)
let id = let x = 93 and rid = 1 in 0x1000 * x + rid in
{ hdr' with user_id = id; group_id = id; uname = user.name; gname = user.name; }
| `Windows _ -> hdr'
| `ByName _ -> hdr'
in
match hdr.Tar.Header.link_indicator with
| Normal ->
Expand Down
4 changes: 2 additions & 2 deletions lib/zfs_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,11 +93,11 @@ end = struct
| false -> fn ()
end

let user = `Unix { Obuilder_spec.uid = Unix.getuid (); gid = Unix.getgid () }
let user = `ById { Obuilder_spec.uid = Unix.getuid (); gid = Unix.getgid () }

module Zfs = struct
let chown ~user t ds =
let { Obuilder_spec.uid; gid } = match user with `Unix user -> user | `Windows _ -> assert false in
let { Obuilder_spec.uid; gid } = match user with `ById user -> user | `ByName _ -> assert false in
Os.sudo ["chown"; strf "%d:%d" uid gid; Dataset.path t ds]

let create t ds =
Expand Down
20 changes: 10 additions & 10 deletions lib_spec/docker.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@ let pp_wrap ~escape =

let pp_cache ~ctx f { Cache.id; target; buildkit_options } =
let buildkit_options = match ctx.user with
| `Unix {uid; gid = _} -> ("uid", string_of_int uid) :: buildkit_options
| `Windows _ -> assert false
| `ById {uid; gid = _} -> ("uid", string_of_int uid) :: buildkit_options
| `ByName _ -> assert false
in
let buildkit_options =
("--mount=type", "cache") ::
Expand All @@ -31,8 +31,8 @@ let pp_cache ~ctx f { Cache.id; target; buildkit_options } =

let pp_mount_secret ~ctx f { Secret.id; target; buildkit_options } =
let buildkit_options = match ctx.user with
| `Unix {uid; gid = _} -> ("uid", string_of_int uid) :: buildkit_options
| `Windows _ -> assert false
| `ById {uid; gid = _} -> ("uid", string_of_int uid) :: buildkit_options
| `ByName _ -> assert false
in
let buildkit_options =
("--mount=type", "secret") ::
Expand Down Expand Up @@ -60,8 +60,8 @@ let pp_copy ~ctx f { Spec.from; src; dst; exclude = _ } =
if is_root ctx.user then None
else (
match ctx.user with
| `Unix { uid; gid } -> Some (Printf.sprintf "%d:%d" uid gid)
| `Windows _ -> None
| `ById { uid; gid } -> Some (Printf.sprintf "%d:%d" uid gid)
| `ByName _ -> None
)
in
Fmt.pf f "COPY %a%a%a %s"
Expand Down Expand Up @@ -91,8 +91,8 @@ let pp_op ~buildkit ~escape ctx f : Spec.op -> ctx = function
| `Run x when buildkit -> pp_run ~escape ~ctx f x; ctx
| `Run x -> pp_run ~escape ~ctx f { x with cache = []; secrets = []}; ctx
| `Copy x -> pp_copy ~ctx f x; ctx
| `User (`Unix { uid; gid } as u) -> Fmt.pf f "USER %d:%d" uid gid; { user = u }
| `User (`Windows { name } as u) -> Fmt.pf f "USER %s" name; { user = u }
| `User (`ById { uid; gid } as u) -> Fmt.pf f "USER %d:%d" uid gid; { user = u }
| `User (`ByName { name } as u) -> Fmt.pf f "USER %s" name; { user = u }
| `Env (k, v) -> Fmt.pf f "ENV %s=\"%s\"" k (quote ~escape v); ctx

let rec convert ~buildkit ~escape ~ctx f (name, { Spec.child_builds; from; ops }) =
Expand All @@ -113,10 +113,10 @@ let rec convert ~buildkit ~escape ~ctx f (name, { Spec.child_builds; from; ops }
let dockerfile_of_spec ~buildkit ~os t =
Fmt.str "%a" (fun f ->
match os with
| `Windows ->
| `ByName ->
let ctx = { user = (Spec.root_windows :> Spec.user) } in
(Fmt.pf f "@[<h>#escape=`@]@.";
convert ~buildkit ~escape:'`' ~ctx f)
| `Unix ->
| `ById ->
let ctx = { user = (Spec.root_unix :> Spec.user) } in
convert ~buildkit ~escape:'\\' ~ctx f) (None, t)
2 changes: 1 addition & 1 deletion lib_spec/docker.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
val dockerfile_of_spec : buildkit:bool -> os:[`Unix | `Windows] -> Spec.t -> string
val dockerfile_of_spec : buildkit:bool -> os:[`ById | `ByName] -> Spec.t -> string
(** [dockerfile_of_spec ~buildkit ~os x] produces a Dockerfile
that aims to be equivalent to [x].
Expand Down
20 changes: 10 additions & 10 deletions lib_spec/spec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,27 +56,27 @@ let copy_inlined = function
let copy_of_sexp x = copy_of_sexp (inflate_record copy_inlined x)
let sexp_of_copy x = deflate_record copy_inlined (sexp_of_copy x)

type unix_user = {
type numeric_user = {
uid : int;
gid : int;
} [@@deriving sexp]

type windows_user = {
type named_user = {
name : string;
} [@@deriving sexp]

type user = [
| `Unix of unix_user
| `Windows of windows_user
| `ById of numeric_user
| `ByName of named_user
] [@@deriving sexp]

let user_of_sexp x =
let open Sexplib.Sexp in
match x with
| List [List [Atom "name"; _]] ->
`Windows (windows_user_of_sexp x)
`ByName (named_user_of_sexp x)
| List [List [Atom "uid"; _]; List [Atom "gid"; _]] ->
`Unix (unix_user_of_sexp x)
`ById (numeric_user_of_sexp x)
| x -> Fmt.failwith "Invalid op: %a" Sexplib.Sexp.pp_hum x

let sexp_of_user x : Sexplib.Sexp.t =
Expand Down Expand Up @@ -175,11 +175,11 @@ let shell xs = `Shell xs
let run ?(cache=[]) ?(network=[]) ?(secrets=[]) fmt = fmt |> Printf.ksprintf (fun x -> `Run { shell = x; cache; network; secrets })
let copy ?(from=`Context) ?(exclude=[]) src ~dst = `Copy { from; src; dst; exclude }
let env k v = `Env (k, v)
let user_unix ~uid ~gid = `User (`Unix { uid; gid })
let user_windows ~name = `User (`Windows { name })
let user_unix ~uid ~gid = `User (`ById { uid; gid })
let user_windows ~name = `User (`ByName { name })

let root_unix = `Unix { uid = 0; gid = 0 }
let root_windows = `Windows { name = "ContainerAdministrator" }
let root_unix = `ById { uid = 0; gid = 0 }
let root_windows = `ByName { name = "ContainerAdministrator" }
let root = if Sys.win32 then root_windows else root_unix

let rec pp_no_boxes f : Sexplib.Sexp.t -> unit = function
Expand Down
12 changes: 6 additions & 6 deletions lib_spec/spec.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,18 +5,18 @@ type copy = {
exclude : string list;
} [@@deriving sexp]

type unix_user = {
type numeric_user = {
uid : int;
gid : int;
} [@@deriving sexp]

type windows_user = {
type named_user = {
name : string;
} [@@deriving sexp]

type user = [
| `Unix of unix_user
| `Windows of windows_user
| `ById of numeric_user
| `ByName of named_user
] [@@deriving sexp]

type run = {
Expand Down Expand Up @@ -53,8 +53,8 @@ val env : string -> string -> op
val user_unix : uid:int -> gid:int -> op
val user_windows : name:string -> op

val root_unix : [`Unix of unix_user]
val root_windows : [`Windows of windows_user]
val root_unix : [`ById of numeric_user]
val root_windows : [`ByName of named_user]
val root : user

val pp : t Fmt.t
Expand Down
4 changes: 2 additions & 2 deletions main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -181,10 +181,10 @@ let buildkit =
["buildkit"]

let escape =
let styles = [("unix", `Unix); ("windows", `Windows)] in
let styles = [("unix", `ById); ("windows", `ByName)] in
let doc = Arg.doc_alts_enum styles |> Printf.sprintf "Dockerfile escape style, must be %s." in
Arg.value @@
Arg.opt Arg.(enum styles) (if Sys.unix then `Unix else `Windows) @@
Arg.opt Arg.(enum styles) (if Sys.unix then `ById else `ByName) @@
Arg.info ~doc
~docv:"STYLE"
["escape"]
Expand Down
4 changes: 2 additions & 2 deletions stress/stress.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,15 +56,15 @@ module Test(Store : S.STORE) = struct
let test_cache t =
let uid = Unix.getuid () in
let gid = Unix.getgid () in
let user = `Unix { Spec.uid = 123; gid = 456 } in
let user = `ById { Spec.uid = 123; gid = 456 } in
let id = "c1" in
(* Create a new cache *)
Store.delete_cache t id >>= fun x ->
assert (x = Ok ());
Store.cache ~user t id >>= fun (c, r) ->
assert ((Unix.lstat c).Unix.st_uid = 123);
assert ((Unix.lstat c).Unix.st_gid = 456);
let user = `Unix { Spec.uid; gid } in
let user = `ById { Spec.uid; gid } in
Os.exec ["sudo"; "chown"; Printf.sprintf "%d:%d" uid gid; "--"; c] >>= fun () ->
assert (Sys.readdir c = [| |]);
write ~path:(c / "data") "v1" >>= fun () ->
Expand Down
6 changes: 3 additions & 3 deletions test/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -443,7 +443,7 @@ let test_tar_long_filename _switch () =
with_file (dst_dir / "out.tar") Lwt_unix.[O_WRONLY; O_CREAT; O_CLOEXEC] 0
@@ fun to_untar ->
let src_manifest = Manifest.generate ~exclude:[] ~src_dir "." |> Result.get_ok in
let user = Spec.(`Unix { uid=1000; gid=1000 }) in
let user = Spec.(`ById { uid=1000; gid=1000 }) in
Tar_transfer.send_file
~src_dir
~src_manifest
Expand Down Expand Up @@ -503,7 +503,7 @@ let test_sexp () =
let test_docker_unix () =
let test ~buildkit name expect sexp =
let spec = Spec.t_of_sexp (Sexplib.Sexp.of_string sexp) in
let got = Obuilder_spec.Docker.dockerfile_of_spec ~buildkit ~os:`Unix spec in
let got = Obuilder_spec.Docker.dockerfile_of_spec ~buildkit ~os:`ById spec in
let expect = remove_indent expect in
Alcotest.(check string) name expect got
in
Expand Down Expand Up @@ -600,7 +600,7 @@ let test_docker_unix () =
let test_docker_windows () =
let test ~buildkit name expect sexp =
let spec = Spec.t_of_sexp (Sexplib.Sexp.of_string sexp) in
let got = Obuilder_spec.Docker.dockerfile_of_spec ~buildkit ~os:`Windows spec in
let got = Obuilder_spec.Docker.dockerfile_of_spec ~buildkit ~os:`ByName spec in
let expect = remove_indent expect in
Alcotest.(check string) name expect got
in
Expand Down

0 comments on commit 6ea9db3

Please sign in to comment.