Skip to content

Commit

Permalink
Fix the detection of the current terminal size
Browse files Browse the repository at this point in the history
Tested on:
* Linux/glibc
* Linux/musl
* macOS
* FreeBSD
* OpenBSD
* NetBSD
* Cygwin
  • Loading branch information
kit-ty-kate committed Oct 21, 2024
1 parent ae6abde commit 5a95f17
Show file tree
Hide file tree
Showing 8 changed files with 50 additions and 20 deletions.
5 changes: 5 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,10 @@ users)

## Remove

## UI
* [BUG] Fix the detection of the current terminal size [#6244 @kit-ty-kate - fix #6243]
* [BUG] Ensure the output of opam commands using a column style UI stay consistent accross environment by setting the number of columns to 80 if stdout is not a tty and if the `COLUMNS` env variable is not set [#6244 @kit-ty-kate]

## Switch

## Config
Expand Down Expand Up @@ -122,3 +126,4 @@ users)
## opam-format

## opam-core
* `OpamStubs.get_stdout_ws_col`: new Unix-only function returning the number of columns of the current terminal window [#6244 @kit-ty-kate]
2 changes: 1 addition & 1 deletion src/core/dune
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@
(wrapped false))

(rule
(deps opamWindows.c opamInject.c)
(deps opamWindows.c opamInject.c opamUnix.c)
(action (copy# opamCommonStubs.c opam_stubs.c)))

(rule
Expand Down
2 changes: 2 additions & 0 deletions src/core/opamCommonStubs.c
Original file line number Diff line number Diff line change
Expand Up @@ -63,4 +63,6 @@ CAMLprim value opam_is_executable(value path)
#ifdef _WIN32
#include "opamInject.c"
#include "opamWindows.c"
#else
#include "opamUnix.c"
#endif
29 changes: 10 additions & 19 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -936,25 +936,16 @@ module OpamSys = struct
)

let get_terminal_columns () =
let fallback = 80 in
let cols =
match (* terminfo *)
Option.replace int_of_string_opt (process_in "tput" ["cols"])
with
| Some x -> x
| None ->
try (* GNU stty *)
begin match
Option.map (fun x -> OpamString.split x ' ')
(process_in "stty" ["size"])
with
| Some [_ ; v] -> int_of_string v
| _ -> failwith "stty"
end
with
| Failure _ -> fallback
in
if cols > 0 then cols else fallback
try int_of_string (Env.get "COLUMNS") with
| Not_found | Failure _ ->
let fallback = 80 in
let cols =
if tty_out then
OpamStubs.get_stdout_ws_col ()
else
fallback
in
if cols > 0 then cols else fallback

let win32_get_console_width default_columns =
try
Expand Down
6 changes: 6 additions & 0 deletions src/core/opamStubs.mli
Original file line number Diff line number Diff line change
Expand Up @@ -165,3 +165,9 @@ val getVersionInfo : string -> win32_version_info option

val get_initial_environment : unit -> string list
(** Windows only. Returns the environment which new processes would receive. *)

val get_stdout_ws_col : unit -> int
(** Unix only. Returns the number of columns of the current terminal window
linked with stdout. If stdout isn't linked to any terminal
(e.g. redirection), then this function will return 0. A valid number
of columns should be strictly above 0. *)
2 changes: 2 additions & 0 deletions src/core/opamStubs.unix.ml
Original file line number Diff line number Diff line change
Expand Up @@ -46,3 +46,5 @@ let getErrorMode = that's_a_no_no
let setConsoleToUTF8 = that's_a_no_no
let getVersionInfo = that's_a_no_no
let get_initial_environment = that's_a_no_no

external get_stdout_ws_col : unit -> int = "opam_stdout_ws_col"
20 changes: 20 additions & 0 deletions src/core/opamUnix.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
/**************************************************************************/
/* */
/* Copyright 2024 Kate Deplaix */
/* */
/* All rights reserved. This file is distributed under the terms of the */
/* GNU Lesser General Public License version 2.1, with the special */
/* exception on linking described in the file LICENSE. */
/* */
/**************************************************************************/

#include <sys/ioctl.h>

CAMLprim value opam_stdout_ws_col(value _unit) {
struct winsize win;

if (-1 == ioctl(STDOUT_FILENO, TIOCGWINSZ, &win)) {
return Val_int(0);
}
return Val_int(win.ws_col);
}
4 changes: 4 additions & 0 deletions src/core/opamWin32Stubs.win32.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,3 +47,7 @@ external getErrorMode : unit -> int = "OPAMW_GetErrorMode"
external setConsoleToUTF8 : unit -> unit = "OPAMW_SetConsoleToUTF8"
external getVersionInfo : string -> 'a option = "OPAMW_GetVersionInfo"
external get_initial_environment : unit -> string list = "OPAMW_CreateEnvironmentBlock"

let that's_a_no_no _ = failwith "Unix only. This function isn't implemented."

let get_stdout_ws_col = that's_a_no_no

0 comments on commit 5a95f17

Please sign in to comment.