Skip to content

Commit

Permalink
stdlib: add auto formatting to the shell
Browse files Browse the repository at this point in the history
  • Loading branch information
frazze-jobb committed Nov 13, 2023
1 parent 67650dc commit e9e1b48
Show file tree
Hide file tree
Showing 7 changed files with 103 additions and 5 deletions.
50 changes: 47 additions & 3 deletions lib/kernel/src/group.erl
Original file line number Diff line number Diff line change
Expand Up @@ -523,16 +523,18 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
{stop,Result,Rest} ->
%% Prompt was valid expression, clear the prompt in user_drv
%% First redraw without the multi line prompt
case LineCont of
{[CL|LB], _, _} ->
FormattedLine = format_expression(LineCont),
put(latest_cmd,FormattedLine),
case lists:reverse(string:split(FormattedLine, "\n", all)) of
[CL|LB] ->
LineCont1 = {LB,{lists:reverse(CL++"\n"), []},[]},
MultiLinePrompt = lists:duplicate(shell:prompt_width(Pbs), $\s),
send_drv_reqs(Drv, [{redraw_prompt, Pbs, MultiLinePrompt, LineCont1},new_prompt]);
_ -> skip %% oldshell mode
end,
_ = case {M,F} of
{io_lib, get_until} ->
save_line_buffer(string:trim(Line, both)++"\n", get_lines(new_stack(get(line_buffer))));
save_line_buffer(string:trim(FormattedLine, both)++"\n", get_lines(new_stack(get(line_buffer))));
_ ->
skip
end,
Expand Down Expand Up @@ -600,6 +602,13 @@ get_line1({open_editor, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
send_drv_reqs(Drv, NewRs),
get_line1(edlin:edit_line(Cs1, NewCont), Drv, Shell, Ls0, Encoding)
end;
get_line1({format_expression, _Cs, Cont, Rs}, Drv, Shell, Ls, Encoding) ->
send_drv_reqs(Drv, Rs),
Cs1 = format_expression(Cont),
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,NewCont,NewRs} = edlin:start(edlin:prompt(Cont)),
send_drv_reqs(Drv, NewRs),
get_line1(edlin:edit_line(Cs1, NewCont), Drv, Shell, Ls, Encoding);
%% Move Up, Down in History: Ctrl+P, Ctrl+N
get_line1({history_up,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
send_drv_reqs(Drv, Rs),
Expand Down Expand Up @@ -886,6 +895,41 @@ get_chars_echo_off1(Drv, Shell) ->
exit(R)
end.

format_expression(Cont) ->
FormatingCommand = application:get_env(stdlib, shell_format_command),
Buffer = edlin:current_line(Cont),
try
case FormatingCommand of
{ok, {M,F}} when is_atom(M), is_atom(F) ->
M:F(Buffer);
{ok, FormatingCommand1} when is_list(FormatingCommand1) ->
format_expression1(Buffer, FormatingCommand1)
end
catch
_:_ -> Buffer
end.
format_expression1(Buffer, FormatingCommand) ->
%% Write the current expression to a file, format it with a formatting tool
%% provided by the user and read the file back
MkTemp = case os:type() of
{win32, _} ->
os:cmd("powershell \"write-host (& New-TemporaryFile | Select-Object -ExpandProperty FullName)\"");
{unix,_} ->
os:cmd("mktemp")
end,
TmpFile = string:chomp(MkTemp) ++ ".erl",
_ = file:write_file(TmpFile, unicode:characters_to_binary(Buffer, unicode)),
FormattingCommand1 = string:replace(FormatingCommand, "${file}", TmpFile),
os:cmd(FormattingCommand1),
{ok, Content} = file:read_file(TmpFile),
_ = file:del_dir_r(TmpFile),
Unicode = case unicode:characters_to_list(Content,unicode) of
{error, _, _} -> unicode:characters_to_list(
unicode:characters_to_list(Content,latin1), unicode);
U -> U
end,
string:chomp(Unicode).

%% We support line editing for the ICANON mode except the following
%% line editing characters, which already has another meaning in
%% echo-on mode (See Advanced Programming in the Unix Environment, 2nd ed,
Expand Down
17 changes: 16 additions & 1 deletion lib/kernel/test/interactive_shell_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@
shell_update_window_unicode_wrap/1,
shell_receive_standard_out/1,
shell_standard_error_nlcr/1, shell_clear/1,
shell_format/1, format_func/1,
remsh_basic/1, remsh_error/1, remsh_longnames/1, remsh_no_epmd/1,
remsh_expand_compatibility_25/1, remsh_expand_compatibility_later_version/1,
external_editor/1, external_editor_visual/1,
Expand Down Expand Up @@ -129,7 +130,7 @@ groups() ->
{tty_latin1,[],[{group,tty_tests}]},
{tty_tests, [parallel],
[shell_navigation, shell_multiline_navigation, shell_multiline_prompt,
shell_xnfix, shell_delete,
shell_xnfix, shell_delete, shell_format,
shell_transpose, shell_search, shell_insert,
shell_update_window, shell_small_window_multiline_navigation, shell_huge_input,
shell_support_ansi_input,
Expand Down Expand Up @@ -477,6 +478,20 @@ shell_multiline_navigation(Config) ->
stop_tty(Term)
end.

format_func(String) ->
lists:flatten(string:replace(String, " ", " ", all)).

shell_format(Config) ->
Term1 = start_tty([{args,["-stdlib","shell_format_command","{interactive_shell_SUITE,format_func}"]}|Config]),
try
send_tty(Term1,"fun(X) ->\n X\nend.\n"),
send_tty(Term1,"Up"),
check_content(Term1, "fun\\(X\\) ->\\s*.. X\\s*.. end."),
ok
after
stop_tty(Term1)
end.

shell_multiline_prompt(Config) ->
Term1 = start_tty([{args,["-stdlib","shell_multiline_prompt","{shell,inverted_space_prompt}"]}|Config]),
Term2 = start_tty([{args,["-stdlib","shell_multiline_prompt","\"...> \""]}|Config]),
Expand Down
17 changes: 17 additions & 0 deletions lib/stdlib/doc/src/shell.xml
Original file line number Diff line number Diff line change
Expand Up @@ -993,6 +993,23 @@ q - quit erlang
</desc>
</func>

<func>
<name name="format_shell_func" arity="1" since="OTP @OTP-18848@"/>
<fsummary>Set the formatting function for submitted shell commands.</fsummary>
<desc>
<p>Can be used to set the formatting of the Erlang shell output. This have 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 default). You can specify a Mod:Func/1 that
expects the whole expression as a string and returns a formatted expressions as a string.</p>
<p>If instead a string is provided, it will be used as a shell command.
Your command must include <c>${file}</c>
somewhere in the string, for the shell to know where the file goes in the command.
Example:
shell:format_shell_func("\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\"").
</p>
</desc>
</func>

<func>
<name name="results" arity="1" since=""/>
<fsummary>Set the number of previous results to keep.</fsummary>
Expand Down
13 changes: 13 additions & 0 deletions lib/stdlib/doc/src/stdlib_app.xml
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,19 @@
<item>
<p>Can be used to override the default keymap configuration for the shell.</p>
</item>
<tag><marker id="shell_format_command"/><c>shell_format_command = {Mod, Func} | string() | default</c></tag>
<item>
<p>Can be used to set the formatting of the Erlang shell output. This have 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 default). You can specify a Mod:Func/1 that
expects the whole expression as a string and returns a formatted expressions as a string.</p>
<p>If instead a string is provided, it will be used as a shell command.
Your command must include <c>${file}</c>
somewhere in the string, for the shell to know where the file goes in the command.
Example:
-stdlib shell_formatting "\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\""
</p>
</item>
<tag><marker id="shell_prompt_func"/><c>shell_prompt_func = {Mod, Func} | default</c></tag>
<item>
<p>where</p>
Expand Down
1 change: 1 addition & 0 deletions lib/stdlib/src/edlin.erl
Original file line number Diff line number Diff line change
Expand Up @@ -171,6 +171,7 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
search_found -> {search_found,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
search_cancel -> {search_cancel,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
search_quit -> {search_quit,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
format_expression -> {format_expression,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
open_editor -> {open_editor,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
history_up -> {history_up,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
history_down -> {history_down,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/edlin_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -215,6 +215,7 @@ normal_map() ->
"\^[d" => kill_word,
"\^[F" => forward_word,
"\^[f" => forward_word,
"\^[r" => format_expression,
"\^[L" => redraw_line,
"\^[l" => redraw_line,
"\^[o" => open_editor,
Expand Down Expand Up @@ -288,6 +289,7 @@ valid_functions() ->
clear_line, %% Clear the current expression
end_of_expression, %% Move to the end of the expression
end_of_line, %% Move to the end of the line
format_expression, %% Format the current expression
forward_char, %% Move forward one character
forward_delete_char, %% Delete the character under the cursor
forward_delete_word, %% Delete the characters until the closest non-word character
Expand Down
8 changes: 7 additions & 1 deletion lib/stdlib/src/shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
-export([get_state/0, get_function/2]).
-export([start_restricted/1, stop_restricted/0]).
-export([local_func/0, local_func/1, local_allowed/3, non_local_allowed/3]).
-export([catch_exception/1, prompt_func/1, multiline_prompt_func/1, strings/1]).
-export([catch_exception/1, prompt_func/1, multiline_prompt_func/1, format_shell_func/1, strings/1]).
-export([start_interactive/0, start_interactive/1]).
-export([read_and_add_records/5]).
-export([default_multiline_prompt/1, inverted_space_prompt/1]).
Expand Down Expand Up @@ -1704,6 +1704,12 @@ prompt_func(PromptFunc) ->
multiline_prompt_func(PromptFunc) ->
set_env(stdlib, shell_multiline_prompt, PromptFunc, ?DEF_PROMPT_FUNC).

-spec format_shell_func(ShellFormatFunc) -> ShellFormatFunc2 when
ShellFormatFunc :: 'default' | {module(),function()} | string(),
ShellFormatFunc2 :: 'default' | {module(),function()} | string().
format_shell_func(ShellFormatFunc) ->
set_env(stdlib, shell_format_command, ShellFormatFunc, default).

-spec strings(Strings) -> Strings2 when
Strings :: boolean(),
Strings2 :: boolean().
Expand Down

0 comments on commit e9e1b48

Please sign in to comment.