File 2611-stdlib-add-auto-formatting-to-the-shell.patch of Package erlang
From 644a4f3ca749e66d3e318eca2ec4cde8ffe8c536 Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Wed, 25 Oct 2023 11:08:21 +0200
Subject: [PATCH 1/3] stdlib: add auto formatting to the shell
---
lib/kernel/src/group.erl | 49 +++++++++++++++++++--
lib/kernel/test/interactive_shell_SUITE.erl | 32 +++++++++++++-
lib/stdlib/doc/src/shell.xml | 18 ++++++++
lib/stdlib/doc/src/stdlib_app.xml | 14 ++++++
lib/stdlib/src/edlin.erl | 2 +
lib/stdlib/src/edlin_key.erl | 2 +
lib/stdlib/src/shell.erl | 8 +++-
7 files changed, 120 insertions(+), 5 deletions(-)
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index f37fc211e9..447a88a20f 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -526,8 +526,9 @@ 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),
+ case lists:reverse(string:split(FormattedLine, "\n", all)) of
+ [CL|LB] when is_list(CL) ->
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]);
@@ -535,7 +536,7 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
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,
@@ -603,6 +604,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, {line, _, _, _} = 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,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
send_drv_reqs(Drv, Rs),
@@ -922,6 +930,41 @@ get_chars_echo_off1(Drv, Shell) ->
exit(R)
end.
+format_expression(Cont) ->
+ FormatingCommand = application:get_env(stdlib, format_shell_func),
+ 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,
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index d6c688f1df..34e6a73f01 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -59,6 +59,7 @@
shell_receive_standard_out/1,
shell_receive_user_output/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,
@@ -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_combining_unicode,
shell_transpose, shell_search, shell_insert,
shell_update_window, shell_small_window_multiline_navigation, shell_huge_input,
@@ -477,6 +478,35 @@ 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","format_shell_func","{interactive_shell_SUITE,format_func}"]}|Config]),
+ DataDir = proplists:get_value(data_dir, Config),
+ EmacsFormat = "\""++DataDir ++ "emacs-format-file\"\n",
+ try
+ send_tty(Term1,"fun(X) ->\n X\nend.\n"),
+ send_tty(Term1,"Up"),
+ check_content(Term1, "fun\\(X\\) ->\\s*.. X\\s*.. end."),
+ send_tty(Term1, "Down"),
+ tmux(["resize-window -t ",tty_name(Term1)," -x ",200]),
+ timer:sleep(1000),
+ send_stdin(Term1, "shell:format_shell_func(\"emacs -batch \${file} -l \"\n"),
+ send_stdin(Term1, EmacsFormat),
+ send_stdin(Term1, "\" -f emacs-format-function\").\n"),
+ check_content(Term1, "{interactive_shell_SUITE,format_func}"),
+ send_tty(Term1, "Up"),
+ send_tty(Term1, "Up"),
+ send_tty(Term1, "\n"),
+ timer:sleep(1000),
+ 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]),
diff --git a/lib/stdlib/doc/src/shell.xml b/lib/stdlib/doc/src/shell.xml
index 9b07d4c900..82fdcfdb57 100644
--- a/lib/stdlib/doc/src/shell.xml
+++ b/lib/stdlib/doc/src/shell.xml
@@ -1042,6 +1042,24 @@ q - quit erlang
</desc>
</func>
+ <func>
+ <name name="format_shell_func" arity="1" since="OTP 27.0"/>
+ <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.
+ See <seeapp marker="STDLIB_app#format_shell_func"><c>stdlib app config</c></seeapp>
+ for how to set it before shell started.</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.
+ </p>
+ <code>shell:format_shell_func("\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\"").</code>
+ </desc>
+ </func>
+
<func>
<name name="results" arity="1" since=""/>
<fsummary>Set the number of previous results to keep.</fsummary>
diff --git a/lib/stdlib/doc/src/stdlib_app.xml b/lib/stdlib/doc/src/stdlib_app.xml
index 35283c4029..f6ade68d02 100644
--- a/lib/stdlib/doc/src/stdlib_app.xml
+++ b/lib/stdlib/doc/src/stdlib_app.xml
@@ -72,6 +72,20 @@
<item>
<p>Can be used to override the default keymap configuration for the shell.</p>
</item>
+ <tag><marker id="format_shell_func"/><c>format_shell_func = {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.
+ See <seemfa marker="shell#format_shell_func/1"><c>shell:format_shell_func/1</c></seemfa>
+ for how to set it from inside the shell.</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.
+ </p>
+ <code>-stdlib format_shell_func "\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\""</code>
+ </item>
<tag><marker id="shell_prompt_func"/><c>shell_prompt_func = {Mod, Func} | default</c></tag>
<item>
<p>where</p>
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 7c512e71db..dff99a0bc6 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -683,6 +683,8 @@ current_chars({line,_,MultiLine,_}) ->
current_line({line,_,MultiLine,_}) ->
current_line(MultiLine) ++ "\n";
%% Convert a multiline tuple into a string with new lines
+current_line(SingleLine) when is_list(SingleLine) ->
+ SingleLine;
current_line({LinesBefore, {Before, After}, LinesAfter}) ->
CurrentLine = lists:reverse(Before, After),
unicode:characters_to_list(lists:flatten(
diff --git a/lib/stdlib/src/edlin_key.erl b/lib/stdlib/src/edlin_key.erl
index 40bbadb9ed..3e2dbee517 100644
--- a/lib/stdlib/src/edlin_key.erl
+++ b/lib/stdlib/src/edlin_key.erl
@@ -236,6 +236,7 @@ normal_map() ->
"\^[d" => kill_word,
"\^[F" => forward_word,
"\^[f" => forward_word,
+ "\^[r" => format_expression,
"\^[h" => help,
"\^[L" => redraw_line,
"\^[l" => redraw_line,
@@ -310,6 +311,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
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 96b1f345cc..f33dd0c944 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -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]).
@@ -1867,6 +1867,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, format_shell_func, ShellFormatFunc, default).
+
-spec strings(Strings) -> Strings2 when
Strings :: boolean(),
Strings2 :: boolean().
--
2.35.3