diff options
Diffstat (limited to 'lib/dialyzer/src')
-rw-r--r-- | lib/dialyzer/src/Makefile | 2 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer.app.src | 5 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer.erl | 16 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer.hrl | 15 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_analysis_callgraph.erl | 10 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_cl.erl | 48 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_cl_parse.erl | 13 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_contracts.erl | 87 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_dataflow.erl | 51 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_dep.erl | 10 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_gui_wx.erl | 33 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_options.erl | 7 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_races.erl | 28 |
13 files changed, 216 insertions, 109 deletions
diff --git a/lib/dialyzer/src/Makefile b/lib/dialyzer/src/Makefile index d7265ba31a..91fbdca5bd 100644 --- a/lib/dialyzer/src/Makefile +++ b/lib/dialyzer/src/Makefile @@ -88,7 +88,7 @@ APPUP_TARGET= $(EBIN)/$(APPUP_FILE) ifeq ($(NATIVE_LIBS_ENABLED),yes) ERL_COMPILE_FLAGS += +native endif -ERL_COMPILE_FLAGS += +warn_exported_vars +warn_unused_import +warn_untyped_record +warn_missing_spec +warnings_as_errors +ERL_COMPILE_FLAGS += +warn_export_vars +warn_unused_import +warn_untyped_record +warn_missing_spec +warnings_as_errors # ---------------------------------------------------- # Targets diff --git a/lib/dialyzer/src/dialyzer.app.src b/lib/dialyzer/src/dialyzer.app.src index 0d048b607e..1756800c4f 100644 --- a/lib/dialyzer/src/dialyzer.app.src +++ b/lib/dialyzer/src/dialyzer.app.src @@ -44,4 +44,7 @@ dialyzer_worker]}, {registered, []}, {applications, [compiler, gs, hipe, kernel, stdlib, wx]}, - {env, []}]}. + {env, []}, + {runtime_dependencies, ["wx-1.2","syntax_tools-1.6.14","stdlib-2.0", + "kernel-3.0","hipe-3.10.3","erts-6.0", + "compiler-5.0"]}]}. diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl index bb7e39dfda..cec94a49fd 100644 --- a/lib/dialyzer/src/dialyzer.erl +++ b/lib/dialyzer/src/dialyzer.erl @@ -2,7 +2,7 @@ %%----------------------------------------------------------------------- %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2013. All Rights Reserved. +%% Copyright Ericsson AB 2006-2014. 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 @@ -172,7 +172,7 @@ run(Opts) -> end, case dialyzer_cl:start(OptsRecord) of {?RET_DISCREPANCIES, Warnings} -> Warnings; - {?RET_NOTHING_SUSPICIOUS, []} -> [] + {?RET_NOTHING_SUSPICIOUS, _} -> [] end catch throw:{dialyzer_error, ErrorMsg} -> @@ -447,7 +447,6 @@ message_to_string({opaque_size, [SizeType, Size]}) -> message_to_string({opaque_call, [M, F, Args, Culprit, OpaqueType]}) -> io_lib:format("The call ~s:~s~s breaks the opaqueness of the term ~s :: ~s\n", [M, F, Args, Culprit, OpaqueType]); - %%----- Warnings for concurrency errors -------------------- message_to_string({race_condition, [M, F, Args, Reason]}) -> io_lib:format("The call ~w:~w~s ~s\n", [M, F, Args, Reason]); @@ -474,7 +473,14 @@ message_to_string({callback_missing, [B, F, A]}) -> io_lib:format("Undefined callback function ~w/~w (behaviour '~w')\n", [F, A, B]); message_to_string({callback_info_missing, [B]}) -> - io_lib:format("Callback info about the ~w behaviour is not available\n", [B]). + io_lib:format("Callback info about the ~w behaviour is not available\n", [B]); +%%----- Warnings for unknown functions, types, and behaviours ------------- +message_to_string({unknown_type, {M, F, A}}) -> + io_lib:format("Unknown type ~w:~w/~w", [M, F, A]); +message_to_string({unknown_function, {M, F, A}}) -> + io_lib:format("Unknown function ~w:~w/~w", [M, F, A]); +message_to_string({unknown_behaviour, B}) -> + io_lib:format("Unknown behaviour ~w", [B]). %%----------------------------------------------------------------------------- %% Auxiliary functions below @@ -557,4 +563,4 @@ form_position_string(ArgNs) -> ordinal(1) -> "1st"; ordinal(2) -> "2nd"; ordinal(3) -> "3rd"; -ordinal(N) when is_integer(N) -> io_lib:format("~wth",[N]). +ordinal(N) when is_integer(N) -> io_lib:format("~wth", [N]). diff --git a/lib/dialyzer/src/dialyzer.hrl b/lib/dialyzer/src/dialyzer.hrl index 105a174e31..9a25f86512 100644 --- a/lib/dialyzer/src/dialyzer.hrl +++ b/lib/dialyzer/src/dialyzer.hrl @@ -2,7 +2,7 @@ %%% %%% %CopyrightBegin% %%% -%%% Copyright Ericsson AB 2006-2012. All Rights Reserved. +%%% Copyright Ericsson AB 2006-2014. 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 @@ -58,6 +58,7 @@ -define(WARN_RACE_CONDITION, warn_race_condition). -define(WARN_BEHAVIOUR, warn_behaviour). -define(WARN_UNDEFINED_CALLBACK, warn_undefined_callbacks). +-define(WARN_UNKNOWN, warn_unknown). %% %% The following type has double role: @@ -73,7 +74,7 @@ | ?WARN_CONTRACT_SUPERTYPE | ?WARN_CALLGRAPH | ?WARN_UNMATCHED_RETURN | ?WARN_RACE_CONDITION | ?WARN_BEHAVIOUR | ?WARN_CONTRACT_RANGE - | ?WARN_UNDEFINED_CALLBACK. + | ?WARN_UNDEFINED_CALLBACK | ?WARN_UNKNOWN. %% %% This is the representation of each warning as they will be returned @@ -88,12 +89,6 @@ -type dial_error() :: any(). %% XXX: underspecified %%-------------------------------------------------------------------- -%% THIS TYPE SHOULD ONE DAY DISAPPEAR -- IT DOES NOT BELONG HERE -%%-------------------------------------------------------------------- - --type ordset(T) :: [T] . %% XXX: temporarily - -%%-------------------------------------------------------------------- %% Basic types used either in the record definitions below or in other %% parts of the application %%-------------------------------------------------------------------- @@ -143,7 +138,7 @@ init_plts = [] :: [file:filename()], include_dirs = [] :: [file:filename()], output_plt = none :: 'none' | file:filename(), - legal_warnings = ordsets:new() :: ordset(dial_warn_tag()), + legal_warnings = ordsets:new() :: ordsets:ordset(dial_warn_tag()), report_mode = normal :: rep_mode(), erlang_mode = false :: boolean(), use_contracts = true :: boolean(), @@ -167,4 +162,4 @@ dialyzer_timing:end_stamp(Server), Var end). --define(timing(Server, Msg, Expr),?timing(Server, Msg, _T, Expr)). +-define(timing(Server, Msg, Expr), ?timing(Server, Msg, _T, Expr)). diff --git a/lib/dialyzer/src/dialyzer_analysis_callgraph.erl b/lib/dialyzer/src/dialyzer_analysis_callgraph.erl index 2a633c5e37..6a33a2acb3 100644 --- a/lib/dialyzer/src/dialyzer_analysis_callgraph.erl +++ b/lib/dialyzer/src/dialyzer_analysis_callgraph.erl @@ -249,7 +249,7 @@ compile_and_store(Files, #analysis_state{codeserver = CServer, timing_server = Timing, parent = Parent} = State) -> send_log(Parent, "Reading files and computing callgraph... "), - {T1, _} = statistics(runtime), + {T1, _} = statistics(wall_clock), Callgraph = dialyzer_callgraph:new(), CompileInit = make_compile_init(State, Callgraph), {{Failed, NoWarn, Modules}, NextLabel} = @@ -272,13 +272,13 @@ compile_and_store(Files, #analysis_state{codeserver = CServer, [[Reason || {_Filename, Reason} <- Failed]]), exit({error, Msg}) end, - {T2, _} = statistics(runtime), + {T2, _} = statistics(wall_clock), Msg1 = io_lib:format("done in ~.2f secs\nRemoving edges... ", [(T2-T1)/1000]), send_log(Parent, Msg1), Callgraph = ?timing(Timing, "clean", _C2, cleanup_callgraph(State, CServer2, Callgraph, Modules)), - {T3, _} = statistics(runtime), + {T3, _} = statistics(wall_clock), Msg2 = io_lib:format("done in ~.2f secs\n", [(T3-T2)/1000]), send_log(Parent, Msg2), {Callgraph, sets:from_list(NoWarn), CServer2}. @@ -620,9 +620,9 @@ dump_callgraph(CallGraph, State, #analysis{callgraph_file = File} = Analysis) -> Extension = filename:extension(File), Start_Msg = io_lib:format("Dumping the callgraph... ", []), send_log(State#analysis_state.parent, Start_Msg), - {T1, _} = statistics(runtime), + {T1, _} = statistics(wall_clock), dump_callgraph(CallGraph, State, Analysis, Extension), - {T2, _} = statistics(runtime), + {T2, _} = statistics(wall_clock), Finish_Msg = io_lib:format("done in ~2f secs\n", [(T2-T1)/1000]), send_log(State#analysis_state.parent, Finish_Msg), ok. diff --git a/lib/dialyzer/src/dialyzer_cl.erl b/lib/dialyzer/src/dialyzer_cl.erl index 3e68d64d53..3e7d9dfa99 100644 --- a/lib/dialyzer/src/dialyzer_cl.erl +++ b/lib/dialyzer/src/dialyzer_cl.erl @@ -504,7 +504,7 @@ hipe_compile(Files, #options{erlang_mode = ErlangMode} = Options) -> _ -> Mods = [lists, dict, digraph, digraph_utils, ets, gb_sets, gb_trees, ordsets, sets, sofs, - cerl, cerl_trees, erl_types, erl_bif_types, + cerl, erl_types, cerl_trees, erl_bif_types, dialyzer_analysis_callgraph, dialyzer, dialyzer_behaviours, dialyzer_codeserver, dialyzer_contracts, dialyzer_coordinator, dialyzer_dataflow, dialyzer_dep, @@ -533,7 +533,7 @@ hc(Mod) -> case code:is_module_native(Mod) of true -> ok; false -> - %% io:format(" ~s", [Mod]), + %% io:format(" ~w", [Mod]), {ok, Mod} = hipe:c(Mod), ok end. @@ -656,7 +656,8 @@ return_value(State = #cl_state{erlang_mode = ErlangMode, mod_deps = ModDeps, output_plt = OutputPlt, plt_info = PltInfo, - stored_warnings = StoredWarnings}, + stored_warnings = StoredWarnings, + legal_warnings = LegalWarnings}, Plt) -> case OutputPlt =:= none of true -> ok; @@ -676,16 +677,33 @@ return_value(State = #cl_state{erlang_mode = ErlangMode, maybe_close_output_file(State), {RetValue, []}; true -> - {RetValue, process_warnings(StoredWarnings)} + Unknown = + case ordsets:is_element(?WARN_UNKNOWN, LegalWarnings) of + true -> + unknown_functions(State) ++ + unknown_types(State) ++ + unknown_behaviours(State); + false -> [] + end, + UnknownWarnings = + [{?WARN_UNKNOWN, {_Filename = "", _Line = 0}, W} || W <- Unknown], + AllWarnings = + UnknownWarnings ++ process_warnings(StoredWarnings), + {RetValue, AllWarnings} end. +unknown_functions(#cl_state{external_calls = Calls}) -> + [{unknown_function, MFA} || MFA <- Calls]. + print_ext_calls(#cl_state{report_mode = quiet}) -> ok; print_ext_calls(#cl_state{output = Output, external_calls = Calls, stored_warnings = Warnings, - output_format = Format}) -> - case Calls =:= [] of + output_format = Format, + legal_warnings = LegalWarnings}) -> + case not ordsets:is_element(?WARN_UNKNOWN, LegalWarnings) + orelse Calls =:= [] of true -> ok; false -> case Warnings =:= [] of @@ -708,14 +726,19 @@ do_print_ext_calls(Output, [{M,F,A}|T], Before) -> do_print_ext_calls(_, [], _) -> ok. +unknown_types(#cl_state{external_types = Types}) -> + [{unknown_type, MFA} || MFA <- Types]. + print_ext_types(#cl_state{report_mode = quiet}) -> ok; print_ext_types(#cl_state{output = Output, external_calls = Calls, external_types = Types, stored_warnings = Warnings, - output_format = Format}) -> - case Types =:= [] of + output_format = Format, + legal_warnings = LegalWarnings}) -> + case not ordsets:is_element(?WARN_UNKNOWN, LegalWarnings) + orelse Types =:= [] of true -> ok; false -> case Warnings =:= [] andalso Calls =:= [] of @@ -738,6 +761,15 @@ do_print_ext_types(Output, [{M,F,A}|T], Before) -> do_print_ext_types(_, [], _) -> ok. +unknown_behaviours(#cl_state{unknown_behaviours = DupBehaviours, + legal_warnings = LegalWarnings}) -> + case ordsets:is_element(?WARN_BEHAVIOUR, LegalWarnings) of + false -> []; + true -> + Behaviours = lists:usort(DupBehaviours), + [{unknown_behaviour, B} || B <- Behaviours] + end. + %%print_unknown_behaviours(#cl_state{report_mode = quiet}) -> %% ok; print_unknown_behaviours(#cl_state{output = Output, diff --git a/lib/dialyzer/src/dialyzer_cl_parse.erl b/lib/dialyzer/src/dialyzer_cl_parse.erl index db27b2037d..04ce0e8bc3 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-2013. All Rights Reserved. +%% Copyright Ericsson AB 2006-2014. 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 @@ -357,12 +357,13 @@ help_warnings() -> help_message() -> S = "Usage: dialyzer [--help] [--version] [--shell] [--quiet] [--verbose] [-pa dir]* [--plt plt] [--plts plt*] [-Ddefine]* - [-I include_dir]* [--output_plt file] [-Wwarn]* + [-I include_dir]* [--output_plt file] [-Wwarn]* [--raw] [--src] [--gui] [files_or_dirs] [-r dirs] [--apps applications] [-o outfile] [--build_plt] [--add_to_plt] [--remove_from_plt] [--check_plt] [--no_check_plt] [--plt_info] [--get_warnings] - [--no_native] [--fullpath] [--statistics] + [--dump_callgraph file] [--no_native] [--fullpath] + [--statistics] Options: files_or_dirs (for backwards compatibility also as: -c files_or_dirs) Use Dialyzer from the command line to detect defects in the @@ -495,14 +496,16 @@ warning_options_msg() -> Suppress warnings for unused functions. -Wno_improper_lists Suppress warnings for construction of improper lists. - -Wno_tuple_as_fun - Suppress warnings for using tuples instead of funs. -Wno_fun_app Suppress warnings for fun applications that will fail. -Wno_match Suppress warnings for patterns that are unused or cannot match. -Wno_opaque Suppress warnings for violations of opaqueness of data types. + -Wno_fail_call + Suppress warnings for failing calls. + -Wno_contracts + Suppress warnings about invalid contracts. -Wno_behaviours Suppress warnings about behaviour callbacks which drift from the published recommended interfaces. diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl index 46eaeaa303..1d2dfc7b2d 100644 --- a/lib/dialyzer/src/dialyzer_contracts.erl +++ b/lib/dialyzer/src/dialyzer_contracts.erl @@ -20,6 +20,8 @@ -module(dialyzer_contracts). +-compile(export_all). + -export([check_contract/2, check_contracts/4, contracts_without_fun/3, @@ -439,7 +441,8 @@ contract_from_form([], _RecDict, _FileLine, TypeAcc, FormAcc) -> {lists:reverse(TypeAcc), lists:reverse(FormAcc)}. process_constraints(Constrs, RecDict, ExpTypes, AllRecords) -> - Init = initialize_constraints(Constrs, RecDict, ExpTypes, AllRecords), + Init0 = initialize_constraints(Constrs, RecDict, ExpTypes, AllRecords), + Init = remove_cycles(Init0), constraints_fixpoint(Init, RecDict, ExpTypes, AllRecords). initialize_constraints(Constrs, RecDict, ExpTypes, AllRecords) -> @@ -479,12 +482,9 @@ constraints_fixpoint(OldVarDict, Constrs, RecDict, ExpTypes, AllRecords) -> constraints_fixpoint(NewVarDict, Constrs, RecDict, ExpTypes, AllRecords) end. --define(TYPE_LIMIT, 4). - final_form(Form, RecDict, ExpTypes, AllRecords, VarDict) -> T1 = erl_types:t_from_form(Form, RecDict, VarDict), - T2 = erl_types:t_solve_remote(T1, ExpTypes, AllRecords), - erl_types:t_limit(T2, ?TYPE_LIMIT). + erl_types:t_solve_remote(T1, ExpTypes, AllRecords). constraints_to_dict(Constrs, RecDict, ExpTypes, AllRecords, VarDict) -> Subtypes = @@ -499,6 +499,74 @@ constraints_to_subs([C|Rest], RecDict, ExpTypes, AllRecords, VarDict, Acc) -> NewAcc = [{subtype, T1, T2}|Acc], constraints_to_subs(Rest, RecDict, ExpTypes, AllRecords, VarDict, NewAcc). +%% Replaces variables with '_' when necessary to break up cycles among +%% the constraints. + +remove_cycles(Constrs0) -> + Uses = find_uses(Constrs0), + G = digraph:new(), + Vs0 = [V || {V, _} <- Uses] ++ [V || {_, V} <- Uses], + Vs = lists:usort(Vs0), + lists:foreach(fun(V) -> _ = digraph:add_vertex(G, V) end, Vs), + lists:foreach(fun({From, To}) -> + _ = digraph:add_edge(G, {From, To}, From, To, []) + end, Uses), + ok = remove_cycles(G, Vs), + ToRemove = ordsets:subtract(ordsets:from_list(Uses), + ordsets:from_list(digraph:edges(G))), + Constrs = remove_uses(ToRemove, Constrs0), + digraph:delete(G), + Constrs. + +find_uses([{Var, Form}|Constrs]) -> + UsedVars = form_vars(Form, []), + VarName = erl_types:t_var_name(Var), + [{VarName, UsedVar} || UsedVar <- UsedVars] ++ find_uses(Constrs); +find_uses([]) -> + []. + +form_vars({var, _, '_'}, Vs) -> Vs; +form_vars({var, _, V}, Vs) -> [V|Vs]; +form_vars(T, Vs) when is_tuple(T) -> + form_vars(tuple_to_list(T), Vs); +form_vars([E|Es], Vs) -> + form_vars(Es, form_vars(E, Vs)); +form_vars(_, Vs) -> Vs. + +remove_cycles(G, Vs) -> + NumberOfEdges = digraph:no_edges(G), + lists:foreach(fun(V) -> + case digraph:get_cycle(G, V) of + false -> true; + [V] -> digraph:del_edge(G, {V, V}); + [V, V1|_] -> digraph:del_edge(G, {V, V1}) + end + end, Vs), + case digraph:no_edges(G) =:= NumberOfEdges of + true -> ok; + false -> remove_cycles(G, Vs) + end. + +remove_uses([], Constrs) -> Constrs; +remove_uses([{Var, Use}|ToRemove], Constrs0) -> + Constrs = remove_uses(Var, Use, Constrs0), + remove_uses(ToRemove, Constrs). + +remove_uses(_Var, _Use, []) -> []; +remove_uses(Var, Use, [Constr|Constrs]) -> + {V, Form} = Constr, + case erl_types:t_var_name(V) =:= Var of + true -> [{V, remove_use(Form, Use)}|Constrs]; + false -> [Constr|remove_uses(Var, Use, Constrs)] + end. + +remove_use({var, L, V}, V) -> {var, L, '_'}; +remove_use(T, V) when is_tuple(T) -> + list_to_tuple(remove_use(tuple_to_list(T), V)); +remove_use([E|Es], V) -> + [remove_use(E, V)|remove_use(Es, V)]; +remove_use(T, _V) -> T. + %% Gets the most general domain of a list of domains of all %% the overloaded contracts @@ -684,14 +752,7 @@ is_remote_types_related(Contract, CSig, Sig, RecDict) -> t_from_forms_without_remote([{FType, []}], RecDict) -> Type0 = erl_types:t_from_form(FType, RecDict), - Map = - fun(Type) -> - case erl_types:t_is_remote(Type) of - true -> erl_types:t_none(); - false -> Type - end - end, - {ok, erl_types:t_map(Map, Type0)}; + {ok, erl_types:subst_all_remote(Type0, erl_types:t_none())}; t_from_forms_without_remote([{_FType, _Constrs}], _RecDict) -> %% 'When' constraints unsupported; diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl index 692684cd99..e0873b17f8 100644 --- a/lib/dialyzer/src/dialyzer_dataflow.erl +++ b/lib/dialyzer/src/dialyzer_dataflow.erl @@ -363,20 +363,24 @@ traverse_list([], Map, State, Acc) -> handle_apply(Tree, Map, State) -> Args = cerl:apply_args(Tree), Op = cerl:apply_op(Tree), - {State1, Map1, ArgTypes} = traverse_list(Args, Map, State), - {State2, Map2, OpType} = traverse(Op, Map1, State1), + {State0, Map1, ArgTypes} = traverse_list(Args, Map, State), + {State1, Map2, OpType} = traverse(Op, Map1, State0), case any_none(ArgTypes) of true -> - {State2, Map2, t_none()}; + {State1, Map2, t_none()}; false -> - {CallSitesKnown, FunList} = - case state__lookup_call_site(Tree, State2) of - error -> {false, []}; - {ok, [external]} -> {false, []}; - {ok, List} -> {true, List} + FunList = + case state__lookup_call_site(Tree, State) of + error -> [external]; %% so that we go directly in the fallback + {ok, List} -> List end, - case CallSitesKnown of - false -> + FunInfoList = [{local, state__fun_info(Fun, State)} || Fun <- FunList], + case + handle_apply_or_call(FunInfoList, Args, ArgTypes, Map2, Tree, State1) + of + {had_external, State2} -> + %% Fallback: use whatever info we collected from traversing the op + %% instead of the result that has been generalized to t_any(). Arity = length(Args), OpType1 = t_inf(OpType, t_fun(Arity, t_any())), case t_is_none(OpType1) of @@ -408,25 +412,23 @@ handle_apply(Tree, Map, State) -> {State2, enter_type(Op, OpType1, Map3), Range} end end; - true -> - FunInfoList = [{local, state__fun_info(Fun, State)} - || Fun <- FunList], - handle_apply_or_call(FunInfoList, Args, ArgTypes, Map2, Tree, State1) + Normal -> Normal end end. handle_apply_or_call(FunInfoList, Args, ArgTypes, Map, Tree, State) -> None = t_none(), handle_apply_or_call(FunInfoList, Args, ArgTypes, Map, Tree, State, - [None || _ <- ArgTypes], None). + [None || _ <- ArgTypes], None, false). handle_apply_or_call([{local, external}|Left], Args, ArgTypes, Map, Tree, State, - _AccArgTypes, _AccRet) -> + _AccArgTypes, _AccRet, _HadExternal) -> handle_apply_or_call(Left, Args, ArgTypes, Map, Tree, State, - ArgTypes, t_any()); + ArgTypes, t_any(), true); handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left], Args, ArgTypes, Map, Tree, - #state{opaques = Opaques} = State, AccArgTypes, AccRet) -> + #state{opaques = Opaques} = State, + AccArgTypes, AccRet, HadExternal) -> Any = t_any(), AnyArgs = [Any || _ <- Args], GenSig = {AnyArgs, fun(_) -> t_any() end}, @@ -573,11 +575,16 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left], NewAccRet = t_sup(AccRet, TotalRet), ?debug("NewAccRet: ~s\n", [t_to_string(NewAccRet)]), handle_apply_or_call(Left, Args, ArgTypes, Map, Tree, - State3, NewAccArgTypes, NewAccRet); + State3, NewAccArgTypes, NewAccRet, HadExternal); handle_apply_or_call([], Args, _ArgTypes, Map, _Tree, State, - AccArgTypes, AccRet) -> - NewMap = enter_type_lists(Args, AccArgTypes, Map), - {State, NewMap, AccRet}. + AccArgTypes, AccRet, HadExternal) -> + case HadExternal of + false -> + NewMap = enter_type_lists(Args, AccArgTypes, Map), + {State, NewMap, AccRet}; + true -> + {had_external, State} + end. apply_fail_reason(FailedSig, FailedBif, FailedContract) -> if diff --git a/lib/dialyzer/src/dialyzer_dep.erl b/lib/dialyzer/src/dialyzer_dep.erl index f1ac41ff04..572e60278d 100644 --- a/lib/dialyzer/src/dialyzer_dep.erl +++ b/lib/dialyzer/src/dialyzer_dep.erl @@ -55,11 +55,11 @@ %% %% Letrecs = a dict mapping var labels to their recursive definition. %% top-level letrecs are not included as they are handled -%% separatedly. +%% separately. %% -spec analyze(cerl:c_module()) -> - {dict:dict(), ordset('external' | label()), dict:dict(), dict:dict()}. + {dict:dict(), ordsets:ordset('external' | label()), dict:dict(), dict:dict()}. analyze(Tree) -> %% io:format("Handling ~w\n", [cerl:atom_val(cerl:module_name(Tree))]), @@ -124,8 +124,10 @@ traverse(Tree, Out, State, CurrentFun) -> TmpState = state__add_deps(Label, O1, State), state__add_deps(CurrentFun, O2,TmpState) end, - {BodyFuns, State2} = traverse(Body, Out, State1, - cerl_trees:get_label(Tree)), + Vars = cerl:fun_vars(Tree), + Out1 = bind_single(Vars, output(set__singleton(external)), Out), + {BodyFuns, State2} = + traverse(Body, Out1, State1, cerl_trees:get_label(Tree)), {output(set__singleton(Label)), state__add_esc(BodyFuns, State2)}; 'let' -> Vars = cerl:let_vars(Tree), diff --git a/lib/dialyzer/src/dialyzer_gui_wx.erl b/lib/dialyzer/src/dialyzer_gui_wx.erl index 08f31c1e13..868857d675 100644 --- a/lib/dialyzer/src/dialyzer_gui_wx.erl +++ b/lib/dialyzer/src/dialyzer_gui_wx.erl @@ -61,7 +61,7 @@ init_plt :: dialyzer_plt:plt(), dir_entry :: wx:wx_object(), file_box :: wx:wx_object(), - files_to_analyze :: ordset(string()), + files_to_analyze :: ordsets:ordset(string()), gui :: wx:wx_object(), log :: wx:wx_object(), menu :: menu(), @@ -699,8 +699,7 @@ handle_add_files(#gui_state{chosen_box = ChosenBox, file_box = FileBox, end. handle_add_dir(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox, - files_to_analyze = FileList, - mode = Mode} = State) -> + files_to_analyze = FileList, mode = Mode} = State) -> case wxDirPickerCtrl:getPath(DirBox) of "" -> State; @@ -714,8 +713,8 @@ handle_add_dir(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox, State#gui_state{files_to_analyze = add_files(filter_mods(NewDir1,Ext), FileList, ChosenBox, Ext)} end. -handle_add_rec(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox, files_to_analyze = FileList, - mode = Mode} = State) -> +handle_add_rec(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox, + files_to_analyze = FileList, mode = Mode} = State) -> case wxDirPickerCtrl:getPath(DirBox) of "" -> State; @@ -723,11 +722,11 @@ handle_add_rec(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox, files_to_a NewDir = ordsets:new(), NewDir1 = ordsets:add_element(Dir,NewDir), TargetDirs = ordsets:union(NewDir1, all_subdirs(NewDir1)), - case wxRadioBox:getSelection(Mode) of - 0 -> Ext = ".beam"; - 1-> Ext = ".erl" - end, - State#gui_state{files_to_analyze = add_files(filter_mods(TargetDirs,Ext), FileList, ChosenBox, Ext)} + Ext = case wxRadioBox:getSelection(Mode) of + 0 -> ".beam"; + 1 -> ".erl" + end, + State#gui_state{files_to_analyze = add_files(filter_mods(TargetDirs, Ext), FileList, ChosenBox, Ext)} end. handle_file_delete(#gui_state{chosen_box = ChosenBox, @@ -886,13 +885,10 @@ config_gui_start(State) -> wxRadioBox:disable(State#gui_state.mode). save_file(#gui_state{frame = Frame, warnings_box = WBox, log = Log} = State, Type) -> - case Type of - warnings -> - Message = "Save Warnings", - Box = WBox; - log -> Message = "Save Log", - Box = Log - end, + {Message, Box} = case Type of + warnings -> {"Save Warnings", WBox}; + log -> {"Save Log", Log} + end, case wxTextCtrl:getValue(Box) of "" -> error_sms(State,"There is nothing to save...\n"); _ -> @@ -936,8 +932,7 @@ include_dialog(#gui_state{gui = Wx, frame = Frame, options = Options}) -> wxButton:connect(DeleteAllButton, command_button_clicked), wxButton:connect(Ok, command_button_clicked), wxButton:connect(Cancel, command_button_clicked), - Dirs = [io_lib:format("~s", [X]) - || X <- Options#options.include_dirs], + Dirs = [io_lib:format("~s", [X]) || X <- Options#options.include_dirs], wxListBox:set(Box, Dirs), Layout = wxBoxSizer:new(?wxVERTICAL), Buttons = wxBoxSizer:new(?wxHORIZONTAL), diff --git a/lib/dialyzer/src/dialyzer_options.erl b/lib/dialyzer/src/dialyzer_options.erl index 06672e595f..a92b8b1958 100644 --- a/lib/dialyzer/src/dialyzer_options.erl +++ b/lib/dialyzer/src/dialyzer_options.erl @@ -2,7 +2,7 @@ %%----------------------------------------------------------------------- %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2012. All Rights Reserved. +%% Copyright Ericsson AB 2006-2014. 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 @@ -51,7 +51,8 @@ build(Opts) -> ?WARN_CONTRACT_TYPES, ?WARN_CONTRACT_SYNTAX, ?WARN_BEHAVIOUR, - ?WARN_UNDEFINED_CALLBACK], + ?WARN_UNDEFINED_CALLBACK, + ?WARN_UNKNOWN], DefaultWarns1 = ordsets:from_list(DefaultWarns), InitPlt = dialyzer_plt:get_default_plt(), DefaultOpts = #options{}, @@ -310,6 +311,8 @@ build_warnings([Opt|Opts], Warnings) -> ordsets:add_element(?WARN_CONTRACT_SUBTYPE, Warnings); underspecs -> ordsets:add_element(?WARN_CONTRACT_SUPERTYPE, Warnings); + no_unknown -> + ordsets:del_element(?WARN_UNKNOWN, Warnings); OtherAtom -> bad_option("Unknown dialyzer warning option", OtherAtom) end, diff --git a/lib/dialyzer/src/dialyzer_races.erl b/lib/dialyzer/src/dialyzer_races.erl index 48fcde8014..28c2ad2c0b 100644 --- a/lib/dialyzer/src/dialyzer_races.erl +++ b/lib/dialyzer/src/dialyzer_races.erl @@ -85,6 +85,12 @@ -type race_tag() :: 'whereis_register' | 'whereis_unregister' | 'ets_lookup_insert' | 'mnesia_dirty_read_write'. +%% The following type is similar to the dial_warning() type but has a +%% tag which is local to this module and is not propagated to outside +-type dial_race_warning() :: {race_warn_tag(), file_line(), {atom(), [term()]}}. +-type race_warn_tag() :: ?WARN_WHEREIS_REGISTER | ?WARN_WHEREIS_UNREGISTER + | ?WARN_ETS_LOOKUP_INSERT | ?WARN_MNESIA_DIRTY_READ_WRITE. + -record(beg_clause, {arg :: var_to_map1(), pats :: var_to_map1(), guard :: cerl:cerl()}). @@ -103,7 +109,7 @@ args :: args(), arg_types :: [erl_types:erl_type()], vars :: [core_vars()], - state :: _, %% XXX: recursive + state :: dialyzer_dataflow:state(), file_line :: file_line(), var_map :: dict:dict()}). -record(fun_call, {caller :: dialyzer_callgraph:mfa_or_funlbl(), @@ -141,7 +147,7 @@ race_tags = [] :: [#race_fun{}], %% true for fun types and warning mode race_analysis = false :: boolean(), - race_warnings = [] :: [dial_warning()]}). + race_warnings = [] :: [dial_race_warning()]}). %%% =========================================================================== %%% @@ -984,8 +990,7 @@ fixup_race_forward_helper(CurrFun, CurrFunLabel, Fun, FunLabel, NewRaceVarMap, Args, NewFunArgs, NewFunTypes, NestingLevel}; {CurrFun, Fun} -> NewCallsToAnalyze = lists:delete(Head, CallsToAnalyze), - NewRaceVarMap = - race_var_map(Args, NewFunArgs, RaceVarMap, bind), + NewRaceVarMap = race_var_map(Args, NewFunArgs, RaceVarMap, bind), RetC = case Fun of InitFun -> @@ -1012,8 +1017,7 @@ fixup_race_forward_helper(CurrFun, CurrFunLabel, Fun, FunLabel, label = FunLabel, var_map = NewRaceVarMap, def_vars = Args, call_vars = NewFunArgs, arg_types = NewFunTypes}| - lists:reverse(StateRaceList)] ++ - RetC; + lists:reverse(StateRaceList)] ++ RetC; _ -> [#curr_fun{status = in, mfa = Fun, label = FunLabel, var_map = NewRaceVarMap, @@ -1048,13 +1052,9 @@ fixup_race_backward(CurrFun, Calls, CallsToAnalyze, Parents, Height) -> false -> [CurrFun|Parents] end; [Head|Tail] -> - MorePaths = - case Head of - {Parent, CurrFun} -> true; - {Parent, _TupleB} -> false - end, - case MorePaths of - true -> + {Parent, TupleB} = Head, + case TupleB =:= CurrFun of + true -> % more paths are needed NewCallsToAnalyze = lists:delete(Head, CallsToAnalyze), NewParents = fixup_race_backward(Parent, NewCallsToAnalyze, @@ -1763,7 +1763,7 @@ ets_list_args(MaybeList) -> catch _:_ -> [?no_label] end; false -> [ets_tuple_args(MaybeList)] - end. + end. ets_list_argtypes(ListStr) -> ListStr1 = string:strip(ListStr, left, $[), |