Skip to content

Commit

Permalink
Merge branch 'lukas/kernel/refactor-file_device-type/OTP-19301' into …
Browse files Browse the repository at this point in the history
…maint

* lukas/kernel/refactor-file_device-type/OTP-19301:
  stdlib: Include specs in docs_v1 for testing purposes
  stdlib: Don't list undocumented types/callbacks in shell_docs
  file: Refactor io_device type
  • Loading branch information
garazdawi committed Oct 22, 2024
2 parents bcafd64 + ac65ad0 commit fdc93dc
Show file tree
Hide file tree
Showing 13 changed files with 100 additions and 105 deletions.
12 changes: 9 additions & 3 deletions lib/kernel/src/file.erl
Original file line number Diff line number Diff line change
Expand Up @@ -238,7 +238,7 @@ operating system kernel.

%% Types that can be used from other modules -- alphabetically ordered.
-export_type([date_time/0, fd/0, file_info/0, filename/0, filename_all/0,
io_device/0, location/0, mode/0, name/0, name_all/0, posix/0]).
io_device/0, io_server/0, location/0, mode/0, name/0, name_all/0, posix/0]).

%%% Includes and defines
-include("file_int.hrl").
Expand All @@ -264,8 +264,14 @@ See the documentation of the `t:name_all/0` type.".
-type file_descriptor() :: #file_descriptor{}.
-doc "A file descriptor representing a file opened in [`raw`](`m:file#raw`) mode.".
-type fd() :: file_descriptor().
-doc "As returned by `open/2`; `t:pid/0` is a process handling I/O-protocols.".
-type io_device() :: pid() | fd().
-doc "A process handling the I/O protocol.".
-type io_server() :: pid().
-doc """
An IO device as returned by `open/2`.
`t:io_server/0` is returned by default and `t:fd/0` is returned if the `raw` option is given.
""".
-type io_device() :: io_server() | fd().
-type location() :: integer() | {'bof', Offset :: integer()}
| {'cur', Offset :: integer()}
| {'eof', Offset :: integer()} | 'bof' | 'cur' | 'eof'.
Expand Down
10 changes: 5 additions & 5 deletions lib/stdlib/src/io.erl
Original file line number Diff line number Diff line change
Expand Up @@ -142,10 +142,10 @@ handled by `user`.
""".
-type user() :: user.
-doc """
An I/O device, either `standard_io`, `standard_error`, `user`, a registered
name, or a pid handling I/O protocols (returned from `file:open/2`).
An I/O device, either `t:standard_io/0`, `t:standard_error/0`, `t:user/0`, a `t:file:io_server/0`,
a registered name, or any pid handling I/O protocols.
""".
-type device() :: atom() | pid() | standard_io() | standard_error() | user().
-type device() :: atom() | pid() | file:io_server() | standard_io() | standard_error() | user().
-type prompt() :: atom() | unicode:chardata().

%% ErrorDescription is whatever the I/O-server sends.
Expand Down Expand Up @@ -494,8 +494,8 @@ The options and values supported by the OTP I/O devices are as follows:
functions can handle any of these modes and so should other, user-written,
modules behaving as clients to I/O servers.
This option is supported by the standard shell (`group.erl`), the 'oldshell'
(`user.erl`), and the file I/O servers.
This option is supported by the `t:standard_io/0`, `t:user/0` and `t:file:io_server/0`
I/O servers.
- **`{echo, boolean()}`** - Denotes if the terminal is to echo input. Only
supported for the standard shell I/O server (`group.erl`)
Expand Down
56 changes: 21 additions & 35 deletions lib/stdlib/src/shell_docs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -857,41 +857,27 @@ render_function(FDocs, #docs_v1{ docs = Docs } = D, Config) ->
end, Grouping).

%% Render the signature of either function, type, or anything else really.
render_signature({{Type,F,A},_Anno,_Sigs,_Docs,Meta}=AST, Specs) ->
MetaSpec = render_meta(Meta),
maybe
M = maps:get(Type, Specs, undefined),
true ?= is_map(M),
{_, _, _, _}=Spec0 ?= maps:get({F, A}, M, undefined),
render_ast(Spec0, MetaSpec)
else
_ ->
{AltSpecs,AltFun} = meta_and_renderer(AST, MetaSpec),
lists:flatmap(AltFun, AltSpecs)
render_signature({{_Type,_F,_A},_Anno,_Sigs,_Docs,#{ signature := Specs } = Meta}, _ASTSpecs) ->
lists:map( fun render_ast/1,Specs) ++ [render_meta(Meta)];
render_signature({{Type,F,A},_Anno,Sigs,_Docs,Meta}, Specs) ->
case maps:find({F, A}, maps:get(Type, Specs, #{})) of
{ok, Spec} ->
[render_ast(Spec) | render_meta(Meta)];
error ->
lists:map(fun(Sig) -> {h2,[],[<<"  "/utf8,Sig/binary>>]} end, Sigs) ++ [render_meta(Meta)]
end.

meta_and_renderer({{_Type,_F,_A},_Anno,Sigs,_Docs, Meta}, MetaSpec) ->
case Meta of
#{ signature := Specs} ->
{Specs, fun(AST0) -> render_ast(AST0, MetaSpec) end};
_ ->
{Sigs, fun (Sig) ->
[{h2,[],[<<"  "/utf8,Sig/binary>>]}|MetaSpec]
end}
end.


render_ast(AST, Meta) ->
PPSpec = erl_pp:attribute(AST,[{encoding,unicode}]),
Spec = case AST of
{_Attribute, _Line, opaque, _} ->
%% We do not want show the internals of the opaque type
hd(string:split(PPSpec,"::"));
_ ->
PPSpec
end,
BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
[{pre,[],[{strong,[],BinSpec}]} | Meta].
render_ast(AST) ->
PPSpec = erl_pp:attribute(AST,[{encoding,unicode}]),
Spec = case AST of
{_Attribute, _Line, opaque, _} ->
%% We do not want show the internals of the opaque type
hd(string:split(PPSpec,"::"));
_ ->
PPSpec
end,
BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
{pre,[],[{strong,[],BinSpec}]}.

render_meta(M) ->
case render_meta_(M) of
Expand Down Expand Up @@ -922,11 +908,11 @@ render_headers_and_docs(Headers, DocContents, #config{} = Config) ->
%%% Functions for rendering type/callback documentation
render_signature_listing(Module, Type, D, Config) when is_map(Config) ->
render_signature_listing(Module, Type, D, init_config(D, Config));
render_signature_listing(Module, Type, #docs_v1{ docs = Docs } = D, #config{}=Config) ->
render_signature_listing(Module, Type, #docs_v1{ docs = Docs, module_doc = MD } = D, #config{}=Config) ->
Config0 = config_module(Module, Config),
Slogan = [{h2,[],[<<"\t",(atom_to_binary(Module))/binary>>]},{br,[],[]}],
case lists:filter(fun({{T, _, _},_Anno,_Sig,_Doc,_Meta}) ->
Type =:= T
Type =:= T andalso is_map(MD)
end, Docs) of
[] ->
render_docs(
Expand Down
59 changes: 47 additions & 12 deletions lib/stdlib/test/shell_docs_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,6 @@ render(Config) ->

lists:foreach(
fun(Module) ->
{ok, [D]} = file:consult(filename:join(DataDir, atom_to_list(Module) ++ ".docs_v1")),
maps:map(
fun(FName, Current) ->
case file:read_file(filename:join(DataDir,FName)) of
Expand All @@ -106,7 +105,7 @@ render(Config) ->
%% available on windows.
ok
end
end, render_module(Module, D))
end, render_module(Module, DataDir))
end, ?RENDER_MODULES).

update_render() ->
Expand All @@ -117,19 +116,52 @@ update_render(DataDir) ->
lists:foreach(
fun(Module) ->
case code:get_doc(Module) of
{ok, D} ->
{ok, Docs} ->
NewEntries =
case beam_lib:chunks(find_path(Module),[abstract_code]) of
{ok,{Module,[{abstract_code,{raw_abstract_v1,AST}}]}} ->
lists:map(fun({{Type, F, A}, Anno, Sig, #{} = Doc, Meta} = E) ->

case lists:search(
fun({attribute, _, spec, {FA, _}}) when Type =:= function ->
FA =:= {F,A};
({attribute, _, What, {Name, _, Args}}) when What =:= Type; What =:= opaque andalso Type =:= type ->
{Name,length(Args)} =:= {F,A};
(_) ->
false
end, AST) of
{value, Signature} ->
{{Type, F, A}, Anno, Sig, Doc, Meta#{ specification => [Signature] }};
_ -> throw({did_not_find, E})
end;
(E) -> E

end, Docs#docs_v1.docs);
{ok,{shell_docs_SUITE,[{abstract_code,no_abstract_code}]}} ->
Docs#docs_v1.docs
end,

ok = file:write_file(
filename:join(DataDir, atom_to_list(Module) ++ ".docs_v1"),
io_lib:format("~w.",[D])),
maps:map(
fun(FName, Output) ->
ok = file:write_file(filename:join(DataDir, FName), Output)
end, render_module(Module, D));
E ->
io:format("Error processing: ~p ~p",[Module, E])
end
io_lib:format("~w.",[Docs#docs_v1{ docs = NewEntries }]));
{error, _} ->
ok
end,
maps:map(
fun(FName, Output) ->
ok = file:write_file(filename:join(DataDir, FName), Output)
end, render_module(Module, DataDir))
end, ?RENDER_MODULES).

find_path(Module) ->
maybe
preloaded ?= code:which(Module),
PreloadedPath = filename:join(code:lib_dir(erts),"ebin"),
filename:join(PreloadedPath, atom_to_list(Module) ++ ".beam")
else
Other -> Other
end.

handle_error({error,_}) ->
ok;
handle_error(Doc) ->
Expand Down Expand Up @@ -461,7 +493,10 @@ render_module(Mod, #docs_v1{ docs = Docs } = D) ->
FName = SMod ++ "_"++atom_to_list(Name)++"_"++integer_to_list(Arity)++"_cb.txt",
Acc#{ sanitize(FName) =>
unicode:characters_to_binary(shell_docs:render_callback(Mod, Name, Arity, D, Opts))}
end, Files, Docs).
end, Files, Docs);
render_module(Mod, Datadir) ->
{ok, [Docs]} = file:consult(filename:join(Datadir, atom_to_list(Mod) ++ ".docs_v1")),
render_module(Mod, Docs).

sanitize(FName) ->
lists:foldl(
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.

Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@

-type io_device() :: pid() | fd().
-type io_device() :: io_server() | fd().

As returned by open/2; pid/0 is a process handling
I/O-protocols.
An IO device as returned by open/2.

io_server/0 is returned by default and fd/0 is returned if the 
raw option is given.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@

-type io_server() :: pid().

A process handling the I/O protocol.
4 changes: 3 additions & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/kernel_file_type.txt
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,9 @@ These types are documented in this module:
 {eof, Offset :: integer()} |
 bof | cur | eof.

-type io_device() :: pid() | fd().
-type io_device() :: io_server() | fd().

-type io_server() :: pid().

-type fd() :: file_descriptor().

Expand Down
42 changes: 1 addition & 41 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_user_drv_type.txt
Original file line number Diff line number Diff line change
@@ -1,43 +1,3 @@
 user_drv

These types are documented in this module:

-type arguments() ::
 #{initial_shell =>
 noshell |
 shell() |
 {remote, unicode:charlist()} |
 {remote,
 unicode:charlist(),
 {module(), atom(), [term()]}},
 input => boolean()}.

-type shell() ::
 {module(), atom(), [term()]} |
 {node(), module(), atom(), [term()]}.

-type request() ::
 {put_chars, unicode, binary()} |
 {put_chars_sync, unicode,
 binary(),
 {From :: pid(), Reply :: term()}} |
 {put_expand, unicode, binary(), integer()} |
 {move_expand, -32768..32767} |
 {move_rel, -32768..32767} |
 {move_line, -32768..32767} |
 {move_combo, -32768..32767, -32768..32767, -32768..32767} |
 {insert_chars, unicode, binary()} |
 {insert_chars_over, unicode, binary()} |
 {delete_chars, -32768..32767} |
 delete_line | delete_after_cursor | beep | clear |
 {requests, [request()]} |
 {open_editor, string()} |
 redraw_prompt |
 {redraw_prompt, string(), string(), tuple()} |
 new_prompt.

-type message() ::
 {Sender :: pid(), request()} |
 {Sender :: pid(), tty_geometry} |
 {Sender :: pid(), get_unicode_state} |
 {Sender :: pid(), set_unicode_state, boolean()}.
There are no types in this module
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/re.docs_v1

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
@@ -1 +1 @@
{docs_v1,{22,2},erlang,<<116,101,120,116,47,109,97,114,107,100,111,119,110>>,hidden,#{otp_doc_vsn => {1,0,0}},[{{function,execute,3},{493,1},[<<101,120,101,99,117,116,101,40,73,116,101,109,44,32,70,44,32,80,105,100,41>>],none,#{}},{{function,render_all,1},{403,1},[<<114,101,110,100,101,114,95,97,108,108,40,68,105,114,41>>],none,#{}},{{function,render_non_native,1},{384,1},[<<114,101,110,100,101,114,95,110,111,110,95,110,97,116,105,118,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,normalize,1},{365,1},[<<110,111,114,109,97,108,105,122,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,links,1},{309,1},[<<108,105,110,107,115,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_prop,1},{304,1},[<<114,101,110,100,101,114,95,112,114,111,112,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_callback,1},{209,1},[<<114,101,110,100,101,114,95,99,97,108,108,98,97,99,107,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_type,1},{186,1},[<<114,101,110,100,101,114,95,116,121,112,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_function,1},{157,1},[<<114,101,110,100,101,114,95,102,117,110,99,116,105,111,110,40,67,111,110,102,105,103,41>>],none,#{}},{{function,update_render,1},{115,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,68,97,116,97,68,105,114,41>>],none,#{}},{{function,update_render,0},{111,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,41>>],none,#{}},{{function,render,1},{86,1},[<<114,101,110,100,101,114,40,67,111,110,102,105,103,41>>],none,#{}},{{function,end_per_group,2},{68,1},[<<101,110,100,95,112,101,114,95,103,114,111,117,112,40,71,114,111,117,112,78,97,109,101,44,32,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_group,2},{63,1},[<<105,110,105,116,95,112,101,114,95,103,114,111,117,112,47,50>>],none,#{}},{{function,end_per_suite,1},{60,1},[<<101,110,100,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_suite,1},{56,1},[<<105,110,105,116,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,49,41>>],none,#{}},{{function,groups,0},{45,1},[<<103,114,111,117,112,115,40,41>>],none,#{}},{{function,all,0},{40,1},[<<97,108,108,40,41>>],none,#{}},{{function,suite,0},{37,1},[<<115,117,105,116,101,40,41>>],none,#{}}]}.
{docs_v1,{22,2},erlang,<<116,101,120,116,47,109,97,114,107,100,111,119,110>>,hidden,#{otp_doc_vsn => {1,0,0}},[{{function,execute,3},{529,1},[<<101,120,101,99,117,116,101,40,73,116,101,109,44,32,70,44,32,80,105,100,41>>],none,#{}},{{function,render_all,1},{436,1},[<<114,101,110,100,101,114,95,97,108,108,40,68,105,114,41>>],none,#{}},{{function,render_non_native,1},{417,1},[<<114,101,110,100,101,114,95,110,111,110,95,110,97,116,105,118,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,normalize,1},{398,1},[<<110,111,114,109,97,108,105,122,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,links,1},{342,1},[<<108,105,110,107,115,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_prop,1},{337,1},[<<114,101,110,100,101,114,95,112,114,111,112,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_callback,1},{242,1},[<<114,101,110,100,101,114,95,99,97,108,108,98,97,99,107,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_type,1},{219,1},[<<114,101,110,100,101,114,95,116,121,112,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_function,1},{190,1},[<<114,101,110,100,101,114,95,102,117,110,99,116,105,111,110,40,67,111,110,102,105,103,41>>],none,#{}},{{function,update_render,1},{115,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,68,97,116,97,68,105,114,41>>],none,#{}},{{function,update_render,0},{111,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,41>>],none,#{}},{{function,render,1},{87,1},[<<114,101,110,100,101,114,40,67,111,110,102,105,103,41>>],none,#{}},{{function,end_per_group,2},{69,1},[<<101,110,100,95,112,101,114,95,103,114,111,117,112,40,71,114,111,117,112,78,97,109,101,44,32,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_group,2},{64,1},[<<105,110,105,116,95,112,101,114,95,103,114,111,117,112,47,50>>],none,#{}},{{function,end_per_suite,1},{61,1},[<<101,110,100,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_suite,1},{57,1},[<<105,110,105,116,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,49,41>>],none,#{}},{{function,groups,0},{46,1},[<<103,114,111,117,112,115,40,41>>],none,#{}},{{function,all,0},{40,1},[<<97,108,108,40,41>>],none,#{}},{{function,suite,0},{37,1},[<<115,117,105,116,101,40,41>>],none,#{}}]}.
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/sofs.docs_v1

Large diffs are not rendered by default.

0 comments on commit fdc93dc

Please sign in to comment.