File 0225-Fix-up-the-built-in-help-text-in-the-shell.patch of Package erlang

From 0b1880b23d6d0cc212416d0f62c9a96d8af545e5 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Thu, 13 Jun 2024 13:08:27 +0200
Subject: [PATCH 1/2] Fix up the built-in help text in the shell

Sort the entries for readability. Document the exit/0 builtin.
Move the code for the builtins help to the shell module itself to
make it easier to keep it in sync. Move text for hcb() and ht()
functions to the c module since they are not shell builtins.
---
 lib/stdlib/src/c.erl             | 60 ++++++++++++++++++--------------
 lib/stdlib/src/shell.erl         | 46 +++++++++++++++++++++++-
 lib/stdlib/src/shell_default.erl | 44 ++---------------------
 3 files changed, 80 insertions(+), 70 deletions(-)

diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index a0f84e1e49..65123a48bd 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -66,36 +66,42 @@ this module.
 
 help() ->
     io:put_chars(<<"bt(Pid)    -- stack backtrace for a process\n"
-		   "c(Mod)     -- compile and load module or file <Mod>\n"
-		   "cd(Dir)    -- change working directory\n"
-		   "flush()    -- flush any messages sent to the shell\n"
-		   "help()     -- help info\n"
+                   "c(Mod)     -- compile and load module or file <Mod>\n"
+                   "cd(Dir)    -- change working directory\n"
+                   "flush()    -- flush any messages sent to the shell\n"
                    "h(M)       -- module documentation\n"
                    "h(M,F)     -- module function documentation\n"
                    "h(M,F,A)   -- module function arity documentation\n"
-		   "i()        -- information about the system\n"
-		   "ni()       -- information about the networked system\n"
-		   "i(X,Y,Z)   -- information about pid <X,Y,Z>\n"
-		   "l(Module)  -- load or reload module\n"
-		   "lm()       -- load all modified modules\n"
-		   "lc([File]) -- compile a list of Erlang modules\n"
-		   "ls()       -- list files in the current directory\n"
-		   "ls(Dir)    -- list files in directory <Dir>\n"
-		   "m()        -- which modules are loaded\n"
-		   "m(Mod)     -- information about module <Mod>\n"
-		   "mm()       -- list all modified modules\n"
-		   "memory()   -- memory allocation information\n"
-		   "memory(T)  -- memory allocation information of type <T>\n"
-		   "nc(File)   -- compile and load code in <File> on all nodes\n"
-		   "nl(Module) -- load module on all nodes\n"
-		   "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n"
-		   "pwd()      -- print working directory\n"
-		   "q()        -- quit - shorthand for init:stop()\n"
-		   "regs()     -- information about registered processes\n"
-		   "nregs()    -- information about all registered processes\n"
-		   "uptime()   -- print node uptime\n"
-		   "xm(M)      -- cross reference check a module\n"
-		   "y(File)    -- generate a Yecc parser\n">>).
+                   "hcb(Mod)   -- help about a module's callbacks\n"
+                   "hcb(Mod,CB) -- help about callback in module\n"
+                   "hcb(Mod,CB,Arity) -- help about callback with arity in module\n"
+                   "ht(Mod)    -- help about a module's types\n"
+                   "ht(Mod,Type) -- help about type in module\n"
+                   "ht(Mod,Type,Arity) -- help about type with arity in module\n"
+                   "help()     -- help info\n"
+                   "i()        -- information about the system\n"
+                   "i(X,Y,Z)   -- information about pid <X,Y,Z>\n"
+                   "l(Module)  -- load or reload module\n"
+                   "lc([File]) -- compile a list of Erlang modules\n"
+                   "lm()       -- load all modified modules\n"
+                   "ls()       -- list files in the current directory\n"
+                   "ls(Dir)    -- list files in directory <Dir>\n"
+                   "m()        -- which modules are loaded\n"
+                   "m(Mod)     -- information about module <Mod>\n"
+                   "memory()   -- memory allocation information\n"
+                   "memory(T)  -- memory allocation information of type <T>\n"
+                   "mm()       -- list all modified modules\n"
+                   "nc(File)   -- compile and load code in <File> on all nodes\n"
+                   "ni()       -- information about the networked system\n"
+                   "nl(Module) -- load module on all nodes\n"
+                   "nregs()    -- information about all registered processes\n"
+                   "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n"
+                   "pwd()      -- print working directory\n"
+                   "q()        -- quit - shorthand for init:stop()\n"
+                   "regs()     -- information about registered processes\n"
+                   "uptime()   -- print node uptime\n"
+                   "xm(M)      -- cross reference check a module\n"
+                   "y(File)    -- generate a Yecc parser\n">>).
 
 %% c(Module)
 %%  Compile a module/file.
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 45d04eddc5..a423cefaf7 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -30,7 +30,7 @@
 -export([read_and_add_records/5]).
 -export([default_multiline_prompt/1, inverted_space_prompt/1]).
 -export([prompt_width/1, prompt_width/2]).
--export([whereis/0]).
+-export([help/0,whereis/0]).
 
 -define(LINEMAX, 30).
 -define(CHAR_MAX, 60).
@@ -1166,6 +1166,49 @@ init_dict([{K,V}|Ds]) ->
     init_dict(Ds);
 init_dict([]) -> true.
 
