Skip to content

Commit

Permalink
stdlib: add type specs to shell docs
Browse files Browse the repository at this point in the history
adds type specifications to shell_docs. allows users to type `ht(ssh,
daemon)` and get the documentation together with the spec.

the types shown are those included in the `beam_lib:chunks`, which
currently shows some types that are not exported by needed by functions.
these types are the same ones shown on the online docs.

the shell_docs_SUITE.erl has been parallelised due to the amount of time
taken to render the new documentation. the reason is that we need parse
the debug_info from a beam file, where we previously were not doing this
and thus, not showing the type information.
  • Loading branch information
kikofernandez committed Sep 20, 2024
1 parent 00a67d7 commit 9fab3e7
Show file tree
Hide file tree
Showing 523 changed files with 12,085 additions and 14,329 deletions.
309 changes: 194 additions & 115 deletions lib/stdlib/src/shell_docs.erl

Large diffs are not rendered by default.

124 changes: 84 additions & 40 deletions lib/stdlib/test/shell_docs_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,10 @@
%%
%% %CopyrightEnd%
%%

-module(shell_docs_SUITE).
-moduledoc false.

-export([all/0, suite/0, groups/0, init_per_suite/1, end_per_suite/1,
init_per_group/2, end_per_group/2]).

Expand All @@ -26,6 +29,8 @@

-export([render_all/1, update_render/0, update_render/1]).

-export([execute/3]).

-include_lib("kernel/include/eep48.hrl").
-include_lib("stdlib/include/assert.hrl").

