Skip to content

Commit d757f31

Browse files
author
José Valim
committed
Unused functions with cyclic dependencies are now also warned as unused
Closes #1105
1 parent 9a0f810 commit d757f31

15 files changed

+328
-75
lines changed

CHANGELOG.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
* bug fix
66
* [Dict] `Enum.to_list` and `Dict.to_list` now return the same results for dicts
77
* [Kernel] Fix a bug where `unquote_splicing` did not work on the left side of a stab op
8+
* [Kernel] Unused functions with cyclic dependencies are now also warned as unused
89
* [Mix] Fix a bug where `mix deps.get` was not retrieving nested dependencies
910
* [Record] Fix a bug where nested records cannot be defined
1011

lib/elixir/include/elixir.hrl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@
1616
name_args=false, %% when true, it means arguments should be named
1717
module=nil, %% the current module
1818
function=nil, %% the current function
19+
function_kind=nil, %% the current function kind
1920
vars=[], %% a dict of defined variables and their alias
2021
temp_vars=[], %% a dict of all variables defined in a particular assign
2122
clause_vars=nil, %% a dict of all variables defined in a particular clause

lib/elixir/lib/gen_server/behaviour.ex

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ defmodule GenServer.Behaviour do
104104
{ :noreply, state }
105105
end
106106

107-
def terminate(reason, state) do
107+
def terminate(_reason, _state) do
108108
:ok
109109
end
110110

Lines changed: 132 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,132 @@
1+
# This is a module Elixir responsible for tracking
2+
# local calls in order to emit proper warnings when
3+
# any local private function is unused.
4+
#
5+
# Since this is required for bootstrap, we can't use
6+
# any of the GenServer.Behaviour conveniences.
7+
defmodule Kernel.LocalsTracker do
8+
@moduledoc false
9+
10+
@timeout 30_000
11+
@behavior :gen_server
12+
13+
def start_link do
14+
{ :ok, pid } = :gen_server.start_link(__MODULE__, [], [])
15+
pid
16+
end
17+
18+
def add_definition(pid, kind, tuple) when kind in [:def, :defp, :defmacro, :defmacrop] do
19+
:gen_server.cast(pid, { :vertex, kind, tuple })
20+
end
21+
22+
def add_dispatch(pid, from, to) do
23+
:gen_server.cast(pid, { :edge, from, to })
24+
end
25+
26+
def reachable(pid) do
27+
:gen_server.call(pid, :reachable, @timeout)
28+
end
29+
30+
def collect_unused(pid, private) do
31+
# Add a vertex for each private given
32+
lc { tuple, kind, _defaults } inlist private do
33+
add_definition(pid, kind, tuple)
34+
end
35+
36+
# Process all unused
37+
reachable = reachable(pid)
38+
:lists.foldl(collect_unused(&1, &2, reachable), [], private)
39+
end
40+
41+
defp collect_unused({ tuple, kind, 0 }, acc, reachable) do
42+
if :lists.member(tuple, reachable) do
43+
acc
44+
else
45+
[{ :unused_def, tuple, kind }|acc]
46+
end
47+
end
48+
49+
defp collect_unused({ tuple, kind, default }, acc, reachable) when default > 0 do
50+
{ name, arity } = tuple
51+
min = arity - default
52+
max = arity
53+
54+
invoked = lc { n, a } inlist reachable, n == name, a in min..max, do: a
55+
56+
if invoked == [] do
57+
[{ :unused_def, tuple, kind }|acc]
58+
else
59+
case :lists.min(invoked) - min do
60+
0 -> acc
61+
^default -> [{ :unused_args, tuple }|acc]
62+
unused_args -> [{ :unused_args, tuple, unused_args }|acc]
63+
end
64+
end
65+
end
66+
67+
def stop(pid) do
68+
:gen_server.cast(pid, :stop)
69+
end
70+
71+
# Callbacks
72+
73+
def init([]) do
74+
d = :digraph.new
75+
:digraph.add_vertex(d, :root)
76+
{ :ok, d }
77+
end
78+
79+
def handle_call(:reachable, _from, d) do
80+
{ :reply, reduce_reachable(d, :root, []), d }
81+
end
82+
83+
def handle_call(_request, _from, d) do
84+
{ :noreply, d }
85+
end
86+
87+
def handle_info(_msg, d) do
88+
{ :noreply, d }
89+
end
90+
91+
def handle_cast({ :edge, from, to }, d) do
92+
:digraph.add_vertex(d, to)
93+
[:"$e"|_] = :digraph.add_edge(d, from, to)
94+
{ :noreply, d }
95+
end
96+
97+
def handle_cast({ :vertex, public, tuple }, d) when public in [:def, :defmacro] do
98+
:digraph.add_vertex(d, tuple)
99+
:digraph.add_edge(d, :root, tuple)
100+
{ :noreply, d }
101+
end
102+
103+
def handle_cast({ :vertex, private, tuple }, d) when private in [:defp, :defmacrop] do
104+
:digraph.add_vertex(d, tuple)
105+
{ :noreply, d }
106+
end
107+
108+
def handle_cast(:stop, d) do
109+
{ :stop, :normal, d }
110+
end
111+
112+
def handle_cast(_msg, d) do
113+
{ :noreply, d }
114+
end
115+
116+
def terminate(_reason, _d) do
117+
:ok
118+
end
119+
120+
def code_change(_old, d, _extra) do
121+
{ :ok, d }
122+
end
123+
124+
# Helpers
125+
126+
defp reduce_reachable(d, vertex, vertices) do
127+
neighbours = :digraph.out_neighbours(d, vertex)
128+
remaining = neighbours -- vertices
129+
vertices = neighbours ++ vertices
130+
:lists.foldl(reduce_reachable(d, &1, &2), vertices, remaining)
131+
end
132+
end

