Skip to content

Commit

Permalink
fixup! erts: Re-Implement shell using nif
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Aug 29, 2022
1 parent 23186c0 commit 530f845
Showing 1 changed file with 65 additions and 55 deletions.
120 changes: 65 additions & 55 deletions erts/emulator/nifs/common/prim_tty_nif.c
Original file line number Diff line number Diff line change
Expand Up @@ -106,46 +106,46 @@ static ErlNifResourceType *tty_rt;

/* The NIFs: */
static ERL_NIF_TERM isatty_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_set(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_create_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_set_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM setlocale_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_select(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_write(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_read(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_select_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_write_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM isprint_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM wcwidth_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM wcswidth_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM sizeof_wchar(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_window_size(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetent(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetnum(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetflag(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetstr(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgoto(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_read_signal(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM sizeof_wchar_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_window_size_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetent_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetnum_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetflag_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgetstr_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_tgoto_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ERL_NIF_TERM tty_read_signal_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);

static ErlNifFunc nif_funcs[] = {
{"isatty", 1, isatty_nif},
{"tty_create", 0, tty_create},
{"tty_init", 3, tty_init},
{"tty_set", 1, tty_set},
{"tty_read_signal", 2, tty_read_signal},
{"tty_create", 0, tty_create_nif},
{"tty_init", 3, tty_init_nif},
{"tty_set", 1, tty_set_nif},
{"tty_read_signal", 2, tty_read_signal_nif},
{"setlocale", 1, setlocale_nif},
{"tty_select", 3, tty_select},
{"tty_window_size", 1, tty_window_size},
{"write_nif", 2, tty_write, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"read_nif", 2, tty_read, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"tty_select", 3, tty_select_nif},
{"tty_window_size", 1, tty_window_size_nif},
{"write_nif", 2, tty_write_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"read_nif", 2, tty_read_nif, ERL_NIF_DIRTY_JOB_IO_BOUND},
{"isprint", 1, isprint_nif},
{"wcwidth", 1, wcwidth_nif},
{"wcswidth", 1, wcswidth_nif},
{"sizeof_wchar", 0, sizeof_wchar},
{"tgetent_nif", 1, tty_tgetent},
{"tgetnum_nif", 1, tty_tgetnum},
{"tgetflag_nif", 1, tty_tgetflag},
{"tgetstr_nif", 1, tty_tgetstr},
{"tgoto_nif", 2, tty_tgoto},
{"tgoto_nif", 3, tty_tgoto}
{"sizeof_wchar", 0, sizeof_wchar_nif},
{"tgetent_nif", 1, tty_tgetent_nif},
{"tgetnum_nif", 1, tty_tgetnum_nif},
{"tgetflag_nif", 1, tty_tgetflag_nif},
{"tgetstr_nif", 1, tty_tgetstr_nif},
{"tgoto_nif", 2, tty_tgoto_nif},
{"tgoto_nif", 3, tty_tgoto_nif}
};

/* NIF interface declarations */
Expand Down Expand Up @@ -274,11 +274,11 @@ static ERL_NIF_TERM wcswidth_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
return enif_make_badarg(env);
}

static ERL_NIF_TERM sizeof_wchar(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM sizeof_wchar_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
return enif_make_int(env, sizeof(wchar_t));
}

static ERL_NIF_TERM tty_write(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_write_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
ERL_NIF_TERM head = argv[1], tail;
ErlNifIOQueue *q = NULL;
ErlNifIOVec vec, *iovec = &vec;
Expand Down Expand Up @@ -343,7 +343,7 @@ static ERL_NIF_TERM tty_write(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[
return atom_ok;
}

static ERL_NIF_TERM tty_read(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
TTYResource *tty;
ErlNifBinary bin;
ERL_NIF_TERM res_term;
Expand All @@ -363,10 +363,14 @@ static ERL_NIF_TERM tty_read(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
}
for (int i = 0; i < inputs_read; i++) {
if (inputs[i].EventType == KEY_EVENT) {
if (inputs[i].Event.KeyEvent.bKeyDown && inputs[i].Event.KeyEvent.uChar.UnicodeChar < 256 && inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
if (inputs[i].Event.KeyEvent.bKeyDown &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar < 256 &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
num_characters++;
}
if (!inputs[i].Event.KeyEvent.bKeyDown && inputs[i].Event.KeyEvent.uChar.UnicodeChar > 255 && inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
if (!inputs[i].Event.KeyEvent.bKeyDown &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar > 255 &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
num_characters++;
}
}
Expand All @@ -377,18 +381,24 @@ static ERL_NIF_TERM tty_read(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
switch (inputs[i].EventType)
{
case KEY_EVENT:
if (inputs[i].Event.KeyEvent.bKeyDown && inputs[i].Event.KeyEvent.uChar.UnicodeChar < 256 && inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
if (inputs[i].Event.KeyEvent.bKeyDown &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar < 256 &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
characters[res++] = inputs[i].Event.KeyEvent.uChar.UnicodeChar;
}
if (!inputs[i].Event.KeyEvent.bKeyDown && inputs[i].Event.KeyEvent.uChar.UnicodeChar > 255 && inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
if (!inputs[i].Event.KeyEvent.bKeyDown &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar > 255 &&
inputs[i].Event.KeyEvent.uChar.UnicodeChar != 0) {
characters[res++] = inputs[i].Event.KeyEvent.uChar.UnicodeChar;
}
break;
case WINDOW_BUFFER_SIZE_EVENT:
enif_send(env, &tty->self, NULL,
enif_make_tuple2(env, enif_make_atom(env, "resize"),
enif_make_tuple2(env, enif_make_int(env, inputs[i].Event.WindowBufferSizeEvent.dwSize.Y),
enif_make_int(env, inputs[i].Event.WindowBufferSizeEvent.dwSize.X))));
enif_make_tuple2(
env,
enif_make_int(env, inputs[i].Event.WindowBufferSizeEvent.dwSize.Y),
enif_make_int(env, inputs[i].Event.WindowBufferSizeEvent.dwSize.X))));
break;
case MENU_EVENT:
case FOCUS_EVENT:
Expand Down Expand Up @@ -478,7 +488,7 @@ static ERL_NIF_TERM setlocale_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM a
#endif
}

static ERL_NIF_TERM tty_tgetent(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_tgetent_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef HAVE_TERMCAP
ErlNifBinary TERM;
if (!enif_inspect_iolist_as_binary(env, argv[0], &TERM))
Expand All @@ -492,7 +502,7 @@ static ERL_NIF_TERM tty_tgetent(ErlNifEnv* env, int argc, const ERL_NIF_TERM arg
#endif
}

static ERL_NIF_TERM tty_tgetnum(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_tgetnum_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef HAVE_TERMCAP
ErlNifBinary TERM;
if (!enif_inspect_iolist_as_binary(env, argv[0], &TERM))
Expand All @@ -503,7 +513,7 @@ static ERL_NIF_TERM tty_tgetnum(ErlNifEnv* env, int argc, const ERL_NIF_TERM arg
#endif
}

static ERL_NIF_TERM tty_tgetflag(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_tgetflag_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef HAVE_TERMCAP
ErlNifBinary TERM;
if (!enif_inspect_iolist_as_binary(env, argv[0], &TERM))
Expand All @@ -516,7 +526,7 @@ static ERL_NIF_TERM tty_tgetflag(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
#endif
}

static ERL_NIF_TERM tty_tgetstr(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_tgetstr_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef HAVE_TERMCAP
ErlNifBinary TERM, ret;
/* tgetstr seems to use a lot of stack buffer space,
Expand Down Expand Up @@ -551,7 +561,7 @@ static int tty_puts_putc(int c) {
}
#endif

static ERL_NIF_TERM tty_tgoto(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_tgoto_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#ifdef HAVE_TERMCAP
ErlNifBinary TERM;
char *ent;
Expand Down Expand Up @@ -581,7 +591,7 @@ static ERL_NIF_TERM tty_tgoto(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[
#endif
}

static ERL_NIF_TERM tty_create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_create_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {

TTYResource *tty = enif_alloc_resource(tty_rt, sizeof(TTYResource));
ERL_NIF_TERM tty_term;
Expand All @@ -604,15 +614,15 @@ static ERL_NIF_TERM tty_create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv
{
tty->dwOutMode = ENABLE_VIRTUAL_TERMINAL_PROCESSING | tty->dwOriginalOutMode;
if (!SetConsoleMode(tty->ofd, tty->dwOutMode)) {
// Failed to set any VT mode, can't do anything here.
/* Failed to set any VT mode, can't do anything here. */
return make_errno_error(env, "SetConsoleMode");
}
}
if (GetConsoleMode(tty->ifd, &tty->dwOriginalInMode))
{
tty->dwInMode = ENABLE_VIRTUAL_TERMINAL_INPUT | tty->dwOriginalInMode;
if (!SetConsoleMode(tty->ifd, tty->dwInMode)) {
// Failed to set any VT mode, can't do anything here.
/* Failed to set any VT mode, can't do anything here. */
return make_errno_error(env, "SetConsoleMode");
}
}
Expand All @@ -627,7 +637,7 @@ static ERL_NIF_TERM tty_create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv
return enif_make_tuple2(env, atom_ok, tty_term);
}

static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {

#if defined(HAVE_TERMCAP) || defined(__WIN32__)
ERL_NIF_TERM canon, echo, sig;
Expand Down Expand Up @@ -675,7 +685,7 @@ static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
tty->tty_smode.c_iflag &= ~ICRNL;
tty->tty_smode.c_lflag &= ~ICANON;
tty->tty_smode.c_oflag &= ~OPOST;
/* Must get these really right or funny effects can occur. */

tty->tty_smode.c_cc[VMIN] = 1;
tty->tty_smode.c_cc[VTIME] = 0;
#ifdef VDSUSP
Expand Down Expand Up @@ -712,8 +722,8 @@ static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
}

#else
// fprintf(stderr, "origOutMode: %x origInMode: %x\r\n",
// tty->dwOriginalOutMode, tty->dwOriginalInMode);
/* fprintf(stderr, "origOutMode: %x origInMode: %x\r\n", */
/* tty->dwOriginalOutMode, tty->dwOriginalInMode); */

/* If we cannot disable NEWLINE_AUTO_RETURN we continue anyway as things work */
if (SetConsoleMode(tty->ofd, tty->dwOutMode | DISABLE_NEWLINE_AUTO_RETURN)) {
Expand All @@ -723,7 +733,7 @@ static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
tty->dwInMode &= ~(ENABLE_ECHO_INPUT | ENABLE_LINE_INPUT);
if (!SetConsoleMode(tty->ifd, tty->dwInMode))
{
// Failed to set disable echo or line input mode
/* Failed to set disable echo or line input mode */
return make_errno_error(env, "SetConsoleMode");
}

Expand All @@ -737,7 +747,7 @@ static ERL_NIF_TERM tty_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]
#endif
}

static ERL_NIF_TERM tty_set(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_set_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
#if defined(HAVE_TERMCAP) || defined(__WIN32__)
TTYResource *tty;
if (!enif_get_resource(env, argv[0], tty_rt, (void **)&tty))
Expand All @@ -755,7 +765,7 @@ static ERL_NIF_TERM tty_set(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
#endif
}

static ERL_NIF_TERM tty_window_size(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_window_size_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
TTYResource *tty;
int width = -1, height = -1;
if (!enif_get_resource(env, argv[0], tty_rt, (void **)&tty))
Expand Down Expand Up @@ -818,7 +828,7 @@ static RETSIGTYPE tty_winch(int sig)

#endif

static ERL_NIF_TERM tty_read_signal(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_read_signal_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
TTYResource *tty;
char buff[1];
ssize_t ret;
Expand Down Expand Up @@ -913,7 +923,7 @@ static void *tty_reader_thread(void *args) {

#endif

static ERL_NIF_TERM tty_select(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
static ERL_NIF_TERM tty_select_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) {
TTYResource *tty;
#ifdef THREADED_READER
struct tty_reader_init *tty_reader_init;
Expand Down

0 comments on commit 530f845

Please sign in to comment.