+
+-doc "Print the help for all shell internal commands.".
+-spec help() -> true.
+help() ->
+    S = ~"""
+         ** shell internal commands **
+         b()        -- display all variable bindings
+         e(N)       -- repeat the expression in query <N>
+         exit()     -- terminate the shell instance
+         f()        -- forget all variable bindings
+         f(X)       -- forget the binding of variable X
+         ff()       -- forget all locally defined functions
+         ff(F,A)    -- forget locally defined function named as atom F and arity A
+         fl()       -- forget all locally defined functions, types and records
+         h()        -- history
+         h(Mod)     -- help about module
+         h(Mod,Func) -- help about function in module
+         h(Mod,Func,Arity) -- help about function with arity in module
+         lf()       -- list locally defined functions
+         lr()       -- list locally defined records
+         lt()       -- list locally defined types
+         rd(R,D)    -- define a record
+         rf()       -- remove all record information
+         rf(R)      -- remove record information about R
+         rl()       -- display all record information
+         rl(R)      -- display record information about R
+         rp(Term)   -- display Term using the shell's record information
+         rr(File)   -- read record information from File (wildcards allowed)
+         rr(F,R)    -- read selected record information from file(s)
+         rr(F,R,O)  -- read selected record information with options
+         tf()       -- forget all locally defined types
+         tf(T)      -- forget locally defined type named as atom T
+         v(N)       -- use the value of query <N>
+         catch_exception(B) -- how exceptions are handled
+         history(N) -- set how many previous commands to keep
+         results(N) -- set how many previous command results to keep
+         save_module(FilePath) -- save all locally defined functions, types and records to a file
+         """,
+    io:put_chars(S),
+    io:nl(),
+    true.
+
+
 %% local_func(Function, Args, Bindings, Shell, RecordTable,
 %%            LocalFuncHandler, ExternalFuncHandler) -> {value,Val,Bs}
 %%  Evaluate local functions, including shell commands.
@@ -1327,6 +1370,7 @@ local_func(tf, [{atom,_,A}], Bs, _Shell, _RT, FT, _Lf, _Ef) ->
 local_func(tf, [_], _Bs, _Shell, _RT, _FT, _Lf, _Ef) ->
     erlang:raise(error, function_clause, [{shell,tf,1}]);
 local_func(rd, [{string, _, TypeDef}], Bs, _Shell, RT, FT, _Lf, _Ef) ->
+    %% currently not documented in help()
     case erl_scan:tokens([], TypeDef, {1,1}, [text,{reserved_word_fun,fun erl_scan:reserved_word/1}]) of
         {done, {ok, Toks, _}, _} ->
             case erl_parse:parse_form(Toks) of
diff --git a/lib/stdlib/src/shell_default.erl b/lib/stdlib/src/shell_default.erl
index bbb1e2e254..2baddfa45c 100644
--- a/lib/stdlib/src/shell_default.erl
+++ b/lib/stdlib/src/shell_default.erl
@@ -72,50 +72,10 @@ code:load_abs("$PATH/user_default").
 -export(['$handle_undefined_function'/2]).
 -import(io, [format/1]).
 
--doc "Print the help for all shell internal commands.".
+-doc "Print the help for all shell commands.".
 -spec help() -> true.
 help() ->
-    S = ~"""
-         ** shell internal commands **
-         b()        -- display all variable bindings
-         e(N)       -- repeat the expression in query <N>
-         f()        -- forget all variable bindings
-         f(X)       -- forget the binding of variable X
-         h()        -- history
-         h(Mod)     -- help about module
-         h(Mod,Func)-- help about function in module
-         h(Mod,Func,Arity) -- help about function with arity in module
-         ht(Mod)    -- help about a module's types
-         ht(Mod,Type) -- help about type in module
-         ht(Mod,Type,Arity) -- help about type with arity in module
-         hcb(Mod)    -- help about a module's callbacks
-         hcb(Mod,CB) -- help about callback in module
-         hcb(Mod,CB,Arity) -- help about callback with arity in module
-         history(N) -- set how many previous commands to keep
-         results(N) -- set how many previous command results to keep
-         catch_exception(B) -- how exceptions are handled
-         v(N)       -- use the value of query <N>
-         rd(R,D)    -- define a record
-         rf()       -- remove all record information
-         rf(R)      -- remove record information about R
-         rl()       -- display all record information
-         rl(R)      -- display record information about R
-         rp(Term)   -- display Term using the shell's record information
-         rr(File)   -- read record information from File (wildcards allowed)
-         rr(F,R)    -- read selected record information from file(s)
-         rr(F,R,O)  -- read selected record information with options
-         lf()       -- list locally defined functions
-         lt()       -- list locally defined types
-         lr()       -- list locally defined records
-         ff()       -- forget all locally defined functions
-         ff({F,A})  -- forget locally defined function named as atom F and arity A
-         tf()       -- forget all locally defined types
-         tf(T)      -- forget locally defined type named as atom T
-         fl()       -- forget all locally defined functions, types and records
-         save_module(FilePath) -- save all locally defined functions, types and records to a file
-         """,
-    io:put_chars(S),
-    io:nl(),
+    shell:help(),
     c:help(),
     format(~"** commands in module i (interpreter interface) **\n"),
     format(~"ih()       -- print help for the i module\n"),
-- 
2.35.3

openSUSE Build Service is sponsored by