lib/elixir/lib/macro/env.ex

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ defmodule Macro.Env do
1212
* `function` - a tuple as `{ atom, integer` }, where the first
1313
element is the function name and the seconds its arity. Returns
1414
`nil` if not inside a function
15+
* `function_kind` - the kind of the function (`def`, `defp`, etc)
1516
* `aliases` - a list of two item tuples, where the first
1617
item is the aliased name and the second the actual name
1718
* `context` - the context of the environment. It can be nil
@@ -31,13 +32,15 @@ defmodule Macro.Env do
3132
@type functions :: [{ module, [name_arity] }]
3233
@type macros :: [{ module, [name_arity] }]
3334
@type context_modules :: [module]
35+
@type function_kind :: :def | :defp | :defmacro | :defmacrop
3436

35-
fields = [:module, :file, :line, :function, :aliases,
36-
:context, :requires, :functions, :macros, :context_modules]
37+
fields = [:module, :file, :line, :function, :aliases, :context, :requires,
38+
:functions, :macros, :context_modules, :function_kind]
3739

3840
types = quote do: [module: module, file: file, line: line,
3941
function: name_arity, aliases: aliases, requires: requires,
40-
functions: functions, macros: macros, context_modules: context_modules]
42+
functions: functions, macros: macros, context_modules: context_modules,
43+
function_kind: function_kind]
4144

4245
Record.deffunctions(fields, __MODULE__)
4346
Record.deftypes(fields, types, __MODULE__)

lib/elixir/src/elixir_compiler.erl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -225,6 +225,7 @@ core_main() ->
225225
"lib/elixir/lib/kernel/cli.ex",
226226
"lib/elixir/lib/kernel/error_handler.ex",
227227
"lib/elixir/lib/kernel/parallel_compiler.ex",
228+
"lib/elixir/lib/kernel/locals_tracker.ex",
228229
"lib/elixir/lib/kernel/record_rewriter.ex"
229230
].
230231

