Skip to content

Commit

Permalink
Check behaviours in the parallel checker
Browse files Browse the repository at this point in the history
  • Loading branch information
marcandre committed Aug 29, 2022
1 parent be33d05 commit c0c2d65
Show file tree
Hide file tree
Showing 5 changed files with 77 additions and 26 deletions.
5 changes: 2 additions & 3 deletions lib/elixir/lib/module.ex
Original file line number Diff line number Diff line change
Expand Up @@ -1802,11 +1802,10 @@ defmodule Module do
defp args_count([], total, defaults), do: {total, defaults}

@doc false
def check_derive_behaviours_and_impls(env, set, bag, all_definitions) do
def check_derive_behaviours_and_impls(env, set, bag) do
check_derive(env, set, bag)
behaviours = bag_lookup_element(bag, {:accumulate, :behaviour}, 2)
impls = bag_lookup_element(bag, :impls, 2)
Module.Behaviour.check_behaviours_and_impls(env, behaviours, impls, all_definitions)
Module.Behaviour.force_runtime_dependencies(behaviours, env)

:ok
end
Expand Down
44 changes: 25 additions & 19 deletions lib/elixir/lib/module/behaviour.ex
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@ defmodule Module.Behaviour do
end

@doc false
def check_behaviours_and_impls(env, behaviours, impls, all_definitions) do
context = check_behaviours(context(env), behaviours)
def check_behaviours_and_impls(module, file, line, behaviours, impls, all_definitions) do
context = check_behaviours(context(module, file, line), behaviours)

context =
if impls != [] do
Expand All @@ -25,20 +25,28 @@ defmodule Module.Behaviour do

context = check_callbacks(context, all_definitions)

for warning <- context.warnings do
{__MODULE__, message, {file, line, _module}} = warning
context.warnings
end

message
|> format_warning()
|> Enum.join()
|> IO.warn(%{context.env | file: file, line: line})
@doc false
# While `@behaviour MyBehaviour` will naturally introduce a runtime dependency,
# `@behaviour :"Elixir.MyBehaviour"` or similar would not.
# We force this dependency by adding the call to `MyBehaviour.behaviour_info/1`
def force_runtime_dependencies(behaviours, env) do
info_env = %{env | function: {:__info__, 1}}

for behaviour <- behaviours do
:elixir_env.trace({:remote_function, [], behaviour, :behaviour_info, 1}, info_env)
end

:ok
end

