Skip to content

Commit

Permalink
Merge pull request #8577 from richcarl/consistent-key-combos
Browse files Browse the repository at this point in the history
Describe key combinations consistently

OTP-19177
  • Loading branch information
jhogberg authored Jul 29, 2024
2 parents 64fcd87 + ea381d0 commit c70a8a2
Show file tree
Hide file tree
Showing 28 changed files with 79 additions and 79 deletions.
2 changes: 1 addition & 1 deletion HOWTO/INSTALL-RASPBERRYPI3.md
Original file line number Diff line number Diff line change
Expand Up @@ -241,7 +241,7 @@ Uncheck option:

$ cat > test.c
$ int main() { printf("Hello, world!\n"); return 0; }
<CTRL+D>
<Ctrl+D>
$ armv8-rpi3-linux-gnueabihf-gcc -o test test.c


Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/break.c
Original file line number Diff line number Diff line change
Expand Up @@ -608,7 +608,7 @@ do_break(void)
case '*': /*
* The asterisk is an read error on windows,
* where sys_get_key isn't that great in console mode.
* The usual reason for a read error is Ctrl-C. Treat this as
* The usual reason for a read error is Ctrl+C. Treat this as
* 'a' to avoid infinite loop.
*/
erts_exit(0, "");
Expand Down
4 changes: 2 additions & 2 deletions erts/emulator/beam/erl_init.c
Original file line number Diff line number Diff line change
Expand Up @@ -542,8 +542,8 @@ void erts_usage(void)
ERTS_MAX_NO_OF_ASYNC_THREADS);
erts_fprintf(stderr, "\n");

erts_fprintf(stderr, "-B[c|d|i] set break (Ctrl-C) behavior; valid letters are:\n");
erts_fprintf(stderr, " 'c' to have Ctrl-C interrupt the Erlang shell;\n");
erts_fprintf(stderr, "-B[c|d|i] set break (Ctrl+C) behavior; valid letters are:\n");
erts_fprintf(stderr, " 'c' to have Ctrl+C interrupt the Erlang shell;\n");
erts_fprintf(stderr, " 'd' (or no extra option) to disable the break handler;\n");
erts_fprintf(stderr, " 'i' to ignore break signals\n");
erts_fprintf(stderr, "\n");
Expand Down
10 changes: 5 additions & 5 deletions erts/emulator/nifs/common/prim_tty_nif.c
Original file line number Diff line number Diff line change
Expand Up @@ -467,7 +467,7 @@ static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
* - Normal key presses
* - Microsoft IME
* - Pasting into console
* - Using ALT+ modifiers
* - Using Alt+ modifiers
*
* ### Normal key presses
*
Expand All @@ -493,11 +493,11 @@ static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
* a keydown event with UnicodeChar set to 0 and then immediately followed by a
* keyup event with the non-ascii text.
*
* ### Using ALT+ modifiers
* ### Using Alt+ modifiers
*
* A very old way of inputting Unicode characters on Windows is to press
* the left alt key and then some numbers on the number pad. For instance
* you can type ALT+1 to write a ☺. When doing this first a keydown
* you can type Alt+1 to write a ☺. When doing this first a keydown
* with 0 is sent and then some events later a keyup with the character
* is sent. This behavior seems to only work on cmd.exe and powershell.
*
Expand All @@ -506,11 +506,11 @@ static ERL_NIF_TERM tty_read_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
* - Normal presses -- Always keydown and keyup events
* - IME -- Always keydown, sometimes keyup
* - Pasting -- Always keydown=0 directly followed by keyup=value
* - ALT+ -- Sometimes keydown=0 followed eventually by keyup=value
* - Alt+ -- Sometimes keydown=0 followed eventually by keyup=value
*
* So in order to read characters we should always read the keydown event,
* except when it is 0, then we should read the adjacent keyup event.
* This covers all modes and consoles except ALT+. If we want ALT+ to work
* This covers all modes and consoles except Alt+. If we want Alt+ to work
* we probably have to use PeekConsoleInput to make sure the correct events
* are available and inspect the state of the key event somehow.
**/
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/sys/unix/erl_child_setup.c
Original file line number Diff line number Diff line change
Expand Up @@ -434,7 +434,7 @@ static int system_properties_fd(void)
#endif /* __ANDROID__ */

