Skip to content

Commit

Permalink
Merge pull request #7502 from garazdawi/lukas/stdlib/fix-shell-docs-m…
Browse files Browse the repository at this point in the history
…ulti-clause/OTP-18683

Fix shell docs multi clause
  • Loading branch information
garazdawi authored Jul 18, 2023
2 parents da52914 + 76342b1 commit d426c32
Show file tree
Hide file tree
Showing 92 changed files with 3,115 additions and 505 deletions.
19 changes: 12 additions & 7 deletions lib/stdlib/src/shell_docs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -595,13 +595,18 @@ render_function(FDocs, D, Config) when is_map(Config) ->
render_function(FDocs, #docs_v1{ docs = Docs } = D, Config) ->
Grouping =
lists:foldl(
fun({_Group,_Anno,_Sig,_Doc,#{ equiv := Group }} = Func,Acc) ->
Members = maps:get(Group, Acc, []),
Acc#{ Group => [Func|Members] };
fun({_Group,_Anno,_Sig,_Doc,#{ equiv := Group }} = Func, Acc) ->
case lists:keytake(Group, 1, Acc) of
false -> [{Group, [Func]} | Acc];
{value, {Group, Members}, NewAcc} ->
[{Group,[Func|Members]} | NewAcc]
end;
({Group, _Anno, _Sig, _Doc, _Meta} = Func, Acc) ->
Members = maps:get(Group, Acc, []),
Acc#{ Group => [Func|Members] }
end, #{}, lists:sort(FDocs)),
[{Group, [Func]} | Acc]
end, [],
%% We sort only on the group element, so that multiple entries with
%% the same group do not change order. For example erlang:halt/1.
lists:sort(fun(A, B) -> element(1, A) =< element(1, B) end, FDocs)),
lists:map(
fun({Group,Members}) ->
Signatures = lists:flatmap(fun render_signature/1, lists:reverse(Members)),
Expand All @@ -621,7 +626,7 @@ render_function(FDocs, #docs_v1{ docs = Docs } = D, Config) ->
Signatures, get_local_doc(Group, Doc, D), D, Config)
end
end
end, maps:to_list(Grouping)).
end, lists:reverse(Grouping)).

%% Render the signature of either function, type, or anything else really.
render_signature({{_Type,_F,_A},_Anno,_Sigs,_Docs,#{ signature := Specs } = Meta}) ->
Expand Down
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.

2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/kernel_file.txt
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,7 @@

• estale - Stale remote file handle

• exdev - Cross-domain link
• exdev - Cross-device link

Performance

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@

-type fd() :: #file_descriptor{}.
  fd()

A file descriptor representing a file opened in raw mode.
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
 Delay :: non_neg_integer()} |
 delayed_write |
 {read_ahead, Size :: pos_integer()} |
 read_ahead | compressed |
 read_ahead | compressed | compressed_one |
 {encoding, unicode:encoding()} |
 sync.

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,10 @@
read_file_info/1 does probably not match the number of bytes
that can be read from a compressed file.

compressed_one:
Read one member of a gzip compressed file. Option 
compressed_one can only be combined with read.

{encoding, Encoding}:
Makes the file perform automatic translation of characters to
and from a specific (Unicode) encoding. Notice that the data
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,14 @@
-spec pid2name(Pid) -> {ok, Filename} | undefined
 when Filename :: filename_all(), Pid :: pid().

Deprecated:
file:pid2name/1 is deprecated and will be removed in OTP 27; this
functionality is no longer supported

Change:
This function is deprecated and will be removed in Erlang/OTP
27.

If Pid is an I/O device, that is, a pid returned from open/2,
this function returns the filename, or rather:

Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_file_type.txt
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ These types are documented in this module:

-type deep_list() :: [char() | atom() | deep_list()].

-type fd() :: #file_descriptor{}.
  fd()

-type filename() :: string().

Expand Down Expand Up @@ -45,7 +45,7 @@ These types are documented in this module:
 Delay :: non_neg_integer()} |
 delayed_write |
 {read_ahead, Size :: pos_integer()} |
 read_ahead | compressed |
 read_ahead | compressed | compressed_one |
 {encoding, unicode:encoding()} |
 sync.

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@

  callback_mode/0

The documentation for callback_mode/0 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
@@ -0,0 +1,5 @@

  init/1

The documentation for init/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
@@ -0,0 +1,5 @@

  init/3

The documentation for init/3 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
@@ -0,0 +1,6 @@

  start_shell/0

The documentation for start_shell/0 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
@@ -0,0 +1,6 @@

  start_shell/1

The documentation for start_shell/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
@@ -0,0 +1,6 @@

  switch_loop/3

The documentation for switch_loop/3 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
@@ -0,0 +1,6 @@

  whereis_group/0

The documentation for whereis_group/0 is hidden. This probably
means that it is internal and not to be used by other
applications.
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/re.docs_v1

Large diffs are not rendered by default.

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

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
 when
 Subject :: iodata() | unicode:charlist(),
 RE :: mp() | iodata(),
 Replacement :: iodata() | unicode:charlist().
 Replacement ::
 iodata() | unicode:charlist() | replace_fun().

Same as replace(Subject, RE, Replacement, []).
55 changes: 46 additions & 9 deletions lib/stdlib/test/shell_docs_SUITE_data/stdlib_re_replace_4_func.txt
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,8 @@
 when
 Subject :: iodata() | unicode:charlist(),
 RE :: mp() | iodata() | unicode:charlist(),
 Replacement :: iodata() | unicode:charlist(),
 Replacement ::
 iodata() | unicode:charlist() | replace_fun(),
 Options :: [Option],
 Option ::
 anchored | global | notbol | noteol |
Expand All @@ -21,8 +22,8 @@
 CompileOpt :: compile_option(),
 NLSpec :: cr | crlf | lf | anycrlf | any.

Replaces the matched part of the Subject string with the
contents of Replacement.
Replaces the matched part of the Subject string with 
Replacement.

The permissible options are the same as for run/3, except that
option capture is not allowed. Instead a {return, ReturnType}
Expand All @@ -37,12 +38,13 @@
to this function, both the regular expression and Subject are to
specified as valid Unicode charlist()s.

The replacement string can contain the special character &,
which inserts the whole matching expression in the result, and the
special sequence \N (where N is an integer > 0), \gN, or \g{
N}, resulting in the subexpression number N, is inserted in the
result. If no subexpression with that number is generated by the
regular expression, nothing is inserted.
If the replacement is given as a string, it can contain the
special character &, which inserts the whole matching expression
in the result, and the special sequence \N (where N is an
integer > 0), \gN, or \g{N}, resulting in the subexpression
number N, is inserted in the result. If no subexpression with that
number is generated by the regular expression, nothing is
inserted.

To insert an & or a \ in the result, precede it with a \. Notice
that Erlang already gives a special meaning to \ in literal
Expand All @@ -65,5 +67,40 @@

"ab[&]d"

If the replacement is given as a fun, it will be called with the
whole matching expression as the first argument and a list of
subexpression matches in the order in which they appear in the
regular expression. The returned value will be inserted in the
result.

Example:

re:replace("abcd", ".(.)", fun(Whole, [<<C>>]) -> <<$#, Whole/binary, $-, (C - $a + $A), $#>> end, [{return, list}]).

gives

"#ab-B#cd"

Note:
Non-matching optional subexpressions will not be included in
the list of subexpression matches if they are the last
subexpressions in the regular expression.

Example:

The regular expression "(a)(b)?(c)?" ("a", optionally
followed by "b", optionally followed by "c") will create the
following subexpression lists:

• [<<"a">>, <<"b">>, <<"c">>] when applied to the string 
"abc"

• [<<"a">>, <<>>, <<"c">>] when applied to the string 
"acx"

• [<<"a">>, <<"b">>] when applied to the string "abx"

• [<<"a">>] when applied to the string "axx"

As with run/3, compilation errors raise the badarg exception. 
compile/2 can be used to get more information about the error.
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@

-type replace_fun() ::
 fun((binary(), [binary()]) -> iodata() | unicode:charlist()).

There is no documentation for replace_fun/0
3 changes: 3 additions & 0 deletions lib/stdlib/test/shell_docs_SUITE_data/stdlib_re_type.txt
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,6 @@ These types are documented in this module:
 {newline, nl_spec()} |
 bsr_anycrlf | bsr_unicode | no_start_optimize | ucp |
 never_utf.

-type replace_fun() ::
 fun((binary(), [binary()]) -> iodata() | unicode:charlist()).
6 changes: 6 additions & 0 deletions lib/stdlib/test/shell_docs_SUITE_data/stdlib_sofs.txt
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,12 @@
elements; every element belongs to the set, and the set contains
every element.

The data representing sofs as used by this module is to be
regarded as opaque by other modules. In abstract terms, the
representation is a composite type of existing Erlang terms. See
note on data types. Any code assuming knowledge of the format is
running on thin ice.

Given a set A and a sentence S(x), where x is a free variable, a
new set B whose elements are exactly those elements of A for which
S(x) holds can be formed, this is denoted B = {x in A : S(x)}.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@

-spec from_sets(TupleOfSets) -> Ordset
 when
 Ordset :: ordset(),
 TupleOfSets :: tuple_of(anyset()).

-spec from_sets(ListOfSets) -> Set
 when Set :: a_set(), ListOfSets :: [anyset()].

Expand All @@ -15,3 +10,11 @@
S = sofs:from_sets([S1,S2]),
sofs:to_external(S).
[[{a,1},{b,2}],[{x,3},{y,4}]]

-spec from_sets(TupleOfSets) -> Ordset
 when
 Ordset :: ordset(),
 TupleOfSets :: tuple_of(anyset()).

Returns the ordered set containing the sets of the non-empty
tuple TupleOfSets.
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@

-spec is_set(AnySet) -> Bool when AnySet :: anyset(), Bool :: boolean().

Returns true if AnySet is an unordered set, and false if 
AnySet is an ordered set or an atomic set.
Returns true if AnySet appears to be an unordered set, and 
false if AnySet is an ordered set or an atomic set or any other
term. Note that the test is shallow and this function will return 
true for any term that coincides with the representation of an
unordered set. See also note on data types.
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@

-spec is_sofs_set(Term) -> Bool when Bool :: boolean(), Term :: term().

Returns true if Term is an unordered set, an ordered set, or
an atomic set, otherwise false.
Returns true if Term appears to be an unordered set, an
ordered set, or an atomic set, otherwise false. Note that this
function will return true for any term that coincides with the
representation of a sofs set. See also note on data types.
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@

-type tuple_of(_T) :: tuple().
  tuple_of(T)

A tuple where the elements are of type T.
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/stdlib_sofs_type.txt
Original file line number Diff line number Diff line change
Expand Up @@ -31,4 +31,4 @@ These types are documented in this module:

-type type() :: term().

-type tuple_of(_T) :: tuple().
  tuple_of(T)
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
characters are encoded using UTF-8 where characters may require
multiple bytes.

Note:
Change:
As from Erlang/OTP 20, atoms can contain any Unicode character
and atom_to_binary(Atom, latin1) may fail if the text
representation for Atom contains a Unicode character > 255.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
Encoding is utf8 or unicode, the binary must contain valid
UTF-8 sequences.

Note:
Change:
As from Erlang/OTP 20, binary_to_atom(Binary, utf8) is
capable of decoding any Unicode character. Earlier versions
would fail if the binary contained Unicode characters > 255.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@
collected to determine the operation result, and the operation
was requested by passing option {allow_gc, false}.

Note:
Change:
Up until ERTS version 8.*, the check process code operation
checks for all types of references to the old code. That is,
direct references (e.g. return addresses on the process
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -169,6 +169,9 @@
The variants http_bin and httph_bin return strings (
HttpString) as binaries instead of lists.

Since OTP 26.0, Host may be an IPv6 address enclosed in [],
as defined in RFC2732 .

Options:

{packet_size, integer() >= 0}:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,11 @@
demonitor(MonitorRef) if this cleanup is wanted.

Note:
For some important information about distributed signals, see
the Blocking Signaling Over Distribution section in the
Processes chapter of the Erlang Reference Manual.

Change:
Before Erlang/OTP R11B (ERTS 5.5) demonitor/1 behaved
completely asynchronously, that is, the monitor was active
until the "demonitor signal" reached the monitored entity.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@
If option info is combined with option flush, false is
returned if a flush was needed, otherwise true.

Note:
Change:
More options can be added in a future release.

Failures:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,6 @@
Prints a text representation of Term on the standard output.

Warning:
This BIF is intended for debugging only.
This BIF is intended for debugging only. The printed
representation may contain internal details that do not match
the high-level representation of the term in Erlang.
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@

  display_string/2

The documentation for display_string/2 is hidden. This probably
means that it is internal and not to be used by other
applications.
Loading

0 comments on commit d426c32

Please sign in to comment.