defp context(env) do
defp context(module, file, line) do
%{
# Macro.Env
env: env,
module: module,
file: file,
line: line,
# Map containing the callbacks to be implemented
callbacks: %{},
# list of warnings {message, env}
Expand All @@ -47,8 +55,7 @@ defmodule Module.Behaviour do
end

defp warn(context, warning, meta \\ []) do
location =
{meta[:file] || context.env.file, meta[:line] || context.env.line, context.env.module}
location = {meta[:file] || context.file, meta[:line] || context.line, context.module}

update_in(context.warnings, &[{__MODULE__, warning, location} | &1])
end
Expand All @@ -57,13 +64,12 @@ defmodule Module.Behaviour do
Enum.reduce(behaviours, context, fn behaviour, context ->
cond do
not Code.ensure_loaded?(behaviour) ->
warn(context, {:undefined_behaviour, context.env.module, behaviour})
warn(context, {:undefined_behaviour, context.module, behaviour})

not function_exported?(behaviour, :behaviour_info, 1) ->
warn(context, {:module_does_not_define_behaviour, context.env.module, behaviour})
warn(context, {:module_does_not_define_behaviour, context.module, behaviour})

true ->
:elixir_env.trace({:require, [from_macro: true], behaviour, []}, context.env)
optional_callbacks = behaviour_info(behaviour, :optional_callbacks)
callbacks = behaviour_info(behaviour, :callbacks)
Enum.reduce(callbacks, context, &add_callback(&2, &1, behaviour, optional_callbacks))
Expand All @@ -79,7 +85,7 @@ defmodule Module.Behaviour do
%{^callback => {_kind, conflict, _optional?}} ->
warn(
context,
{:duplicate_behaviour, context.env.module, behaviour, conflict, kind, callback}
{:duplicate_behaviour, context.module, behaviour, conflict, kind, callback}
)

%{} ->
Expand All @@ -95,12 +101,12 @@ defmodule Module.Behaviour do
context ->
case :lists.keyfind(callback, 1, all_definitions) do
false when not optional? ->
warn(context, {:missing_callback, context.env.module, callback, kind, behaviour})
warn(context, {:missing_callback, context.module, callback, kind, behaviour})

{_, wrong_kind, _, _} when kind != wrong_kind ->
warn(
context,
{:callback_mismatch, context.env.module, callback, kind, wrong_kind, behaviour}
{:callback_mismatch, context.module, callback, kind, wrong_kind, behaviour}
)

_ ->
Expand Down
22 changes: 20 additions & 2 deletions lib/elixir/lib/module/parallel_checker.ex
Original file line number Diff line number Diff line change
Expand Up @@ -214,17 +214,35 @@ defmodule Module.ParallelChecker do
## Module checking

defp check_module(module_map, cache) do
%{module: module, file: file, compile_opts: compile_opts, definitions: definitions} =
module_map
%{
module: module,
file: file,
line: line,
compile_opts: compile_opts,
definitions: definitions,
uses_behaviours: uses_behaviours,
impls: impls
} = module_map

no_warn_undefined =
compile_opts
|> extract_no_warn_undefined()
|> merge_compiler_no_warn_undefined()

behaviour_warnings =
Module.Behaviour.check_behaviours_and_impls(
module,
file,
line,
uses_behaviours,
impls,
definitions
)

warnings =
module
|> Module.Types.warnings(file, definitions, no_warn_undefined, cache)
|> Kernel.++(behaviour_warnings)
|> group_warnings()
|> emit_warnings()

Expand Down
8 changes: 6 additions & 2 deletions lib/elixir/src/elixir_module.erl
Original file line number Diff line number Diff line change
Expand Up @@ -127,11 +127,13 @@ compile(Line, Module, Block, Vars, E) ->
make_readonly(Module),

(not elixir_config:is_bootstrap()) andalso
'Elixir.Module':check_derive_behaviours_and_impls(E, DataSet, DataBag, AllDefinitions),
'Elixir.Module':check_derive_behaviours_and_impls(E, DataSet, DataBag),

RawCompileOpts = bag_lookup_element(DataBag, {accumulate, compile}, 2),
CompileOpts = validate_compile_opts(RawCompileOpts, AllDefinitions, Unreachable, File, Line),
AfterVerify = bag_lookup_element(DataBag, {accumulate, after_verify}, 2),
UsesBehaviours = bag_lookup_element(DataBag, {accumulate, behaviour}, 2),
Impls = bag_lookup_element(DataBag, impls, 2),

ModuleMap = #{
struct => get_struct(DataSet),
Expand All @@ -145,7 +147,9 @@ compile(Line, Module, Block, Vars, E) ->
after_verify => AfterVerify,
compile_opts => CompileOpts,
deprecated => get_deprecated(DataBag),
defines_behaviour => defines_behaviour(DataBag)
defines_behaviour => defines_behaviour(DataBag),
uses_behaviours => UsesBehaviours,
impls => Impls
},

Binary = elixir_erl:compile(ModuleMap),
Expand Down
24 changes: 24 additions & 0 deletions lib/mix/test/mix/tasks/xref_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -268,6 +268,30 @@ defmodule Mix.Tasks.XrefTest do
assert_trace("lib/b.ex", files, output)
end

test "shows module with `@behaviour` calling `behaviour_info/1`" do
files = %{
"lib/a.ex" => ~S"""
defmodule A do
@callback fun() :: integer
end
""",
"lib/b.ex" => ~S"""
defmodule B do
@behaviour :"Elixir.A"
def fun, do: 42
end
"""
}

output = """
Compiling 2 files (.ex)
Generated sample app
lib/b.ex:1: call A.behaviour_info/1 (runtime)
"""

assert_trace("lib/b.ex", files, output)
end

test "filters per label" do
files = %{
"lib/a.ex" => ~S"""
Expand Down

0 comments on commit c0c2d65

Please sign in to comment.