/*
If beam is terminated using kill -9 or Ctrl-C when +B is set it may not
If beam is terminated using kill -9 or Ctrl+C when +B is set it may not
cleanup the terminal properly. So to clean it up we save the initial state in
erl_child_setup and then reset the terminal if we detect that beam terminated.
Expand Down
12 changes: 6 additions & 6 deletions erts/emulator/sys/unix/sys.c
Original file line number Diff line number Diff line change
Expand Up @@ -759,24 +759,24 @@ void erts_set_ignore_break(void) {
* typing certain key combinations at the
* controlling terminal...
*/
sys_signal(SIGINT, SIG_IGN); /* Ctrl-C */
sys_signal(SIGQUIT, SIG_IGN); /* Ctrl-\ */
sys_signal(SIGTSTP, SIG_IGN); /* Ctrl-Z */
sys_signal(SIGINT, SIG_IGN); /* Ctrl+C */
sys_signal(SIGQUIT, SIG_IGN); /* Ctrl+\ */
sys_signal(SIGTSTP, SIG_IGN); /* Ctrl+Z */
}

/* Don't use ctrl-c for break handler but let it be
/* Don't use Ctrl+C for break handler but let it be
used by the shell instead (see user_drv.erl) */
void erts_replace_intr(void) {
struct termios mode;

if (isatty(0)) {
tcgetattr(0, &mode);

/* here's an example of how to replace ctrl-c with ctrl-u */
/* here's an example of how to replace Ctrl+C with Ctrl+U */
/* mode.c_cc[VKILL] = 0;
mode.c_cc[VINTR] = CKILL; */

mode.c_cc[VINTR] = 0; /* disable ctrl-c */
mode.c_cc[VINTR] = 0; /* disable Ctrl+C */
tcsetattr(0, TCSANOW, &mode);
replace_intr = 1;
}
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/sys/win32/sys_interrupt.c
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ BOOL WINAPI ctrl_handler_replace_intr(DWORD dwCtrlType)
}


/* Don't use ctrl-c for break handler but let it be
/* Don't use Ctrl+C for break handler but let it be
used by the shell instead (see user_drv.erl) */
void erts_replace_intr(void) {
HANDLE hIn = GetStdHandle(STD_INPUT_HANDLE);
Expand Down
8 changes: 4 additions & 4 deletions lib/debugger/test/dbg_ui_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -192,10 +192,10 @@ Interpret one module").
"Start the debugger and interpret the modules [test, lists1, ordsets1]. Close the Interpret dialog. Set Attach on First Call and Attach on Break.").

?MAN_CASE(all_step3, "Click Step through all evaluation",
"In the shell, call test:test1(). Use the Step button, the Process->Step menu item and the ctrl-s shortcut to step through the *entire* execution of the call. (Approx 36 steps). Then close the Attach window. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").
"In the shell, call test:test1(). Use the Step button, the Process->Step menu item and the Ctrl+S shortcut to step through the *entire* execution of the call. (Approx 36 steps). Then close the Attach window. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").

?MAN_CASE(all_next3,"Click Next through all evaluation",
"Again call test:test1() in the shell. This time Use the Next button, the Process->Next menu and the ctrl-n shortcut to quickly step over the execution of the four lines in the test1-function. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").
"Again call test:test1() in the shell. This time Use the Next button, the Process->Next menu and the Ctrl+N shortcut to quickly step over the execution of the four lines in the test1-function. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").

?MAN_CASE(save3, "Save the debugger state",
"Use File->Save Settings to save the debugger state with the name 'three.state'").
Expand Down Expand Up @@ -256,7 +256,7 @@ Interpret one module").


?MAN_CASE(all_step6, "Click Step through all evaluation",
"In the bar shell, call test:test1().This should open an attach window. Use the Step button, the Process->Step menu item and the ctrl-s shortcut to step through the *entire* execution of the call. (Approx 36 steps). Then close the Attach window. The result printed in the bar shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").
"In the bar shell, call test:test1().This should open an attach window. Use the Step button, the Process->Step menu item and the Ctrl+S shortcut to step through the *entire* execution of the call. (Approx 36 steps). Then close the Attach window. The result printed in the bar shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").

