aboutsummaryrefslogtreecommitdiffstats
path: root/lib/dialyzer/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/dialyzer/src')
-rw-r--r--lib/dialyzer/src/dialyzer.erl35
-rw-r--r--lib/dialyzer/src/dialyzer.hrl19
-rw-r--r--lib/dialyzer/src/dialyzer_cl.erl20
-rw-r--r--lib/dialyzer/src/dialyzer_cl_parse.erl58
-rw-r--r--lib/dialyzer/src/dialyzer_dataflow.erl260
-rw-r--r--lib/dialyzer/src/dialyzer_options.erl26
-rw-r--r--lib/dialyzer/src/dialyzer_plt.erl22
-rw-r--r--lib/dialyzer/src/dialyzer_succ_typings.erl26
-rw-r--r--lib/dialyzer/src/dialyzer_utils.erl24
9 files changed, 332 insertions, 158 deletions
diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl
index 471f9fccd2..5014a4244c 100644
--- a/lib/dialyzer/src/dialyzer.erl
+++ b/lib/dialyzer/src/dialyzer.erl
@@ -2,7 +2,7 @@
%%-----------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -38,7 +38,8 @@
gui/0,
gui/1,
plt_info/1,
- format_warning/1]).
+ format_warning/1,
+ format_warning/2]).
-include("dialyzer.hrl").
@@ -48,6 +49,8 @@
%% - run/1: Erlang interface for a command line-like analysis
%% - gui/0/1: Erlang interface for the gui.
%% - format_warning/1: Get the string representation of a warning.
+%% - format_warning/1: Likewise, but with an option whether
+%% to display full path names or not
%% - plt_info/1: Get information of the specified plt.
%%--------------------------------------------------------------------
@@ -281,11 +284,19 @@ cl_check_log(Output) ->
-spec format_warning(dial_warning()) -> string().
-format_warning({_Tag, {File, Line}, Msg}) when is_list(File),
- is_integer(Line) ->
- BaseName = filename:basename(File),
+format_warning(W) ->
+ format_warning(W, basename).
+
+-spec format_warning(dial_warning(), fopt()) -> string().
+
+format_warning({_Tag, {File, Line}, Msg}, FOpt) when is_list(File),
+ is_integer(Line) ->
+ F = case FOpt of
+ fullpath -> File;
+ basename -> filename:basename(File)
+ end,
String = lists:flatten(message_to_string(Msg)),
- lists:flatten(io_lib:format("~s:~w: ~s", [BaseName, Line, String])).
+ lists:flatten(io_lib:format("~s:~w: ~s", [F, Line, String])).
%%-----------------------------------------------------------------------------
@@ -323,8 +334,13 @@ message_to_string({guard_fail, []}) ->
"Clause guard cannot succeed.\n";
message_to_string({guard_fail, [Arg1, Infix, Arg2]}) ->
io_lib:format("Guard test ~s ~s ~s can never succeed\n", [Arg1, Infix, Arg2]);
+message_to_string({neg_guard_fail, [Arg1, Infix, Arg2]}) ->
+ io_lib:format("Guard test not(~s ~s ~s) can never succeed\n",
+ [Arg1, Infix, Arg2]);
message_to_string({guard_fail, [Guard, Args]}) ->
io_lib:format("Guard test ~w~s can never succeed\n", [Guard, Args]);
+message_to_string({neg_guard_fail, [Guard, Args]}) ->
+ io_lib:format("Guard test not(~w~s) can never succeed\n", [Guard, Args]);
message_to_string({guard_fail_pat, [Pat, Type]}) ->
io_lib:format("Clause guard cannot succeed. The ~s was matched"
" against the type ~s\n", [Pat, Type]);
@@ -352,6 +368,9 @@ message_to_string({record_constr, [Name, Field, Type]}) ->
message_to_string({record_matching, [String, Name]}) ->
io_lib:format("The ~s violates the"
" declared type for #~w{}\n", [String, Name]);
+message_to_string({record_match, [Pat, Type]}) ->
+ io_lib:format("Matching of ~s tagged with a record name violates the declared"
+ " type of ~s\n", [Pat, Type]);
message_to_string({pattern_match, [Pat, Type]}) ->
io_lib:format("The ~s can never match the type ~s\n", [Pat, Type]);
message_to_string({pattern_match_cov, [Pat, Type]}) ->
@@ -378,6 +397,10 @@ message_to_string({contract_supertype, [M, F, _A, Contract, Sig]}) ->
io_lib:format("Type specification ~w:~w~s"
" is a supertype of the success typing: ~w:~w~s\n",
[M, F, Contract, M, F, Sig]);
+message_to_string({contract_range, [Contract, M, F, ArgStrings, Line, CRet]}) ->
+ io_lib:format("The contract ~w:~w~s cannot be right because the inferred"
+ " return for ~w~s on line ~w is ~s\n",
+ [M, F, Contract, F, ArgStrings, Line, CRet]);
message_to_string({invalid_contract, [M, F, A, Sig]}) ->
io_lib:format("Invalid type specification for function ~w:~w/~w."
" The success typing is ~s\n", [M, F, A, Sig]);
diff --git a/lib/dialyzer/src/dialyzer.hrl b/lib/dialyzer/src/dialyzer.hrl
index 1d98574585..9d2e554981 100644
--- a/lib/dialyzer/src/dialyzer.hrl
+++ b/lib/dialyzer/src/dialyzer.hrl
@@ -2,7 +2,7 @@
%%%
%%% %CopyrightBegin%
%%%
-%%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%%
%%% The contents of this file are subject to the Erlang Public License,
%%% Version 1.1, (the "License"); you may not use this file except in
@@ -31,7 +31,7 @@
-define(RET_DISCREPANCIES, 2).
-type dial_ret() :: ?RET_NOTHING_SUSPICIOUS
- | ?RET_INTERNAL_ERROR
+ | ?RET_INTERNAL_ERROR
| ?RET_DISCREPANCIES.
%%--------------------------------------------------------------------
@@ -52,10 +52,11 @@
-define(WARN_CONTRACT_NOT_EQUAL, warn_contract_not_equal).
-define(WARN_CONTRACT_SUBTYPE, warn_contract_subtype).
-define(WARN_CONTRACT_SUPERTYPE, warn_contract_supertype).
+-define(WARN_CONTRACT_RANGE, warn_contract_range).
-define(WARN_CALLGRAPH, warn_callgraph).
-define(WARN_UNMATCHED_RETURN, warn_umatched_return).
-define(WARN_RACE_CONDITION, warn_race_condition).
--define(WARN_BEHAVIOUR,warn_behaviour).
+-define(WARN_BEHAVIOUR, warn_behaviour).
%%
%% The following type has double role:
@@ -70,7 +71,7 @@
| ?WARN_CONTRACT_NOT_EQUAL | ?WARN_CONTRACT_SUBTYPE
| ?WARN_CONTRACT_SUPERTYPE | ?WARN_CALLGRAPH
| ?WARN_UNMATCHED_RETURN | ?WARN_RACE_CONDITION
- | ?WARN_BEHAVIOUR.
+ | ?WARN_BEHAVIOUR | ?WARN_CONTRACT_RANGE.
%%
%% This is the representation of each warning as they will be returned
@@ -87,7 +88,7 @@
%%--------------------------------------------------------------------
%% THIS TYPE SHOULD ONE DAY DISAPPEAR -- IT DOES NOT BELONG HERE
%%--------------------------------------------------------------------
-
+
-type ordset(T) :: [T] . %% XXX: temporarily
%%--------------------------------------------------------------------
@@ -102,6 +103,8 @@
-type dial_define() :: {atom(), term()}.
-type dial_option() :: {atom(), term()}.
-type dial_options() :: [dial_option()].
+-type fopt() :: 'basename' | 'fullpath'.
+-type format() :: 'formatted' | 'raw'.
-type label() :: non_neg_integer().
-type rep_mode() :: 'quiet' | 'normal' | 'verbose'.
-type start_from() :: 'byte_code' | 'src_code'.
@@ -137,10 +140,10 @@
erlang_mode = false :: boolean(),
use_contracts = true :: boolean(),
output_file = none :: 'none' | file:filename(),
- output_format = formatted :: 'raw' | 'formatted',
+ output_format = formatted :: format(),
+ filename_opt = basename :: fopt(),
callgraph_file = "" :: file:filename(),
- check_plt = true :: boolean()
- }).
+ check_plt = true :: boolean()}).
-record(contract, {contracts = [] :: [contract_pair()],
args = [] :: [erl_types:erl_type()],
diff --git a/lib/dialyzer/src/dialyzer_cl.erl b/lib/dialyzer/src/dialyzer_cl.erl
index 1987c1732c..8d61216b7a 100644
--- a/lib/dialyzer/src/dialyzer_cl.erl
+++ b/lib/dialyzer/src/dialyzer_cl.erl
@@ -2,7 +2,7 @@
%%-------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -46,7 +46,8 @@
legal_warnings = ordsets:new() :: [dial_warn_tag()],
mod_deps = dict:new() :: dict(),
output = standard_io :: io:device(),
- output_format = formatted :: 'raw' | 'formatted',
+ output_format = formatted :: format(),
+ filename_opt = basename :: fopt(),
output_plt = none :: 'none' | file:filename(),
plt_info = none :: 'none' | dialyzer_plt:plt_info(),
report_mode = normal :: rep_mode(),
@@ -188,6 +189,12 @@ init_opts_for_remove(Opts) ->
plt_common(#options{init_plts = [InitPlt]} = Opts, RemoveFiles, AddFiles) ->
case check_plt(Opts, RemoveFiles, AddFiles) of
ok ->
+ case Opts#options.output_plt of
+ none -> ok;
+ OutPlt ->
+ {ok, Binary} = file:read_file(InitPlt),
+ file:write_file(OutPlt, Binary)
+ end,
case Opts#options.report_mode of
quiet -> ok;
_ -> io:put_chars(" yes\n")
@@ -532,8 +539,10 @@ hc(Mod) ->
new_state() ->
#cl_state{}.
-init_output(State0, #options{output_file = OutFile, output_format = OutFormat}) ->
- State = State0#cl_state{output_format = OutFormat},
+init_output(State0, #options{output_file = OutFile,
+ output_format = OutFormat,
+ filename_opt = FOpt}) ->
+ State = State0#cl_state{output_format = OutFormat, filename_opt = FOpt},
case OutFile =:= none of
true ->
State;
@@ -766,6 +775,7 @@ print_warnings(#cl_state{stored_warnings = []}) ->
ok;
print_warnings(#cl_state{output = Output,
output_format = Format,
+ filename_opt = FOpt,
stored_warnings = Warnings}) ->
PrWarnings = process_warnings(Warnings),
case PrWarnings of
@@ -773,7 +783,7 @@ print_warnings(#cl_state{output = Output,
[_|_] ->
S = case Format of
formatted ->
- [dialyzer:format_warning(W) || W <- PrWarnings];
+ [dialyzer:format_warning(W, FOpt) || W <- PrWarnings];
raw ->
[io_lib:format("~p. \n", [W]) || W <- PrWarnings]
end,
diff --git a/lib/dialyzer/src/dialyzer_cl_parse.erl b/lib/dialyzer/src/dialyzer_cl_parse.erl
index 5ca7599b35..690ad7b8d3 100644
--- a/lib/dialyzer/src/dialyzer_cl_parse.erl
+++ b/lib/dialyzer/src/dialyzer_cl_parse.erl
@@ -2,7 +2,7 @@
%%-----------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -20,10 +20,8 @@
-module(dialyzer_cl_parse).
-%% Avoid warning for local function error/1 clashing with autoimported BIF.
--compile({no_auto_import,[error/1]}).
--export([start/0]).
--export([collect_args/1]). % used also by typer_options.erl
+-export([start/0, get_lib_dir/1]).
+-export([collect_args/1]). % used also by typer
-include("dialyzer.hrl").
@@ -32,9 +30,11 @@
-type dial_cl_parse_ret() :: {'check_init', #options{}}
| {'plt_info', #options{}}
| {'cl', #options{}}
- | {{'gui', 'gs' | 'wx'}, #options{}}
+ | {{'gui', 'gs' | 'wx'}, #options{}}
| {'error', string()}.
+-type deep_string() :: string() | [deep_string()].
+
%%-----------------------------------------------------------------------
-spec start() -> dial_cl_parse_ret().
@@ -55,7 +55,7 @@ cl(["--add_to_plt"|T]) ->
put(dialyzer_options_analysis_type, plt_add),
cl(T);
cl(["--apps"|T]) ->
- T1 = get_lib_dir(T, []),
+ T1 = get_lib_dir(T),
{Args, T2} = collect_args(T1),
append_var(dialyzer_options_files_rec, Args),
cl(T2);
@@ -82,7 +82,7 @@ cl(["--get_warnings"|T]) ->
put(dialyzer_options_get_warnings, true),
cl(T);
cl(["-D"|_]) ->
- error("No defines specified after -D");
+ cl_error("No defines specified after -D");
cl(["-D"++Define|T]) ->
Def = re:split(Define, "=", [{return, list}]),
append_defines(Def),
@@ -92,7 +92,7 @@ cl(["-h"|_]) ->
cl(["--help"|_]) ->
help_message();
cl(["-I"]) ->
- error("no include directory specified after -I");
+ cl_error("no include directory specified after -I");
cl(["-I", Dir|T]) ->
append_include(Dir),
cl(T);
@@ -113,14 +113,14 @@ cl(["--com"++_|T]) ->
NewTail = command_line(T),
cl(NewTail);
cl(["--output"]) ->
- error("No outfile specified");
+ cl_error("No outfile specified");
cl(["-o"]) ->
- error("No outfile specified");
+ cl_error("No outfile specified");
cl(["--output",Output|T]) ->
put(dialyzer_output, Output),
cl(T);
cl(["--output_plt"]) ->
- error("No outfile specified for --output_plt");
+ cl_error("No outfile specified for --output_plt");
cl(["--output_plt",Output|T]) ->
put(dialyzer_output_plt, Output),
cl(T);
@@ -133,10 +133,13 @@ cl(["-o"++Output|T]) ->
cl(["--raw"|T]) ->
put(dialyzer_output_format, raw),
cl(T);
+cl(["--fullpath"|T]) ->
+ put(dialyzer_filename_opt, fullpath),
+ cl(T);
cl(["-pa", Path|T]) ->
case code:add_patha(Path) of
true -> cl(T);
- {error, _} -> error("Bad directory for -pa: "++Path)
+ {error, _} -> cl_error("Bad directory for -pa: " ++ Path)
end;
cl(["--plt"]) ->
error("No plt specified for --plt");
@@ -171,14 +174,14 @@ cl(["--verbose"|T]) ->
put(dialyzer_options_report_mode, verbose),
cl(T);
cl(["-W"|_]) ->
- error("-W given without warning");
+ cl_error("-W given without warning");
cl(["-Whelp"|_]) ->
help_warnings();
cl(["-W"++Warn|T]) ->
append_var(dialyzer_warnings, [list_to_atom(Warn)]),
cl(T);
cl(["--dump_callgraph"]) ->
- error("No outfile specified for --dump_callgraph");
+ cl_error("No outfile specified for --dump_callgraph");
cl(["--dump_callgraph", File|T]) ->
put(dialyzer_callgraph_file, File),
cl(T);
@@ -194,7 +197,7 @@ cl([H|_] = L) ->
NewTail = command_line(L),
cl(NewTail);
false ->
- error("Unknown option: " ++ H)
+ cl_error("Unknown option: " ++ H)
end;
cl([]) ->
{RetTag, Opts} =
@@ -213,7 +216,7 @@ cl([]) ->
end
end,
case dialyzer_options:build(Opts) of
- {error, Msg} -> error(Msg);
+ {error, Msg} -> cl_error(Msg);
OptsRecord -> {RetTag, OptsRecord}
end.
@@ -229,7 +232,9 @@ command_line(T0) ->
end,
T.
-error(Str) ->
+-spec cl_error(deep_string()) -> no_return().
+
+cl_error(Str) ->
Msg = lists:flatten(Str),
throw({dialyzer_cl_parse_error, Msg}).
@@ -243,6 +248,7 @@ init() ->
put(dialyzer_options_defines, DefaultOpts#options.defines),
put(dialyzer_options_files, DefaultOpts#options.files),
put(dialyzer_output_format, formatted),
+ put(dialyzer_filename_opt, basename),
put(dialyzer_options_check_plt, DefaultOpts#options.check_plt),
ok.
@@ -281,6 +287,7 @@ cl_options() ->
{files_rec, get(dialyzer_options_files_rec)},
{output_file, get(dialyzer_output)},
{output_format, get(dialyzer_output_format)},
+ {filename_opt, get(dialyzer_filename_opt)},
{analysis_type, get(dialyzer_options_analysis_type)},
{get_warnings, get(dialyzer_options_get_warnings)},
{callgraph_file, get(dialyzer_callgraph_file)}
@@ -299,6 +306,9 @@ common_options() ->
%%-----------------------------------------------------------------------
+get_lib_dir(Apps) ->
+ get_lib_dir(Apps, []).
+
get_lib_dir([H|T], Acc) ->
NewElem =
case code:lib_dir(list_to_atom(H)) of
@@ -322,11 +332,15 @@ get_plts([], Acc) -> {lists:reverse(Acc), []}.
%%-----------------------------------------------------------------------
+-spec help_warnings() -> no_return().
+
help_warnings() ->
S = warning_options_msg(),
io:put_chars(S),
erlang:halt(?RET_NOTHING_SUSPICIOUS).
+-spec help_message() -> no_return().
+
help_message() ->
S = "Usage: dialyzer [--help] [--version] [--shell] [--quiet] [--verbose]
[-pa dir]* [--plt plt] [--plts plt*] [-Ddefine]*
@@ -335,7 +349,7 @@ help_message() ->
[--apps applications] [-o outfile]
[--build_plt] [--add_to_plt] [--remove_from_plt]
[--check_plt] [--no_check_plt] [--plt_info] [--get_warnings]
- [--no_native]
+ [--no_native] [--fullpath]
Options:
files_or_dirs (for backwards compatibility also as: -c files_or_dirs)
Use Dialyzer from the command line to detect defects in the
@@ -437,6 +451,8 @@ Options:
Bypass the native code compilation of some key files that Dialyzer
heuristically performs when dialyzing many files; this avoids the
compilation time but it may result in (much) longer analysis time.
+ --fullpath
+ Display the full path names of files for which warnings are emitted.
--gui
Use the gs-based GUI.
--wx
@@ -484,13 +500,13 @@ warning_options_msg() ->
Include warnings about behaviour callbacks which drift from the published
recommended interfaces.
-Wunderspecs ***
- Warn about underspecified functions
+ Warn about underspecified functions
(those whose -spec is strictly more allowing than the success typing).
The following options are also available but their use is not recommended:
(they are mostly for Dialyzer developers and internal debugging)
-Woverspecs ***
- Warn about overspecified functions
+ Warn about overspecified functions
(those whose -spec is strictly less allowing than the success typing).
-Wspecdiffs ***
Warn when the -spec is different than the success typing.
diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index b80c7efc1a..7137dbc036 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -2,7 +2,7 @@
%%--------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -657,7 +657,8 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
true -> opaque;
false -> structured
end,
- RetWithoutLocal = t_inf(t_inf(ContrRet, BifRet, RetMode), SigRange, RetMode),
+ RetWithoutContr = t_inf(SigRange, BifRet, RetMode),
+ RetWithoutLocal = t_inf(ContrRet, RetWithoutContr, RetMode),
?debug("--------------------------------------------------------\n", []),
?debug("Fun: ~p\n", [Fun]),
?debug("Args: ~s\n", [erl_types:t_to_string(t_product(ArgTypes))]),
@@ -666,6 +667,7 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
[erl_types:t_to_string(t_product(NewArgsContract))]),
?debug("NewArgsBif: ~s\n", [erl_types:t_to_string(t_product(NewArgsBif))]),
?debug("NewArgTypes: ~s\n", [erl_types:t_to_string(t_product(NewArgTypes))]),
+ ?debug("RetWithoutContr: ~s\n",[erl_types:t_to_string(RetWithoutContr)]),
?debug("RetWithoutLocal: ~s\n", [erl_types:t_to_string(RetWithoutLocal)]),
?debug("BifRet: ~s\n", [erl_types:t_to_string(BifRange(NewArgTypes))]),
?debug("ContrRet: ~s\n", [erl_types:t_to_string(CRange(TmpArgTypes))]),
@@ -700,22 +702,39 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
State2 =
case FailedConj andalso not (IsFailBif orelse IsFailSig) of
true ->
- FailedSig = any_none(NewArgsSig),
- FailedContract = any_none([CRange(TmpArgsContract)|NewArgsContract]),
- FailedBif = any_none([BifRange(NewArgsBif)|NewArgsBif]),
- InfSig = t_inf(t_fun(SigArgs, SigRange),
- t_fun(BifArgs, BifRange(BifArgs))),
- FailReason = apply_fail_reason(FailedSig, FailedBif, FailedContract),
- Msg = get_apply_fail_msg(Fun, Args, ArgTypes, NewArgTypes, InfSig,
- Contr, CArgs, State1, FailReason),
- WarnType = case Msg of
- {call, _} -> ?WARN_FAILING_CALL;
- {apply, _} -> ?WARN_FAILING_CALL;
- {call_with_opaque, _} -> ?WARN_OPAQUE;
- {call_without_opaque, _} -> ?WARN_OPAQUE;
- {opaque_type_test, _} -> ?WARN_OPAQUE
- end,
- state__add_warning(State1, WarnType, Tree, Msg);
+ case t_is_none(RetWithoutLocal) andalso
+ not t_is_none(RetWithoutContr) andalso
+ not any_none(NewArgTypes) of
+ true ->
+ {value, C1} = Contr,
+ Contract = dialyzer_contracts:contract_to_string(C1),
+ {M1, F1, A1} = state__lookup_name(Fun, State),
+ ArgStrings = format_args(Args, ArgTypes, State),
+ CRet = erl_types:t_to_string(RetWithoutContr),
+ %% This Msg will be post_processed by dialyzer_succ_typings
+ Msg =
+ {contract_range, [Contract, M1, F1, A1, ArgStrings, CRet]},
+ state__add_warning(State1, ?WARN_CONTRACT_RANGE, Tree, Msg);
+ false ->
+ FailedSig = any_none(NewArgsSig),
+ FailedContract =
+ any_none([CRange(TmpArgsContract)|NewArgsContract]),
+ FailedBif = any_none([BifRange(NewArgsBif)|NewArgsBif]),
+ InfSig = t_inf(t_fun(SigArgs, SigRange),
+ t_fun(BifArgs, BifRange(BifArgs))),
+ FailReason =
+ apply_fail_reason(FailedSig, FailedBif, FailedContract),
+ Msg = get_apply_fail_msg(Fun, Args, ArgTypes, NewArgTypes, InfSig,
+ Contr, CArgs, State1, FailReason),
+ WarnType = case Msg of
+ {call, _} -> ?WARN_FAILING_CALL;
+ {apply, _} -> ?WARN_FAILING_CALL;
+ {call_with_opaque, _} -> ?WARN_OPAQUE;
+ {call_without_opaque, _} -> ?WARN_OPAQUE;
+ {opaque_type_test, _} -> ?WARN_OPAQUE
+ end,
+ state__add_warning(State1, WarnType, Tree, Msg)
+ end;
false -> State1
end,
State3 =
@@ -1350,7 +1369,7 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
bind_pat_vars(Pats, ArgTypes, [], Map1, State1)
end,
case BindRes of
- {error, BindOrOpaque, NewPats, Type, OpaqueTerm} ->
+ {error, ErrorType, NewPats, Type, OpaqueTerm} ->
?debug("Failed binding pattern: ~s\nto ~s\n",
[cerl_prettypr:format(C), format_type(ArgType0, State1)]),
case state__warning_mode(State1) of
@@ -1358,8 +1377,9 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
{State1, Map, t_none(), ArgType0};
true ->
PatString =
- case BindOrOpaque of
+ case ErrorType of
bind -> format_patterns(Pats);
+ record -> format_patterns(Pats);
opaque -> format_patterns(NewPats)
end,
{Msg, Force} =
@@ -1399,13 +1419,15 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
false ->
true
end,
- PatTypes = case BindOrOpaque of
+ PatTypes = case ErrorType of
bind -> [PatString, format_type(ArgType0, State1)];
+ record -> [PatString, format_type(Type, State1)];
opaque -> [PatString, format_type(Type, State1),
format_type(OpaqueTerm, State1)]
- end,
- FailedMsg = case BindOrOpaque of
+ end,
+ FailedMsg = case ErrorType of
bind -> {pattern_match, PatTypes};
+ record -> {record_match, PatTypes};
opaque -> {opaque_match, PatTypes}
end,
{FailedMsg, Force0}
@@ -1413,6 +1435,7 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
WarnType = case Msg of
{opaque_match, _} -> ?WARN_OPAQUE;
{pattern_match, _} -> ?WARN_MATCHING;
+ {record_match, _} -> ?WARN_MATCHING;
{pattern_match_cov, _} -> ?WARN_MATCHING
end,
{state__add_warning(State1, WarnType, C, Msg, Force),
@@ -1457,6 +1480,7 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
false ->
WarnType = case Msg of
{guard_fail, _} -> ?WARN_MATCHING;
+ {neg_guard_fail, _} -> ?WARN_MATCHING;
{opaque_guard, _} -> ?WARN_OPAQUE
end,
state__add_warning(State1, WarnType, FailGuard, Msg);
@@ -1505,14 +1529,18 @@ bind_pat_vars(Pats, Types, Acc, Map, State) ->
try
bind_pat_vars(Pats, Types, Acc, Map, State, false)
catch
- throw:Error -> Error % Error = {error, bind | opaque, ErrorPats, ErrorType}
+ throw:Error ->
+ %% Error = {error, bind | opaque | record, ErrorPats, ErrorType}
+ Error
end.
bind_pat_vars_reverse(Pats, Types, Acc, Map, State) ->
try
bind_pat_vars(Pats, Types, Acc, Map, State, true)
catch
- throw:Error -> Error % Error = {error, bind | opaque, ErrorPats, ErrorType}
+ throw:Error ->
+ %% Error = {error, bind | opaque | record, ErrorPats, ErrorType}
+ Error
end.
bind_pat_vars([Pat|PatLeft], [Type|TypeLeft], Acc, Map, State, Rev) ->
@@ -1567,18 +1595,21 @@ bind_pat_vars([Pat|PatLeft], [Type|TypeLeft], Acc, Map, State, Rev) ->
end;
tuple ->
Es = cerl:tuple_es(Pat),
- Prototype =
+ {TypedRecord, Prototype} =
case Es of
- [] -> t_tuple([]);
+ [] -> {false, t_tuple([])};
[Tag|Left] ->
case cerl:is_c_atom(Tag) of
true ->
TagAtom = cerl:atom_val(Tag),
case state__lookup_record(TagAtom, length(Left), State) of
- error -> t_tuple(length(Es));
- {ok, Record} -> Record
+ error -> {false, t_tuple(length(Es))};
+ {ok, Record} ->
+ [_Head|AnyTail] = [t_any() || _ <- Es],
+ UntypedRecord = t_tuple([t_atom(TagAtom)|AnyTail]),
+ {not erl_types:t_is_equal(Record, UntypedRecord), Record}
end;
- false -> t_tuple(length(Es))
+ false -> {false, t_tuple(length(Es))}
end
end,
Tuple = t_inf(Prototype, Type),
@@ -1603,7 +1634,11 @@ bind_pat_vars([Pat|PatLeft], [Type|TypeLeft], Acc, Map, State, Rev) ->
bind_error([Pat], Tuple, Opaque, opaque);
false ->
case [M || {M, _} <- Results, M =/= error] of
- [] -> bind_error([Pat], Tuple, t_none(), bind);
+ [] ->
+ case TypedRecord of
+ true -> bind_error([Pat], Tuple, Prototype, record);
+ false -> bind_error([Pat], Tuple, t_none(), bind)
+ end;
Maps ->
Map1 = join_maps(Maps, Map),
TupleType = t_sup([t_tuple(EsTypes)
@@ -1748,7 +1783,7 @@ bind_opaque_pats(GenType, Type, Pat, Map, State, Rev) ->
bind_guard(Guard, Map, State) ->
try bind_guard(Guard, Map, dict:new(), pos, State) of
- {Map1, _Type} -> Map1
+ {Map1, _Type} -> Map1
catch
throw:{fail, Warning} -> {error, Warning};
throw:{fatal_fail, Warning} -> {error, Warning}
@@ -1869,8 +1904,8 @@ handle_guard_gen_fun({M, F, A}, Guard, Map, Env, Eval, State) ->
true ->
%% Is this an error-bif?
case t_is_none(erl_bif_types:type(M, F, A)) of
- true -> signal_guard_fail(Guard, As, State);
- false -> signal_guard_fatal_fail(Guard, As, State)
+ true -> signal_guard_fail(Eval, Guard, As, State);
+ false -> signal_guard_fatal_fail(Eval, Guard, As, State)
end;
false ->
BifArgs = case erl_bif_types:arg_types(M, F, A) of
@@ -1887,7 +1922,7 @@ handle_guard_gen_fun({M, F, A}, Guard, Map, Env, Eval, State) ->
case t_is_none(Ret) of
true ->
case Eval =:= pos of
- true -> signal_guard_fail(Guard, As, State);
+ true -> signal_guard_fail(Eval, Guard, As, State);
false -> throw({fail, none})
end;
false -> {Map2, Ret}
@@ -1900,7 +1935,7 @@ handle_guard_type_test(Guard, F, Map, Env, Eval, State) ->
case bind_type_test(Eval, F, ArgType, State) of
error ->
?debug("Type test: ~w failed\n", [F]),
- signal_guard_fail(Guard, [ArgType], State);
+ signal_guard_fail(Eval, Guard, [ArgType], State);
{ok, NewArgType, Ret} ->
?debug("Type test: ~w succeeded, NewType: ~s, Ret: ~s\n",
[F, t_to_string(NewArgType), t_to_string(Ret)]),
@@ -1963,18 +1998,19 @@ handle_guard_comp(Guard, Comp, Map, Env, Eval, State) ->
true when Eval =:= pos -> {Map, t_atom(true)};
true when Eval =:= dont_know -> {Map, t_atom(true)};
true when Eval =:= neg -> {Map, t_atom(true)};
- false when Eval =:= pos -> signal_guard_fail(Guard, ArgTypes, State);
+ false when Eval =:= pos ->
+ signal_guard_fail(Eval, Guard, ArgTypes, State);
false when Eval =:= dont_know -> {Map, t_atom(false)};
false when Eval =:= neg -> {Map, t_atom(false)}
end;
{literal, var} when IsInt1 andalso IsInt2 andalso (Eval =:= pos) ->
case bind_comp_literal_var(Arg1, Arg2, Type2, Comp, Map1) of
- error -> signal_guard_fail(Guard, ArgTypes, State);
+ error -> signal_guard_fail(Eval, Guard, ArgTypes, State);
{ok, NewMap} -> {NewMap, t_atom(true)}
end;
{var, literal} when IsInt1 andalso IsInt2 andalso (Eval =:= pos) ->
case bind_comp_literal_var(Arg2, Arg1, Type1, invert_comp(Comp), Map1) of
- error -> signal_guard_fail(Guard, ArgTypes, State);
+ error -> signal_guard_fail(Eval, Guard, ArgTypes, State);
{ok, NewMap} -> {NewMap, t_atom(true)}
end;
{_, _} ->
@@ -2014,7 +2050,7 @@ handle_guard_is_function(Guard, Map, Env, Eval, State) ->
[FunType0, ArityType0] = ArgTypes0,
ArityType = t_inf(ArityType0, t_integer()),
case t_is_none(ArityType) of
- true -> signal_guard_fail(Guard, ArgTypes0, State);
+ true -> signal_guard_fail(Eval, Guard, ArgTypes0, State);
false ->
FunTypeConstr =
case t_number_vals(ArityType) of
@@ -2026,7 +2062,7 @@ handle_guard_is_function(Guard, Map, Env, Eval, State) ->
case t_is_none(FunType) of
true ->
case Eval of
- pos -> signal_guard_fail(Guard, ArgTypes0, State);
+ pos -> signal_guard_fail(Eval, Guard, ArgTypes0, State);
neg -> {Map1, t_atom(false)};
dont_know -> {Map1, t_atom(false)}
end;
@@ -2062,7 +2098,7 @@ handle_guard_is_record(Guard, Map, Env, Eval, State) ->
case t_is_none(Type) of
true ->
case Eval of
- pos -> signal_guard_fail(Guard,
+ pos -> signal_guard_fail(Eval, Guard,
[RecType, t_from_term(Tag),
t_from_term(Arity)],
State);
@@ -2085,7 +2121,10 @@ handle_guard_eq(Guard, Map, Env, Eval, State) ->
true ->
if
Eval =:= pos -> {Map, t_atom(true)};
- Eval =:= neg -> throw({fail, none});
+ Eval =:= neg ->
+ ArgTypes = [t_from_term(cerl:concrete(Arg1)),
+ t_from_term(cerl:concrete(Arg2))],
+ signal_guard_fail(Eval, Guard, ArgTypes, State);
Eval =:= dont_know -> {Map, t_atom(true)}
end;
false ->
@@ -2095,7 +2134,7 @@ handle_guard_eq(Guard, Map, Env, Eval, State) ->
Eval =:= pos ->
ArgTypes = [t_from_term(cerl:concrete(Arg1)),
t_from_term(cerl:concrete(Arg2))],
- signal_guard_fail(Guard, ArgTypes, State)
+ signal_guard_fail(Eval, Guard, ArgTypes, State)
end
end;
{literal, _} when Eval =:= pos ->
@@ -2140,7 +2179,10 @@ handle_guard_eqeq(Guard, Map, Env, Eval, State) ->
{literal, literal} ->
case cerl:concrete(Arg1) =:= cerl:concrete(Arg2) of
true ->
- if Eval =:= neg -> throw({fail, none});
+ if Eval =:= neg ->
+ ArgTypes = [t_from_term(cerl:concrete(Arg1)),
+ t_from_term(cerl:concrete(Arg2))],
+ signal_guard_fail(Eval, Guard, ArgTypes, State);
Eval =:= pos -> {Map, t_atom(true)};
Eval =:= dont_know -> {Map, t_atom(true)}
end;
@@ -2150,7 +2192,7 @@ handle_guard_eqeq(Guard, Map, Env, Eval, State) ->
Eval =:= pos ->
ArgTypes = [t_from_term(cerl:concrete(Arg1)),
t_from_term(cerl:concrete(Arg2))],
- signal_guard_fail(Guard, ArgTypes, State)
+ signal_guard_fail(Eval, Guard, ArgTypes, State)
end
end;
{literal, _} when Eval =:= pos ->
@@ -2172,7 +2214,7 @@ bind_eqeq_guard(Guard, Arg1, Arg2, Map, Env, Eval, State) ->
case Eval of
neg -> {Map2, t_atom(false)};
dont_know -> {Map2, t_atom(false)};
- pos -> signal_guard_fail(Guard, [Type1, Type2], State)
+ pos -> signal_guard_fail(Eval, Guard, [Type1, Type2], State)
end;
false ->
case Eval of
@@ -2199,29 +2241,29 @@ bind_eqeq_guard(Guard, Arg1, Arg2, Map, Env, Eval, State) ->
end.
bind_eqeq_guard_lit_other(Guard, Arg1, Arg2, Map, Env, State) ->
- %% Assumes positive evaluation
+ Eval = dont_know,
case cerl:concrete(Arg1) of
true ->
{_, Type} = MT = bind_guard(Arg2, Map, Env, pos, State),
case t_is_atom(true, Type) of
true -> MT;
false ->
- {_, Type0} = bind_guard(Arg2, Map, Env, dont_know, State),
- signal_guard_fail(Guard, [Type0, t_atom(true)], State)
+ {_, Type0} = bind_guard(Arg2, Map, Env, Eval, State),
+ signal_guard_fail(Eval, Guard, [Type0, t_atom(true)], State)
end;
false ->
{Map1, Type} = bind_guard(Arg2, Map, Env, neg, State),
case t_is_atom(false, Type) of
true -> {Map1, t_atom(true)};
false ->
- {_, Type0} = bind_guard(Arg2, Map, Env, dont_know, State),
- signal_guard_fail(Guard, [Type0, t_atom(true)], State)
+ {_, Type0} = bind_guard(Arg2, Map, Env, Eval, State),
+ signal_guard_fail(Eval, Guard, [Type0, t_atom(false)], State)
end;
Term ->
LitType = t_from_term(Term),
- {Map1, Type} = bind_guard(Arg2, Map, Env, dont_know, State),
+ {Map1, Type} = bind_guard(Arg2, Map, Env, Eval, State),
case t_is_subtype(LitType, Type) of
- false -> signal_guard_fail(Guard, [Type, LitType], State);
+ false -> signal_guard_fail(Eval, Guard, [Type, LitType], State);
true ->
case cerl:is_c_var(Arg2) of
true -> {enter_type(Arg2, LitType, Map1), t_atom(true)};
@@ -2236,11 +2278,11 @@ handle_guard_and(Guard, Map, Env, Eval, State) ->
pos ->
{Map1, Type1} = bind_guard(Arg1, Map, Env, Eval, State),
case t_is_atom(true, Type1) of
- false -> throw({fail, none});
+ false -> signal_guard_fail(Eval, Guard, [Type1, t_any()], State);
true ->
{Map2, Type2} = bind_guard(Arg2, Map1, Env, Eval, State),
case t_is_atom(true, Type2) of
- false -> throw({fail, none});
+ false -> signal_guard_fail(Eval, Guard, [Type1, Type2], State);
true -> {Map2, t_atom(true)}
end
end;
@@ -2250,31 +2292,37 @@ handle_guard_and(Guard, Map, Env, Eval, State) ->
catch throw:{fail, _} -> bind_guard(Arg2, Map, Env, pos, State)
end,
{Map2, Type2} =
- try bind_guard(Arg1, Map, Env, neg, State)
- catch throw:{fail, _} -> bind_guard(Arg2, Map, Env, pos, State)
+ try bind_guard(Arg2, Map, Env, neg, State)
+ catch throw:{fail, _} -> bind_guard(Arg1, Map, Env, pos, State)
end,
case t_is_atom(false, Type1) orelse t_is_atom(false, Type2) of
true -> {join_maps([Map1, Map2], Map), t_atom(false)};
- false -> throw({fail, none})
+ false -> signal_guard_fail(Eval, Guard, [Type1, Type2], State)
end;
dont_know ->
- True = t_atom(true),
{Map1, Type1} = bind_guard(Arg1, Map, Env, dont_know, State),
- case t_is_none(t_inf(Type1, t_boolean())) of
- true -> throw({fail, none});
+ {Map2, Type2} = bind_guard(Arg2, Map, Env, dont_know, State),
+ Bool1 = t_inf(Type1, t_boolean()),
+ Bool2 = t_inf(Type2, t_boolean()),
+ case t_is_none(Bool1) orelse t_is_none(Bool2) of
+ true -> throw({fatal_fail, none});
false ->
- {Map2, Type2} = bind_guard(Arg2, Map1, Env, Eval, State),
- case t_is_none(t_inf(Type2, t_boolean())) of
- true -> throw({fail, none});
- false -> {Map2, True}
- end
+ NewMap = join_maps([Map1, Map2], Map),
+ NewType =
+ case {t_atom_vals(Bool1), t_atom_vals(Bool2)} of
+ {['true'] , ['true'] } -> t_atom(true);
+ {['false'], _ } -> t_atom(false);
+ {_ , ['false']} -> t_atom(false);
+ {_ , _ } -> t_boolean()
+ end,
+ {NewMap, NewType}
end
end.
handle_guard_or(Guard, Map, Env, Eval, State) ->
[Arg1, Arg2] = cerl:call_args(Guard),
case Eval of
- pos ->
+ pos ->
{Map1, Bool1} =
try bind_guard(Arg1, Map, Env, pos, State)
catch
@@ -2289,25 +2337,36 @@ handle_guard_or(Guard, Map, Env, Eval, State) ->
orelse
(t_is_atom(true, Bool2) andalso t_is_boolean(Bool1))) of
true -> {join_maps([Map1, Map2], Map), t_atom(true)};
- false -> throw({fail, none})
+ false -> signal_guard_fail(Eval, Guard, [Bool1, Bool2], State)
end;
neg ->
{Map1, Type1} = bind_guard(Arg1, Map, Env, neg, State),
case t_is_atom(false, Type1) of
- false -> throw({fail, none});
+ false -> signal_guard_fail(Eval, Guard, [Type1, t_any()], State);
true ->
{Map2, Type2} = bind_guard(Arg2, Map1, Env, neg, State),
case t_is_atom(false, Type2) of
- false -> throw({fail, none});
+ false -> signal_guard_fail(Eval, Guard, [Type1, Type2], State);
true -> {Map2, t_atom(false)}
end
end;
dont_know ->
- {Map1, Bool1} = bind_guard(Arg1, Map, Env, dont_know, State),
- {Map2, Bool2} = bind_guard(Arg2, Map, Env, dont_know, State),
- case t_is_boolean(Bool1) andalso t_is_boolean(Bool2) of
- true -> {join_maps([Map1, Map2], Map), t_sup(Bool1, Bool2)};
- false -> throw({fail, none})
+ {Map1, Type1} = bind_guard(Arg1, Map, Env, dont_know, State),
+ {Map2, Type2} = bind_guard(Arg2, Map, Env, dont_know, State),
+ Bool1 = t_inf(Type1, t_boolean()),
+ Bool2 = t_inf(Type2, t_boolean()),
+ case t_is_none(Bool1) orelse t_is_none(Bool2) of
+ true -> throw({fatal_fail, none});
+ false ->
+ NewMap = join_maps([Map1, Map2], Map),
+ NewType =
+ case {t_atom_vals(Bool1), t_atom_vals(Bool2)} of
+ {['false'], ['false']} -> t_atom(false);
+ {['true'] , _ } -> t_atom(true);
+ {_ , ['true'] } -> t_atom(true);
+ {_ , _ } -> t_boolean()
+ end,
+ {NewMap, NewType}
end
end.
@@ -2318,13 +2377,17 @@ handle_guard_not(Guard, Map, Env, Eval, State) ->
{Map1, Type} = bind_guard(Arg, Map, Env, pos, State),
case t_is_atom(true, Type) of
true -> {Map1, t_atom(false)};
- false -> throw({fail, none})
+ false ->
+ {_, Type0} = bind_guard(Arg, Map, Env, Eval, State),
+ signal_guard_fail(Eval, Guard, [Type0], State)
end;
pos ->
{Map1, Type} = bind_guard(Arg, Map, Env, neg, State),
case t_is_atom(false, Type) of
true -> {Map1, t_atom(true)};
- false -> throw({fail, none})
+ false ->
+ {_, Type0} = bind_guard(Arg, Map, Env, Eval, State),
+ signal_guard_fail(Eval, Guard, [Type0], State)
end;
dont_know ->
{Map1, Type} = bind_guard(Arg, Map, Env, dont_know, State),
@@ -2349,10 +2412,12 @@ bind_guard_list([G|Gs], Map, Env, Eval, State, Acc) ->
bind_guard_list([], Map, _Env, _Eval, _State, Acc) ->
{Map, lists:reverse(Acc)}.
--spec signal_guard_fail(cerl:c_call(), [erl_types:erl_type()], state()) ->
- no_return().
+-type eval() :: 'pos' | 'neg' | 'dont_know'.
-signal_guard_fail(Guard, ArgTypes, State) ->
+-spec signal_guard_fail(eval(), cerl:c_call(), [erl_types:erl_type()],
+ state()) -> no_return().
+
+signal_guard_fail(Eval, Guard, ArgTypes, State) ->
Args = cerl:call_args(Guard),
F = cerl:atom_val(cerl:call_name(Guard)),
MFA = {cerl:atom_val(cerl:call_module(Guard)), F, length(Args)},
@@ -2361,11 +2426,17 @@ signal_guard_fail(Guard, ArgTypes, State) ->
true ->
[ArgType1, ArgType2] = ArgTypes,
[Arg1, Arg2] = Args,
- {guard_fail, [format_args_1([Arg1], [ArgType1], State),
- atom_to_list(F),
- format_args_1([Arg2], [ArgType2], State)]};
+ Kind =
+ case Eval of
+ neg -> neg_guard_fail;
+ pos -> guard_fail;
+ dont_know -> guard_fail
+ end,
+ {Kind, [format_args_1([Arg1], [ArgType1], State),
+ atom_to_list(F),
+ format_args_1([Arg2], [ArgType2], State)]};
false ->
- mk_guard_msg(F, Args, ArgTypes, State)
+ mk_guard_msg(Eval, F, Args, ArgTypes, State)
end,
throw({fail, {Guard, Msg}}).
@@ -2380,20 +2451,25 @@ is_infix_op({erlang, '>=', 2}) -> true;
is_infix_op({M, F, A}) when is_atom(M), is_atom(F),
is_integer(A), 0 =< A, A =< 255 -> false.
--spec signal_guard_fatal_fail(cerl:c_call(), [erl_types:erl_type()], state()) ->
- no_return().
+-spec signal_guard_fatal_fail(eval(), cerl:c_call(), [erl_types:erl_type()],
+ state()) -> no_return().
-signal_guard_fatal_fail(Guard, ArgTypes, State) ->
+signal_guard_fatal_fail(Eval, Guard, ArgTypes, State) ->
Args = cerl:call_args(Guard),
F = cerl:atom_val(cerl:call_name(Guard)),
- Msg = mk_guard_msg(F, Args, ArgTypes, State),
+ Msg = mk_guard_msg(Eval, F, Args, ArgTypes, State),
throw({fatal_fail, {Guard, Msg}}).
-mk_guard_msg(F, Args, ArgTypes, State) ->
+mk_guard_msg(Eval, F, Args, ArgTypes, State) ->
FArgs = [F, format_args(Args, ArgTypes, State)],
case any_has_opaque_subtype(ArgTypes) of
true -> {opaque_guard, FArgs};
- false -> {guard_fail, FArgs}
+ false ->
+ case Eval of
+ neg -> {neg_guard_fail, FArgs};
+ pos -> {guard_fail, FArgs};
+ dont_know -> {guard_fail, FArgs}
+ end
end.
bind_guard_case_clauses(Arg, Clauses, Map, Env, Eval, State) ->
@@ -2741,8 +2817,6 @@ state__new(Callgraph, Tree, Plt, Module, Records, BehaviourTranslations) ->
FunTab = init_fun_tab(Funs, dict:new(), TreeMap, Callgraph, Plt, Opaques),
Work = init_work([get_label(Tree)]),
Env = dict:store(top, map__new(), dict:new()),
- Opaques = erl_types:module_builtin_opaques(Module) ++
- erl_types:t_opaque_from_records(Records),
#state{callgraph = Callgraph, envs = Env, fun_tab = FunTab, opaques = Opaques,
plt = Plt, races = dialyzer_races:new(), records = Records,
warning_mode = false, warnings = [], work = Work, tree_map = TreeMap,
diff --git a/lib/dialyzer/src/dialyzer_options.erl b/lib/dialyzer/src/dialyzer_options.erl
index 2c0afa6e2b..b2a67de8bd 100644
--- a/lib/dialyzer/src/dialyzer_options.erl
+++ b/lib/dialyzer/src/dialyzer_options.erl
@@ -2,7 +2,7 @@
%%-----------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -47,6 +47,7 @@ build(Opts) ->
?WARN_FAILING_CALL,
?WARN_BIN_CONSTRUCTION,
?WARN_CALLGRAPH,
+ ?WARN_CONTRACT_RANGE,
?WARN_CONTRACT_TYPES,
?WARN_CONTRACT_SYNTAX],
DefaultWarns1 = ordsets:from_list(DefaultWarns),
@@ -120,12 +121,18 @@ build_options([{OptName, undefined}|Rest], Options) when is_atom(OptName) ->
build_options(Rest, Options);
build_options([{OptionName, Value} = Term|Rest], Options) ->
case OptionName of
+ apps ->
+ OldValues = Options#options.files_rec,
+ AppDirs = get_app_dirs(Value),
+ assert_filenames(Term, AppDirs),
+ build_options(Rest, Options#options{files_rec = AppDirs ++ OldValues});
files ->
assert_filenames(Term, Value),
build_options(Rest, Options#options{files = Value});
files_rec ->
+ OldValues = Options#options.files_rec,
assert_filenames(Term, Value),
- build_options(Rest, Options#options{files_rec = Value});
+ build_options(Rest, Options#options{files_rec = Value ++ OldValues});
analysis_type ->
NewOptions =
case Value of
@@ -169,6 +176,9 @@ build_options([{OptionName, Value} = Term|Rest], Options) ->
output_format ->
assert_output_format(Value),
build_options(Rest, Options#options{output_format = Value});
+ filename_opt ->
+ assert_filename_opt(Value),
+ build_options(Rest, Options#options{filename_opt = Value});
output_plt ->
assert_filename(Value),
build_options(Rest, Options#options{output_plt = Value});
@@ -188,6 +198,11 @@ build_options([{OptionName, Value} = Term|Rest], Options) ->
build_options([], Options) ->
Options.
+get_app_dirs(Apps) when is_list(Apps) ->
+ dialyzer_cl_parse:get_lib_dir([atom_to_list(A) || A <- Apps]);
+get_app_dirs(Apps) ->
+ bad_option("Use a list of otp applications", Apps).
+
assert_filenames(Term, [FileName|Left]) when length(FileName) >= 0 ->
case filelib:is_file(FileName) orelse filelib:is_dir(FileName) of
true -> ok;
@@ -218,6 +233,13 @@ assert_output_format(formatted) ->
assert_output_format(Term) ->
bad_option("Illegal value for output_format", Term).
+assert_filename_opt(basename) ->
+ ok;
+assert_filename_opt(fullpath) ->
+ ok;
+assert_filename_opt(Term) ->
+ bad_option("Illegal value for filename_opt", Term).
+
assert_plt_op(#options{analysis_type = OldVal},
#options{analysis_type = NewVal}) ->
case is_plt_mode(OldVal) andalso is_plt_mode(NewVal) of
diff --git a/lib/dialyzer/src/dialyzer_plt.erl b/lib/dialyzer/src/dialyzer_plt.erl
index a7ba270c41..807c9af44f 100644
--- a/lib/dialyzer/src/dialyzer_plt.erl
+++ b/lib/dialyzer/src/dialyzer_plt.erl
@@ -28,8 +28,6 @@
%%%-------------------------------------------------------------------
-module(dialyzer_plt).
-%% Avoid warning for local function error/1 clashing with autoimported BIF.
--compile({no_auto_import,[error/1]}).
-export([check_plt/3,
compute_md5_from_files/1,
contains_mfa/2,
@@ -56,8 +54,7 @@
plt_and_info_from_file/1,
get_specs/1,
get_specs/4,
- to_file/4
- ]).
+ to_file/4]).
%% Debug utilities
-export([pp_non_returning/0, pp_mod/1]).
@@ -68,6 +65,8 @@
-type mod_deps() :: dict().
+-type deep_string() :: string() | [deep_string()].
+
%% The following are used for searching the PLT when using the GUI
%% (e.g. in show or search PLT contents). The user might be searching
%% with a partial specification, in which case the missing items
@@ -203,8 +202,8 @@ get_default_plt() ->
false ->
case os:getenv("HOME") of
false ->
- error("The HOME environment variable needs to be set " ++
- "so that Dialyzer knows where to find the default PLT");
+ plt_error("The HOME environment variable needs to be set " ++
+ "so that Dialyzer knows where to find the default PLT");
HomeDir -> filename:join(HomeDir, ".dialyzer_plt")
end;
UserSpecPlt -> UserSpecPlt
@@ -226,7 +225,7 @@ from_file(FileName, ReturnInfo) ->
case check_version(Rec) of
error ->
Msg = io_lib:format("Old PLT file ~s\n", [FileName]),
- error(Msg);
+ plt_error(Msg);
ok ->
Plt = #plt{info = Rec#file_plt.info,
types = Rec#file_plt.types,
@@ -241,8 +240,9 @@ from_file(FileName, ReturnInfo) ->
end
end;
{error, Reason} ->
- error(io_lib:format("Could not read PLT file ~s: ~p\n",
- [FileName, Reason]))
+ Msg = io_lib:format("Could not read PLT file ~s: ~p\n",
+ [FileName, Reason]),
+ plt_error(Msg)
end.
-type err_rsn() :: 'not_valid' | 'no_such_file' | 'read_error'.
@@ -518,7 +518,9 @@ expand_args([ArgType|Left]) ->
end ++
","|expand_args(Left)].
-error(Msg) ->
+-spec plt_error(deep_string()) -> no_return().
+
+plt_error(Msg) ->
throw({dialyzer_error, lists:flatten(Msg)}).
%%---------------------------------------------------------------------------
diff --git a/lib/dialyzer/src/dialyzer_succ_typings.erl b/lib/dialyzer/src/dialyzer_succ_typings.erl
index 8bfc66fc39..daf68d24f0 100644
--- a/lib/dialyzer/src/dialyzer_succ_typings.erl
+++ b/lib/dialyzer/src/dialyzer_succ_typings.erl
@@ -131,8 +131,9 @@ get_warnings_from_modules([M|Ms], State, DocPlt,
%% Check if there are contracts for functions that do not exist
Warnings1 =
dialyzer_contracts:contracts_without_fun(Contracts, AllFuns, Callgraph),
- {Warnings2, FunTypes, RaceCode, PublicTables, NamedTables} =
+ {RawWarnings2, FunTypes, RaceCode, PublicTables, NamedTables} =
dialyzer_dataflow:get_warnings(ModCode, Plt, Callgraph, Records, NoWarnUnused),
+ {NewAcc, Warnings2} = postprocess_dataflow_warns(RawWarnings2, State, Acc),
Attrs = cerl:module_attrs(ModCode),
Warnings3 = if BehavioursChk ->
dialyzer_behaviours:check_callbacks(M, Attrs,
@@ -145,10 +146,31 @@ get_warnings_from_modules([M|Ms], State, DocPlt,
NamedTables),
State1 = st__renew_state_calls(NewCallgraph, State),
get_warnings_from_modules(Ms, State1, NewDocPlt, BehavioursChk,
- [Warnings1, Warnings2, Warnings3|Acc]);
+ [Warnings1, Warnings2, Warnings3|NewAcc]);
get_warnings_from_modules([], #st{plt = Plt}, DocPlt, _, Acc) ->
{lists:flatten(Acc), Plt, DocPlt}.
+postprocess_dataflow_warns(RawWarnings, State, WarnAcc) ->
+ postprocess_dataflow_warns(RawWarnings, State, WarnAcc, []).
+
+postprocess_dataflow_warns([], _State, WAcc, Acc) ->
+ {WAcc, lists:reverse(Acc)};
+postprocess_dataflow_warns([{?WARN_CONTRACT_RANGE, {File, CallL}, Msg}|Rest],
+ #st{codeserver = Codeserver} = State, WAcc, Acc) ->
+ {contract_range, [Contract, M, F, A, ArgStrings, CRet]} = Msg,
+ {ok, {{File, _ContrL} = FileLine, _C}} =
+ dialyzer_codeserver:lookup_mfa_contract({M,F,A}, Codeserver),
+ NewMsg =
+ {contract_range, [Contract, M, F, ArgStrings, CallL, CRet]},
+ W = {?WARN_CONTRACT_RANGE, FileLine, NewMsg},
+ Filter =
+ fun({?WARN_CONTRACT_TYPES, FL, _}) when FL =:= FileLine -> false;
+ (_) -> true
+ end,
+ postprocess_dataflow_warns(Rest, State, lists:filter(Filter, WAcc), [W|Acc]);
+postprocess_dataflow_warns([W|Rest], State, Wacc, Acc) ->
+ postprocess_dataflow_warns(Rest, State, Wacc, [W|Acc]).
+
refine_succ_typings(ModulePostorder, State) ->
?debug("Module postorder: ~p\n", [ModulePostorder]),
refine_succ_typings(ModulePostorder, State, []).
diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl
index 248fdf6835..12f8dec67e 100644
--- a/lib/dialyzer/src/dialyzer_utils.erl
+++ b/lib/dialyzer/src/dialyzer_utils.erl
@@ -2,7 +2,7 @@
%%-----------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -214,14 +214,13 @@ get_record_and_type_info([], _Module, Records, RecDict) ->
?debug(_NewRecDict),
Ok;
{error, Name, Error} ->
- {error, lists:flatten(io_lib:format(" Error while parsing #~w{}: ~s\n",
- [Name, Error]))}
+ {error, flat_format(" Error while parsing #~w{}: ~s\n", [Name, Error])}
end.
add_new_type(TypeOrOpaque, Name, TypeForm, ArgForms, Module, RecDict) ->
case erl_types:type_is_defined(TypeOrOpaque, Name, RecDict) of
true ->
- throw({error, io_lib:format("Type already defined: ~w\n", [Name])});
+ throw({error, flat_format("Type ~s already defined\n", [Name])});
false ->
ArgTypes = [erl_types:t_from_form(X) || X <- ArgForms],
case lists:all(fun erl_types:t_is_var/1, ArgTypes) of
@@ -229,8 +228,8 @@ add_new_type(TypeOrOpaque, Name, TypeForm, ArgForms, Module, RecDict) ->
ArgNames = [erl_types:t_var_name(X) || X <- ArgTypes],
dict:store({TypeOrOpaque, Name}, {Module, TypeForm, ArgNames}, RecDict);
false ->
- throw({error, io_lib:format("Type declaration for ~w does not "
- "have variables as parameters", [Name])})
+ throw({error, flat_format("Type declaration for ~w does not "
+ "have variables as parameters", [Name])})
end
end.
@@ -338,14 +337,14 @@ get_spec_info([{attribute, Ln, spec, {Id, TypeSpec}}|Left],
get_spec_info(Left, NewSpecDict, RecordsDict, ModName, File);
{ok, {{OtherFile, L},_C}} ->
{Mod, Fun, Arity} = MFA,
- Msg = io_lib:format(" Contract for function ~w:~w/~w "
- "already defined in ~s:~w\n",
- [Mod, Fun, Arity, OtherFile, L]),
+ Msg = flat_format(" Contract for function ~w:~w/~w "
+ "already defined in ~s:~w\n",
+ [Mod, Fun, Arity, OtherFile, L]),
throw({error, Msg})
catch
throw:{error, Error} ->
- {error, lists:flatten(io_lib:format(" Error while parsing contract "
- "in line ~w: ~s\n", [Ln, Error]))}
+ {error, flat_format(" Error while parsing contract in line ~w: ~s\n",
+ [Ln, Error])}
end;
get_spec_info([{attribute, _, file, {IncludeFile, _}}|Left],
SpecDict, RecordsDict, ModName, _File) ->
@@ -419,6 +418,9 @@ format_sig(Type, RecDict) ->
")" ++ RevSig = lists:reverse(Sig),
lists:reverse(RevSig).
+flat_format(Fmt, Lst) ->
+ lists:flatten(io_lib:format(Fmt, Lst)).
+
%%-------------------------------------------------------------------
%% Author : Per Gustafsson <[email protected]>
%% Description : Provides better printing of binaries.