Age | Commit message (Collapse) | Author |
|
Before OTP 22, the option `{nowarn_deprecated_function,MFAs}` was only
recognized when given in the file with the attribute
`-compile()`. (The option `{nowarn_unused_function,FAs}`
was incorrectly documented to only work in a file, but it also
worked when given in the option list.) Starting from OTP 22, all
options that can be given in the file can also be given in the option
list.
|
|
An external fun could inadvertently suppress warnings for
unused variables, such as in this example:
bug() ->
BugVar = foo(),
if true ->
fun m:f/1
end.
There would be no warning that `BugVar` was unused.
The bug was introduced in ff432e262e652, which was the commit
that extended external funs to allow variables.
https://bugs.erlang.org/browse/ERL-762
|
|
The check is used by evaluating modules such as erl_eval.
An example: "if map_size(#{}) =:= 0 -> ok end.".
|
|
Those warnings don't make sense any more since erlang:get_stacktrace/0
is now deprecated.
|
|
This makes it possible to print unicode atoms at the same time as
suppressing detection of printable lists.
|
|
This commit adds a new syntax for retrieving the stacktrace
without calling erlang:get_stacktrace/0. That allow us to
deprecate erlang:get_stacktrace/0 and ultimately remove it.
The problem with erlang:get_stacktrace/0 is that it can keep huge
terms in a process for an indefinite time after an exception. The
stacktrace can be huge after a 'function_clause' exception or a failed
call to a BIF or operator, because the arguments for the call will be
included in the stacktrace. For example:
1> catch abs(lists:seq(1, 1000)).
{'EXIT',{badarg,[{erlang,abs,
[[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20|...]],
[]},
{erl_eval,do_apply,6,[{file,"erl_eval.erl"},{line,674}]},
{erl_eval,expr,5,[{file,"erl_eval.erl"},{line,431}]},
{shell,exprs,7,[{file,"shell.erl"},{line,687}]},
{shell,eval_exprs,7,[{file,"shell.erl"},{line,642}]},
{shell,eval_loop,3,[{file,"shell.erl"},{line,627}]}]}}
2> erlang:get_stacktrace().
[{erlang,abs,
[[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,
23,24|...]],
[]},
{erl_eval,do_apply,6,[{file,"erl_eval.erl"},{line,674}]},
{erl_eval,expr,5,[{file,"erl_eval.erl"},{line,431}]},
{shell,exprs,7,[{file,"shell.erl"},{line,687}]},
{shell,eval_exprs,7,[{file,"shell.erl"},{line,642}]},
{shell,eval_loop,3,[{file,"shell.erl"},{line,627}]}]
3>
We can extend the syntax for clauses in try/catch to optionally bind
the stacktrace to a variable.
Here is an example using the current syntax:
try
Expr
catch C:E ->
Stk = erlang:get_stacktrace(),
.
.
.
In the new syntax, it would look like:
try
Expr
catch
C:E:Stk ->
.
.
.
Only a variable (not a pattern) is allowed in the stacktrace position,
to discourage matching of the stacktrace. (Matching would also be
expensive, because the raw format of the stacktrace would have to be
converted to the cooked form before matching.)
Note that:
try
Expr
catch E ->
.
.
.
is a shorthand for:
try
Expr
catch throw:E ->
.
.
.
If the stacktrace is to be retrieved for a throw, the 'throw:'
prefix must be explicitly included:
try
Expr
catch throw:E:Stk ->
.
.
.
|
|
* siri/string-new-api: (28 commits)
hipe (test): Do not use deprecated functions in string(3)
dialyzer (test): Do not use deprecated functions in string(3)
eunit (test): Do not use deprecated functions in string(3)
system (test): Do not use deprecated functions in string(3)
system (test): Do not use deprecated functions in string(3)
mnesia (test): Do not use deprecated functions in string(3)
Deprecate old string functions
observer: Do not use deprecated functions in string(3)
common_test: Do not use deprecated functions in string(3)
eldap: Do not use deprecated functions in string(3)
et: Do not use deprecated functions in string(3)
os_mon: Do not use deprecated functions in string(3)
debugger: Do not use deprecated functions in string(3)
runtime_tools: Do not use deprecated functions in string(3)
asn1: Do not use deprecated functions in string(3)
compiler: Do not use deprecated functions in string(3)
sasl: Do not use deprecated functions in string(3)
reltool: Do not use deprecated functions in string(3)
kernel: Do not use deprecated functions in string(3)
hipe: Do not use deprecated functions in string(3)
...
Conflicts:
lib/eunit/src/eunit_lib.erl
lib/observer/src/crashdump_viewer.erl
lib/reltool/src/reltool_target.erl
|
|
There could be a false warning for erlang:get_stacktrace/0
being outside a try block when it was actually inside a try
block.
https://bugs.erlang.org/browse/ERL-478
|
|
|
|
The check of bad nowarn_deprecated_function tags in -compile
attributes often made it impossible to compile modules with the
warnings_as_errors option in two consecutive releases.
|
|
Unicode atoms are handled better by the Erlang code linter.
Module names are checked for character codes greater than 255. This
means that modules invoked after the linter can assume that module
names have only Latin-1 characters.
|
|
erlang:get_stacktrace/0 returns the stacktrace for the latest
exception. The problem is that the stacktrace is kept until the next
exception occurs. If the last exception was a 'function_clause' or a
'badarg', the arguments for the call are also kept forever. The
arguments can be terms of any size (potentially huge).
In a future release, we would like to only allow
erlang:get_stacktrace/0 from within a 'try' expression. That would
make it possible to clear the stacktrace when the 'try' expression is
exited.
The 'catch' expression has no natural end where the stacktrace could
be cleared. The stacktrace could be cleared at the end of the function
that the 'catch' occurs in, but that would cause problems in the
following scenario (from real life, but simplified):
try
...
catch _:_ ->
io:format(...),
io:format("~p\n", [erlang:get_stacktrace()])
end.
%% In io.erl.
format(Fmt, Args) ->
Res = case ... of
SomePattern ->
catch...
...;
SomeOtherPattern ->
%% Output the formatted string here
...
end,
clear_stacktrace(), %% Inserted by compiler.
Res.
The call to io:format() would always clear the stacktrace before
it could be retrieved.
That problem could be solved by tightning the scope in which the
stacktrace is kept, but the rules for how long erlang:get_stacktrace/0
would work would become complicated.
Therefore, the solution we suggest for a future major release of
OTP is that erlang:get_stacktrace/0 will return [] if it is called
outside the 'catch' part of a 'try' expression.
To help users prepare, introduce a warning when it is likely that
erlang:get_stacktrace/0 will always return an empty list, for example
in this code:
catch error(foo),
Stk = erlang:get_stacktrace()
or in this code:
try Expr
catch _:_ -> ok end,
Stk = erlang:get_stacktrace()
|
|
As of the introduction of Unicode characters in atoms, the control
sequences 'w' and 'W' can return non-Latin-1 characters, unless some
measure is taken.
This commit makes sure that '~w' and '~W' always return Latin-1
characters, or bytes, which can be output to ports or written to raw
files.
The Unicode translation modifier 't' is needed to return non-Latin-1
characters.
|
|
The same checks are also performed by the Dialyzer.
|
|
In OTP 20, all Unicode characters are allowed in atoms.
However, we have decided that we will not allow non-latin1
characters in module names in OTP 20. This restriction may
be lifted in a future major release of OTP.
Enforce the restriction in erl_lint, so that it will be a
compilation error to have a module name containing non-latin1
characters. That means that tools such as debugger, xref,
dialyzer, syntax_tools, and so on, do not have to be modified
to handle non-latin1 module names.
|
|
|
|
|
|
The filters in a list comprehension can be guard expressions or
an ordinary expressions.
If a guard expression is used as a filter, an exception will basically
mean the same as 'false':
t() ->
L = [{some_tag,42},an_atom],
[X || X <- L, element(1, X) =:= some_tag]
%% Returns [{some_tag,42}]
On the other hand, if an ordinary expression is used as a filter, there
will be an exception:
my_element(N, T) -> element(N, T).
t() ->
L = [{some_tag,42},an_atom],
[X || X <- L, my_element(1, X) =:= some_tag]
%% Causes a 'badarg' exception when element(1, an_atom) is evaluated
It has been allowed for several releases to override a BIF with
a local function. Thus, if we define a function called element/2,
it will be called instead of the BIF element/2 within the module.
We must use the "erlang:" prefix to call the BIF.
Therefore, the following code is expected to work the same way as in
our second example above:
-compile({no_auto_import,[element/2]}).
element(N, T) ->
erlang:element(N, T).
t() ->
L = [{some_tag,42},an_atom],
[X || X <- L, element(1, X) =:= some_tag].
%% Causes a 'badarg' exception when element(1, an_atom) is evaluated
But the compiler refuses to compile the code with the following
diagnostic:
call to local/imported function element/2 is illegal in guard
|
|
The compiler would crash in v3_codegen when trying to compile the
following code:
is_port(_) -> false.
foo(P) when port(P) -> ok.
We *could* have the compiler interpret the code as:
is_port(_) -> false.
foo(P) when erlang:is_port(P) -> ok.
But that would encourage using the obsolete form of the guard tests.
Note that the following code is illegal:
is_port(_) -> false.
foo(P) when is_port(P) -> ok.
It produces the following diagnostic:
call to local/imported function is_port/1 is illegal in guard
Therefore, we should refuse to compile the code.
|
|
|
|
|
|
Map keys cannot be bound and then used in parallel matching.
Example:
#{ K := V } = #{ k := K } = M.
This is illegal if 'K' is not already bound.
|
|
|
|
|
|
|
|
|
|
* maint:
xmerl: Remove 'no_return' Dialyzer warnings
xmerl: Add suppression of Dialyzer warnings
eunit: Add suppression of Dialyzer warnings
debugger: Add suppression of Dialyzer warnings
kernel: Add suppression of Dialyzer warnings
mnesia: Add suppression of Dialyzer warnings
observer: Add suppression of Dialyzer warnings
runtime_tools: Add suppression of Dialyzer warnings
stdlib: Add suppression of Dialyzer warnings
test_server: Add suppression of Dialyzer warnings
tools: Add suppression of Dialyzer warnings
Conflicts:
lib/stdlib/src/erl_lint.erl
lib/stdlib/src/otp_internal.erl
|
|
|
|
Calls to map_anno(), fold_anno(), and mapfold_anno() with lists of
erl_parse trees have been replaced. Those functions accept lists of
erl_parse trees, but it was not the intention when the functions were
introduced, and it is not documented.
|
|
* maint:
stdlib: Fix linter crash due to missing -module declaration
Conflicts:
lib/stdlib/test/erl_lint_SUITE.erl
|
|
The Erlang Code Linter no longer crashes if there is a -deprecated()
attribute but no -module() declaration.
See also ERL-62 at bugs.erlang.org.
|
|
The syntax -spec/callback F/A :: FunctionType; has been removed.
No deprecation was deemed necessary.
|
|
* maint:
Extend erl_lint:format_error/1 to handle bittype mismatches
erl_lint_SUITE: Add smoke test of format_error/1
|
|
erl_lint:format_error/1 would crash with a function error if
conflicting types were given. That was most easily noticed in the
shell:
Eshell V7.0.3 (abort with ^G)
1> <<0/integer-binary>>.
*** ERROR: Shell process terminated! ***
Noticed-by: Aleksei Magusev
|
|
This type modifier was missed in 90efeaf21147505b1e8207822e606027f94183cc.
|
|
The recently added module erl_anno can no longer handle
negative line numbers.
|
|
|
|
* josevalim/jv-annotate-form-type:
Annotate used types in erl_lint
OTP-12800
|
|
This is a follow up to commit b5ee5c6.
Similar to function calls, we also need to annotate used types
on call site since this information is used later on when showing
undefined type errors.
Notice we don't need to annotate the type export because
it is an attribute and those are always properly annotated.
|
|
* josevalim/jv-annotate-form:
Only annotate forms when linting in the compiler
OTP-12772
|
|
A lot of time spent on linting is due to eval_file_attribute/2
function that recursively traverses all the AST, annotating
the file name on the AST nodes. This traversal happens so
it is easier to add errors and warnings later on by simply
introspecting the node.
This patch changes eval_file_attribute/2 to only annotate
forms (i.e. attributes and functions) and rely on the #lint
record to keep the proper file information (which it already
did before this patch).
To summarize, both pre scan and pos scan will use the annotated
file attribute in forms, however form/2 already maintains the
proper file in #lint, which we pass around when retrieving the
location information.
After this patch, linting of a regular erlang module with 500LOC
became twice faster when measured with eprof.
|
|
Parameterized modules were removed in cdf8060868575, but a few
vestiges still remained in erl_lint.
|
|
When compiling parser files, because they rely heavily
on inline annotations, retrieving the nowarn_bif_clash
information from the compiler options is expensive.
This patch stores nowarn_bif_clash in the lint record.
By using erlc +'{eprof,lint_module}' when compiling the
erlang parser, we noticed the time spent on
nowarn_function/2 reduced from 30% to 0.01%.
|
|
|
|
* nox/stdlib/erl_lint-maps/OTP-12515:
Properly lint map expressions in erl_lint
|
|
* nox/stdlib/erl_lint-expr_list:
Remove a few superfluous vt operations in erl_lint
|
|
Given any Vt1 and Vt2 values, vtmerge(vtnew(Vt1, Vt2), vtold(Vt1, Vt2)) is always
equal to Vt1.
|
|
The returned variable table when linting a map expression shouldn't include
variables that didn't appear in the expression.
Reported-By: Alexei Sholik
|
|
The -dialyzer() attribute can be used for suppressing warnings in a
module by specifying functions or warning options. It can also be used
for requesting warnings in a module.
|
|
Robert has OK'ed the removal of the token ':-'.
|