Skip to content

Commit

Permalink
Merge pull request #1070 from AltGr/patch-errors
Browse files Browse the repository at this point in the history
Fixed error messages on patch errors
  • Loading branch information
AltGr committed Jan 9, 2014
2 parents d29f132 + 5683629 commit 1d1fa96
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 13 deletions.
16 changes: 7 additions & 9 deletions src/client/opamAction.ml
Expand Up @@ -540,16 +540,14 @@ let build_and_install_package_aux t ~metadata nv =
let metadata = get_metadata t in
OpamFilename.exec ~env ~name ~metadata p_build commands in

Some exec
with e -> None
exec
with e ->
raise
(OpamGlobals.Package_error
(Printf.sprintf "Could not get the source for %s:\n%s"
(OpamPackage.to_string nv)
(Printexc.to_string e)))
in
match exec with
| None ->
raise
(OpamGlobals.Package_error
(Printf.sprintf "Could not get the source for %s."
(OpamPackage.to_string nv)))
| Some exec ->
try
(* First, we build the package. *)
exec ("Building " ^ OpamPackage.to_string nv) OpamFile.OPAM.build;
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamClient.ml
Expand Up @@ -150,7 +150,7 @@ let with_switch_backup command f =
OpamPackage.Set.equal t.installed_roots t1.installed_roots then
OpamFilename.remove file
else
Printf.eprintf "The former state can be restored with \
Printf.eprintf "\nThe former state can be restored with \
%s switch import -f %S\n%!"
Sys.argv.(0) (OpamFilename.to_string file);
raise err
Expand Down
7 changes: 4 additions & 3 deletions src/core/opamSystem.ml
Expand Up @@ -591,9 +591,9 @@ let download ~overwrite ~filename:src ~dst:dst =
really_download ~overwrite ~src ~dst

let patch p =
let max_trying = 20 in
let max_trying = 4 in
if not (Sys.file_exists p) then
internal_error "Cannot find %s." p;
internal_error "Patch file %S not found." p;
let patch ~dryrun n =
let opts = if dryrun then
let open OpamGlobals in
Expand All @@ -607,7 +607,7 @@ let patch p =
command ?verbose ("patch" :: ("-p" ^ string_of_int n) :: "-i" :: p :: opts) in
let rec aux n =
if n = max_trying then
internal_error "Application of %s failed: can not determine the correct patch level." p
internal_error "Patch %s does not apply." p
else if None = try Some (patch ~dryrun:true n) with _ -> None then
aux (succ n)
else
Expand All @@ -633,6 +633,7 @@ let () =
| Process_error r -> Some (OpamProcess.string_of_result r)
| Internal_error m -> Some (with_opam_info m)
| Command_not_found c -> Some (Printf.sprintf "%S: command not found." c)
| Sys.Break -> Some "User interruption"
| Unix.Unix_error (e, fn, msg) ->
let msg = if msg = "" then "" else " on " ^ msg in
let error = Printf.sprintf "%s: %S failed%s: %s"
Expand Down

0 comments on commit 1d1fa96

Please sign in to comment.