?MAN_CASE(all_next6,"Click Next through all evaluation",
"Again, in the bar shell, call test:test1(). This time Use the Next button, the Process->Next menu and the ctrl-n shortcut to quickly step over the execution of the four lines in the test1-function. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").
"Again, in the bar shell, call test:test1(). This time Use the Next button, the Process->Next menu and the Ctrl+N shortcut to quickly step over the execution of the four lines in the test1-function. The result printed in the shell should be: {\"peter\",[1,2,4,a,b,c],\"olin\"}").
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,14 @@
%% Enter
"\n" => new_line_finish,
"\r" => new_line_finish,
%%% Alt-Enter or Esc + Enter
%%% Alt+Enter or Esc + Enter
"\^[\n" => new_line,
"\^[\r" => new_line,

%% Tab ^I
"\t" => tab_expand,

%% Ctrl-alpha keys 0-31
%% Ctrl+alpha keys 0-31
"\^A" => beginning_of_line,
"\^B" => history_up,
%"\^C" => sig_term_menu, %% cannot be changed, yet
Expand Down Expand Up @@ -53,7 +53,7 @@
"\^[[15~" => clear,
"\^[[15;5~" => clear,

%% Alt-alpha_key or Esc + alpha_key, can distinguish case
%% Alt+alpha_key or Esc + alpha_key, can distinguish case
%"\^[A
"\^[B" => backward_word,
"\^[b" => backward_word,
Expand Down Expand Up @@ -154,4 +154,4 @@ default => search_quit},

