otp icon indicating copy to clipboard operation
otp copied to clipboard

Can we add a way to specify dynamic callbacks?

Open elbrujohalcon opened this issue 3 years ago • 9 comments

There are behaviors where the callback function list includes 1-to-n functions with unspecified names but a particular arity. Examples of this are ct_suite's Module:TestCase/0 and Module:TestCase/1, and gen_statem's Module:StateName/3 in all its variants. These callbacks, which I would like to call dynamic callbacks, are only specified in the documentation (particularly in the XML files that correspond to the modules describing the behaviors). For tools like rebar3_hank and likely others (probably dialyzer among them), it would be very convenient to have them specified along with the regular callbacks.

Describe the solution you'd like

I would like to be able to add callback specifications like the following one:

-callback Testcase() -> [ct_info()].

And I would like to get that information out of Module:behavior_info(callbacks), maybe with something like this…

1> ct_suite:behaviour_info(callbacks).
[{all,0},
 {groups,0},
 {suite,0},
 {init_per_suite,1},
 {end_per_suite,1},
 {group,1},
 {init_per_group,2},
 {end_per_group,2},
 {init_per_testcase,2},
 {end_per_testcase,2},
 {"TestCase", 0},
 {"TestCase", 3}]

It can be a string (as I showed above) or any other term that you find suitable. I originally considered using '_' but that will lose information. Maybe {dynamic, "TestCase", 0} can work, too. Whatever is easier.

Additional context We discussed this issue in https://github.com/AdRoll/rebar3_hank/pull/124#issuecomment-841066228

elbrujohalcon avatar May 18 '21 18:05 elbrujohalcon

@elbrujohalcon, I'd also like to see some form of this make it into Erlang. At the same time, I'm curious as to how that type of declaration would allow us to distinguish between a regular exported function and a callback; maybe the distinction isn't important (?).

e.g.

-module(the_module).

-behaviour(ct_suite). % declaring -callback Testcase() -> [ct_info()].

-export([fun_a/0]).
-export([fun_b/0]).

...

fun_a() ->
    return_for_a.

fun_b() ->
    return_for_b.

☝️ does this mean both exported functions should be considered potential callbacks? Wouldn't that confuse e.g. hank?

paulo-ferraz-oliveira avatar May 19 '21 09:05 paulo-ferraz-oliveira

To answer that, we should dive a bit into Hank to learn how he deals with behaviors for the unnecesary_function_arguments rule.

Let's start with the goal of that rule

The rule emits a warning for each function argument that is consistently ignored in all function clauses.

So… for a function like…

handle_call(Msg, _From, State) -> do_the_call(Msg, State).

…it should emit a warning stating that you don't really need its second argument.

But if the module is a gen_server implementation, that would be a mistake.

That's why, to avoid false positives like that, the rule checks if your module is implementing a behavior. Let's imagine there are no dynamic callbacks for a minute like we originally did in AdRoll/rebar3_hank#40. If Hank is analyzing a gen_server implementation with the function above, before emitting a warning, it can call gen_server:behavior_info(callbacks) and verify that handle_call/3 is in that list. Therefore that function is a callback, and no warning should be emitted. As discussed on that ticket, there are ways to do that for all behaviors, so that would be great.

Now, let's go back to the real world:tm:…

Behaviors like gen_statem, gen_fsm and ct_suite expect callbacks with no previously specified name (just arity), a.k.a. dymamic callbacks. So, considering that…

  1. There is no way to know (from the AST alone) that a certain behavior has dynamic callbacks.
  2. Hank wants to avoid false positives at all costs, for instance by allowing the presence of false negatives (i.e. not emitting warnings for parameters that are actually unnecessary). …for 1.1.0, what @pbrudnick implemented is the following…

Except for those known behaviors where we can be 100% sure that they don't need dynamic callbacks, we assume that any other behavior might have dynamic callbacks and then… Hank ignores the whole module, just in case.

If this change is ever implemented, Hank will be less confused in two main areas:

  1. It will no longer need a list of known behaviors, since it will be able to assume that if the behavior doesn't declare a dynamic callback, the only functions that can be callback implementations (and therefore should be ignored) will be the ones listed by behaviour_info(callbacks). It will analyze all other functions 💪
  2. For behaviors with dynamic callbacks, Hank will be able to just ignore the functions with the desired arity, instead of ignoring all functions entirely. That means that, for instance, it will be able to emit the proper warning for the code below…
-module my_SUITE.
-export [all/0, a_test/1, not_a_test/2].

all() -> [a_test].

%% No warning for this parameter, since it "can be" a callback function.
a_test(_) ->
  not_a_test(another_function(apple), orange).

%% Hank will raise a warning here!
not_a_test(_, Fruit) ->
  orange = Fruit.

%% False negative. It might be a callback function so it raises no warning.
another_function(_) ->
  something.

In the end, Hank will be far less confused, if anything. It won't be able to spot every unnecessary argument, but it will spot many many more.

elbrujohalcon avatar May 19 '21 10:05 elbrujohalcon

Thanks for the thorough explanation, @elbrujohalcon. This gives readers more context and insight. And as you stated, "confused, but less so" 😄

paulo-ferraz-oliveira avatar May 19 '21 10:05 paulo-ferraz-oliveira

More dimensions to explore when designing something like this: define types for such callbacks, and allow callback modules to annotate such functions accordingly.

The behavior module could define precisely what types of "extra" callbacks it supports (I personally find the term "extra" good enough, compared to dynamic, but I might be simplifying this more than necessary):

