File 2601-stdlib-display-help-output-in-expand-area.patch of Package erlang
From 7b47e8095cfe3bb0dfa613197ea8ddb3c79792da Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Tue, 7 Nov 2023 17:02:32 +0100
Subject: [PATCH 1/2] stdlib: display help output in expand area
---
lib/kernel/src/group.erl | 18 +++++++++++++++
lib/stdlib/src/c.erl | 38 +++++++++++++++++---------------
lib/stdlib/src/edlin.erl | 6 ++++-
lib/stdlib/src/edlin_context.erl | 4 +++-
lib/stdlib/src/edlin_key.erl | 13 ++++++++++-
5 files changed, 58 insertions(+), 21 deletions(-)
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 930bf99b6c..743bc6fd81 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -660,6 +660,24 @@ get_line1({search,Cs,Cont,Rs}, Drv, Shell, Ls, Encoding) ->
{more_chars,Ncont,_Nrs} = edlin:start(Pbs, {search,none}),
put(search, new_search),
get_line1(edlin:edit_line1(Cs, Ncont), Drv, Shell, Ls, Encoding);
+get_line1({help, Before, Cs0, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
+ send_drv_reqs(Drv, Rs),
+ {_,Word,_} = edlin:over_word(Before, [], 0),
+ Docs = case edlin_context:get_context(Before) of
+ {function, Mod} when Word =/= [] -> try
+ c:h1(list_to_atom(Mod), list_to_atom(Word))
+ catch _:_ ->
+ c:h1(list_to_atom(Mod))
+ end;
+ {function, Mod} -> c:h1(list_to_atom(Mod));
+ {function, Mod, Fun, _Args, _Unfinished, _Nesting} -> c:h1(list_to_atom(Mod), list_to_atom(Fun));
+ _ -> ""
+ end,
+ case Docs of
+ {error, _} -> send_drv(Drv, beep);
+ _ -> send_drv(Drv, {put_expand, unicode, ["\n",unicode:characters_to_binary(string:trim(Docs, both))]})
+ end,
+ get_line1(edlin:edit_line(Cs0, Cont), Drv, Shell, Ls0, Encoding);
get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
when Expand =:= expand; Expand =:= expand_full ->
send_drv_reqs(Drv, Rs),
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index f95852b890..327705cc85 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -30,7 +30,7 @@
lc_batch/0, lc_batch/1,
i/3,pid/3,m/0,m/1,mm/0,lm/0,
bt/1, q/0,
- h/1,h/2,h/3,ht/1,ht/2,ht/3,hcb/1,hcb/2,hcb/3,
+ h/1,h/2,h/3,h1/1,h1/2,h1/3,ht/1,ht/2,ht/3,hcb/1,hcb/2,hcb/3,
erlangrc/0,erlangrc/1,bi/1, flush/0, regs/0, uptime/0,
nregs/0,pwd/0,ls/0,ls/1,cd/1,memory/1,memory/0, xm/1]).
@@ -164,31 +164,33 @@ c(SrcFile, NewOpts, Filter, BeamFile, Info) ->
-spec h(module()) -> h_return().
h(Module) ->
- case code:get_doc(Module) of
- {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
- format_docs(shell_docs:render(Module, Docs));
- {ok, #docs_v1{ format = Enc }} ->
- {error, {unknown_format, Enc}};
- Error ->
- Error
- end.
+ h2(Module, fun(Docs) -> format_docs(shell_docs:render(Module, Docs)) end).
-spec h(module(),function()) -> hf_return().
h(Module,Function) ->
- case code:get_doc(Module) of
- {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
- format_docs(shell_docs:render(Module, Function, Docs));
- {ok, #docs_v1{ format = Enc }} ->
- {error, {unknown_format, Enc}};
- Error ->
- Error
- end.
+ h2(Module, fun(Docs) ->
+ format_docs(shell_docs:render(Module, Function, Docs))
+ end).
-spec h(module(),function(),arity()) -> hf_return().
h(Module,Function,Arity) ->
+ h2(Module, fun(Docs) ->
+ format_docs(shell_docs:render(Module, Function, Arity, Docs))
+ end).
+
+h1(Module) ->
+ h2(Module, fun(Docs) -> shell_docs:render(Module, Docs) end).
+
+h1(Module,Function) ->
+ h2(Module, fun(Docs) -> shell_docs:render(Module, Function, Docs) end).
+
+h1(Module,Function,Arity) ->
+ h2(Module, fun(Docs) -> shell_docs:render(Module, Function, Arity, Docs) end).
+
+h2(Module, RenderFunction) ->
case code:get_doc(Module) of
{ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
- format_docs(shell_docs:render(Module, Function, Arity, Docs));
+ RenderFunction(Docs);
{ok, #docs_v1{ format = Enc }} ->
{error, {unknown_format, Enc}};
Error ->
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 9eff2ee3c4..7c512e71db 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -141,7 +141,8 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode1, EscapePrefix}, Rs0) ->
normal -> {insert, C1};
search when $\s =< C1 ->{insert_search, C1};
search -> search_quit;
- tab_expand -> tab_expand_quit
+ tab_expand -> tab_expand_quit;
+ help -> tab_expand_quit
end,
case Op of
tab_expand_quit ->
@@ -196,6 +197,9 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode1, EscapePrefix}, Rs0) ->
clear ->
Rs = redraw(P, MultiLine, [clear|Rs0]),
edit(Cs, P, MultiLine, {NextMode, none}, Rs);
+ help ->
+ {help, chars_before(MultiLine), Cs,{line, P, MultiLine, {help, none}},
+ reverse(Rs0)};
tab_expand ->
{expand, chars_before(MultiLine), Cs,
{line, P, MultiLine, {tab_expand, none}},
diff --git a/lib/stdlib/src/edlin_context.erl b/lib/stdlib/src/edlin_context.erl
index 73e42cedf2..979d838a7c 100644
--- a/lib/stdlib/src/edlin_context.erl
+++ b/lib/stdlib/src/edlin_context.erl
@@ -65,6 +65,7 @@
| {fun_, Mod, Fun} %% cursor is in a fun mod:fun statement
| {new_fun, Unfinished}
| {function}
+ | {function, Mod}
| {function, Mod, Fun, Args, Unfinished, Nesting}
| {map, Binding, Keys}
| {map_or_record}
@@ -220,7 +221,8 @@ get_context([$:|Bef2], _) ->
{Bef3, Mod} = edlin_expand:over_word(Bef2),
case edlin_expand:over_word(Bef3) of
{_, "fun"} -> {fun_, Mod};
- _ -> {function}
+ _ when Mod =:= [] -> {function};
+ _ -> {function, Mod}
end;
get_context([$/|Bef1], _) ->
{Bef2, Fun} = edlin_expand:over_word(Bef1),
diff --git a/lib/stdlib/src/edlin_key.erl b/lib/stdlib/src/edlin_key.erl
index 8d16f1237b..40bbadb9ed 100644
--- a/lib/stdlib/src/edlin_key.erl
+++ b/lib/stdlib/src/edlin_key.erl
@@ -113,7 +113,7 @@ get_valid_escape_key(Rest, Acc) ->
{invalid, Acc, Rest}.
merge(KeyMap) ->
- merge(KeyMap, [normal, search, tab_expand], key_map()).
+ merge(KeyMap, [normal, search, tab_expand, help], key_map()).
merge(_, [], KeyMap) ->
KeyMap;
merge(InputKeyMap, [Mode|ShellModes], KeyMap) ->
@@ -179,6 +179,15 @@ key_map() -> #{
"\^[[5~" => scroll_expand_up,
"\t" => tab_expand_full,
default => tab_expand_quit %% go to normal mode and evaluate key input again
+ },
+ help => #{
+ "\^[OA" => move_expand_up,
+ "\^[[A" => move_expand_up,
+ "\^[OB" => move_expand_down,
+ "\^[[B" => move_expand_down,
+ "\^[[6~" => scroll_expand_down,
+ "\^[[5~" => scroll_expand_up,
+ default => tab_expand_quit %% go to normal mode and evaluate key input again
}
}.
@@ -227,6 +236,7 @@ normal_map() ->
"\^[d" => kill_word,
"\^[F" => forward_word,
"\^[f" => forward_word,
+ "\^[h" => help,
"\^[L" => redraw_line,
"\^[l" => redraw_line,
"\^[o" => open_editor,
@@ -305,6 +315,7 @@ valid_functions() ->
forward_delete_word, %% Delete the characters until the closest non-word character
forward_line, %% Move forward one line
forward_word, %% Move forward one word
+ help, %% Open up a pager with help for function or module closest to the cursor
history_down, %% Move to the next item in the history
history_up, %% Move to the previous item in the history
%%jcl_menu,
--
2.35.3