Expand Down Expand Up @@ -122,14 +127,14 @@ update_render(DataDir) ->
render_smoke(_Config) ->
docsmap(
fun(Mod, #docs_v1{ docs = Docs } = D) ->
lists:foreach(
E = fun({error,_}) ->
ok;
(Doc) ->
unicode:characters_to_binary(Doc)
end,
pmap(
fun(Config) ->
try
E = fun({error,_}) ->
ok;
(Doc) ->
unicode:characters_to_binary(Doc)
end,
E(shell_docs:render(Mod, D, Config)),
E(shell_docs:render_type(Mod, D, Config)),
E(shell_docs:render_callback(Mod, D, Config)),
Expand Down Expand Up @@ -166,16 +171,50 @@ render_smoke(_Config) ->
io:format("Failed to render ~p~n~p:~p~n",[Mod,R,ST]),
exit(R)
end
end, [#{},
#{ ansi => false },
#{ ansi => true },
#{ columns => 5 },
#{ columns => 150 },
#{ encoding => unicode },
#{ encoding => latin1 }])
end, format_configurations())
end),
ok.

docsmap(Fun) ->
F = fun F({Mod,_,_}) ->
F(Mod);
F(Mod) when is_list(Mod) ->
F(list_to_atom(Mod));
F(Mod) ->
case code:get_doc(Mod) of
{error, missing} ->
ok;
{error, cover_compiled} ->
ok;
{error, E} when E =:= eperm; E =:= eacces; E =:= eio ->
%% This can happen in BSD's for some reason...
ok;
{error, eisdir} ->
%% Uhm?
ok;
{ok, Docs} ->
try
_ = Fun(Mod, Docs),
{ok, self(), Mod}
catch E:R:ST ->
io:format("Failed to render ~p~n~p:~p:~p~n",[Mod,E,R,ST]),
erlang:raise(E,R,ST)
end
end
end,
pmap(F, code:all_available()),
ok.


format_configurations() ->
[#{},
#{ ansi => false },
#{ ansi => true },
#{ columns => 5 },
#{ columns => 150 },
#{ encoding => unicode },
#{ encoding => latin1 }].

markdown_to_shelldoc(#docs_v1{format = Format}=Docs) ->
DefaultFormat = <<"text/markdown">>,
DFormat = binary_to_list(DefaultFormat),
Expand Down Expand Up @@ -376,30 +415,35 @@ sanitize(FName) ->
end, FName, [{"/","slash"},{":","colon"},
{"\\*","star"},{"<","lt"},{">","gt"},{"=","eq"}]).

docsmap(Fun) ->
lists:map(
fun F({Mod,_,_}) ->
F(Mod);
F(Mod) when is_list(Mod) ->
F(list_to_atom(Mod));
F(Mod) ->
case code:get_doc(Mod) of
{error, missing} ->
ok;
{error, cover_compiled} ->
ok;
{error, E} when E =:= eperm; E =:= eacces; E =:= eio ->
%% This can happen in BSD's for some reason...
ok;
{error, eisdir} ->
%% Uhm?
ok;
{ok, Docs} ->
try
Fun(Mod, Docs)
catch E:R:ST ->
io:format("Failed to render ~p~n~p:~p:~p~n",[Mod,E,R,ST]),
erlang:raise(E,R,ST)
end
end
end, code:all_available()).
%%
%% Parallel map function.
%%
%% Parallel map function that discards the result of the function
%% `F` applied to each of the items in `Ls`. It spawns as many
%% processes as items there are in `Ls`. If the list is large,
%% consider adding a set of working processes that round-robin on
%% the job to do be done.
%%
%% - `F` is the function to perform
%% - `Ls` the list of items to iterate on
%%
pmap(F, Ls) when is_function(F),
is_list(Ls) ->
_ = lists:foreach(fun(Config) ->
spawn_link(?MODULE, execute,[Config, F, self()])
end, Ls),
ResponseCounter = length(Ls),
ok = sync(ResponseCounter),
ok.

execute(Item, F, Pid) ->
_ = F(Item),
Pid ! ok.

sync(0) ->
ok;
sync(N) ->
receive
ok ->
sync(N-1)
end.
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/erlang.docs_v1

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/file.docs_v1

Large diffs are not rendered by default.

14 changes: 9 additions & 5 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_file.txt
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,8 @@

This module provides an interface to the file system.

Warning:
Warning

File operations are only guaranteed to appear atomic when
going through the same file server. A NIF or other OS process
may observe intermediate steps on certain operations on some
Expand Down Expand Up @@ -50,7 +51,8 @@
See also section Notes About Raw Filenames in the STDLIB User's
Guide.

Note:
Note

File operations used to accept filenames containing null
characters (integer value zero). This caused the name to be
truncated and in some cases arguments to primitive operations
Expand Down Expand Up @@ -136,7 +138,8 @@
another node, or if the file server runs as slave to the file
server of another node, also binaries are copied.

Note:
Note

Raw files use the file system of the host machine of the node.
For normal files (non-raw), the file server is used to find
the files, and if the node is running its file server as slave
Expand Down Expand Up @@ -190,12 +193,13 @@
contents of the binaries without copying the data at all, except
for perhaps deep down in the operating system kernel.

Warning:
Warning

If an error occurs when accessing an open file with module io,
the process handling the file exits. The dead file process can
hang if a process tries to access it later. This will be fixed
in a future release.

See Also

filename(3)
filename
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,6 @@
Since:
OTP R14B

Types:
-type posix_file_advise() ::
normal | sequential | random | no_reuse | will_need |
dont_need.

advise/4 can be used to announce an intention to access file data
in a specific pattern in the future, thus allowing the operating
system to perform appropriate optimizations.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@

  altname/1
-spec altname(Name :: name_all()) -> any().

The documentation for altname/1 is hidden. This probably means
that it is internal and not to be used by other applications.
Original file line number Diff line number Diff line change
Expand Up @@ -10,20 +10,19 @@
 Mod :: module(),
 Term :: term()}.

Reads Erlang terms, separated by '.', from Filename. Returns one
Reads Erlang terms, separated by ., from Filename. Returns one
of the following:

{ok, Terms}:
The file was successfully read.
• {ok, Terms} - The file was successfully read.

{error, atom()}:
An error occurred when opening the file or reading it. For a
list of typical error codes, see open/2.
{error, atom()} - An error occurred when opening the file
or reading it. For a list of typical error codes, see 
open/2.

{error, {Line, Mod, Term}}:
An error occurred when interpreting the Erlang terms in the
file. To convert the three-element tuple to an English
description of the error, use format_error/1.
{error, {Line, Mod, Term}} - An error occurred when
interpreting the Erlang terms in the file. To convert the
three-element tuple to an English description of the error,
use format_error/1.

Example:

Expand All @@ -34,4 +33,4 @@
{ok,[{person,"kalle",25},{person,"pelle",30}]}

The encoding of Filename can be set by a comment, as described
in epp(3).
in epp.
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,7 @@

Copies ByteCount bytes from Source to Destination. Source
and Destination refer to either filenames or IO devices from,
for example, open/2. ByteCount defaults to infinity,
denoting an infinite number of bytes.
for example, open/2.

Argument Modes is a list of possible modes, see open/2, and
defaults to [].
Expand Down
30 changes: 2 additions & 28 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_file_copy_func.txt
Original file line number Diff line number Diff line change
Expand Up @@ -9,32 +9,7 @@
 BytesCopied :: non_neg_integer(),
 Reason :: posix() | badarg | terminated.

Copies ByteCount bytes from Source to Destination. Source
and Destination refer to either filenames or IO devices from,
for example, open/2. ByteCount defaults to infinity,
denoting an infinite number of bytes.

Argument Modes is a list of possible modes, see open/2, and
defaults to [].

If both Source and Destination refer to filenames, the files
are opened with [read, binary] and [write, binary] prepended
to their mode lists, respectively, to optimize the copy.

If Source refers to a filename, it is opened with read mode
prepended to the mode list before the copy, and closed when done.

If Destination refers to a filename, it is opened with write
mode prepended to the mode list before the copy, and closed when
done.

Returns {ok, BytesCopied}, where BytesCopied is the number of
bytes that was copied, which can be less than ByteCount if end
of file was encountered on the source. If the operation fails, 
{error, Reason} is returned.

Typical error reasons: as for open/2 if a file had to be opened,
and as for read/2 and write/2.
There is no documentation for copy(Source, Destination, infinity)

-spec copy(Source, Destination, ByteCount) ->
 {ok, BytesCopied} | {error, Reason}
Expand All @@ -50,8 +25,7 @@

Copies ByteCount bytes from Source to Destination. Source
and Destination refer to either filenames or IO devices from,
for example, open/2. ByteCount defaults to infinity,
denoting an infinite number of bytes.
for example, open/2.

Argument Modes is a list of possible modes, see open/2, and
defaults to [].
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,20 +7,15 @@

Typical error reasons:

eacces:
Missing search or write permissions for the parent directories
of Dir.
• eacces - Missing search or write permissions for the parent
directories of Dir.

eexist:
The directory is not empty.
• eexist - The directory is not empty.

enoent:
The directory does not exist.
• enoent - The directory does not exist.

enotdir:
A component of Dir is not a directory. On some platforms, 
enoent is returned instead.
• enotdir - A component of Dir is not a directory. On some
platforms, enoent is returned instead.

einval:
Attempt to delete the current directory. On some platforms, 
eacces is returned instead.
• einval - Attempt to delete the current directory. On some
platforms, eacces is returned instead.
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,9 @@
Deletes file or directory File. If File is a directory, its
contents is first recursively deleted. Returns:

ok:
The operation completed without errors.
• ok - The operation completed without errors.

{error, posix()}:
An error occurred when accessing or deleting File. If some
file or directory under File could not be deleted, File
cannot be deleted as it is non-empty, and {error, eexist} is
returned.
• {error, posix()} - An error occurred when accessing or
deleting File. If some file or directory under File
could not be deleted, File cannot be deleted as it is
non-empty, and {error, eexist} is returned.
Loading

0 comments on commit 9fab3e7

Please sign in to comment.