File 2344-stdlib-Add-checks-of-the-dialyzer-attribute-to-the-l.patch of Package erlang

From 3dd15a193e4a5aea1dd100d6a4e5ad3401334dfe Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 11 Apr 2017 13:06:50 +0200
Subject: [PATCH] stdlib: Add checks of the dialyzer attribute to the linter

The same checks are also performed by the Dialyzer.
---
 lib/dialyzer/doc/src/dialyzer.xml     |  7 +---
 lib/dialyzer/src/dialyzer_options.erl |  3 ++
 lib/dialyzer/test/plt_SUITE.erl       | 37 ++++++++++++++------
 lib/stdlib/src/erl_lint.erl           | 63 +++++++++++++++++++++++++++++++++--
 lib/stdlib/test/erl_lint_SUITE.erl    | 52 ++++++++++++++++++++++++++---
 5 files changed, 138 insertions(+), 24 deletions(-)

diff --git a/lib/dialyzer/doc/src/dialyzer.xml b/lib/dialyzer/doc/src/dialyzer.xml
index 4b7eb4ad6..e34ffd6de 100644
--- a/lib/dialyzer/doc/src/dialyzer.xml
+++ b/lib/dialyzer/doc/src/dialyzer.xml
@@ -4,7 +4,7 @@
 <erlref>
   <header>
     <copyright>
-      <year>2006</year><year>2016</year>
+      <year>2006</year><year>2017</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -457,11 +457,6 @@ dialyzer --plts plt_1 ... plt_n -- files_to_analyze</code>
       <c>gui/1</c></seealso> below (<c>WarnOpts</c>).</p>
 
     <note>
-      <p>Attribute <c>-dialyzer()</c> is not checked by the Erlang
-        compiler, but by Dialyzer itself.</p>
-    </note>
-
-    <note>
       <p>Warning option <c>-Wrace_conditions</c> has no effect when
         set in source files.</p>
     </note>
diff --git a/lib/dialyzer/src/dialyzer_options.erl b/lib/dialyzer/src/dialyzer_options.erl
index 616e8834f..ec3f41311 100644
--- a/lib/dialyzer/src/dialyzer_options.erl
+++ b/lib/dialyzer/src/dialyzer_options.erl
@@ -277,6 +277,9 @@ assert_solvers([Term|_]) ->
 
 -spec build_warnings([atom()], dial_warn_tags()) -> dial_warn_tags().
 
+%% The warning options are checked by the code linter.
+%% The function erl_lint:is_module_dialyzer_option/1 must
+%% be updated if options are added or removed.
 build_warnings([Opt|Opts], Warnings) ->
   NewWarnings =
     case Opt of
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 0789f5dfb..78b7a0e75 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -404,6 +404,10 @@ format_error({not_exported_opaque, {TypeName, Arity}}) ->
 format_error({underspecified_opaque, {TypeName, Arity}}) ->
     io_lib:format("opaque type ~w~s is underspecified and therefore meaningless",
                   [TypeName, gen_type_paren(Arity)]);
+format_error({bad_dialyzer_attribute,Term}) ->
+    io_lib:format("badly formed dialyzer attribute: ~w", [Term]);
+format_error({bad_dialyzer_option,Term}) ->
+    io_lib:format("unknown dialyzer warning option: ~w", [Term]);
 %% --- obsolete? unused? ---
 format_error({format_error, {Fmt, Args}}) ->
     io_lib:format(Fmt, Args).
@@ -796,8 +800,7 @@ attribute_state(Form, St) ->
 %%      State'
 %%  Allow for record, type and opaque type definitions and spec
 %%  declarations to be intersperced within function definitions.
-%%  Dialyzer attributes are also allowed everywhere, but are not
-%%  checked at all.
+%%  Dialyzer attributes are also allowed everywhere.
 
 function_state({attribute,L,record,{Name,Fields}}, St) ->
     record_def(L, Name, Fields, St);
@@ -883,7 +886,8 @@ post_traversal_check(Forms, St0) ->
     StD = check_on_load(StC),
     StE = check_unused_records(Forms, StD),
     StF = check_local_opaque_types(StE),
-    check_callback_information(StF).
+    StG = check_dialyzer_attribute(Forms, StF),
+    check_callback_information(StG).
 
 %% check_behaviour(State0) -> State
 %% Check that the behaviour attribute is valid.
@@ -3116,6 +3120,59 @@ check_local_opaque_types(St) ->
         end,
     dict:fold(FoldFun, St, Ts).
 
+check_dialyzer_attribute(Forms, St0) ->
+    Vals = [{L,V} ||
+               {attribute,L,dialyzer,Val} <- Forms,
+               V0 <- lists:flatten([Val]),
+               V <- case V0 of
+                        {O,F} ->
+                            [{A,B} ||
+                                A <- lists:flatten([O]),
+                                B <- lists:flatten([F])];
+                        T -> [T]
+                    end],
+    {Wellformed, Bad} =
+        lists:partition(fun ({_,{Option,FA}}) when is_atom(Option) ->
+                                is_fa(FA);
+                            ({_,Option}) when is_atom(Option) -> true;
+                            (_) -> false
+                        end, Vals),
+    St1 = foldl(fun ({L,Term}, St) ->
+		  add_error(L, {bad_dialyzer_attribute,Term}, St)
+	  end, St0, Bad),
+    DefFunctions = (gb_sets:to_list(St0#lint.defined) -- pseudolocals()),
+    Fun = fun ({L,{Option,FA}}, St) ->
+                  case is_function_dialyzer_option(Option) of
+                      true ->
+                          case lists:member(FA, DefFunctions) of
+                              true -> St;
+                              false ->
+                                  add_error(L, {undefined_function,FA}, St)
+                          end;
+                      false ->
+                          add_error(L, {bad_dialyzer_option,Option}, St)
+                  end;
+              ({L,Option}, St) ->
+                  case is_module_dialyzer_option(Option) of
+                      true -> St;
+                      false ->
+                          add_error(L, {bad_dialyzer_option,Option}, St)
+                  end
+          end,
+    foldl(Fun, St1, Wellformed).
+
+is_function_dialyzer_option(nowarn_function) -> true;
+is_function_dialyzer_option(Option) ->
+    is_module_dialyzer_option(Option).
+
+is_module_dialyzer_option(Option) ->
+    lists:member(Option,
+                 [no_return,no_unused,no_improper_lists,no_fun_app,
+                  no_match,no_opaque,no_fail_call,no_contracts,
+                  no_behaviours,no_undefined_callbacks,unmatched_returns,
+                  error_handling,race_conditions,no_missing_calls,
+                  specdiffs,overspecs,underspecs,unknown]).
+
 %% icrt_clauses(Clauses, In, ImportVarTable, State) ->
 %%      {UpdVt,State}.
 
-- 
2.12.2

openSUSE Build Service is sponsored by