Skip to content

Commit

Permalink
compiler: implementation of EEP-59
Browse files Browse the repository at this point in the history
Implementation of EEP-59 - Documentation Attributes

- Documentation attributes are added to the binary beam file, following
format of [EEP-48](https://www.erlang.org/eeps/eep-0048), via
`+beam_docs` compiler flag

- Warnings related to documentation attributes are dealt with in the
`beam_docs.erl` instead of adding them to `erl_lint.erl`

*Example 1*

```erlang
-module(warn_missing_doc).

-export([test/0, test/1, test/2]).
-export_type([test/0, test/1]).

-type test() :: ok.
-type test(N) :: N.

-callback test() -> ok.

-include("warn_missing_doc.hrl").

test() -> ok.
test(N) -> N.
```

Using the compiler flag `warn_missing_doc` will raise a warning when
doc. attributes are missing in exported functions, types, and callbacks.

*Example 2*

```erlang
-module(doc_with_file).

-export([main/1]).

-moduledoc {file, "README"}.

-doc {file, "FUN"}.
-spec main(Var) -> foo(Var).
main(X) ->
    X.
```

`moduledoc`s and `doc`s may refer to external files to be embedded.

*Example 3 - Warnings and Types*

```erlang
-export([uses_public/0]).
-export_type([public/0]).

-doc false.
-type hidden_type() :: integer().

-type intermediate() :: hidden_type().
-type public() :: intermediate().

-spec uses_public() -> public().
uses_public() ->
    ok.
```

Compiler warns about exported functions whose specs refer to hidden
types. In the example above, the `hidden_type()` is set as `hidden`
either via `-doc false` or `-doc hidden` and `public() :> intermediate()
:> hidden_type()`. When documentation attributes mark a type as hidden,
they won't be part of the documentation. Thus, the warning that the
`hidden_type()` is not part of the documentation, yet used in an
exported function.
  • Loading branch information
kikofernandez committed Jan 3, 2024
1 parent dc539b2 commit f2f48e3
Show file tree
Hide file tree
Showing 79 changed files with 3,460 additions and 83 deletions.
Binary file added bootstrap/lib/compiler/ebin/beam_doc.beam
Binary file not shown.
Binary file modified bootstrap/lib/compiler/ebin/compile.beam
Binary file not shown.
Binary file modified bootstrap/lib/kernel/ebin/erl_erts_errors.beam
Binary file not shown.
Binary file modified bootstrap/lib/kernel/ebin/group.beam
Binary file not shown.
Binary file modified bootstrap/lib/kernel/ebin/prim_tty.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/argparse.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/beam_lib.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/c.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/edlin.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/edlin_context.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/edlin_expand.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/edlin_key.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/epp.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/erl_lint.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/erl_parse.beam
Binary file not shown.
2 changes: 1 addition & 1 deletion erts/preloaded/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ KERNEL_SRC=$(ERL_TOP)/lib/kernel/src
KERNEL_INCLUDE=$(ERL_TOP)/lib/kernel/include
STDLIB_INCLUDE=$(ERL_TOP)/lib/stdlib/include

ERL_COMPILE_FLAGS += +debug_info -I$(KERNEL_SRC) -I$(KERNEL_INCLUDE)
ERL_COMPILE_FLAGS += +debug_info +no_docs -I$(KERNEL_SRC) -I$(KERNEL_INCLUDE)

ifeq ($(ERL_DETERMINISTIC),yes)
ERL_COMPILE_FLAGS += deterministic
Expand Down
29 changes: 29 additions & 0 deletions lib/compiler/doc/src/compile.xml
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,16 @@
exception at runtime).</p>
</item>

