File 3481-dialyzer-Track-type-behaviour-dependencies.patch of Package erlang

From cdfd163ea704410320b3c113780900e9bb59dbe9 Mon Sep 17 00:00:00 2001
From: Tom Davies <TD5@users.noreply.github.com>
Date: Wed, 8 Dec 2021 07:48:06 -0800
Subject: [PATCH] dialyzer: Track type & behaviour dependencies

Dialyzer now tracks the dependencies between modules induced by
type-level information, such as type definitions & specs, as well
as behaviour callbacks.

Previously, only function calls were considered when computing dependencies.
This was incomplete because changes to types and behaviours can also affect
the result of a Dialyzer analysis.
---
 lib/dialyzer/src/Makefile                     |   2 +
 lib/dialyzer/src/dialyzer.app.src             |   1 +
 lib/dialyzer/src/dialyzer.hrl                 |   1 +
 .../src/dialyzer_analysis_callgraph.erl       |  19 +-
 lib/dialyzer/src/dialyzer_behaviours.erl      |   8 +-
 lib/dialyzer/src/dialyzer_callgraph.erl       |  56 ++-
 lib/dialyzer/src/dialyzer_cl.erl              |  10 +-
 lib/dialyzer/src/dialyzer_contracts.erl       |  13 +-
 lib/dialyzer/src/dialyzer_plt.erl             |  41 +-
 lib/dialyzer/src/dialyzer_typegraph.erl       | 109 +++++
 lib/dialyzer/src/erl_types.erl                | 137 +++++-
 lib/dialyzer/test/Makefile                    |   1 +
 lib/dialyzer/test/dialyzer_cl_SUITE.erl       | 129 +++++
 .../call_to_missing_example.erl               |   5 +
 .../previously_defined.erl                    |   5 +
 .../unknown_function_example.erl              |   5 +
 lib/dialyzer/test/dialyzer_common.erl         |  17 +-
 lib/dialyzer/test/plt_SUITE.erl               | 441 ++++++++++++++++--
 .../test/plt_SUITE_data/type_deps.erl         |  18 +
 19 files changed, 929 insertions(+), 89 deletions(-)
 create mode 100644 lib/dialyzer/src/dialyzer_typegraph.erl
 create mode 100644 lib/dialyzer/test/dialyzer_cl_SUITE.erl
 create mode 100644 lib/dialyzer/test/dialyzer_cl_SUITE_data/call_to_missing_example.erl
 create mode 100644 lib/dialyzer/test/dialyzer_cl_SUITE_data/previously_defined.erl
 create mode 100644 lib/dialyzer/test/dialyzer_cl_SUITE_data/unknown_function_example.erl
 create mode 100644 lib/dialyzer/test/plt_SUITE_data/type_deps.erl

diff --git a/lib/dialyzer/src/Makefile b/lib/dialyzer/src/Makefile
index 5f0edccfef..aac9ef899b 100644
--- a/lib/dialyzer/src/Makefile
+++ b/lib/dialyzer/src/Makefile
@@ -67,6 +67,7 @@ MODULES = \
 	dialyzer_succ_typings \
 	dialyzer_timing \
 	dialyzer_typesig \
+	dialyzer_typegraph \
 	dialyzer_coordinator \
 	dialyzer_worker \
 	dialyzer_utils \
@@ -150,6 +151,7 @@ $(EBIN)/dialyzer_race_data_server.beam: dialyzer.hrl
 $(EBIN)/dialyzer_races.beam: dialyzer.hrl
 $(EBIN)/dialyzer_succ_typings.beam: dialyzer.hrl
 $(EBIN)/dialyzer_typesig.beam: dialyzer.hrl
+$(EBIN)/dialyzer_typegraph.beam: dialyzer.hrl
 $(EBIN)/dialyzer_utils.beam: dialyzer.hrl
 
 # ----------------------------------------------------
diff --git a/lib/dialyzer/src/dialyzer.app.src b/lib/dialyzer/src/dialyzer.app.src
index 1514aaa42b..ef22d35bd2 100644
--- a/lib/dialyzer/src/dialyzer.app.src
+++ b/lib/dialyzer/src/dialyzer.app.src
@@ -27,6 +27,7 @@
 	     dialyzer_analysis_callgraph,
 	     dialyzer_behaviours,
 	     dialyzer_callgraph,
+	     dialyzer_typegraph,
 	     dialyzer_cl,
 	     dialyzer_cl_parse,
              dialyzer_clean_core,
diff --git a/lib/dialyzer/src/dialyzer.hrl b/lib/dialyzer/src/dialyzer.hrl
index 9338d76ef2..9236d6be3a 100644
--- a/lib/dialyzer/src/dialyzer.hrl
+++ b/lib/dialyzer/src/dialyzer.hrl
@@ -168,6 +168,7 @@
 -define(ERROR_LOCATION, column).
 
 -type doc_plt() :: 'undefined' | dialyzer_plt:plt().
