Skip to content

Conversation

@josevalim
Copy link
Contributor

No description provided.

@essen
Copy link

essen commented Dec 9, 2025

Would this also work? I didn't see an example.

Key = get_key().
Fun = fun maps:get(Key, _).

@josevalim
Copy link
Contributor Author

@essen yes, literals or variables as arguments are supported. I will clarify that in a later pass of the proposal once I collect all feedback. Thank you!

@albsch
Copy link

albsch commented Dec 9, 2025

Here is another alternative, that one can already try out in Erlang.

cuts from erlando.

I just tried it out, the parse transfrom still works with the current Erlang.

Here is how the examples would look like:

1> Fun = maps:get(username, _).
2> Fun(#{username => "Joe"}).
"Joe"

Which is also equivalent to:

1> Fun = fun(X) -> maps:get(username, X) end.
2> Fun(#{username => "Joe"}).
"Joe"
{some_config, some_mod:some_fun(_, answer, 42)}.
{some_config, fun(X) -> some_mod:some_fun(X, answer, 42) end}.
hello(_, world, _)
fun(X, Y) -> hello(X, world, Y) end

This example does not work with cuts, it still needs to be wrapped in a fun manually.

fun Mod:Fun(arg1, arg2, arg3)

like this:

fun() -> Mod:Fun(arg1, arg2, arg3) end

The example from the comment would look like this

f() ->
  Key = get_key(),
  Fun = maps:get(Key, _),
  io:format(user,"got: ~p~n", [Fun(#{k1 => 2})]).

get_key() -> k1.

1 > f().
got: 2

@josevalim
Copy link
Contributor Author

@albsch good call. Although erlando is missing the runtime support (the focus of this proposal), I should list that in the alternatives!

Do you know if it restricts the arguments in any way? For example, can the arguments be complex expressions, such as maps:get(lists:flatten([]), _)?

@albsch
Copy link

albsch commented Dec 9, 2025

Yes, runtime support for something like this would be great.

Complex expressions are also allowed (by complex expression you mean the function application flatten I think?). Your example works:

f() ->
  Fun = maps:get(lists:flatten([]), _),
  io:format(user,"got: ~p~n", [Fun(#{[] => 3})]).
1 > f().
got: 3
ok

It's equivalent to (or rather, syntactically transformed into):

 Fun = fun(X) -> maps:get(lists:flatten([]), X) end

@RaimoNiskanen
Copy link
Contributor

How would fun foo({ok,_}) work? Can an argument be any pattern?

Can an argument be an unbound variable? fun foo(X)

Can the fun name be a bound variable?

    F = foo,
    fun F(_),
    F(bar),

or does it have to be a literal function name foo or mod:foo?

This would be allowed, right?

foo(Y) -> Y-1.
bar(X) ->
    F1 = fun Foo(X) -> X+1 end, % Arity 1
    F2 = fun foo(X),            % Arity 0
    F3 = fun foo/1,             % Arity 1
    {F1(X), F2(), F3(X)}.

bar(3) -> {4,2,2}
where on line F1 there would be warnings that X is shadowed and that Foo it not used.

Maybe what I am getting at is that it is a bit subtle that F2 defines a function body (with a hidden header) where F1 and F3 defines a function header (and for F1 also a body).

@josevalim
Copy link
Contributor Author

Thank you @albsch and @RaimoNiskanen!

How would fun foo({ok,_}) work? Can an argument be any pattern?

I would say {ok, _} would not work. An argument is either a literal or a variable.

Can the fun name be a bound variable?

Since fun F/1 is not valid today, I assume fun F(Arg1, ...) shouldn't be valid either. But given fun Mod:Fun/Arity is valid, I assume fun Mod:Fun(Arg1, ...) should be implementable at runtime with the properties I outlined here, as long as Mod and Fun are bound variables. I will clarify it.

Maybe what I am getting at is that it is a bit subtle that F2 defines a function body (with a hidden header) where F1 and F3 defines a function header (and for F1 also a body).

I agree they feel a bit too close. There are some trade-offs that could be made here:

  1. Don't allow fun some_mod:some_fun(Args) or fun some_fun(Args) when there are no placeholders. After all, if there are no placeholders, it means they could be represented as a fun some_mod:another_fun/0 where another_fun calls the original some_fun with all arguments statically. FWIW, Elixir has this restriction.

  2. Only allow remote partially applied functions, so fun foo(_, ok) doesn't work, only fun some_mod:foo(_, ok), but I am afraid it will lead to developers doing external calls when a local call would suffice for the syntax convenience.

  3. Do nothing, since named anonymous functions are not common anyway.

Any thoughts?

@RaimoNiskanen
Copy link
Contributor

I think that it is tempting to be able to create an arity 0 fun for spawn:

Parent = self(),
State = #{},
Pid = spawn(fun ?MODULE:server_loop(Parent, nolink, State)),

F = fun foo(X, _) would be a local fun with X in its environment, this exists already, right?

But F = fun ?MODULE:foo(X, _) would be a new thing - an anonymous export entry with an arity and an environment.(?) How should this thing should be named to be oblivious of module upgrades. Or should it be a new term type that refers to an export entry?

@josevalim
Copy link
Contributor Author

F = fun foo(X, _) would be a local fun with X in its environment, this exists already, right?

Yes, I think this one wouldn't need runtime changes, since local functions are not external/serializable/persistent (we need a better way to describe those...).

But F = fun ?MODULE:foo(X, _) would be a new thing - an anonymous export entry with an arity and an environment.(?)

Unfortunately I cannot speak about the implementation details. I assume one option is to extend the existing external function types to have a field that points to its partially applied arguments? For all existing fun Mod:Fun/Arity, this field is empty.

@josevalim
Copy link
Contributor Author

I have updated the proposal with the feedback so far.

@RaimoNiskanen, I have added a section on "Visual Cluttering", which includes your example and possible solutions. I included one additional solution, not mentioned above, which is to require partially applied functions to explicit list the arity too, hence fun foo(X) has to be written as: fun foo(X)/0. fun maps:get(username, _) as fun maps:get(username, _)/1.

If the version with arity is preferred, then the fun prefix could also be dropped, if desired, as there is no ambiguity.

@RaimoNiskanen
Copy link
Contributor

Specifying the arity is redundant, but maybe more readable. To me it associates more towards being a fun declaration instead of a function call. It is also clearer that it is a fun object of arity N that is created.

If the version with arity is preferred, then the fun prefix could also be dropped, if desired, as there is no ambiguity.

Isn't there a syntactical ambiguity in that foo(X)/0 today means call foo(X) then divide by 0, which will fail, but fun foo(X)/0 would obviously define a fun. I like that all fun definitions start with fun. It is more fun! (sorry, pun intended, I had to!)

@tsloughter
Copy link

Next up, an operator |> of type (A, fun((A) -> B)) -> B:

http_req:new() 
|> fun http_req:set_header(~"Content-Type", ~"application/json", _)
|> fun http_req:run(_)

:)

@jhogberg
Copy link
Contributor

Or should it be a new term type that refers to an export entry?

As per the current fun header definition:

/* Fun objects.
 *
 * These have a special tag scheme to make the representation as compact as
 * possible. For normal headers, we have:
 *
 *     aaaaaaaaaaaaaaaa aaaaaaaaaatttt00       arity:26, tag:4
 *
 * Since the arity and number of free variables are both limited to 255, we can
 * fit them both into the header word.
 *
 *     0000000keeeeeeee aaaaaaaa00010100       kind:1,environment:8,arity:8
 *
 * Note that the lowest byte contains only the function subtag, and the next
 * byte after that contains only the arity. This lets us combine the type
 * and/or arity check into a single comparison without masking, by using 8- or
 * 16-bit operations on the header word. */

#define FUN_HEADER_ARITY_OFFS (_HEADER_ARITY_OFFS + 2)
#define FUN_HEADER_ENV_SIZE_OFFS (FUN_HEADER_ARITY_OFFS + 8)
#define FUN_HEADER_KIND_OFFS (FUN_HEADER_ENV_SIZE_OFFS + 8)

#define MAKE_FUN_HEADER(Arity, NumFree, External)                             \
    (ASSERT((!(External)) || ((NumFree) == 0)),                               \
     (_TAG_HEADER_FUN |                                                       \
     (((Arity)) << FUN_HEADER_ARITY_OFFS) |                                   \
     (((NumFree)) << FUN_HEADER_ENV_SIZE_OFFS) |                              \
     ((!!(External)) << FUN_HEADER_KIND_OFFS)))

There's a few places that assume that external funs don't have an environment at the moment, notably in the external term format, but otherwise it would be easy to let them have an environment too.

I think it's possible to make these terms round-trip to old nodes and back without loss, by using NEW_FUN_EXT with an impossible signature (old_uniq is always derived from uniq IIRC). They wouldn't be callable on the old nodes, appearing as an anonymous function that always badfun's when called, but it would work when passed onward to a new node.

@josevalim
Copy link
Contributor Author

@jhogberg one thing of note is that this new environment maps arguments to positions. They are still ordered, but they can have gaps, such as fun foo:bar(_, arg1, _, arg2). I am unsure if that complicates the format in any way...

eeps/eep-00XX.md Outdated
nodes nor be persisted to disk, so when dealing with distribution,
disk persistence, or hot code upgrades, you must carefully stick with
MFArgs. Similarly, configuration files do not support anonymous
functions, and MFArgs are the main option.
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Passing an anonymous function with an environment over the distribution works. I must be misunderstanding something?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Poor phrasing on my end, I should clarify it only works if you have the exact same module version (which, unless you declare a version, will change even with minor changes to the source). I will improve that on a future pass to the EEP.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Ok, thanks. Yes, I think the versioning issue should be mentioned.

@jhogberg
Copy link
Contributor

We've discussed this internally, and though we didn't reach a final decision, we liked the proposal and agreed on the following:

  1. It makes sense to be able to partially apply lambdas, too:

    Lambda = maps:get/2,
    F = fun Lambda(username, _),
    F(#{ username => "Joe" })
    
  2. We prefer to allow any expressions as arguments, but they are evaluated before fun creation, just as they are evaluated before a function call. In other words, spawn(fun ?MODULE:server_loop(self(), #{})) is valid and largely equivalent to spawn(?MODULE, server_loop, [self(), #{}]).

    Of course, in a configuration file or the likes the arguments must be literals.

  3. Because of the above, explaining fun hello(_, world, _) as fun(X, Y) -> hello(X, world, Y) end becomes confusing (consider self() instead of world, is self() evaluated within the body or upon fun creation?). It would be better to explain it plainly as "partial application" and leaving it at that, followed by a few nice examples, instead of trying to explain things in terms of "equivalent lambdas."

  4. The visual cluttering isn't a big problem, the lack of parentheses or an arrow (function body) should be enough to distinguish the different kinds.

@jhogberg
Copy link
Contributor

@jhogberg one thing of note is that this new environment maps arguments to positions. They are still ordered, but they can have gaps, such as fun foo:bar(_, arg1, _, arg2). I am unsure if that complicates the format in any way...

Not by much, the implementations I had in mind are relatively easy to implement with reasonable performance.

@josevalim
Copy link
Contributor Author

Thanks everyone, I have applied the latest round of feedback, including the ones from @jhogberg.

It would be better to explain it plainly as "partial application" and leaving it at that, followed by a few nice examples, instead of trying to explain things in terms of "equivalent lambdas."

I decided to include spawn(fun ?MODULE:server_loop(self(), #{})) as an example with its literal translation because I think it can be confusing, so I decided to explicitly call it out.

The visual cluttering isn't a big problem, the lack of parentheses or an arrow (function body) should be enough to distinguish the different kinds.

I kept that section in for discussion, it can be removed in future revisions.

eeps/eep-00XX.md Outdated
Comment on lines 34 to 36
nodes nor be persisted to disk if they preserve the same module version.
Therefore, when dealing with distribution, disk persistence, or hot code
upgrades, it is preferrable to use MFArgs instead. Similarly, configuration
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Suggested details change:

nodes or be persisted to disk if it is the same module version on both ends.
Therefore, when dealing with distribution, disk persistence, or hot code
upgrades, it is preferrable/essential to use MFArgs instead. Similarly, configuration

Copy link
Contributor

@Maria-12648430 Maria-12648430 left a comment

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Some typos, some questions/suggestions/opinions :)

Comment on lines +225 to +228
* Only allow remote partially applied functions, so `fun foo(_, ok)`
is invalid, but `fun some_mod:foo(_, ok)` is accepted. Unfortunately,
this may lead to developers doing external calls when a local call
would suffice;
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This does not look practical to me. Or useful. Or a good way. Or whatever 🤷‍♀️

Comment on lines +219 to +223
* Require all partially applied functions to have at least one `_`,
forbidding `fun foo(X)` or `fun some_mod:some_fun(Args)`. This does
add a syntactical annoyance but it does not remove any capability
as any function without placeholder can be written as a zero-arity
function;
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't like that one. The restriction would read like "... unless your partial application results in full application", which IMO is a stumbling block that at least I wouldn't want.

Comment on lines +291 to +292
The lack of a prefix makes it harder to spot when a function is created
and also leads to visual ambiguity, such as in the code below:
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

... which kind of drives home my point made re dropping or keeping the fun

Co-authored-by: Maria Scott <67057258+Maria-12648430@users.noreply.github.com>
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Labels

None yet

Projects

None yet

Development

Successfully merging this pull request may close these issues.