Skip to content

Commit

Permalink
Add core config var OPAMERRLOGLEN to control error output
Browse files Browse the repository at this point in the history
I also pushed the default from 10 to 12. Closes #2111
  • Loading branch information
AltGr committed Apr 15, 2015
1 parent 7834a6d commit 43eabd3
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 3 deletions.
5 changes: 5 additions & 0 deletions src/core/opamCoreConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ type t = {
lock_retries: int;
log_dir: string;
keep_log_dir: bool;
errlog_length: int;
}

type 'a options_fun =
Expand All @@ -39,6 +40,7 @@ type 'a options_fun =
?lock_retries:int ->
?log_dir:string ->
?keep_log_dir:bool ->
?errlog_length:int ->
unit -> 'a

let default = {
Expand All @@ -55,6 +57,7 @@ let default = {
let base = Printf.sprintf "opam-%s-%d" user (Unix.getpid()) in
Filename.(concat (get_temp_dir_name ()) base));
keep_log_dir = false;
errlog_length = 12;
}

let setk k t
Expand All @@ -68,6 +71,7 @@ let setk k t
?lock_retries
?log_dir
?keep_log_dir
?errlog_length
()
=
let (+) x opt = match opt with Some x -> x | None -> x in
Expand All @@ -82,6 +86,7 @@ let setk k t
lock_retries = t.lock_retries + lock_retries;
log_dir = t.log_dir + log_dir;
keep_log_dir = t.keep_log_dir + keep_log_dir;
errlog_length = t.errlog_length + errlog_length;
}

let set t = setk (fun x -> x) t
Expand Down
3 changes: 3 additions & 0 deletions src/core/opamCoreConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,8 @@ type t = private {
(** Where to store log and temporary files (output from commands...) *)
keep_log_dir : bool;
(** Whether to cleanup temporary and log files on exit *)
errlog_length : int;
(** The number of log lines displayed on process error. 0 for all *)
}

type 'a options_fun =
Expand All @@ -51,6 +53,7 @@ type 'a options_fun =
?lock_retries:int ->
?log_dir:string ->
?keep_log_dir:bool ->
?errlog_length:int ->
unit -> 'a

val default : t
Expand Down
6 changes: 3 additions & 3 deletions src/core/opamProcess.ml
Original file line number Diff line number Diff line change
Expand Up @@ -466,7 +466,6 @@ let cleanup ?(force=false) r =
if force || (not (OpamConsole.debug ()) && is_success r) then
List.iter safe_unlink r.r_cleanup

let log_limit = 10
let log_line_limit = 5 * 80
let truncate_str = "[...]"

Expand All @@ -481,7 +480,6 @@ let truncate_line str =
(* Take the last [n] elements of [l] (trying to keep an unindented header line
for context, like diff) *)
let truncate l =
let l = List.rev l in
let unindented s =
String.length s > 0 && s.[0] <> ' ' && s.[0] <> '\t'
in
Expand All @@ -495,7 +493,9 @@ let truncate l =
with Not_found -> truncate_str :: truncate_line x :: acc)
| x::r -> cut (n-1) (truncate_line x :: acc) r
in
cut log_limit [] l
let len = OpamCoreConfig.(!r.errlog_length) in
if len <= 0 then l
else cut len [] (List.rev l)

let string_of_result ?(color=`yellow) r =
let b = Buffer.create 2048 in
Expand Down
1 change: 1 addition & 0 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -876,6 +876,7 @@ module Config = struct
?lock_retries:(env_int "LOCKRETRIES")
?log_dir:(env_string "LOGS")
?keep_log_dir:(env_bool "KEEPLOGS")
?errlog_length:(env_int "ERRLOGLEN")

This comment has been minimized.

Copy link
@samoht

samoht Apr 15, 2015

Member

any documentation with the ERRLOGLEN env variable?

This comment has been minimized.

Copy link
@AltGr

AltGr Apr 15, 2015

Author Member

It's in the mli :D
Seriously, not yet.

()
end

Expand Down

0 comments on commit 43eabd3

Please # to comment.