Skip to content

Commit

Permalink
fix: only sign executables (#8361)
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro authored Aug 12, 2023
1 parent c9e5de7 commit ade58ac
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 3 deletions.
3 changes: 2 additions & 1 deletion bin/install_uninstall.ml
Original file line number Diff line number Diff line change
Expand Up @@ -340,7 +340,8 @@ module File_ops_real (W : sig
| Dune_package -> process_dune_package ~get_location:conf.get_location
in
copy_special_file ~src ~package ~ic ~oc ~f)
| None -> Dune_rules.Artifact_substitution.copy_file ~conf ~src ~dst ~chmod ()
| None ->
Dune_rules.Artifact_substitution.copy_file ~conf ~executable ~src ~dst ~chmod ()
;;

let remove_file_if_exists dst =
Expand Down
2 changes: 2 additions & 0 deletions doc/changes/8361.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- Stop signing source files with substitutions. Sign only binaries instead
(#8361, fixes #8360, @anmonteiro)
14 changes: 12 additions & 2 deletions src/dune_rules/artifact_substitution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -649,7 +649,15 @@ let replace_if_different ~delete_dst_if_it_is_a_directory ~src ~dst =
if not up_to_date then Path.rename src dst
;;

let copy_file ~conf ?chmod ?(delete_dst_if_it_is_a_directory = false) ~src ~dst () =
let copy_file
~conf
?(executable = false)
?chmod
?(delete_dst_if_it_is_a_directory = false)
~src
~dst
()
=
(* We create a temporary file in the same directory to ensure it's on the same
partition as [dst] (otherwise, [Path.rename temp_file dst] won't work). The
prefix ".#" is used because Dune ignores such files and so creating this
Expand All @@ -664,7 +672,9 @@ let copy_file ~conf ?chmod ?(delete_dst_if_it_is_a_directory = false) ~src ~dst
let open Fiber.O in
Path.parent dst |> Option.iter ~f:Path.mkdir_p;
let* has_subst = copy_file_non_atomic ~conf ?chmod ~src ~dst:temp_file () in
let+ () = run_sign_hook conf ~has_subst temp_file in
let+ () =
if executable then run_sign_hook conf ~has_subst temp_file else Fiber.return ()
in
replace_if_different ~delete_dst_if_it_is_a_directory ~src:temp_file ~dst)
~finally:(fun () ->
Path.unlink_no_err temp_file;
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/artifact_substitution.mli
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ val decode : string -> t option
and then atomically renamed to [dst]. *)
val copy_file
: conf:conf
-> ?executable:bool
-> ?chmod:(int -> int)
-> ?delete_dst_if_it_is_a_directory:bool
-> src:Path.t
Expand Down

0 comments on commit ade58ac

Please sign in to comment.