tab_expand => #{
"\t" => tab_expand_full,
default => tab_expand_quit}}}]}].
default => tab_expand_quit}}}]}].
4 changes: 2 additions & 2 deletions lib/observer/src/observer_port_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -374,9 +374,9 @@ create_menus(Parent) ->
MenuEntries =
[{"View",
[#create_menu{id = ?ID_PORT_INFO_SELECTED,
text = "Port info for selected ports\tCtrl-I"},
text = "Port info for selected ports\tCtrl+I"},
separator,
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl-R"},
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl+R"},
#create_menu{id = ?ID_REFRESH_INTERVAL, text = "Refresh Interval..."}
]},
{"Trace",
Expand Down
2 changes: 1 addition & 1 deletion lib/observer/src/observer_pro_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ create_pro_menu(Parent, Holder) ->
type=check,
check=call(Holder, {get_accum, self()})},
separator,
#create_menu{id=?ID_REFRESH, text="Refresh\tCtrl-R"},
#create_menu{id=?ID_REFRESH, text="Refresh\tCtrl+R"},
#create_menu{id=?ID_REFRESH_INTERVAL, text="Refresh Interval"}]},
{"Trace",
[#create_menu{id=?ID_TRACE_PIDS, text="Trace processes"},
Expand Down
2 changes: 1 addition & 1 deletion lib/observer/src/observer_procinfo.erl
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@ init_log_page(Parent, Pid, Table) ->

create_menus(MenuBar) ->
Menus = [{"File", [#create_menu{id=?wxID_CLOSE, text="Close"}]},
{"View", [#create_menu{id=?REFRESH, text="Refresh\tCtrl-R"}]}],
{"View", [#create_menu{id=?REFRESH, text="Refresh\tCtrl+R"}]}],
observer_lib:create_menus(Menus, MenuBar, new_window).

process_info_fields(Pid, WSz) ->
Expand Down
4 changes: 2 additions & 2 deletions lib/observer/src/observer_sock_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -418,9 +418,9 @@ create_menus(Parent) ->
MenuEntries =
[{"View",
[#create_menu{id = ?ID_SOCKET_INFO_SELECTED,
text = "Socket info for selected sockets\tCtrl-I"},
text = "Socket info for selected sockets\tCtrl+I"},
separator,
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl-R"},
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl+R"},
#create_menu{id = ?ID_REFRESH_INTERVAL, text = "Refresh Interval..."}
]}%% ,
%% {"Debug",
Expand Down
2 changes: 1 addition & 1 deletion lib/observer/src/observer_sys_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ init([Notebook, Parent, Config]) ->


create_sys_menu(Parent) ->
View = {"View", [#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl-R"},
View = {"View", [#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl+R"},
#create_menu{id = ?ID_REFRESH_INTERVAL, text = "Refresh interval"}]},
observer_wx:create_menus(Parent, [View]).

Expand Down
4 changes: 2 additions & 2 deletions lib/observer/src/observer_trace_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -992,8 +992,8 @@ create_logwindow(Parent, true) ->
LogWin = wxFrame:new(Parent, ?LOG_WIN, "Trace Log", [{size, {750*Scale, 800*Scale}}]),
MB = wxMenuBar:new(),
File = wxMenu:new(),
wxMenu:append(File, ?LOG_CLEAR, "Clear Log\tCtrl-C"),
wxMenu:append(File, ?LOG_SAVE, "Save Log\tCtrl-S"),
wxMenu:append(File, ?LOG_CLEAR, "Clear Log\tCtrl+C"),
wxMenu:append(File, ?LOG_SAVE, "Save Log\tCtrl+S"),
wxMenu:append(File, ?wxID_CLOSE, "Close"),
wxMenuBar:append(MB, File, "File"),
wxFrame:setMenuBar(LogWin, MB),
Expand Down
8 changes: 4 additions & 4 deletions lib/observer/src/observer_tv_table.erl
Original file line number Diff line number Diff line change
Expand Up @@ -177,16 +177,16 @@ add_columns(Grid, Start, ColumnNames) ->

create_menus(MB) ->
File = wxMenu:new(),
wxMenu:append(File, ?ID_TABLE_INFO, "Table Information\tCtrl-I"),
wxMenu:append(File, ?ID_TABLE_INFO, "Table Information\tCtrl+I"),
wxMenu:append(File, ?wxID_CLOSE, "Close"),
wxMenuBar:append(MB, File, "File"),
Edit = wxMenu:new(),
wxMenu:append(Edit, ?ID_EDIT, "Edit Object"),
wxMenu:append(Edit, ?ID_DELETE, "Delete Object\tCtrl-D"),
wxMenu:append(Edit, ?ID_DELETE, "Delete Object\tCtrl+D"),
wxMenu:appendSeparator(Edit),
wxMenu:append(Edit, ?ID_SEARCH, "Search\tCtrl-S"),
wxMenu:append(Edit, ?ID_SEARCH, "Search\tCtrl+S"),
wxMenu:appendSeparator(Edit),
wxMenu:append(Edit, ?ID_REFRESH, "Refresh\tCtrl-R"),
wxMenu:append(Edit, ?ID_REFRESH, "Refresh\tCtrl+R"),
wxMenu:append(Edit, ?ID_REFRESH_INTERVAL, "Refresh interval..."),
wxMenuBar:append(MB, Edit, "Edit"),
Help = wxMenu:new(),
Expand Down
4 changes: 2 additions & 2 deletions lib/observer/src/observer_tv_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@ code_change(_, _, State) ->

create_menus(Parent, #opts{sys_hidden=Sys, unread_hidden=UnR, type=Type}) ->
MenuEntries = [{"View",
[#create_menu{id = ?ID_TABLE_INFO, text = "Table information\tCtrl-I"},
[#create_menu{id = ?ID_TABLE_INFO, text = "Table information\tCtrl+I"},
separator,
#create_menu{id = ?ID_ETS, text = "&Ets Tables",
type=radio, check=Type==ets},
Expand All @@ -303,7 +303,7 @@ create_menus(Parent, #opts{sys_hidden=Sys, unread_hidden=UnR, type=Type}) ->
#create_menu{id = ?ID_SYSTEM_TABLES, text = "View &System Tables",
type=check, check=not Sys},
separator,
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl-R"},
#create_menu{id = ?ID_REFRESH, text = "Refresh\tCtrl+R"},
#create_menu{id = ?ID_REFRESH_INTERVAL, text = "Refresh Interval..."}
]}],
observer_wx:create_menus(Parent, MenuEntries).
Expand Down
2 changes: 1 addition & 1 deletion lib/reltool/test/reltool_manual_gui_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@ config(Config) ->
{ok,ServerPid} = reltool:get_server(SysPid),
unlink(SysPid),
break("the system window is still alive",
"terminate reltool by hitting 'Ctrl-q' (linux) or clicking the "
"terminate reltool by hitting 'Ctrl+Q' (linux) or clicking the "
"close box on the top fram when system window is active"),
false = erlang:is_process_alive(SysPid),
false = erlang:is_process_alive(ServerPid),
Expand Down
4 changes: 2 additions & 2 deletions lib/ssh/src/ssh_connect.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -180,8 +180,8 @@
-define(VEOL,6). %% End-of-line character in addition to carriage return
%% or,and). linefeed.
-define(VEOL2,7). %% Additional end-of-line character.
-define(VSTART,8). %% Continues paused output (normally control-Q).
-define(VSTOP,9). %% Pauses output (normally control-S).
-define(VSTART,8). %% Continues paused output (normally Ctrl+Q).
-define(VSTOP,9). %% Pauses output (normally Ctrl+S).
-define(VSUSP,10). %% Suspends the current program.
-define(VDSUSP,11). %% Another suspend character.
-define(VREPRINT,12). %% Reprints the current input line.
Expand Down
2 changes: 1 addition & 1 deletion lib/ssl/test/dtls_api_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -478,7 +478,7 @@ flush() ->

client_restarts_multiple_acceptors(Config) ->
%% Can also be tested with openssl by connecting a client and hit
%% Ctrl-C to kill openssl process, so that the connection is not
%% Ctrl+C to kill openssl process, so that the connection is not
%% closed.
%% Then do a new openssl connect with the same client port.

Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/doc/stdlib_app.md
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ For more information about configuration parameters, see the
- **`format_shell_func = {Mod, Func} | string() | default`{: #format_shell_func
}** - Can be used to set the formatting of the Erlang shell output. This has
an effect on commands that have been submitted and how it is saved in history
or if the formatting hotkey is pressed while editing an expression (Alt-f by
or if the formatting hotkey is pressed while editing an expression (Alt+F by
default). You can specify a Mod:Func/1 that expects the whole expression as a
string and returns a formatted expressions as a string. See
`shell:format_shell_func/1` for how to set it from inside the shell.
Expand Down
10 changes: 5 additions & 5 deletions lib/stdlib/src/edlin_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -197,13 +197,13 @@ normal_map() ->
%% Enter
"\n" => new_line_finish,
"\r" => new_line_finish,
%%% Alt-Enter or Esc + Enter
%%% Alt+Enter or Esc + Enter
"\^[\n" => new_line,
"\^[\r" => new_line,
%% Tab ^I
"\t" => tab_expand,
%% Ctrl-alpha_key, can not distinguish case
%% Ctrl+alpha_key, can not distinguish case
"\^A" => beginning_of_line,
"\^B" => backward_char,
%%"\^C" => sig_term_menu, currently handled by user_drv.erl
Expand All @@ -227,9 +227,9 @@ normal_map() ->
%%"\^X" => ,
"\^Y" => yank,
%%"\^Z" => sig_stop, currently not handled by edlin.erl
"\^]" => auto_blink, % ctrl+5 seems to do the same thing,
"\^]" => auto_blink, % Ctrl+5 seems to do the same thing,
%%# Alt-alpha_key or Esc + alpha_key, can distinguish case,
%%# Alt+alpha_key or Esc + alpha_key, can distinguish case,
"\^[B" => backward_word,
"\^[b" => backward_word,
"\^[c" => clear_line,
Expand Down Expand Up @@ -355,7 +355,7 @@ valid_functions() ->
%% ^V
%% ^@, ^\, ^], ^^, ^_ %% not straightforward how to type these
%%
%% Alt-Shift-char, Alt-char or Esc + Shift-char, Esc + char
%% Alt+Shift+char, Alt+char or Esc + Shift+char, Esc + char
%% ^[A, a
%% ^[C
%% ^[E, e
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/erl_scan.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1718,7 +1718,7 @@ scan_escape([$x,H1], _Col) when ?HEX(H1) ->
more;
scan_escape([$x|Cs], Col) ->
{error,Cs,{illegal,character},incr_column(Col, 1)};
%% \^X -> Control-X
%% \^X -> Ctrl+X
scan_escape([$^=C0,C|Cs], Col) when ?CHAR(C) ->
case caret_char_code(C) of
error ->
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2024,7 +2024,7 @@ multiline_prompt_func(PromptFunc) ->
Can be used to set the formatting of the Erlang shell output.
This has an effect on commands that have been submitted, and how it is saved in history.
Or if the formatting hotkey is pressed while editing an expression (Alt-r by default). You
Or if the formatting hotkey is pressed while editing an expression (Alt+R by default). You
can specify a `Mod:Func/1` that expects the whole expression as a string and
returns a formatted expressions as a string. See
[`stdlib app config`](stdlib_app.md#format_shell_func) for how to set it before
Expand Down
Loading

0 comments on commit c70a8a2

Please sign in to comment.