<tag><c>no_docs</c><marker id="beam_docs"/></tag>
<item>
<p>The compiler by default extracts <seeguide marker="system/reference_manual:documentation">documentation</seeguide> from
<seeguide marker="system/reference_manual:modules#documentation-attributes"><c>-doc</c> attributes</seeguide>
and places them in the <seetype marker="stdlib:beam_lib#chunkid"><c>Docs</c> chunk</seetype> according to <seeguide marker="kernel:eep48_chapter">EEP-48</seeguide>.
</p>
<p>This option switches off the placement of <seeguide marker="system/reference_manual:modules#documentation-attributes"><c>-doc</c> attributes</seeguide>
in the <seetype marker="stdlib:beam_lib#chunkid"><c>Docs</c> chunk</seetype></p>.
</item>

<tag><c>binary</c></tag>
<item>
<p>The compiler returns the object code in a
Expand Down Expand Up @@ -875,6 +885,25 @@ module.beam: module.erl \
warnings.</p>
</item>

<tag><c>warn_missing_doc</c><marker id="warn_missing_doc"/></tag>
<item>
<p>By default, warnings are not emitted when <c>-doc</c>
attribute for an exported function is not given. Use this
option to turn on this kind of warning.</p>
</item>

<tag><c>nowarn_hidden_doc</c> | <c>{nowarn_hidden_doc,NAs}</c>
<marker id="nowarn_hidden_doc"/></tag>
<item>
<p>By default, warnings are emitted when <c>-doc false</c>
attribute is set on a <seeguide marker="system/reference_manual:documentation#What-is-visible-versus-hidden">callback or referenced type</seeguide>. You can set
<c>nowarn_hidden_doc</c> to suppress all those warnings,
or <c>{nowarn_hidden_doc, NAs}</c> to suppress specific
callbacks or types. <c>NAs</c> is a tuple <c>{Name, Arity}</c>
or a list of such tuples.
</p>
</item>

<tag><c>warn_missing_spec</c></tag>
<item>
<p>By default, warnings are not emitted when a specification
Expand Down
1 change: 1 addition & 0 deletions lib/compiler/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ MODULES = \
beam_dict \
beam_digraph \
beam_disasm \
beam_doc \
beam_flatten \
beam_jump \
beam_listing \
Expand Down
1,073 changes: 1,073 additions & 0 deletions lib/compiler/src/beam_doc.erl

Large diffs are not rendered by default.

81 changes: 57 additions & 24 deletions lib/compiler/src/compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -340,19 +340,19 @@ format_error_reason(Class, Reason, Stack) ->
erl_error:format_exception(Class, Reason, Stack, Opts).

%% The compile state record.
-record(compile, {filename="" :: file:filename(),
dir="" :: file:filename(),
base="" :: file:filename(),
ifile="" :: file:filename(),
ofile="" :: file:filename(),
module=[] :: module() | [],
abstract_code=[] :: abstract_code(), %Abstract code for debugger.
options=[] :: [option()], %Options for compilation
mod_options=[] :: [option()], %Options for module_info
encoding=none :: none | epp:source_encoding(),
errors=[] :: errors(),
warnings=[] :: warnings(),
extra_chunks=[] :: [{binary(), binary()}]}).
-record(compile, {filename="" :: file:filename(),
dir="" :: file:filename(),
base="" :: file:filename(),
ifile="" :: file:filename(),
ofile="" :: file:filename(),
module=[] :: module() | [],
abstract_code=[] :: abstract_code(), %Abstract code for debugger.
options=[] :: [option()], %Options for compilation
mod_options=[] :: [option()], %Options for module_info
encoding=none :: none | epp:source_encoding(),
errors=[] :: errors(),
warnings=[] :: warnings(),
extra_chunks=[] :: [{binary(), binary()}]}).

internal({forms,Forms}, Opts0) ->
{_,Ps} = passes(forms, Opts0),
Expand Down Expand Up @@ -812,6 +812,8 @@ standard_passes() ->

{iff,'dpp',{listing,"pp"}},
?pass(lint_module),
{unless,no_docs,?pass(beam_docs)},
?pass(remove_doc_attributes),

{iff,'P',{src_listing,"P"}},
{iff,'to_pp',{done,"P"}},
Expand All @@ -821,7 +823,9 @@ standard_passes() ->