-module(ct_suite).
[...]
-type testcase_info() :: fun()-> info(). 
-type testcase() :: fun(config()) -> term().
-extra_callback_types([testcase_info/0, testcase/0]). % New

I don't like that the types show up as 0-arity "entries" in the extra_callback_types annotation, when they actually correspond to function types of other arities, but I have no good ideas right now.

The callback modules can then have annotations for such callback functions, e.g.

-module(my_SUITE).
-behaviour(ct_suite).
[...]
-extra_callbacks ct_suite:testcase() :: [test1/1, test2/1]. % New

In this particular example, I don't like the implied duplication of the list of testcases, which is however a very ct_suite-specific detail.

If one skips the annotations in the callback module Hank can decide to treat any functions with the right arities as possible callbacks.

I also don't like that one cannot easily express that "this callback module has no extra callbacks (-extra_callbacks foo() :: [] is likely not good enough).

Maybe -extra_callbacks([{ct_suite:testcase(), [test1/1, test2/1]}]). is actually better, although it mixes unique syntax elements from "export lists" (test1/1), types (ct_suite:testcase()), and what is arguably executable code ({_, _})...

aronisstav avatar Jun 04 '21 08:06 aronisstav

@aronisstav I don't like "extra" that much because, to me, it implies that the module will be implementing the behavior even if non of those callbacks are actually defined and that's… only… technically true. Modules implementing ct_suite or gen_statem are expected to define these callbacks. It's also too similar to optional_callbacks.

In any case, I think your comments are mostly addressing an issue that's slightly orthogonal to mine: The fact that modules like ct_suite or gen_statem don't have a standard way of retrieving the list of dynamic/extra/other callbacks from their implementors. ct_suite uses all/0, gen_statem just… doesn't need a list of callbacks at all.

If we end up having something like…

-module(my_SUITE).
-behaviour(ct_suite).
[...]
-extra_callbacks ct_suite:testcase() :: [test1/1, test2/1]. % New

…then we'll be able to remove all/0 from the list of ct_suite callbacks. That's nice, and that would help Hank for sure, but… gen_statem, for instance, doesn't really need such a list. I'm not sure that forcing gen_statem implementors to add that attribute would be a good idea.

In a nutshell: I don't dislike your ideas (except for the extra name 🙈 ), but at least for me (speaking as a maintainer of Hank) having a way to specify that there are dynamic callbacks in a behavior is more than enough. If we do it with types or with variables in -callback specs, I don't mind.

elbrujohalcon avatar Jun 04 '21 08:06 elbrujohalcon

Oh, and BTW… I proposed the use of variables in -callbacks because that's how they're described in the docs.

elbrujohalcon avatar Jun 04 '21 08:06 elbrujohalcon

I just found another scenario where this would be very handy: xref. I added @RaimoNiskanen's gen_statem example to my app and then I run rebar3 xref with exports_not_used on…

src/code_lock.erl:68: Warning: code_lock:locked/3 is unused export (Xref)
src/code_lock.erl:93: Warning: code_lock:open/3 is unused export (Xref)

Those are state callbacks. I would like for xref to be smart enough not to list them as unused exports 🙏🏻

elbrujohalcon avatar Nov 25 '21 10:11 elbrujohalcon

I just found another scenario where this comes in hand: Elixir's @impl. If you're implementing, say… a :gen_statem , and you have a state callback (that is, one of the dynamic ones), you may want to write your code like this…

defmodule Your.Module do
  @moduledoc "A gen_statem implementation"

  @behaviour :gen_statem

  @impl :gen_statem
  def my_state(_event_type, _old_state, data), do: {:next_state, :other_state, data}

  @impl :gen_statem
  def callback_mode, do: [:state_functions, :state_enter]

  @impl :gen_statem
  def init(_), do: {:ok, :my_state, :data}

  …
end

But that will result in the following warning:

Compiling 1 file (.ex)
warning: got "@impl :gen_statem" for function my_state/3 but this behaviour does not specify such callback. The known callbacks are:

  * :gen_statem.callback_mode/0 (function)
  * :gen_statem.code_change/4 (function)
  * :gen_statem.format_status/2 (function)
  * :gen_statem.handle_event/4 (function)
  * :gen_statem.init/1 (function)
  * :gen_statem.state_name/3 (function)
  * :gen_statem.terminate/3 (function)

  path/to/your_module.ex:7: Your.Module (module)

elbrujohalcon avatar Jul 28 '22 11:07 elbrujohalcon

@elbrujohalcon In CloudI there is a flexible approach for representing dynamic callback functions as a few separate types:

{Module :: module(), FunctionName :: atom()} |
{{Module :: module(), FunctionName :: atom()}} |
fun()

The dynamic callback function validation functions are in the cloudi_args_type module, with the validation functions function_required/2, function_required_pick/2 and function_optional/2.

{Module, FunctionName} is straight-forward and provides a way of representing the function as data for module loading when the source code decides that is appropriate. Using a tuple allows the data to be stored in configuration that is read with file:consult/1.

If a closure is necessary with arity 0 to create the function dynamically, {{Module, FunctionName}} is used. Using that likely means the function depends on global state.

Otherwise, an anonymous function or function reference can be used in source code.

I am not convinced that dynamic callbacks functionality needs to be added to Erlang syntax in an attribute. If they were, it seems best to provide as much flexibility as possible for the data representation of the dynamic callback.

okeuday avatar Sep 22 '22 03:09 okeuday