Skip to content

Commit 7feb978

Browse files
authored
Merge pull request #10309 from bjorng/bjorn/stdlib/epp/GH-10280/OTP-19821
Support fun types as macro arguments
2 parents 85862a0 + fe6dd6a commit 7feb978

File tree

2 files changed

+66
-3
lines changed

2 files changed

+66
-3
lines changed

lib/stdlib/src/epp.erl

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2024,7 +2024,8 @@ macro_arg([{'if',Li}|Toks], E, Arg) ->
20242024
macro_arg([{'case',Lc}|Toks], E, Arg) ->
20252025
macro_arg(Toks, ['end'|E], [{'case',Lc}|Arg]);
20262026
macro_arg([{'fun',Lc}|[{'(',_}|_]=Toks], E, Arg) ->
2027-
macro_arg(Toks, ['end'|E], [{'fun',Lc}|Arg]);
2027+
%% This can be either a fun definition or a fun type.
2028+
macro_arg(Toks, [fun_end|E], [{'fun',Lc}|Arg]);
20282029
macro_arg([{'fun',_}=Fun,{var,_,_}=Name|[{'(',_}|_]=Toks], E, Arg) ->
20292030
macro_arg(Toks, ['end'|E], [Name,Fun|Arg]);
20302031
macro_arg([{'maybe',Lb}|Toks], E, Arg) ->
@@ -2035,6 +2036,23 @@ macro_arg([{'try',Lr}|Toks], E, Arg) ->
20352036
macro_arg(Toks, ['end'|E], [{'try',Lr}|Arg]);
20362037
macro_arg([{'cond',Lr}|Toks], E, Arg) ->
20372038
macro_arg(Toks, ['end'|E], [{'cond',Lr}|Arg]);
2039+
macro_arg([{'when',_}|_]=Toks, [fun_end|E], Arg) ->
2040+
%% This is the `when` inside a fun definition such as:
2041+
%% fun() when true, true -> true end.
2042+
macro_arg(Toks, ['end'|E], Arg);
2043+
macro_arg([{'->',_}|_]=Toks, [fun_end|E], Arg) ->
2044+
%% This is the `->` inside a fun definition such as:
2045+
%% fun() -> ok end.
2046+
macro_arg(Toks, ['end'|E], Arg);
2047+
macro_arg([{Rb,_Lrb}=T|Toks], [fun_end|E], Arg) ->
2048+
case Rb of
2049+
Eb when Eb =:= ','; Eb =:= ')' ->
2050+
%% This is the end of a fun type such as:
2051+
%% fun(() -> 'ok').
2052+
macro_arg([T|Toks], E, Arg);
2053+
_ ->
2054+
macro_arg(Toks, [fun_end|E], [T|Arg])
2055+
end;
20382056
macro_arg([{Rb,Lrb}|Toks], [Rb|E], Arg) -> %Found matching close
20392057
macro_arg(Toks, E, [{Rb,Lrb}|Arg]);
20402058
macro_arg([T|Toks], E, Arg) ->

lib/stdlib/test/epp_SUITE.erl

Lines changed: 47 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,8 @@
3535
deterministic_include/1, nondeterministic_include/1,
3636
gh_8268/1,
3737
moduledoc_include/1,
38-
stringify/1
38+
stringify/1,
39+
fun_type_arg/1
3940
]).
4041

4142
-export([epp_parse_erl_form/2]).
@@ -82,7 +83,8 @@ all() ->
8283
deterministic_include, nondeterministic_include,
8384
gh_8268,
8485
moduledoc_include,
85-
stringify].
86+
stringify,
87+
fun_type_arg].
8688

8789
groups() ->
8890
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -2139,6 +2141,49 @@ stringify(Config) ->
21392141
[] = run(Config, Ts),
21402142
ok.
21412143

2144+
%% GH-10280. A fun type could not be used as a macro argument.
2145+
fun_type_arg(Config) ->
2146+
Ts = [{fun_type_1,
2147+
~"""
2148+
-define(FOO(X), X).
2149+
-define(BAR(X, Y), {X,Y}).
2150+
2151+
-type foo() :: ?FOO(fun(() -> 'ok')).
2152+
-type bar() :: ?BAR(fun((integer()) -> integer()), integer()).
2153+
-type frotz() :: ?FOO(fun((integer()) -> {atom(),integer()})).
2154+
2155+
-define(mk_fun_var(Fun, Vars), mk_fun_var(Fun, Vars)).
2156+
2157+
t() ->
2158+
ok = f(fun() -> ok end),
2159+
42 = g({fun(I) -> 2 * I end, 21}),
2160+
{ok,7} = h(fun(I) -> {ok,I} end),
2161+
#{a := 1, b := 2} =
2162+
?mk_fun_var(fun(Map0) ->
2163+
Map1 = Map0#{a => 1},
2164+
Map1#{b => 2}
2165+
end, #{}),
2166+
42 = ?FOO(fun(((I))) -> I + 1 end)(41),
2167+
true = (?FOO(fun (_) when true, true -> true end))(0),
2168+
ok.
2169+
2170+
-spec f(foo()) -> 'ok'.
2171+
f(F) -> F().
2172+
2173+
-spec g(bar()) -> integer().
2174+
g({F,I}) -> F(I).
2175+
2176+
-spec h(frotz()) -> {atom(),integer()}.
2177+
h(H) -> H(7).
2178+
2179+
mk_fun_var(Fun, Vars) -> Fun(Vars).
2180+
""",
2181+
[],
2182+
ok}],
2183+
[] = run(Config, Ts),
2184+
ok.
2185+
2186+
21422187
%% Start location is 1.
21432188
check(Config, Tests) ->
21442189
eval_tests(Config, fun check_test/3, Tests).

0 commit comments

Comments
 (0)