Skip to content

Commit

Permalink
Merge pull request #5999 from kit-ty-kate/lock-stderr
Browse files Browse the repository at this point in the history
Display lock hold/release messages on stderr instead of stdout
  • Loading branch information
kit-ty-kate committed Jun 6, 2024
2 parents 1ff0770 + c9fe9f3 commit 5c582e1
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 8 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ users)
## Global CLI
* Fix a typo in the variable description returned by "opam var" [#5961 @jmid]
* Out-of-the-box UTF-8 paged --help on Windows [#5970 @kit-ty-kate]
* ✘ Display lock hold/release messages on stderr instead of stdout [#5999 @kit-ty-kate - fix #5990]

## Plugins

Expand Down Expand Up @@ -180,3 +181,4 @@ users)
* `OpamStubs.getVersionInfo`: on Windows, retrives the version information block of an executable/library [#5963 @dra27]
* `OpamStubs.readRegistry`: on Windows, complements `OpamStubs.writeRegistry` [#5963 @dra27]
* `OpamStubs.get_initial_environment`: on Windows, returns the pristine environment for new shells [#5963 @dra27]
* `OpamConsole`: Add `formatted_errmsg` [#5999 @kit-ty-kate]
12 changes: 7 additions & 5 deletions src/core/opamConsole.ml
Original file line number Diff line number Diff line change
Expand Up @@ -610,7 +610,13 @@ let note fmt =
(OpamStd.Format.reformat ~start_column:7 ~indent:7 str)
) fmt

let formatted_msg_aux ~indent out fmt =
Printf.ksprintf
(fun s -> print_message out "%s" (OpamStd.Format.reformat ?indent s))
fmt

let errmsg fmt = print_message `stderr fmt
let formatted_errmsg ?indent fmt = formatted_msg_aux ~indent `stderr fmt

let error_and_exit reason fmt =
Printf.ksprintf (fun str ->
Expand All @@ -619,11 +625,7 @@ let error_and_exit reason fmt =
) fmt

let msg fmt = print_message `stdout fmt

let formatted_msg ?indent fmt =
Printf.ksprintf
(fun s -> print_message `stdout "%s" (OpamStd.Format.reformat ?indent s))
fmt
let formatted_msg ?indent fmt = formatted_msg_aux ~indent `stdout fmt

let last_status = ref ""

Expand Down
1 change: 1 addition & 0 deletions src/core/opamConsole.mli
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@ val note : ('a, unit, string, unit) format4 -> 'a
(** Message without prefix, reformat or newline, to stderr (useful to continue
error messages without repeating "[ERROR]") *)
val errmsg : ('a, unit, string, unit) format4 -> 'a
val formatted_errmsg : ?indent:int -> ('a, unit, string, unit) format4 -> 'a

val error_and_exit :
OpamStd.Sys.exit_reason -> ('a, unit, string, 'b) format4 -> 'a
Expand Down
6 changes: 3 additions & 3 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1224,15 +1224,15 @@ let rec flock_update
OpamConsole.error_and_exit `Locked
"Another process has locked %s and non blocking mode enabled"
file;
OpamConsole.formatted_msg
OpamConsole.formatted_errmsg
"Another process has locked %s, waiting (%s to abort)... "
file (if Sys.win32 then "CTRL+C" else "C-c");
let rec lock_w_ignore_sig () =
try Unix.lockf fd (unix_lock_op ~dontblock:false flag) 0;
with Sys.Break as e -> (OpamConsole.msg "\n"; raise e)
with Sys.Break as e -> (OpamConsole.errmsg "\n"; raise e)
| Unix.Unix_error (Unix.EINTR,_,_) -> lock_w_ignore_sig ()
in lock_w_ignore_sig ();
OpamConsole.msg "lock acquired.\n");
OpamConsole.errmsg "lock acquired.\n");
lock.kind <- (flag :> lock_flag)
| _ -> assert false
Expand Down

0 comments on commit 5c582e1

Please sign in to comment.