abstr_passes(AbstrStatus) ->
case AbstrStatus of
non_verified_abstr -> [{unless, no_lint, ?pass(lint_module)}];
non_verified_abstr -> [{unless, no_lint, ?pass(lint_module)},
{unless,no_docs,?pass(beam_docs)},
?pass(remove_doc_attributes)];
verified_abstr -> []
end ++
[
Expand Down Expand Up @@ -1027,17 +1031,20 @@ parse_module(_Code, St) ->
Ret
end.

do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
deterministic_filename(#compile{ifile=File,options=Opts}) ->
SourceName0 = proplists:get_value(source, Opts, File),
SourceName = case member(deterministic, Opts) of
true ->
filename:basename(SourceName0);
false ->
case member(absolute_source, Opts) of
true -> paranoid_absname(SourceName0);
false -> SourceName0
end
end,
case member(deterministic, Opts) of
true ->
filename:basename(SourceName0);
false ->
case member(absolute_source, Opts) of
true -> paranoid_absname(SourceName0);
false -> SourceName0
end
end.

do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
SourceName = deterministic_filename(St),
StartLocation = case with_columns(Opts) of
true ->
{1,1};
Expand Down Expand Up @@ -1589,6 +1596,31 @@ core_inline_module(Code0, #compile{options=Opts}=St) ->
save_abstract_code(Code, St) ->
{ok,Code,St#compile{abstract_code=erl_parse:anno_to_term(Code)}}.

-define(META_DOC_CHUNK, <<"Docs">>).


%% Adds documentation attributes to extra_chunks (beam file)
beam_docs(Code, #compile{dir = Dir, options = Options,
extra_chunks = ExtraChunks }=St) ->
SourceName = deterministic_filename(St),
{ok, Docs, Ws} = beam_doc:main(Dir, SourceName, Code, Options),
MetaDocs = [{?META_DOC_CHUNK, term_to_binary(Docs)} | ExtraChunks],
{ok, Code, St#compile{extra_chunks = MetaDocs,
warnings = St#compile.warnings ++ Ws}}.

%% Strips documentation attributes from the code
remove_doc_attributes(Code, St) ->
{ok, [Attr || Attr <- Code, not is_doc_attribute(Attr)], St}.


is_doc_attribute(Attr) ->
case Attr of
{attribute, _Anno, DocAttr, _Meta}
when DocAttr =:= doc; DocAttr =:= moduledoc; DocAttr =:= docformat ->
true;
_ -> false
end.

debug_info(#compile{module=Module,ofile=OFile}=St) ->
{DebugInfo,Opts2} = debug_info_chunk(St),
case member(encrypt_debug_info, Opts2) of
Expand Down Expand Up @@ -2123,6 +2155,7 @@ pre_load() ->
beam_core_to_ssa,
beam_dict,
beam_digraph,
beam_doc,
beam_flatten,
beam_jump,
beam_opcodes,
Expand Down
3 changes: 2 additions & 1 deletion lib/compiler/src/compiler.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@
beam_dict,
beam_digraph,
beam_disasm,
beam_doc,
beam_flatten,
beam_jump,
beam_listing,
Expand Down Expand Up @@ -83,5 +84,5 @@
{registered, []},
{applications, [kernel, stdlib]},
{env, []},
{runtime_dependencies, ["stdlib-5.0","kernel-8.4","erts-13.0",
{runtime_dependencies, ["stdlib-@OTP-18622@","kernel-8.4","erts-13.0",
"crypto-5.1"]}]}.
1 change: 1 addition & 0 deletions lib/compiler/test/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ MODULES= \
beam_bounds_SUITE \
beam_validator_SUITE \
beam_disasm_SUITE \
beam_doc_SUITE \
beam_except_SUITE \
beam_jump_SUITE \
beam_reorder_SUITE \
Expand Down
Loading

0 comments on commit f2f48e3

Please sign in to comment.