lib/elixir/src/elixir_def.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,7 @@ store_definition(Kind, Line, _CheckClauses, nil, _Name, _Args, _Guards, _Body, #
110110

111111
store_definition(Kind, Line, CheckClauses, Module, Name, Args, Guards, Body, #elixir_scope{} = DS) ->
112112
Arity = length(Args),
113-
S = DS#elixir_scope{function={Name,Arity}, module=Module},
113+
S = DS#elixir_scope{module=Module, function={Name,Arity}, function_kind=Kind},
114114

115115
CO = elixir_compiler:get_opts(),
116116
Location = retrieve_file(Line, Module, S, CO),

lib/elixir/src/elixir_def_local.erl

Lines changed: 52 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,53 @@
11
%% Module responsible for local invocation of macros and functions.
22
-module(elixir_def_local).
33
-export([
4-
macro_for/3,
5-
function_for/3,
6-
format_error/1,
7-
check_unused_local/3
4+
setup/1, cleanup/1,
5+
record/2, record_root/2,
6+
macro_for/3, function_for/3,
7+
check_unused_local/3, format_error/1
88
]).
99
-include("elixir.hrl").
1010

11+
-define(attr, '__locals_tracker').
12+
-define(tracker, 'Elixir.Kernel.LocalsTracker').
13+
14+
setup(Module) ->
15+
case code:ensure_loaded(?tracker) of
16+
{ module, _ } -> ets:insert(Module, { ?attr, ?tracker:start_link() });
17+
{ error, _ } -> ok
18+
end.
19+
20+
cleanup(Module) ->
21+
if_tracker(Module, fun(Pid) -> ?tracker:stop(Pid) end).
22+
23+
record(Tuple, #elixir_scope{function=Function})
24+
when Function == nil; Function == Tuple -> false;
25+
record(Tuple, #elixir_scope{module=Module, function=Function, function_kind=Kind}) ->
26+
if_tracker(Module, fun(Pid) ->
27+
?tracker:add_definition(Pid, Kind, Function),
28+
?tracker:add_dispatch(Pid, Function, Tuple),
29+
true
30+
end).
31+
32+
record_root(Module, Tuple) ->
33+
if_tracker(Module, fun(Pid) ->
34+
?tracker:add_dispatch(Pid, root, Tuple),
35+
true
36+
end).
37+
38+
if_tracker(Module, Callback) ->
39+
case ets:lookup(Module, ?attr) of
40+
[{ ?attr, Pid }] -> Callback(Pid);
41+
_ -> false
42+
end.
43+
1144
%% Used by elixir_dispatch, returns false if no macro is found
1245
macro_for(_Tuple, _All, #elixir_scope{module=nil}) -> false;
1346

1447
macro_for(Tuple, All, #elixir_scope{module=Module} = S) ->
1548
try elixir_def:lookup_definition(Module, Tuple) of
1649
{ { Tuple, Kind, Line, _, _, _, _ }, Clauses } when Kind == defmacro; All, Kind == defmacrop ->
17-
elixir_import:record_local(Tuple, S),
50+
record(Tuple, S),
1851
get_function(Line, Module, Clauses);
1952
_ ->
2053
false
@@ -72,40 +105,18 @@ rewrite_clause(Else, _) -> Else.
72105

73106
%% Error handling
74107

75-
check_unused_local(File, Recorded, Private) ->
76-
[check_unused_local(Fun, Kind, Line, File, Defaults, Recorded) ||
77-
{ Fun, Kind, Line, true, Defaults } <- Private].
78-
79-
check_unused_local(Fun, Kind, Line, File, 0, Recorded) ->
80-
not(lists:member(Fun, Recorded)) andalso
81-
elixir_errors:handle_file_warning(File, { Line, ?MODULE, { unused_def, Kind, Fun } });
108+
check_unused_local(File, Module, Private) ->
109+
if_tracker(Module, fun(Pid) ->
110+
Args = [ { Fun, Kind, Defaults } ||
111+
{ Fun, Kind, _Line, true, Defaults } <- Private],
82112

83-
check_unused_local({ Name, Arity } = Fun, Kind, Line, File, Defaults, Recorded) when Defaults > 0 ->
84-
Min = Arity - Defaults,
85-
Max = Arity,
113+
Unused = ?tracker:collect_unused(Pid, Args),
86114

87-
Invoked = [A || { N, A } <- Recorded, A >= Min, A =< Max, N == Name],
88-
89-
case Invoked of
90-
[] ->
91-
elixir_errors:handle_file_warning(File, { Line, ?MODULE, { unused_def, Kind, Fun } });
92-
_ ->
93-
UnusedArgs = lists:min(Invoked) - Min,
94-
if
95-
UnusedArgs == 0 ->
96-
ok;
97-
UnusedArgs == Defaults ->
98-
elixir_errors:handle_file_warning(File, { Line, ?MODULE, { unused_args, Fun } });
99-
true ->
100-
elixir_errors:handle_file_warning(File, { Line, ?MODULE, { unused_args, Fun, UnusedArgs } })
101-
end
102-
end;
103-
104-
check_unused_local(_Fun, _Kind, _Line, _File, _Defaults, _Recorded) ->
105-
ok.
106-
107-
format_error({unused_def,defp,{Name, Arity}}) ->
108-
io_lib:format("function ~ts/~B is unused", [Name, Arity]);
115+
[ begin
116+
{ _, _, Line, _, _ } = lists:keyfind(element(2, Error), 1, Private),
117+
elixir_errors:handle_file_warning(File, { Line, ?MODULE, Error })
118+
end || Error <- Unused ]
119+
end).
109120

110121
format_error({unused_args,{Name, Arity}}) ->
111122
io_lib:format("default arguments in ~ts/~B are never used", [Name, Arity]);
@@ -116,5 +127,8 @@ format_error({unused_args,{Name, Arity},1}) ->
116127
format_error({unused_args,{Name, Arity},Count}) ->
117128
io_lib:format("the first ~B default arguments in ~ts/~B are never used", [Count, Name, Arity]);
118129

119-
format_error({unused_def,defmacrop,{Name, Arity}}) ->
130+
format_error({unused_def,{Name, Arity},defp}) ->
131+
io_lib:format("function ~ts/~B is unused", [Name, Arity]);
132+
133+
format_error({unused_def,{Name, Arity},defmacrop}) ->
120134
io_lib:format("macro ~ts/~B is unused", [Name, Arity]).

lib/elixir/src/elixir_dispatch.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import_function(Meta, Name, Arity, S) ->
4141
{ import, Receiver } ->
4242
require_function(Meta, Receiver, Name, Arity, S);
4343
nomatch ->
44-
elixir_import:record_local(Tuple, S),
44+
elixir_def_local:record(Tuple, S),
4545
{ { 'fun', ?line(Meta), { function, Name, Arity } }, S }
4646
end.
4747

lib/elixir/src/elixir_import.erl

Lines changed: 6 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,19 @@
22
%% in between local functions and imports.
33
%% For imports dispatch, please check elixir_dispatch.
44
-module(elixir_import).
5-
-export([import/5, record_local/2, recorded_locals/1, format_error/1,
5+
-export([import/5, format_error/1,
66
ensure_no_import_conflict/4, ensure_no_local_conflict/4,
77
ensure_all_imports_used/3,
88
build_table/1, delete_table/1, record/3]).
99
-include("elixir.hrl").
1010

1111
%% This table keeps:
1212
%%
13-
%% * Invoked imports and requires in the format { { Name, Arity }, Module }
14-
%% * The current warn status imports and requires in the format { Module, Line :: integer }
15-
%% * Invoked locals in the format { { Name, Arity }, Public :: boolean }
13+
%% * Invoked imports and requires in the format
14+
%% { { Name, Arity }, Module }
15+
%
16+
%% * The current warn status imports and requires
17+
%% in the format { Module, Line :: integer }
1618
%%
1719
table(Module) -> ?atom_concat([i, Module]).
1820

@@ -30,11 +32,6 @@ record(Tuple, Receiver, Module) ->
3032
error:badarg -> false
3133
end.
3234

33-
record_local(Tuple, #elixir_scope{function=Function})
34-
when Function == nil; Function == Tuple -> false;
35-
record_local(Tuple, #elixir_scope{module=Module}) ->
36-
record(Tuple, true, Module).
37-
3835
record_warn(_Meta, _Ref, _Opts, #elixir_scope{module=nil}) -> false;
3936
record_warn(Meta, Ref, Opts, S) ->
4037
Table = table(S#elixir_scope.module),
@@ -49,16 +46,6 @@ record_warn(Meta, Ref, Opts, S) ->
4946

5047
Warn andalso ets:insert(Table, { Ref, ?line(Meta) }).
5148

52-
recorded_locals(Module) ->
53-
Table = table(Module),
54-
Match = module_local_spec(),
55-
Result = ets:select(Table, Match),
56-
ets:select_delete(Table, Match),
57-
Result.
58-
59-
module_local_spec() ->
60-
[{ { '$1', '$2' }, [{ 'orelse', {'==','$2',true}, {'==','$2',false} }], ['$1'] }].
61-
6249
%% IMPORT HELPERS
6350

6451
%% Update the scope to consider the imports for aliases

0 commit comments

Comments
 (0)