Skip to content

Commit

Permalink
Delay the creation of the context used when a package failed to build…
Browse files Browse the repository at this point in the history
… up until the package failed
  • Loading branch information
kit-ty-kate committed Oct 29, 2024
1 parent fabb40f commit c0bcb68
Show file tree
Hide file tree
Showing 8 changed files with 25 additions and 24 deletions.
4 changes: 2 additions & 2 deletions src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -643,7 +643,7 @@ let make_command st opam ?dir ?text_command (cmd, args) =
let cmd, args = OpamStd.Option.default (cmd, args) text_command in
OpamProcess.make_command_text name ~args cmd
in
let context =
let context = lazy begin
let open OpamStd.Option.Op in
String.concat " | " [
OpamVersion.(to_string current);
Expand Down Expand Up @@ -684,7 +684,7 @@ let make_command st opam ?dir ?text_command (cmd, args) =
OpamUrl.to_string repo.repo_url ^
OpamStd.Option.to_string (fun s -> "#"^s) stamp
]
in
end in
OpamSystem.make_command ~env ~name ?dir ~text
~resolve_path:OpamStateConfig.(not !r.dryrun)
~metadata:["context", context]
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamCliMain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ let rec main_catch_all f =
OpamConsole.errmsg "%s Command %S failed:\n%s\n"
(OpamConsole.colorise `red "[ERROR]")
(try
OpamStd.List.assoc String.equal "command" result.OpamProcess.r_info
OpamStd.List.assoc String.equal "command" (Lazy.force result.OpamProcess.r_info)
with Not_found -> "")
(Printexc.to_string e);
OpamConsole.errmsg "%s" (OpamStd.Exn.pretty_backtrace e);
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -294,7 +294,7 @@ module Json = struct
`O [ ("process-error",
`O ([ ("code", `String (string_of_int r_code));
("duration", `Float r_duration);
("info", `O (lmap (fun (k,v) -> (k, `String v)) r_info)); ]
("info", `O (lmap (fun (k,v) -> (k, `String v)) (Lazy.force r_info))); ]
@ if OpamCoreConfig.(!r.merged_output) then
[("output", `A (lmap (fun s -> `String s) r_stdout))]
else
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamFilename.mli
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ val env_of_list: (string * string) list -> string array

(** Execute a list of commands in a given directory *)
val exec: Dir.t -> ?env:(string * string) list -> ?name:string ->
?metadata:(string * string) list -> ?keep_going:bool -> string list list -> unit
?metadata:(string * string Lazy.t) list -> ?keep_going:bool -> string list list -> unit

(** Move a directory *)
val move_dir: src:Dir.t -> dst:Dir.t -> unit
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamParallel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -277,7 +277,7 @@ module Make (G : G) = struct
| _ -> OpamProcess.wait_one (List.map fst processes)
with e -> fail (fst (snd (List.hd processes))) e
in
let n,cont = OpamStd.(List.assoc Compare.equal process processes) in
let n,cont = OpamStd.List.assoc OpamProcess.equal process processes in
log "Collected task for job %a (ret:%d)"
(slog (string_of_int @* V.hash)) n result.OpamProcess.r_code;
let next =
Expand Down
21 changes: 11 additions & 10 deletions src/core/opamProcess.ml
Original file line number Diff line number Diff line change
Expand Up @@ -208,7 +208,7 @@ type command = {
cmd_stdout: string option;
cmd_verbose: bool option;
cmd_name: string option;
cmd_metadata: (string * string) list option;
cmd_metadata: (string * string Lazy.t) list option;
}

let string_of_command c = String.concat " " (c.cmd::c.args)
Expand Down Expand Up @@ -249,7 +249,7 @@ type t = {
p_stderr : string option;
p_env : string option;
p_info : string option;
p_metadata: (string * string) list;
p_metadata: (string * string Lazy.t) list;
p_verbose: bool;
p_tmp_files: string list;
}
Expand Down Expand Up @@ -285,7 +285,7 @@ let make_info ?code ?signal
| None -> ()
| Some s -> print name s in

List.iter (fun (k,v) -> print k v) metadata;
List.iter (fun (k,v) -> print k (Lazy.force v)) metadata;
print "path" cwd;
print "command" (String.concat " " (cmd :: args));
print_opt "exit-code" (OpamStd.Option.map string_of_int code);
Expand Down Expand Up @@ -484,7 +484,7 @@ type result = {
r_code : int;
r_signal : int option;
r_duration : float;
r_info : (string * string) list;
r_info : (string * string) list Lazy.t;
r_stdout : string list;
r_stderr : string list;
r_cleanup : string list;
Expand All @@ -494,7 +494,7 @@ let empty_result = {
r_code = 0;
r_signal = None;
r_duration = 0.;
r_info = [];
r_info = Lazy.from_val [];
r_stdout = [];
r_stderr = [];
r_cleanup = [];
Expand Down Expand Up @@ -612,7 +612,7 @@ let set_verbose_f, print_verbose_f, isset_verbose_f, stop_verbose_f =
(* implem relies on sigalrm, not implemented on win32.
This will fall back to buffered output. *)
if Sys.win32 then () else
let files = OpamStd.List.sort_nodup compare files in
let files = OpamStd.List.sort_nodup OpamStd.Compare.compare files in
let ics =
List.map
(open_in_gen [Open_nonblock;Open_rdonly;Open_text;Open_creat] 0o600)
Expand Down Expand Up @@ -658,10 +658,11 @@ let exit_status p return =
if p.p_stdout <> p.p_stderr then
List.iter verbose_print_out stderr;
flush Stdlib.stdout);
let info =
let info = lazy begin
make_info ?code ?signal
~cmd:p.p_name ~args:p.p_args ~cwd:p.p_cwd ~metadata:p.p_metadata
~env_file:p.p_env ~stdout_file:p.p_stdout ~stderr_file:p.p_stderr () in
~env_file:p.p_env ~stdout_file:p.p_stdout ~stderr_file:p.p_stderr ()
end in
{
r_code = OpamStd.Option.default 256 code;
r_signal = signal;
Expand Down Expand Up @@ -825,7 +826,7 @@ let string_of_result ?(color=`yellow) r =
print str;
Buffer.add_char b '\n' in

print (string_of_info ~color r.r_info);
print (string_of_info ~color (Lazy.force r.r_info));

if r.r_stdout <> [] then
if r.r_stderr = r.r_stdout then
Expand All @@ -849,7 +850,7 @@ let string_of_result ?(color=`yellow) r =

let result_summary r =
Printf.sprintf "%S exited with code %d%s"
(try OpamStd.List.assoc String.equal "command" r.r_info
(try OpamStd.List.assoc String.equal "command" (Lazy.force r.r_info)
with Not_found -> "command")
r.r_code
(if r.r_code = 0 then "" else
Expand Down
8 changes: 4 additions & 4 deletions src/core/opamProcess.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ type command = private {
cmd_stdout: string option;
cmd_verbose: bool option;
cmd_name: string option;
cmd_metadata: (string * string) list option;
cmd_metadata: (string * string Lazy.t) list option;
}

(** Builds a shell command for later execution.
Expand All @@ -40,7 +40,7 @@ val command:
?env:string array ->
?verbose:bool ->
?name:string ->
?metadata:(string*string) list ->
?metadata:(string * string Lazy.t) list ->
?dir:string ->
?allow_stdin:bool ->
?stdout:string ->
Expand Down Expand Up @@ -71,7 +71,7 @@ type t = {
p_stderr : string option; (** stderr dump file *)
p_env : string option; (** dump environment variables *)
p_info : string option; (** dump process info *)
p_metadata: (string * string) list; (** Metadata associated to the process *)
p_metadata: (string * string Lazy.t) list; (** Metadata associated to the process *)
p_verbose: bool; (** whether output of the process should be
displayed *)
p_tmp_files: string list; (** temporary files that should be cleaned up upon
Expand All @@ -86,7 +86,7 @@ type result = {
r_code : int; (** Process exit code, or 256 on error *)
r_signal : int option; (** Signal received if the processed was killed *)
r_duration : float; (** Process duration *)
r_info : (string * string) list; (** Process info *)
r_info : (string * string) list Lazy.t; (** Process info *)
r_stdout : string list; (** Content of stdout dump file *)
r_stderr : string list; (** Content of stderr dump file *)
r_cleanup : string list; (** List of files to clean-up *)
Expand Down
8 changes: 4 additions & 4 deletions src/core/opamSystem.mli
Original file line number Diff line number Diff line change
Expand Up @@ -178,7 +178,7 @@ val directories_with_links: string -> string list
case you can end up with a process error instead) *)
val make_command:
?verbose:bool -> ?env:string array -> ?name:string -> ?text:string ->
?metadata:(string * string) list -> ?allow_stdin:bool -> ?stdout:string ->
?metadata:(string * string Lazy.t) list -> ?allow_stdin:bool -> ?stdout:string ->
?dir:string -> ?resolve_path:bool ->
string -> string list -> OpamProcess.command

Expand Down Expand Up @@ -214,14 +214,14 @@ val apply_cygpath: string -> string
(** [command cmd] executes the command [cmd] in the correct OPAM
environment. *)
val command: ?verbose:bool -> ?env:string array -> ?name:string ->
?metadata:(string * string) list -> ?allow_stdin:bool ->
?metadata:(string * string Lazy.t) list -> ?allow_stdin:bool ->
command -> unit

(** [commands cmds] executes the commands [cmds] in the correct OPAM
environment. It stops whenever one command fails unless [keep_going] is set
to [true]. In this case, the first error is re-raised at the end. *)
val commands: ?verbose:bool -> ?env:string array -> ?name:string ->
?metadata:(string * string) list -> ?keep_going:bool -> command list -> unit
?metadata:(string * string Lazy.t) list -> ?keep_going:bool -> command list -> unit

(** [read_command_output cmd] executes the command [cmd] in the
correct OPAM environment and return the lines from output if the command
Expand All @@ -230,7 +230,7 @@ val commands: ?verbose:bool -> ?env:string array -> ?name:string ->
It returns stdout and stder combiend, unless [ignore_stderr] is st to true.
*)
val read_command_output: ?verbose:bool -> ?env:string array ->
?metadata:(string * string) list -> ?allow_stdin:bool ->
?metadata:(string * string Lazy.t) list -> ?allow_stdin:bool ->
?ignore_stderr:bool -> command -> string list

(** END *)
Expand Down

0 comments on commit c0bcb68

Please sign in to comment.