+-record(plt_info, {files :: [dialyzer_plt:file_md5()], mod_deps :: dict:dict()}).
 
 -record(analysis, {analysis_pid			   :: pid() | 'undefined',
 		   type		  = succ_typings   :: anal_type(),
diff --git a/lib/dialyzer/src/dialyzer_analysis_callgraph.erl b/lib/dialyzer/src/dialyzer_analysis_callgraph.erl
index 75da4457dd..ee795a54dc 100644
--- a/lib/dialyzer/src/dialyzer_analysis_callgraph.erl
+++ b/lib/dialyzer/src/dialyzer_analysis_callgraph.erl
@@ -131,7 +131,7 @@ analysis_start(Parent, Analysis, LegalWarnings) ->
                           solvers = Analysis#analysis.solvers
 			 },
   Files = ordsets:from_list(Analysis#analysis.files),
-  {Callgraph, TmpCServer0} = compile_and_store(Files, State),
+  {Callgraph, ModCallDeps, Modules, TmpCServer0} = compile_and_store(Files, State),
   %% Remote type postprocessing
   Args = {Plt, Analysis, Parent},
   NewCServer = remote_type_postprocessing(TmpCServer0, Args),
@@ -145,6 +145,9 @@ analysis_start(Parent, Analysis, LegalWarnings) ->
   NonExports = sets:subtract(sets:from_list(AllNodes, [{version, 2}]), Exports),
   NonExportsList = sets:to_list(NonExports),
   State2 = analyze_callgraph(Callgraph, State1),
+  ModTypeDeps = dict:from_list(maps:to_list(dialyzer_typegraph:module_type_deps(Analysis#analysis.use_contracts, CServer, Modules))),
+  ModDeps = dialyzer_callgraph:merge_module_deps(ModCallDeps, ModTypeDeps),
+  send_mod_deps(Parent, ModDeps),
   #analysis_state{plt = Plt2,
                   doc_plt = DocPlt,
                   codeserver = Codeserver0} = State2,
@@ -227,6 +230,7 @@ analyze_callgraph(Callgraph, #analysis_state{codeserver = Codeserver,
 					     doc_plt = DocPlt,
                                              plt = Plt,
 					     timing_server = TimingServer,
+					     parent = Parent,
                                              solvers = Solvers} = State) ->
   case State#analysis_state.analysis_type of
     plt_build ->
@@ -238,10 +242,10 @@ analyze_callgraph(Callgraph, #analysis_state{codeserver = Codeserver,
     succ_typings ->
       {Warnings, NewPlt, NewDocPlt} =
         dialyzer_succ_typings:get_warnings(Callgraph, Plt, DocPlt, Codeserver,
-                                           TimingServer, Solvers),
+                                          TimingServer, Solvers),
       dialyzer_callgraph:delete(Callgraph),
       Warnings1 = filter_warnings(Warnings, Codeserver),
-      send_warnings(State#analysis_state.parent, Warnings1),
+      send_warnings(Parent, Warnings1),
       State#analysis_state{plt = NewPlt, doc_plt = NewDocPlt}
     end.
 
@@ -307,13 +311,13 @@ compile_and_store(Files, #analysis_state{codeserver = CServer,
   {T2, _} = statistics(wall_clock),
   Msg1 = io_lib:format("done in ~.2f secs\nRemoving edges... ", [(T2-T1)/1000]),
   send_log(Parent, Msg1),
-  Callgraph =
+  {ModCallDeps, Callgraph} =
     ?timing(Timing, "clean", _C2,
 	    cleanup_callgraph(State, CServer2, Callgraph, Modules)),
   {T3, _} = statistics(wall_clock),
   Msg2 = io_lib:format("done in ~.2f secs\n", [(T3-T2)/1000]),
   send_log(Parent, Msg2),
-  {Callgraph, CServer2}.
+  {Callgraph, ModCallDeps, Modules, CServer2}.
 
 -opaque compile_init_data()  :: #compile_init{}.
 -type error_reason()         :: string().
@@ -366,8 +370,7 @@ cleanup_callgraph(#analysis_state{plt = InitPlt, parent = Parent,
 				  codeserver = CodeServer
 				 },
 		  CServer, Callgraph, Modules) ->
-  ModuleDeps = dialyzer_callgraph:module_deps(Callgraph),
-  send_mod_deps(Parent, ModuleDeps),
+  ModCallDeps = dialyzer_callgraph:module_call_deps(Callgraph),
   {Callgraph1, ExtCalls} = dialyzer_callgraph:remove_external(Callgraph),
   ExtCalls1 = [Call || Call = {_From, To} <- ExtCalls,
 		       not dialyzer_plt:contains_mfa(InitPlt, To)],
@@ -394,7 +397,7 @@ cleanup_callgraph(#analysis_state{plt = InitPlt, parent = Parent,
           {From, To} <- RealExtCalls],
       send_ext_calls(Parent, ExtCallsWithFileAndLocation)
   end,
-  Callgraph1.
+  {ModCallDeps, Callgraph1}.
 
 compile_src(File, Includes, Defines, Callgraph, CServer, UseContracts,
             LegalWarnings) ->
diff --git a/lib/dialyzer/src/dialyzer_behaviours.erl b/lib/dialyzer/src/dialyzer_behaviours.erl
index 4be84502a1..2462c2173f 100644
--- a/lib/dialyzer/src/dialyzer_behaviours.erl
+++ b/lib/dialyzer/src/dialyzer_behaviours.erl
@@ -22,7 +22,7 @@
 
 -module(dialyzer_behaviours).
 
--export([check_callbacks/5]).
+-export([check_callbacks/5, get_behaviours/1]).
 
 -export_type([behaviour/0]).
 
@@ -39,7 +39,7 @@
 -record(state, {plt        :: dialyzer_plt:plt(),
 		codeserver :: dialyzer_codeserver:codeserver(),
 		filename   :: file:filename(),
-		behlines   :: [{behaviour(), non_neg_integer()}],
+		behlines   :: [{behaviour(), file_location()}],
 		records    :: rectab()}).
 
 %%--------------------------------------------------------------------
@@ -64,6 +64,8 @@ check_callbacks(Module, Attrs, Records, Plt, Codeserver) ->
 
 %%--------------------------------------------------------------------
 
+-spec get_behaviours([{cerl:cerl(), cerl:cerl()}]) -> {[behaviour()], [{behaviour(), term()}]}.
+
 get_behaviours(Attrs) ->
   BehaviourListsAndLocation =
     [{cerl:concrete(L2), hd(cerl:get_ann(L2))} ||
@@ -101,7 +103,7 @@ check_all_callbacks(Module, Behaviour, [Cb|Rest],
   CbReturnType = dialyzer_contracts:get_contract_return(Callback),
   CbArgTypes = dialyzer_contracts:get_contract_args(Callback),
   Acc0 = Acc,
-  Acc1 = 
+  Acc1 =
     case dialyzer_plt:lookup(Plt, CbMFA) of
       'none' ->
         case lists:member(optional_callback, Xtra) of
diff --git a/lib/dialyzer/src/dialyzer_callgraph.erl b/lib/dialyzer/src/dialyzer_callgraph.erl
index f5607bbc5c..aec4bd7169 100644
--- a/lib/dialyzer/src/dialyzer_callgraph.erl
+++ b/lib/dialyzer/src/dialyzer_callgraph.erl
@@ -15,7 +15,7 @@
 %%%-------------------------------------------------------------------
 %%% File    : dialyzer_callgraph.erl
 %%% Author  : Tobias Lindahl <tobiasl@it.uu.se>
-%%% Description : 
+%%% Description :
 %%%
 %%% Created : 30 Mar 2005 by Tobias Lindahl <tobiasl@it.uu.se>
 %%%-------------------------------------------------------------------
@@ -35,7 +35,8 @@
 	 lookup_label/2,
 	 lookup_name/2,
 	 modules/1,
-	 module_deps/1,
+	 module_call_deps/1,
+	 merge_module_deps/2,
 	 %% module_postorder/1,
 	 module_postorder_from_funs/2,
 	 new/0,
@@ -63,10 +64,10 @@
 %%-----------------------------------------------------------------------------
 %% A callgraph is a directed graph where the nodes are functions and a
 %% call between two functions is an edge from the caller to the callee.
-%% 
+%%
 %% calls	-  A mapping from call site (and apply site) labels
 %%		   to the possible functions that can be called.
-%% digraph	-  A digraph representing the callgraph. 
+%% digraph	-  A digraph representing the callgraph.
 %%		   Nodes are represented as MFAs or labels.
 %% esc		-  A set of all escaping functions as reported by dialyzer_dep.
 %% letrec_map	-  A dict mapping from letrec bound labels to function labels.
@@ -129,7 +130,7 @@ all_nodes(#callgraph{digraph = DG}) ->
 
 -spec lookup_rec_var(label(), callgraph()) -> 'error' | {'ok', mfa()}.
 
-lookup_rec_var(Label, #callgraph{rec_var_map = RecVarMap}) 
+lookup_rec_var(Label, #callgraph{rec_var_map = RecVarMap})
   when is_integer(Label) ->
   ets_lookup_dict(Label, RecVarMap).
 
@@ -216,7 +217,7 @@ find_non_local_calls([{{M,_,_}, {M,_,_}}|Left], Set) ->
 find_non_local_calls([{{M1,_,_}, {M2,_,_}} = Edge|Left], Set) when M1 =/= M2 ->
   find_non_local_calls(Left, sets:add_element(Edge, Set));
 find_non_local_calls([{{_,_,_}, Label}|Left], Set) when is_integer(Label) ->
-  find_non_local_calls(Left, Set);  
+  find_non_local_calls(Left, Set);
 find_non_local_calls([{Label, {_,_,_}}|Left], Set) when is_integer(Label) ->
   find_non_local_calls(Left, Set);
 find_non_local_calls([{Label1, Label2}|Left], Set) when is_integer(Label1),
@@ -225,6 +226,7 @@ find_non_local_calls([{Label1, Label2}|Left], Set) when is_integer(Label1),
 find_non_local_calls([], Set) ->
   sets:to_list(Set).
 
+%% Only considers call dependencies, not type dependencies, which are dealt with elsewhere
 -spec get_depends_on(scc() | module(), callgraph()) -> [scc()].
 
 get_depends_on(SCC, #callgraph{active_digraph = {'e', Out, _In, Maps}}) ->
@@ -281,10 +283,11 @@ edge_fold({{M1,_,_},{M2,_,_}}, Set) ->
 edge_fold(_, Set) -> Set.
 
 
-%% The module deps of a module are modules that depend on the module
--spec module_deps(callgraph()) -> mod_deps().
+%% The module call deps of a module are modules that depend on the module to
+%% make function calls
+-spec module_call_deps(callgraph()) -> mod_deps().
 
-module_deps(#callgraph{digraph = DG}) ->
+module_call_deps(#callgraph{digraph = DG}) ->
   Edges = lists:foldl(fun edge_fold/2, sets:new([{version, 2}]), digraph_edges(DG)),
   Modules = ordsets:from_list([M || {M,_F,_A} <- digraph_vertices(DG)]),
   MDG = digraph:new(),
@@ -296,6 +299,17 @@ module_deps(#callgraph{digraph = DG}) ->
   digraph_delete(MDG),
   dict:from_list(Deps).
 
+-spec merge_module_deps(mod_deps(), mod_deps()) -> mod_deps().
+merge_module_deps(Left, Right) ->
+    dict:merge(
+      fun (_Mod, L, R) ->
+        gb_sets:to_list(gb_sets:union(
+          gb_sets:from_list(L),
+          gb_sets:from_list(R)))
+      end,
+      Left,
+      Right).
+
 -spec strip_module_deps(mod_deps(), sets:set(module())) -> mod_deps().
 
 strip_module_deps(ModDeps, StripSet) ->
@@ -369,10 +383,10 @@ scan_core_tree(Tree, #callgraph{calls = ETSCalls,
   true = ets:insert(ETSEsc, [{E} || E <- EscapingFuns]),
 
   LabelEdges = get_edges_from_deps(Deps0),
-  
+
   %% Find the self recursive functions. Named functions get both the
   %% key and their name for convenience.
-  SelfRecs0 = lists:foldl(fun({Key, Key}, Acc) -> 
+  SelfRecs0 = lists:foldl(fun({Key, Key}, Acc) ->
 			      case ets_lookup_dict(Key, ETSNameMap) of
 				error      -> [Key|Acc];
 				{ok, Name} -> [Key, Name|Acc]
@@ -380,9 +394,9 @@ scan_core_tree(Tree, #callgraph{calls = ETSCalls,
 			     (_, Acc) -> Acc
 			  end, [], LabelEdges),
   true = ets:insert(ETSSelfRec, [{S} || S <- SelfRecs0]),
-  
+
   NamedEdges1 = name_edges(LabelEdges, ETSNameMap),
-  
+
   %% We need to scan for inter-module calls since these are not tracked
   %% by dialyzer_dep. Note that the caller is always recorded as the
   %% top level function. This is OK since the included functions are
@@ -404,7 +418,7 @@ scan_core_tree(Tree, #callgraph{calls = ETSCalls,
 
 build_maps(Tree, ETSRecVarMap, ETSNameMap, ETSRevNameMap, ETSLetrecMap) ->
   %% We only care about the named (top level) functions. The anonymous
-  %% functions will be analysed together with their parents. 
+  %% functions will be analysed together with their parents.
   Defs = cerl:module_defs(Tree),
   Mod = cerl:atom_val(cerl:module_name(Tree)),
   Fun =
@@ -427,7 +441,7 @@ get_edges_from_deps(Deps) ->
   %% this information.
   Edges = dict:fold(fun(external, _Set, Acc) -> Acc;
 		       (Caller, Set, Acc)    ->
-			[[{Caller, Callee} || Callee <- Set, 
+			[[{Caller, Callee} || Callee <- Set,
 					      Callee =/= external]|Acc]
 		    end, [], Deps),
   lists:flatten(Edges).
@@ -469,9 +483,9 @@ scan_one_core_fun(TopTree, FunName) ->
 		    CalleeF = cerl:call_name(Tree),
 		    CalleeArgs = cerl:call_args(Tree),
 		    A = length(CalleeArgs),
-		    case (cerl:is_c_atom(CalleeM) andalso 
+		    case (cerl:is_c_atom(CalleeM) andalso
 			  cerl:is_c_atom(CalleeF)) of
-		      true -> 
+		      true ->
 			M = cerl:atom_val(CalleeM),
 			F = cerl:atom_val(CalleeF),
 			case erl_bif_types:is_known(M, F, A) of
@@ -500,7 +514,7 @@ scan_one_core_fun(TopTree, FunName) ->
 			    end;
 			  false -> [{FunName, {M, F, A}}|Acc]
 			end;
-		      false -> 
+		      false ->
 			%% We cannot handle run-time bindings
 			Acc
 		    end;
@@ -556,7 +570,7 @@ digraph_confirm_vertices([MFA|Left], DG) ->
   digraph_confirm_vertices(Left, DG);
 digraph_confirm_vertices([], _DG) ->
   ok.
-  
+
 digraph_remove_external(DG) ->
   Vertices = digraph:vertices(DG),
   Unconfirmed = remove_unconfirmed(Vertices, DG),
@@ -598,7 +612,7 @@ digraph_in_neighbours(V, DG) ->
     List -> List
   end.
 
-digraph_reaching_subgraph(Funs, DG) ->  
+digraph_reaching_subgraph(Funs, DG) ->
   Vertices = digraph_utils:reaching(Funs, DG),
   digraph_utils:subgraph(DG, Vertices).
 
@@ -616,7 +630,7 @@ to_dot(#callgraph{digraph = DG, esc = Esc} = CG, File) ->
 	      {ok, Name} -> Name
 	    end
 	end,
-  Escaping = [{Fun(L), {color, red}} 
+  Escaping = [{Fun(L), {color, red}}
 	      || L <- [E || {E} <- ets:tab2list(Esc)], L =/= external],
   Vertices = digraph_edges(DG),
   dialyzer_dot:translate_list(Vertices, File, "CG", Escaping).
diff --git a/lib/dialyzer/src/dialyzer_cl.erl b/lib/dialyzer/src/dialyzer_cl.erl
index 0987de39eb..25fdef948e 100644
--- a/lib/dialyzer/src/dialyzer_cl.erl
+++ b/lib/dialyzer/src/dialyzer_cl.erl
@@ -47,7 +47,7 @@
          indent_opt      = ?INDENT_OPT    :: iopt(),
          error_location  = ?ERROR_LOCATION :: error_location(),
 	 output_plt      = none           :: 'none' | file:filename(),
-	 plt_info        = none           :: 'none' | dialyzer_plt:plt_info(),
+	 plt_info        = none           :: 'none' | #plt_info{},
 	 report_mode     = normal         :: rep_mode(),
 	 return_status= ?RET_NOTHING_SUSPICIOUS	:: dial_ret(),
 	 stored_warnings = []             :: [raw_warning()]
@@ -73,7 +73,7 @@ build_plt(Opts) ->
   Opts1 = init_opts_for_build(Opts),
   Files = get_files_from_opts(Opts1),
   Md5 = dialyzer_plt:compute_md5_from_files(Files),
-  PltInfo = {Md5, dict:new()},
+  PltInfo = #plt_info{files = Md5, mod_deps = dict:new()},
   do_analysis(Files, Opts1, dialyzer_plt:new(), PltInfo).
 
 init_opts_for_build(Opts) ->
@@ -200,7 +200,7 @@ plt_common(#options{init_plts = [InitPlt]} = Opts, RemoveFiles, AddFiles) ->
       end,
       {?RET_NOTHING_SUSPICIOUS, []};
     {old_version, Md5} ->
-      PltInfo = {Md5, dict:new()},
+      PltInfo = #plt_info{files = Md5, mod_deps = dict:new()},
       Files = [F || {F, _} <- Md5],
       do_analysis(Files, Opts, dialyzer_plt:new(), PltInfo);
     {differ, Md5, DiffMd5, ModDeps} ->
@@ -212,10 +212,10 @@ plt_common(#options{init_plts = [InitPlt]} = Opts, RemoveFiles, AddFiles) ->
 	true ->
 	  %% Only removed stuff. Just write the PLT.
 	  dialyzer_plt:to_file(Opts#options.output_plt, Plt, ModDeps, 
-			       {Md5, ModDeps}),
+                         #plt_info{files = Md5, mod_deps = ModDeps}),
 	  {?RET_NOTHING_SUSPICIOUS, []};
 	false ->
-	  do_analysis(AnalFiles, Opts, Plt, {Md5, ModDeps1})
+	  do_analysis(AnalFiles, Opts, Plt, #plt_info{files = Md5, mod_deps = ModDeps1})
       end;
     {error, no_such_file} ->
       Msg = io_lib:format("Could not find the PLT: ~ts\n~s",
diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl
index 2fda1255f6..713e475b17 100644
--- a/lib/dialyzer/src/dialyzer_contracts.erl
+++ b/lib/dialyzer/src/dialyzer_contracts.erl
@@ -25,7 +25,8 @@
 	 %% get_contract_signature/1,
 	 is_overloaded/1,
 	 process_contract_remote_types/1,
-	 store_tmp_contract/6]).
+	 store_tmp_contract/6,
+   constraint_form_to_remote_modules/1]).
 
 %% For dialyzer_worker.
 -export([process_contract_remote_types_module/2]).
@@ -1019,3 +1020,13 @@ blame_remote_list([CArg|CArgs], [NRArg|NRArgs], [SArg|SArgs], Opaques) ->
 is_subtype(T1, T2, Opaques) ->
   Inf = erl_types:t_inf(T1, T2, Opaques),
   erl_types:t_is_equal(T1, Inf).
+
+-spec constraint_form_to_remote_modules(Constraint :: term()) -> [module()].
+
+constraint_form_to_remote_modules([]) ->
+  [];
+
+constraint_form_to_remote_modules([{type, _, constraint, [{atom, _, _}, Types]}|Rest]) ->
+  ModulesFromTypes = erl_types:type_form_to_remote_modules(Types),
+  ModulesFromSubsequentConstraints = constraint_form_to_remote_modules(Rest),
+  lists:usort(lists:append(ModulesFromTypes, ModulesFromSubsequentConstraints)).
diff --git a/lib/dialyzer/src/dialyzer_plt.erl b/lib/dialyzer/src/dialyzer_plt.erl
index acece3f9e7..409d1f65c5 100644
--- a/lib/dialyzer/src/dialyzer_plt.erl
+++ b/lib/dialyzer/src/dialyzer_plt.erl
@@ -50,13 +50,16 @@
 	 get_specs/1,
 	 get_specs/4,
 	 to_file/4,
-         delete/1
+   delete/1,
+   get_all_types/1,
+   get_all_contracts/1,
+   get_all_callbacks/1
 	]).
 
 %% Debug utilities
 -export([pp_non_returning/0, pp_mod/1]).
 
--export_type([plt/0, plt_info/0]).
+-export_type([plt/0, file_md5/0]).
 
 -include_lib("stdlib/include/ms_transform.hrl").
 
@@ -89,7 +92,6 @@
 -include("dialyzer.hrl").
 
 -type file_md5() :: {file:filename(), binary()}.
--type plt_info() :: {[file_md5()], dict:dict()}.
 
 -record(file_plt, {version = ""                :: string(),
 		   file_md5_list = []          :: [file_md5()],
@@ -240,7 +242,7 @@ get_default_plt() ->
     UserSpecPlt -> UserSpecPlt
   end.
 
--spec plt_and_info_from_file(file:filename()) -> {plt(), plt_info()}.
+-spec plt_and_info_from_file(file:filename()) -> {plt(), #plt_info{}}.
 
 plt_and_info_from_file(FileName) ->
   from_file(FileName, true).
@@ -296,8 +298,8 @@ from_file1(Plt, FileName, ReturnInfo) ->
 	  case ReturnInfo of
 	    false -> {ok, Plt};
 	    true ->
-	      PltInfo = {Rec#file_plt.file_md5_list,
-			 Rec#file_plt.mod_deps},
+	      PltInfo = #plt_info{files = Rec#file_plt.file_md5_list,
+                            mod_deps = Rec#file_plt.mod_deps},
 	      {ok, {Plt, PltInfo}}
 	  end
       end;
@@ -407,8 +409,8 @@ find_duplicates(List) ->
   ModList = [filename:basename(E) || E <- List],
   SortedList = lists:usort(ModList),
   lists:usort(ModList -- SortedList).
-  
--spec to_file(file:filename(), plt(), mod_deps(), {[file_md5()], mod_deps()}) -> 'ok'.
+
+-spec to_file(file:filename(), plt(), mod_deps(), #plt_info{}) -> 'ok'.
 
 %% Write the PLT to file, and delete the PLT.
 to_file(FileName, Plt, ModDeps, MD5_OldModDeps) ->
@@ -423,7 +425,7 @@ to_file(FileName, Plt, ModDeps, MD5_OldModDeps) ->
 to_file1(FileName,
 	#plt{info = ETSInfo, types = ETSTypes, contracts = ETSContracts,
 	     callbacks = ETSCallbacks, exported_types = ETSExpTypes},
-	ModDeps, {MD5, OldModDeps}) ->
+	ModDeps, #plt_info{files = MD5, mod_deps = OldModDeps}) ->
   NewModDeps = dict:merge(fun(_Key, OldVal, NewVal) ->
 			      ordsets:union(OldVal, NewVal)
 			  end,
@@ -845,3 +847,24 @@ pp_mod(Mod) when is_atom(Mod) ->
       io:format("dialyzer: Found no module named '~s' in the PLT\n", [Mod])
   end,
   delete(Plt).
+
+
+%% Returns all contracts stored in the PLT
+-spec get_all_contracts(plt()) -> #{mfa() => #contract{}}.
+get_all_contracts(#plt{contracts = ETSContracts}) ->
+  maps:from_list(ets:tab2list(ETSContracts)).
+
+%% Returns all callbacks stored in the PLT
+-spec get_all_callbacks(plt()) -> #{mfa() => #contract{}}.
+get_all_callbacks(#plt{callbacks = ETSCallbacks}) ->
+  CallbacksList =
+      [Cb ||
+        {_M, Cbs} <- ets:tab2list(ETSCallbacks),
+        Cb <- Cbs],
+  maps:from_list(CallbacksList).
+
+%% Returns all types stored in the PLT
+-spec get_all_types(plt()) -> #{module() => erl_types:type_table()}.
+get_all_types(#plt{types = ETSTypes}) ->
+  Types = ets:tab2list(ETSTypes),
+  maps:from_list(Types).
diff --git a/lib/dialyzer/src/dialyzer_typegraph.erl b/lib/dialyzer/src/dialyzer_typegraph.erl
new file mode 100644
index 0000000000..5818236fa7
--- /dev/null
+++ b/lib/dialyzer/src/dialyzer_typegraph.erl
@@ -0,0 +1,109 @@
+%% -*- erlang-indent-level: 2 -*-
+-module(dialyzer_typegraph).
+
+-export([module_type_deps/3]).
+
+-export_type([type_mod_deps/0]).
+
+-include("dialyzer.hrl").
+
+%% Maps a module to those modules that depend on it
+-type type_mod_deps() :: #{module() => [module()]}.
+
+%% We track type dependecies so that we know which modules we ultimately
+%% depend upon for type definitions which, in turn, affect the checking
+%% of a module.
+
+%% Any non-local types that are used in a spec (aka contract) / callback, any
+%% locally-defined types that may depend on a non-local type, and any
+%% implementations of a behaviour, introduce type-level dependencies on other
+%% modules such that if the definition of that other module were to change,
+%% this module would need to be checked again to account for those changes.
+
+-spec module_type_deps(UseContracts :: boolean(), dialyzer_codeserver:codeserver(), [module()]) -> type_mod_deps().
+
+%% The module type deps of a module are modules that depend on the module to
+%% define types, contracts, callbacks or behaviours
+module_type_deps(UseContracts, CodeServer, Modules) ->
+
+  Contracts =
+    case UseContracts of
+      true -> maps:from_list(dict:to_list(dialyzer_codeserver:get_contracts(CodeServer)));
+      false -> []
+    end,
+  Callbacks = maps:from_list(dialyzer_codeserver:get_callbacks(CodeServer)),
+  TypeDefinitions =
+    maps:from_list(
+      [{M, dialyzer_codeserver:lookup_mod_records(M, CodeServer)} || M <- Modules]
+    ),
+  Behaviours =
+    maps:from_list(
+      [{M, get_behaviours_for_module(M, CodeServer)} || M <- Modules]
+    ),
+  collect_module_type_deps(Contracts, Callbacks, TypeDefinitions, Behaviours).
+
+-spec get_behaviours_for_module(module(), dialyzer_codeserver:codeserver()) -> [module()].
+
+get_behaviours_for_module(M, CodeServer) ->
+  ModCode = dialyzer_codeserver:lookup_mod_code(M, CodeServer),
+  Attrs = cerl:module_attrs(ModCode),
+  {Behaviours, _BehaviourLocations} = dialyzer_behaviours:get_behaviours(Attrs),
+  Behaviours.
+
+-spec collect_module_type_deps(Specs, Callbacks, TypeDefinitions, Behaviours) -> type_mod_deps() when
+    Specs :: #{mfa() => dialyzer_contracts:file_contract()},
+    Callbacks :: #{mfa() => dialyzer_contracts:file_contract()},
+    TypeDefinitions :: #{module() => erl_types:type_table()},
+    Behaviours :: #{module() => [module()]}.
+
+collect_module_type_deps(Specs, Callbacks, TypeDefinitions, Behaviours) ->
+
+  Contracts =
+    [{M, Spec} || {{M, _F, _A}, {_FileLine, Spec, _Extra}} <- maps:to_list(Specs)] ++
+    [{M, Callback} || {{M, _F, _A}, {_FileLine, Callback, _Extra}} <- maps:to_list(Callbacks)],
+
+  ModulesMentionedInTypeDefinitions =
+    [{FromTypeDefM, erl_types:module_type_deps_of_type_defs(TypeTable)}
+      || {FromTypeDefM, TypeTable} <- maps:to_list(TypeDefinitions)],
+
+  ModulesMentionedInContracts =
+    [{FromContractM, module_type_deps_of_contract(C)}
+      || {FromContractM, C} <- Contracts],
+
+  ModulesMentionedAsBehaviours =
+    maps:to_list(Behaviours),
+
+  AllDepsRaw =
+    ModulesMentionedInContracts ++
+    ModulesMentionedInTypeDefinitions ++
+    ModulesMentionedAsBehaviours,
+
+  %% Find the union of module dependencies from all sources, removing
+  %% self-references, and flipping the direction of the mapping to
+  %% match the expectations of Dialyzer elsewhere,
+  %% i.e., from:
+  %%   module -> those modules it depends on
+  %% to
+  %%   module -> those modules that depend on it
+  S0 = sofs:relation(AllDepsRaw, [{atom,[atom]}]),
+  S1 = sofs:relation_to_family(S0),
+  S2 = sofs:family_union(S1),
+  S3 = sofs:family_to_relation(S2),
+  S4 = sofs:converse(S3),
+  S5 = sofs:strict_relation(S4),
+  S6 = sofs:relation_to_family(S5),
+  S7 = sofs:to_external(S6),
+  ModuleToThoseModulesThatDependOnIt = maps:from_list(S7),
+
+  ModuleToThoseModulesThatDependOnIt.
+
+-spec module_type_deps_of_contract(#contract{}) -> [module()].
+
+module_type_deps_of_contract(#contract{forms = Forms}) ->
+  TypeForms = [TypeForm || {TypeForm, _Constraints} <- Forms],
+  ConstraintForms =
+    lists:append([Constraints || {_TypeForm, Constraints} <- Forms]),
+  lists:usort(
+    lists:append(
+      erl_types:type_form_to_remote_modules(TypeForms),
+      dialyzer_contracts:constraint_form_to_remote_modules(ConstraintForms))).
diff --git a/lib/dialyzer/src/erl_types.erl b/lib/dialyzer/src/erl_types.erl
index 3b79e625a4..f4c7e8ef17 100644
--- a/lib/dialyzer/src/erl_types.erl
+++ b/lib/dialyzer/src/erl_types.erl
@@ -217,7 +217,9 @@
 	 is_erl_type/1,
 	 atom_to_string/1,
 	 var_table__new/0,
-	 cache__new/0
+	 cache__new/0,
+	 module_type_deps_of_type_defs/1,
+   type_form_to_remote_modules/1
 	]).
 
 -compile({no_auto_import,[min/2,max/2,map_get/2]}).
@@ -360,15 +362,15 @@
 
 -type file_line()    :: {file:name(), erl_anno:line()}.
 -type record_key()   :: {'record', atom()}.
--type type_key()     :: {'type' | 'opaque', mfa()}.
+-type type_key()     :: {'type' | 'opaque', {atom(), arity()}}.
 -type field()        :: {atom(), erl_parse:abstract_expr(), erl_type()}.
 -type record_value() :: {file_line(),
                          [{RecordSize :: non_neg_integer(), [field()]}]}.
 -type type_value()   :: {{module(), file_line(),
                           erl_parse:abstract_type(), ArgNames :: [atom()]},
                          erl_type()}.
--type type_table() :: #{record_key() | type_key() =>
-                        record_value() | type_value()}.
+-type type_table() :: #{record_key() => record_value()} |
+                        #{type_key() => type_value()}.
 
 -type var_name() :: atom() | integer().
 -type var_table() :: #{ var_name() => erl_type() }.
@@ -5705,3 +5707,130 @@ handle_base(Unit, Neg) ->
 
 var_table__new() ->
   maps:new().
+
+%%=============================================================================
+%%
+%% Utilities for finding a module's type dependencies
+%%
+%%=============================================================================
+
+
+-spec module_type_deps_of_type_defs(type_table()) -> [module()].
+
+module_type_deps_of_type_defs(TypeTable) ->
+  ModuleTypeDependencies =
+    [module_type_deps_of_entry(TypeTableEntry)
+      || TypeTableEntry <- maps:to_list(TypeTable)],
+  lists:append(ModuleTypeDependencies).
+
+-spec module_type_deps_of_entry(
+  {type_key(), type_value()}
+  | {record_key(), record_value()}) -> [module()].
+
+module_type_deps_of_entry({{'type', _TypeName, _A}, {{_FromM, _FileLine, AbstractType, _ArgNames}, _}}) ->
+  type_form_to_remote_modules(AbstractType);
+
+module_type_deps_of_entry({{'opaque', _TypeName, _A}, {{_FromM, _FileLine, AbstractType, _ArgNames}, _}}) ->
+  type_form_to_remote_modules(AbstractType);
+
+module_type_deps_of_entry({{'record', _Name}, {_FileLine, SizesAndFields}}) ->
+  AllFields = lists:append([Fields || {_Size, Fields} <- SizesAndFields]),
+  FieldTypes = [AbstractType || {_, AbstractType, _} <- AllFields],
+  type_form_to_remote_modules(FieldTypes).
+
+%% Whilst this function is depth-limited, it should be limited in precisely
+%% the same way as Dialyzer's other analyses - i.e. it should only ignore
+%% sub-components of types Diaylzer wouldn't explore anyway
+-spec type_form_to_remote_modules(parse_form() | [parse_form()]) -> [module()].
+
+type_form_to_remote_modules([]) ->
+  [];
+
+type_form_to_remote_modules([_|_] = Forms) ->
+  D = ?EXPAND_DEPTH,
+  L = ?EXPAND_LIMIT,
+  {_, Mods} = list_get_modules_mentioned(Forms, D, L, []),
+  lists:usort(Mods);
+
+type_form_to_remote_modules(Form) ->
+  D = ?EXPAND_DEPTH,
+  L = ?EXPAND_LIMIT,
+  {_, Mods} = get_modules_mentioned(Form, D, L, []),
+  lists:usort(Mods).
+
+-spec get_modules_mentioned(TypeForm :: parse_form(), expand_depth(), expand_limit(), Acc :: [module()]) -> {expand_depth(), [module()]}.
+
+get_modules_mentioned(_, D, L, Acc) when D =< 0 ; L =< 0 ->
+  {L, Acc};
+get_modules_mentioned({var, _L, '_'}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({var, _L, _Name}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({ann_type, _L, [_Var, Type]}, D, L, Acc) ->
+  get_modules_mentioned(Type, D, L, Acc);
+get_modules_mentioned({paren_type, _L, [Type]}, D, L, Acc) ->
+  get_modules_mentioned(Type, D, L, Acc);
+get_modules_mentioned({atom, _L, _Atom}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({integer, _L, _Int}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({char, _L, _Char}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({op, _L, _Op, _Arg}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({op, _L, _Op, _Arg1, _Arg2}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({type, _L, 'fun', [{type, _, any}, Range]}, D, L, Acc) ->
+  get_modules_mentioned(Range, D - 1, L - 1, Acc);
+get_modules_mentioned({type, _L, 'fun', [{type, _, product, Domain}, Range]}, D, L, Acc) ->
+  {L1, Acc1} = list_get_modules_mentioned(Domain, D, L, Acc),
+  get_modules_mentioned(Range, D, L1, Acc1);
+get_modules_mentioned({type, _L, list, [Type]}, D, L, Acc) ->
+  get_modules_mentioned(Type, D - 1, L - 1, Acc);
+get_modules_mentioned({type, _L, map, any}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({type, _L, map, List}, D0, L, Acc) ->
+  fun PairsFromForm(_, L1, Acc1) when L1 =< 0 -> Acc1;
+      PairsFromForm([], L1, Acc1) -> {L1, Acc1};
+      PairsFromForm([{type, _, _Oper, [KF, VF]}|T], L1, Acc1) ->
+        D = D0 - 1,
+        {L2, Acc2} = get_modules_mentioned(KF, D, L1, Acc1),
+        {L3, Acc3} = get_modules_mentioned(VF, D, L2, Acc2),
+        PairsFromForm(T, L3 - 1, Acc3)
+  end(List, L, Acc);
+get_modules_mentioned({type, _L, nonempty_list, [Type]}, D, L, Acc) ->
+  get_modules_mentioned(Type, D, L - 1, Acc);
+get_modules_mentioned({type, _L, nonempty_improper_list, [Cont, Term]}, D, L, Acc) ->
+  {L1, Acc1} = get_modules_mentioned(Cont, D, L - 1, Acc),
+  get_modules_mentioned(Term, D, L1, Acc1);
+get_modules_mentioned({type, _L, nonempty_maybe_improper_list, [Cont, Term]}, D, L, Acc) ->
+  {L1, Acc1} = get_modules_mentioned(Cont, D, L - 1, Acc),
+  get_modules_mentioned(Term, D, L1, Acc1);
+get_modules_mentioned({type, _L, maybe_improper_list, [Content, Termination]}, D, L, Acc) ->
+  {L1, Acc1} = get_modules_mentioned(Content, D, L - 1, Acc),
+  get_modules_mentioned(Termination, D, L1, Acc1);
+get_modules_mentioned({type, _L, product, Elements}, D, L, Acc) ->
+  list_get_modules_mentioned(Elements, D - 1, L, Acc);
+get_modules_mentioned({type, _L, range, [_From, _To]}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({type, _L, tuple, any}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({type, _L, tuple, Args}, D, L, Acc) ->
+  list_get_modules_mentioned(Args, D - 1, L, Acc);
+get_modules_mentioned({type, _L, union, Args}, D, L, Acc) ->
+  list_get_modules_mentioned(Args, D, L, Acc);
+get_modules_mentioned({remote_type, _L, [{atom, _, Module}, {atom, _, _Type}, Args]}, D, L, Acc) ->
+  Acc1 = [Module|Acc],
+  list_get_modules_mentioned(Args, D, L, Acc1);
+get_modules_mentioned({user_type, _L, _Name, Args}, D, L, Acc) ->
+  list_get_modules_mentioned(Args, D, L, Acc);
+get_modules_mentioned({type, _L, _Name, []}, _D, L, Acc) ->
+  {L, Acc};
+get_modules_mentioned({type, _L, _Name, Args}, D, L, Acc) ->
+  list_get_modules_mentioned(Args, D, L, Acc).
+
+list_get_modules_mentioned([], _D, L, Acc) ->
+  {L, Acc};
+list_get_modules_mentioned([H|Tail], D, L, Acc) ->
+  {L1, Acc1} = get_modules_mentioned(H, D, L - 1, Acc),
+  list_get_modules_mentioned(Tail, D, L1, Acc1).
diff --git a/lib/dialyzer/test/Makefile b/lib/dialyzer/test/Makefile
index 60c5ea5c2e..7308c20400 100644
--- a/lib/dialyzer/test/Makefile
+++ b/lib/dialyzer/test/Makefile
@@ -12,6 +12,7 @@ AUXILIARY_FILES=\
 	dialyzer_common.erl\
 	file_utils.erl\
 	dialyzer_SUITE.erl\
+	dialyzer_cl_SUITE.erl\
 	abstract_SUITE.erl\
 	plt_SUITE.erl\
 	typer_SUITE.erl\
diff --git a/lib/dialyzer/test/dialyzer_cl_SUITE.erl b/lib/dialyzer/test/dialyzer_cl_SUITE.erl
new file mode 100644
index 0000000000..ed84fc6068
--- /dev/null
+++ b/lib/dialyzer/test/dialyzer_cl_SUITE.erl
@@ -0,0 +1,129 @@
+-module(dialyzer_cl_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
+-include_lib("dialyzer/src/dialyzer.hrl").
+
+%% Test server specific exports
+-export([all/0, suite/0, init_per_suite/1, end_per_suite/1]).
+
+%% Test cases must be exported.
+-export([
+    unknown_function_warning_includes_callsite/1,
+    call_to_missing_warning_includes_callsite/1
+]).
+
+suite() -> [{timetrap, {minutes, 1}}].
+
+all() ->
+    [
+        unknown_function_warning_includes_callsite,
+        call_to_missing_warning_includes_callsite
+    ].
+
+init_per_suite(Config) ->
+    %% Prime PLT with common stuff so we don't get errors about get_module_info
+    %% being unknown, etc.
+    PrivDir = proplists:get_value(priv_dir,Config),
+    PltBase = plt_base_file(PrivDir),
+    _ = dialyzer:run([{analysis_type, plt_build},
+                      {apps, [erts]},
+                      {output_plt, PltBase}]),
+    Config.
+
+end_per_suite(Config) ->
+    Config.
+
+plt_base_file(PrivDir) ->
+    filename:join(PrivDir, "dialyzer_cl_base.plt").
+
+%%%
+%%% Test cases starts here.
+%%%
+
+%% Test running Dialyzer programatically can yield call to missing
+%% errors with information on both the callsite and the unknown call
+%% itself.
+%% Missing function logic is tested elsewhere, but here we're specifically
+%% interested in the details of the error that are accessible from the
+%% dialyzer_cl API
+call_to_missing_warning_includes_callsite(Config) when is_list(Config) ->
+
+    PrivDir = proplists:get_value(priv_dir,Config),
+    PltBase = plt_base_file(PrivDir),
+    Plt = filename:join(PrivDir, "previously_defined.plt"),
+
+    {ok, BeamFileForPlt} = compile(Config, previously_defined, []),
+    [] = dialyzer:run([{analysis_type, plt_build},
+                      {files, [BeamFileForPlt]},
+                      {output_plt, Plt}]),
+
+    {ok, Beam} = compile(Config, call_to_missing_example, []),
+    Opts =
+        #options{
+            analysis_type = succ_typings,
+            init_plts = [Plt, PltBase],
+            output_file = none,
+            get_warnings = true,
+            legal_warnings = ordsets:from_list([warn_unknown, warn_callgraph]),
+            erlang_mode = true,
+            files = [Beam]
+        },
+    Res = dialyzer_cl:start(Opts),
+
+    ?assertMatch(
+        {2, [
+            {warn_callgraph, {_Filename, {5, 5}}, {
+                call_to_missing, [
+                    previously_defined, function, 0
+                ]
+            }}
+        ]},
+        Res),
+
+    ok.
+
+%% Test running Dialyzer programatically can yield unknown function
+%% errors with information on both the callsite and the unknown call
+%% itself.
+%% Missing function logic is tested elsewhere, but here we're specifically
+%% interested in the details of the error that are accessible from the
+%% dialyzer_cl API
+unknown_function_warning_includes_callsite(Config) when is_list(Config) ->
+
+    PrivDir = proplists:get_value(priv_dir,Config),
+    PltBase = plt_base_file(PrivDir),
+
+    {ok, Beam} = compile(Config, unknown_function_example, []),
+    Opts =
+        #options{
+            analysis_type = succ_typings,
+            init_plts = [PltBase],
+            output_file = none,
+            get_warnings = true,
+            legal_warnings = ordsets:from_list([warn_unknown, warn_callgraph]),
+            erlang_mode = true,
+            files = [Beam]
+        },
+    Res = dialyzer_cl:start(Opts),
+
+    ?assertMatch(
+        {2, [
+            {warn_unknown, {_Filename, {5,5}},
+                {unknown_function, {
+                    does_not_exist, function, 0
+                }}
+            }
+        ]},
+        Res),
+
+    ok.
+
+compile(Config, Module, CompileOpts) ->
+    Source = lists:concat([Module, ".erl"]),
+    PrivDir = proplists:get_value(priv_dir,Config),
+    DataDir = proplists:get_value(data_dir,Config),
+    SrcFilename = filename:join([DataDir, Source]),
+    Opts = [{outdir, PrivDir}, debug_info | CompileOpts],
+    {ok, Module} = compile:file(SrcFilename, Opts),
+    {ok, filename:join([PrivDir, lists:concat([Module, ".beam"])])}.
diff --git a/lib/dialyzer/test/dialyzer_cl_SUITE_data/call_to_missing_example.erl b/lib/dialyzer/test/dialyzer_cl_SUITE_data/call_to_missing_example.erl
new file mode 100644
index 0000000000..96670f1221
--- /dev/null
+++ b/lib/dialyzer/test/dialyzer_cl_SUITE_data/call_to_missing_example.erl
@@ -0,0 +1,5 @@
+-module(call_to_missing_example).
+-export([call_to_missing_test/0]).
+
+call_to_missing_test() ->
+    previously_defined:function().
diff --git a/lib/dialyzer/test/dialyzer_cl_SUITE_data/previously_defined.erl b/lib/dialyzer/test/dialyzer_cl_SUITE_data/previously_defined.erl
new file mode 100644
index 0000000000..5b03eb2b7c
--- /dev/null
+++ b/lib/dialyzer/test/dialyzer_cl_SUITE_data/previously_defined.erl
@@ -0,0 +1,5 @@
+-module(previously_defined).
+
+-export([do_thing/0]).
+
+do_thing() -> ok.
diff --git a/lib/dialyzer/test/dialyzer_cl_SUITE_data/unknown_function_example.erl b/lib/dialyzer/test/dialyzer_cl_SUITE_data/unknown_function_example.erl
new file mode 100644
index 0000000000..c9a93010c8
--- /dev/null
+++ b/lib/dialyzer/test/dialyzer_cl_SUITE_data/unknown_function_example.erl
@@ -0,0 +1,5 @@
+-module(unknown_function_example).
+-export([unknown_function_test/0]).
+
+unknown_function_test() ->
+    does_not_exist:function().
diff --git a/lib/dialyzer/test/dialyzer_common.erl b/lib/dialyzer/test/dialyzer_common.erl
index 392c41306e..3b39cf99ab 100644
--- a/lib/dialyzer/test/dialyzer_common.erl
+++ b/lib/dialyzer/test/dialyzer_common.erl
@@ -13,6 +13,7 @@
 
 -define(suite_suffix, "_SUITE").
 -define(data_folder, "_data").
+-define(excludes, ["dialyzer_cl", "plt"]). % _SUITE_data dirs that we shouldn't automatically make suites for
 -define(suite_data, ?suite_suffix ++ ?data_folder).
 -define(erlang_extension, ".erl").
 -define(output_file_mode, write).
@@ -45,7 +46,7 @@ check_plt(OutDir) ->
 	{error, _ } ->
 	    io:format("No plt found in test run directory!"),
 	    PltLockFile = filename:join(OutDir, ?plt_lockfile),
-	    case file:read_file_info(PltLockFile) of 
+	    case file:read_file_info(PltLockFile) of
 		{ok, _} ->
 		    explain_fail_with_lock(),
 		    fail;
@@ -178,7 +179,7 @@ fix_options([{pa, Path} | Rest], Dir, Acc) ->
 	true       -> fix_options(Rest, Dir, Acc);
 	{error, _} -> erlang:error("Bad directory for pa: " ++ Path)
     end;
-fix_options([{DirOption, RelativeDirs} | Rest], Dir, Acc) 
+fix_options([{DirOption, RelativeDirs} | Rest], Dir, Acc)
   when DirOption =:= include_dirs ;
        DirOption =:= files_rec ;
        DirOption =:= files ->
@@ -215,15 +216,21 @@ get_suites(Dir) ->
 	{error, _} -> [];
 	{ok, Filenames} ->
 	    FullFilenames = [filename:join(Dir, F) || F <-Filenames ],
-	    Dirs = [suffix(filename:basename(F), ?suite_data) ||
+	    Dirs = [is_suite_data(filename:basename(F), ?suite_data) ||
 		       F <- FullFilenames,
 		       file_utils:file_type(F) =:= {ok, 'directory'}],
 	    [S || {yes, S} <- Dirs]
     end.
 
-suffix(String, Suffix) ->
+is_suite_data(String, Suffix) ->
     case string:split(String, Suffix, trailing) of
-	[Prefix,[]] -> {yes, Prefix};
+        [Prefix,[]] ->
+            case lists:member(Prefix, ?excludes) of
+                true ->
+                   no;
+                false ->
+                   {yes, Prefix}
+            end;
         _ -> no
     end.
 
diff --git a/lib/dialyzer/test/plt_SUITE.erl b/lib/dialyzer/test/plt_SUITE.erl
index e216981cbe..3c38b0a483 100644
--- a/lib/dialyzer/test/plt_SUITE.erl
+++ b/lib/dialyzer/test/plt_SUITE.erl
@@ -4,13 +4,41 @@
 -module(plt_SUITE).
 
 -include_lib("common_test/include/ct.hrl").
+-include_lib("dialyzer/src/dialyzer.hrl").
 -include("dialyzer_test_constants.hrl").
 
 -export([suite/0, all/0, build_plt/1, beam_tests/1, update_plt/1,
          local_fun_same_as_callback/1,
          remove_plt/1, run_plt_check/1, run_succ_typings/1,
          bad_dialyzer_attr/1, merge_plts/1, bad_record_type/1,
-         letrec_rvals/1, missing_plt_file/1]).
+         letrec_rvals/1,
+         missing_plt_file/1,
+         build_xdg_plt/1,
+         mod_dep_from_behaviour/1,
+         mod_dep_from_record_definition_field_value_default_used/1,
+         mod_dep_from_record_definition_field_value_default_unused/1,
+         mod_dep_from_record_definition_field_type/1,
+         mod_dep_from_overloaded_callback/1,
+         mod_dep_from_exported_overloaded_fun_spec/1,
+         mod_dep_from_unexported_overloaded_fun_spec/1,
+         mod_dep_from_callback_constraint/1,
+         mod_dep_from_unexported_fun_spec_constraint/1,
+         mod_dep_from_exported_fun_spec_constraint/1,
+         mod_dep_from_exported_type/1,
+         mod_dep_from_callback_return/1,
+         mod_dep_from_callback_args/1,
+         mod_dep_from_unexported_opaque_type_args/1,
+         mod_dep_from_exported_opaque_type_args/1,
+         mod_dep_from_unexported_opaque_type/1,
+         mod_dep_from_exported_opaque_type/1,
+         mod_dep_from_unexported_type_args/1,
+         mod_dep_from_exported_type_args/1,
+         mod_dep_from_unexported_fun_spec_args/1,
+         mod_dep_from_exported_fun_spec_args/1,
+         mod_dep_from_unexported_fun_spec_return/1,
+         mod_dep_from_exported_fun_spec_return/1,
+         mod_dep_from_unexported_type/1
+         ]).
 
 suite() ->
   [{timetrap, ?plt_timeout}].
@@ -18,39 +46,65 @@ suite() ->
 all() -> [build_plt, beam_tests, update_plt, run_plt_check,
           remove_plt, run_succ_typings, local_fun_same_as_callback,
           bad_dialyzer_attr, merge_plts, bad_record_type,
-          letrec_rvals, missing_plt_file].
+          letrec_rvals,
+          missing_plt_file,
+          mod_dep_from_behaviour,
+          mod_dep_from_record_definition_field_value_default_used,
+          mod_dep_from_record_definition_field_value_default_unused,
+          mod_dep_from_record_definition_field_type,
+          mod_dep_from_overloaded_callback,
+          mod_dep_from_exported_overloaded_fun_spec,
+          mod_dep_from_unexported_overloaded_fun_spec,
+          mod_dep_from_callback_constraint,
+          mod_dep_from_unexported_fun_spec_constraint,
+          mod_dep_from_exported_fun_spec_constraint,
+          mod_dep_from_exported_type,
+          mod_dep_from_callback_return,
+          mod_dep_from_callback_args,
+          mod_dep_from_unexported_opaque_type_args,
+          mod_dep_from_exported_opaque_type_args,
+          mod_dep_from_unexported_opaque_type,
+          mod_dep_from_exported_opaque_type,
+          mod_dep_from_unexported_type_args,
+          mod_dep_from_exported_type_args,
+          mod_dep_from_unexported_fun_spec_args,
+          mod_dep_from_exported_fun_spec_args,
+          mod_dep_from_unexported_fun_spec_return,
+          mod_dep_from_exported_fun_spec_return,
+          mod_dep_from_unexported_type
+          ].
 
 build_plt(Config) ->
-  OutDir = ?config(priv_dir, Config),
+  OutDir = proplists:get_value(priv_dir, Config),
   case dialyzer_common:check_plt(OutDir) of
     ok   -> ok;
     fail -> ct:fail(plt_build_fail)
   end.
 
 beam_tests(Config) when is_list(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Plt = filename:join(PrivDir, "beam_tests.plt"),
-    Prog = <<"
-              -module(no_auto_import).
+    Src = <<"
+        -module(no_auto_import).
 
-              %% Copied from erl_lint_SUITE.erl, clash6
+        %% Copied from erl_lint_SUITE.erl, clash6
 
-              -export([size/1]).
+        -export([size/1]).
 
-              size([]) ->
-                  0;
-              size({N,_}) ->
-                  N;
-              size([_|T]) ->
-                  1+size(T).
-             ">>,
+        size([]) ->
+            0;
+        size({N,_}) ->
+            N;
+        size([_|T]) ->
+            1+size(T).
+    ">>,
     Opts = [no_auto_import],
-    {ok, BeamFile} = compile(Config, Prog, no_auto_import, Opts),
+    {ok, BeamFile} = compile(Config, Src, no_auto_import, Opts),
     [] = run_dialyzer(plt_build, [BeamFile], [{output_plt, Plt}]),
     ok.
 
 run_plt_check(Config) when is_list(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Plt = filename:join(PrivDir, "run_plt_check.plt"),
     Mod1 = <<"
 	      -module(run_plt_check1).
@@ -106,14 +160,14 @@ run_plt_check(Config) when is_list(Config) ->
 
     {ok, BeamFile2} = compile(Config, Mod2B, run_plt_check2, []),
 
-    % callgraph warning as run_plt_check2:call/1 makes a call to unexported
-    % function run_plt_check1:call/1.
+    %% callgraph warning as run_plt_check2:call/1 makes a call to unexported
+    %% function run_plt_check1:call/1.
     [_] = run_dialyzer(plt_check, [], [{init_plt, Plt}]),
 
     ok.
 
 run_succ_typings(Config) when is_list(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Plt = filename:join(PrivDir, "run_succ_typings.plt"),
     Mod1A = <<"
 	       -module(run_succ_typings1).
@@ -145,11 +199,11 @@ run_succ_typings(Config) when is_list(Config) ->
 
     {ok, BeamFile1} = compile(Config, Mod1B, run_succ_typings1, []),
     {ok, BeamFile2} = compile(Config, Mod2, run_succ_typings2, []),
-    % contract types warning as run_succ_typings2:call/0 makes a call to
-    % run_succ_typings1:call/0, which returns a (not b) in the PLT.
+    %% contract types warning as run_succ_typings2:call/0 makes a call to
+    %% run_succ_typings1:call/0, which returns a (not b) in the PLT.
     [_] = run_dialyzer(succ_typings, [BeamFile2],
                        [{check_plt, false}, {init_plt, Plt}]),
-    % warning not returned as run_succ_typings1 is updated in the PLT.
+    %% warning not returned as run_succ_typings1 is updated in the PLT.
     [] = run_dialyzer(succ_typings, [BeamFile2],
                       [{check_plt, true}, {init_plt, Plt}]),
 
@@ -165,7 +219,7 @@ run_succ_typings(Config) when is_list(Config) ->
 %%% contract types warning, might be emitted when the removed function
 %%% nolonger exists.
 update_plt(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Prog1 = <<"-module(plt_gc).
                -export([one/0]).
                one() ->
@@ -211,7 +265,7 @@ update_plt(Config) ->
 %%% up the callback table. This bug was reported by Brujo Benavides.
 
 local_fun_same_as_callback(Config) when is_list(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Prog1 =
       <<"-module(bad_behaviour).
          -callback bad() -> bad.
@@ -263,7 +317,7 @@ local_fun_same_as_callback(Config) when is_list(Config) ->
 %%% from a PLT when the beam file no longer exists. Dialyzer should not to
 %%% check files exist on disk when removing from the PLT.
 remove_plt(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Prog1 = <<"-module(m1).
                -export([t/0]).
                t() ->
@@ -301,7 +355,7 @@ remove_plt(Config) ->
 %% needs to be updated when/if the Dialyzer can analyze Core Erlang
 %% without compiling abstract code.
 bad_dialyzer_attr(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Source = lists:concat([dial, ".erl"]),
     Filename = filename:join(PrivDir, Source),
     ok = dialyzer_common:check_plt(PrivDir),
@@ -378,7 +432,7 @@ types() ->
 	     ">>,
     {Mod1, Mod2}.
 
-callbacks() -> % A very shallow test.
+callbacks() -> %% A very shallow test.
     Mod1 = <<"-module(merge_plts_1).
               -callback t() -> merge_plts_2:t().
 	      ">>,
@@ -389,7 +443,7 @@ callbacks() -> % A very shallow test.
     {Mod1, Mod2}.
 
 create_plts(Mod1, Mod2, Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Plt1 = filename:join(PrivDir, "merge_plts_1.plt"),
     Plt2 = filename:join(PrivDir, "merge_plts_2.plt"),
     ErlangBeam = erlang_beam(),
@@ -404,7 +458,7 @@ create_plts(Mod1, Mod2, Config) ->
 %% End of merge_plts().
 
 bad_record_type(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Source = lists:concat([bad_record_type, ".erl"]),
     Filename = filename:join(PrivDir, Source),
     PltFilename = dialyzer_common:plt_file(PrivDir),
@@ -430,7 +484,7 @@ bad_record_type(Config) ->
     ok.
 
 letrec_rvals(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     Plt = filename:join(PrivDir, "letrec_rvals.plt"),
     Prog = <<"
 -module(letrec_rvals).
@@ -465,7 +519,7 @@ check_done(_) ->
 
 %% GH-4501
 missing_plt_file(Config) ->
-    PrivDir = ?config(priv_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
     PltFile = filename:join(PrivDir, "missing_plt_file.plt"),
     Prog2 = <<"-module(missing_plt_file2).
               t() -> foo.">>,
@@ -521,6 +575,316 @@ check(PltFile, _BeamFile2) ->
     dialyzer:run([{plts,[PltFile]},
                   {analysis_type, plt_check}]).
 
+mod_dep_from_record_definition_field_value_default_unused(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -record(my_record,
+        { num_field = type_deps:get_num() :: number(),
+          str_field,
+          bool_field
+        }).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, []}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_record_definition_field_value_default_used(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export([f/0]).
+
+      -record(my_record,
+        { num_field = type_deps:get_num() :: number(),
+          str_field,
+          bool_field
+        }).
+
+      f() -> #my_record{str_field = \"foo\", bool_field = true}. % type_deps:get_num() used implicitly here
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_behaviour(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -behaviour(type_deps).
+      -export([quux/1]).
+
+      quux(N) -> N + 1. % Depends on behaviour module to check the callback implementation
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_record_definition_field_type(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -record(my_record,
+        { num_field = 1 :: type_deps:number_like(),
+          str_field,
+          bool_field
+        }).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_overloaded_callback(Config) ->
+    DependerSrc1 = <<"
+      -module(depender).
+
+      -callback f(string()) -> string()
+                ; (type_deps:number_like()) -> type_deps:number_like().
+      ">>,
+    DependerSrc2 = <<"
+      -module(depender).
+
+      -callback f(type_deps:number_like()) -> type_deps:number_like()
+                ; (string()) -> string().
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc1, ExpectedTypeDepsInPlt),
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc2, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_overloaded_fun_spec(Config) ->
+    DependerSrc1 = <<"
+      -module(depender).
+      -export([f/1]).
+
+      -spec f({a, atom()}) -> atom()
+            ; ({n, type_deps:number_like()}) -> type_deps:number_like().
+      f({a, X}) when is_atom(X) -> X;
+      f({n, X}) when is_number(X) -> X.
+      ">>,
+    DependerSrc2 = <<"
+      -module(depender).
+      -export([f/1]).
+
+      -spec f({n, type_deps:number_like()}) -> type_deps:number_like()
+            ; ({a, atom()}) -> atom().
+      f({n, X}) when is_number(X) -> X;
+      f({a, X}) when is_atom(X) -> X.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc1, ExpectedTypeDepsInPlt),
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc2, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_overloaded_fun_spec(Config) ->
+    DependerSrc1 = <<"
+      -module(depender).
+      -compile({nowarn_unused_function, [f/1]}).
+
+      -spec f({a, atom()}) -> atom()
+            ; ({n, type_deps:number_like()}) -> type_deps:number_like().
+      f({a, X}) when is_atom(X) -> X;
+      f({n, X}) when is_number(X) -> X.
+      ">>,
+    DependerSrc2 = <<"
+      -module(depender).
+      -compile({nowarn_unused_function, [f/1]}).
+
+      -spec f({n, type_deps:number_like()}) -> type_deps:number_like()
+            ; ({a, atom()}) -> atom().
+      f({n, X}) when is_number(X) -> X;
+      f({a, X}) when is_atom(X) -> X.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc1, ExpectedTypeDepsInPlt),
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc2, ExpectedTypeDepsInPlt).
+
+mod_dep_from_callback_constraint(Config) ->
+    DependerSrc1 = <<"
+      -module(depender).
+
+      -callback f(X) -> string() when X :: type_deps:number_like().
+      ">>,
+    DependerSrc2 = <<"
+      -module(depender).
+
+      -callback f(X :: type_deps:number_like()) -> string().
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc1, ExpectedTypeDepsInPlt),
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc2, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_fun_spec_constraint(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -compile({nowarn_unused_function, [f/1]}).
+
+      -spec f(N) -> number() when N :: type_deps:number_like().
+      f(N) -> N.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_fun_spec_constraint(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export([f/1]).
+
+      -spec f(N) -> number() when N :: type_deps:number_like().
+      f(N) -> N.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_callback_return(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -callback f(string()) -> type_deps:number_like().
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_callback_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -callback f(type_deps:number_like()) -> string().
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_opaque_type(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -opaque my_type() :: {string(), type_deps:number_like()}.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_opaque_type(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export_type([my_type/0]).
+
+      -opaque my_type() :: {string(), type_deps:number_like()}.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_opaque_type_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -type my_type() :: type_deps:my_opaque(number()).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_opaque_type_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export_type([my_type/0]).
+
+      -type my_type() :: type_deps:my_opaque(number()).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_type_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -type my_type() :: {string(), type_deps:number_like()}.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_type_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export_type([my_type/0]).
+
+      -type my_type() :: {string(), type_deps:number_like()}.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_fun_spec_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -compile({nowarn_unused_function, [f/1]}).
+
+      -spec f(type_deps:number_like()) -> number().
+      f(N) -> N.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_fun_spec_args(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export([f/1]).
+
+      -spec f(N :: type_deps:number_like()) -> number().
+      f(N) -> N.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_fun_spec_return(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -compile({nowarn_unused_function, [f/0]}).
+
+      -spec f() -> type_deps:number_like().
+      f() -> 1.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_fun_spec_return(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export([f/0]).
+
+      -spec f() -> type_deps:number_like().
+      f() -> 1.
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_unexported_type(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+
+      -type my_type() :: type_deps:list_like(number()).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+mod_dep_from_exported_type(Config) ->
+    DependerSrc = <<"
+      -module(depender).
+      -export_type([my_type/0]).
+
+      -type my_type() :: type_deps:list_like(number()).
+      ">>,
+    ExpectedTypeDepsInPlt = [{depender, []}, {type_deps, [depender]}],
+    ok = check_plt_deps(Config, ?FUNCTION_NAME, DependerSrc, ExpectedTypeDepsInPlt).
+
+check_plt_deps(Config, TestName, DependerSrc, ExpectedTypeDepsInPltUnsorted) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    PltFile = filename:join(PrivDir, atom_to_list(TestName) ++ ".plt"),
+    {ok, DepsBeamFile} = compile(Config, type_deps, []),
+    {ok, DependerBeamFile} = compile(Config, DependerSrc, depender, []),
+    [] = run_dialyzer(plt_build, [DependerBeamFile, DepsBeamFile], [{output_plt, PltFile}]),
+    {_ResPlt, #plt_info{mod_deps = DepsByModule}} = dialyzer_plt:plt_and_info_from_file(PltFile),
+
+    ActualTypeDepsInPlt =
+      lists:sort(dict:to_list(dict:erase(erlang, DepsByModule))),
+    ExpectedTypeDepsInPlt =
+      lists:usort(ExpectedTypeDepsInPltUnsorted),
+
+    ?assertEqual(
+      ExpectedTypeDepsInPlt,
+      ActualTypeDepsInPlt,
+      {missing, ExpectedTypeDepsInPlt -- ActualTypeDepsInPlt,
+       extra, ActualTypeDepsInPlt -- ExpectedTypeDepsInPlt}).
+
 erlang_beam() ->
     case code:where_is_file("erlang.beam") of
         non_existing ->
@@ -531,9 +895,20 @@ erlang_beam() ->
             EBeam
     end.
 
+%% Builds the named module using the source in the plt_SUITE_data dir
+compile(Config, Module, CompileOpts) ->
+    Source = lists:concat([Module, ".erl"]),
+    PrivDir = proplists:get_value(priv_dir,Config),
+    DataDir = proplists:get_value(data_dir,Config),
+    SrcFilename = filename:join([DataDir, Source]),
+    Opts = [{outdir, PrivDir}, debug_info | CompileOpts],
+    {ok, Module} = compile:file(SrcFilename, Opts),
+    {ok, filename:join([PrivDir, lists:concat([Module, ".beam"])])}.
+
+%% Builds the named module using the literal source given
 compile(Config, Prog, Module, CompileOpts) ->
     Source = lists:concat([Module, ".erl"]),
-    PrivDir = ?config(priv_dir,Config),
+    PrivDir = proplists:get_value(priv_dir,Config),
     Filename = filename:join([PrivDir, Source]),
     ok = file:write_file(Filename, Prog),
     Opts = [{outdir, PrivDir}, debug_info | CompileOpts],
diff --git a/lib/dialyzer/test/plt_SUITE_data/type_deps.erl b/lib/dialyzer/test/plt_SUITE_data/type_deps.erl
new file mode 100644
index 0000000000..f6fcfc3d23
--- /dev/null
+++ b/lib/dialyzer/test/plt_SUITE_data/type_deps.erl
@@ -0,0 +1,18 @@
+-module(type_deps).
+
+-export([func/1, get_num/0]).
+
+-export_type([number_like/0, my_opaque/1, list_like/1]).
+
+-type number_like() :: number().
+-type list_like(X) :: [X].
+-opaque my_opaque(X) :: {X,X}.
+
+-callback quux(number()) -> number().
+
+-spec func(T) -> T.
+func(X) ->
+  X + X.
+
+get_num() ->
+  3.
-- 
2.31.1

openSUSE Build Service is sponsored by