Skip to content

Commit

Permalink
erts: Fix isatty on windows
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Oct 17, 2024
1 parent efb0b71 commit 8129a6b
Show file tree
Hide file tree
Showing 2 changed files with 75 additions and 20 deletions.
57 changes: 43 additions & 14 deletions erts/emulator/nifs/common/prim_tty_nif.c
Original file line number Diff line number Diff line change
Expand Up @@ -239,18 +239,48 @@ static int tty_get_fd(ErlNifEnv *env, ERL_NIF_TERM atom, int *fd) {
return 1;
}

static ERL_NIF_TERM isatty_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef __WIN32__
static HANDLE tty_get_handle(ErlNifEnv *env, ERL_NIF_TERM atom) {
HANDLE handle = INVALID_HANDLE_VALUE;
int fd;
if (tty_get_fd(env, atom, &fd)) {

switch (fd) {
case 0: handle = GetStdHandle(STD_INPUT_HANDLE); break;
case 1: handle = GetStdHandle(STD_OUTPUT_HANDLE); break;
case 2: handle = GetStdHandle(STD_ERROR_HANDLE); break;
}
}
return handle;
}
#endif

static ERL_NIF_TERM isatty_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef __WIN32__
HANDLE handle = tty_get_handle(env, argv[0]);

if (handle == INVALID_HANDLE_VALUE)
return atom_ebadf;

switch (GetFileType(handle)) {
case FILE_TYPE_CHAR: return atom_true;
case FILE_TYPE_PIPE:
case FILE_TYPE_DISK: return atom_false;
default: return atom_ebadf;
}
#else
int fd;
if (tty_get_fd(env, argv[0], &fd)) {
if (isatty(fd)) {
return atom_true;
} else if (errno == EINVAL || errno == ENOTTY) {
return atom_false;
} else {
}
else {
return atom_ebadf;
}
}
#endif

return enif_make_badarg(env);
}
Expand Down Expand Up @@ -650,22 +680,21 @@ static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
/* Poll if stdin/stdout/stderr are still open. */
static ERL_NIF_TERM tty_is_open(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
TTYResource *tty;
#ifdef __WIN32__
HANDLE handle;
#else
int fd;
#endif

if (!enif_get_resource(env, argv[0], tty_rt, (void **)&tty))
return enif_make_badarg(env);

if (tty_get_fd(env, argv[1], &fd)) {
#ifdef __WIN32__

#ifdef WIN32
HANDLE handle;
DWORD bytesAvailable = 0;
handle = tty_get_handle(env, argv[1]);

switch (fd) {
case 0: handle = GetStdHandle(STD_INPUT_HANDLE); break;
case 1: handle = GetStdHandle(STD_OUTPUT_HANDLE); break;
case 2: handle = GetStdHandle(STD_ERROR_HANDLE); break;
}
if (handle != INVALID_HANDLE_VALUE) {
DWORD bytesAvailable = 0;

switch (GetFileType(handle)) {
case FILE_TYPE_CHAR: {
Expand Down Expand Up @@ -695,9 +724,9 @@ static ERL_NIF_TERM tty_is_open(ErlNifEnv* env, int argc, const ERL_NIF_TERM arg
return atom_true;
}
}

}
#else

if (tty_get_fd(env, argv[1], &fd)) {
struct pollfd fds[1];
int ret;

Expand All @@ -713,8 +742,8 @@ static ERL_NIF_TERM tty_is_open(ErlNifEnv* env, int argc, const ERL_NIF_TERM arg
} else if (ret == 1 && fds[0].revents & POLLHUP) {
return atom_false;
}
#endif
}
#endif
return enif_make_badarg(env);
}

Expand Down
38 changes: 32 additions & 6 deletions lib/stdlib/test/io_proto_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -316,19 +316,45 @@ setopts_getopts(Config) when is_list(Config) ->
{expect, "true"}
],[],"",["-oldshell"]),

%% Test that terminal options when used in non-terminal
%% are returned as they should
%% Test that terminal options when used in non-terminal are returned as they should
%% both when run as an os:cmd and when run directly as a port.
Erl = ct:get_progname(),
Str = os:cmd(Erl ++ " -noshell -eval \"io:format(~s'~p.',[io:getopts()])\" -s init stop"),
CmdStr = os:cmd(Erl ++ " -noshell -eval \"io:format(~s'~p.',[io:getopts()])\" -s init stop"),
maybe
{ok, T, _} ?= erl_scan:string(Str),
{ok, T, _} ?= erl_scan:string(CmdStr),
{ok, Opts} ?= erl_parse:parse_term(T),
?assertEqual(false, proplists:get_value(terminal,Opts)),
?assertEqual(false, proplists:get_value(stdin,Opts)),
case os:type() of
{win32, nt} ->
%% On Windows stdin will be a tty
?assertEqual(true, proplists:get_value(stdin,Opts));
_ ->
?assertEqual(false, proplists:get_value(stdin,Opts))
end,
?assertEqual(false, proplists:get_value(stdout,Opts)),
?assertEqual(false, proplists:get_value(stderr,Opts))
else
_ -> ct:fail({failed_to_parse, Str})
_ -> ct:fail({failed_to_parse, CmdStr})
end,

Port = erlang:open_port({spawn, Erl ++ " -noshell -eval \"io:format(~s'~p.',[io:getopts()])\" -s init stop"},
[exit_status]),
PortStr = (fun F() ->
receive
{Port,{data,D}} -> D ++ F();
{Port,{exit_status,0}} -> []
end
end)(),

maybe
{ok, PortT, _} ?= erl_scan:string(PortStr),
{ok, PortOpts} ?= erl_parse:parse_term(PortT),
?assertEqual(false, proplists:get_value(terminal,PortOpts)),
?assertEqual(false, proplists:get_value(stdin,PortOpts)),
?assertEqual(false, proplists:get_value(stdout,PortOpts)),
?assertEqual(proplists:get_value(stderr, io:getopts()), proplists:get_value(stderr,PortOpts))
else
_ -> ct:fail({failed_to_parse, PortStr})
end,
ok.

Expand Down

0 comments on commit 8129a6b

Please sign in to comment.