Skip to content

Commit

Permalink
Compute sign hook lazily
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Oct 17, 2022
1 parent d319f05 commit cecedc0
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 7 deletions.
12 changes: 6 additions & 6 deletions src/dune_rules/artifact_substitution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ type conf =
; get_location : Section.t -> Package.Name.t -> Path.t
; get_config_path : configpath -> Path.t option
; hardcoded_ocaml_path : hardcoded_ocaml_path
; sign_hook : (Path.t -> unit Fiber.t) option
; sign_hook : (Path.t -> unit Fiber.t) option Lazy.t
}

let mac_codesign_hook ~codesign path =
Expand All @@ -74,7 +74,7 @@ let conf_of_context (context : Context.t option) =
; get_location = (fun _ _ -> Code_error.raise "no context available" [])
; get_config_path = (fun _ -> Code_error.raise "no context available" [])
; hardcoded_ocaml_path = Hardcoded []
; sign_hook = None
; sign_hook = lazy None
}
| Some context ->
let get_location = Install.Section.Paths.get_local_location context.name in
Expand All @@ -87,7 +87,7 @@ let conf_of_context (context : Context.t option) =
let install_dir = Path.build (Path.Build.relative install_dir "lib") in
Hardcoded (install_dir :: context.default_ocamlpath)
in
let sign_hook = sign_hook_of_context context in
let sign_hook = lazy (sign_hook_of_context context) in
{ get_vcs = Source_tree.nearest_vcs
; get_location
; get_config_path
Expand All @@ -111,15 +111,15 @@ let conf_for_install ~relocatable ~default_ocamlpath ~stdlib_dir ~roots ~context
| Sourceroot -> None
| Stdlib -> Some stdlib_dir
in
let sign_hook = sign_hook_of_context context in
let sign_hook = lazy (sign_hook_of_context context) in
{ get_location; get_vcs; get_config_path; hardcoded_ocaml_path; sign_hook }

let conf_dummy =
{ get_vcs = (fun _ -> Memo.return None)
; get_location = (fun _ _ -> Path.root)
; get_config_path = (fun _ -> None)
; hardcoded_ocaml_path = Hardcoded []
; sign_hook = None
; sign_hook = lazy None
}

let to_dyn = function
Expand Down Expand Up @@ -570,7 +570,7 @@ let copy_file_non_atomic ~conf ?chmod ~src ~dst () =

let run_sign_hook conf ~has_subst file =
match (conf.sign_hook, has_subst) with
| Some hook, true -> hook file
| (lazy (Some hook)), true -> hook file
| _ -> Fiber.return ()

(** This is just an optimisation: skip the renaming if the destination exists
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/artifact_substitution.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ type conf = private
; get_config_path : configpath -> Path.t option
; hardcoded_ocaml_path : hardcoded_ocaml_path
(** Initial prefix of installation when relocatable chosen *)
; sign_hook : (Path.t -> unit Fiber.t) option
; sign_hook : (Path.t -> unit Fiber.t) option Lazy.t
(** Called on binary after if has been edited *)
}

Expand Down

0 comments on commit cecedc0

Please sign in to comment.