Skip to content

Commit 2ec8da5

Browse files
committed
Overlapping function clauses
1 parent 60f7d00 commit 2ec8da5

File tree

4 files changed

+118
-8
lines changed

4 files changed

+118
-8
lines changed

lib/elixir/lib/module/types/apply.ex

Lines changed: 22 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -472,7 +472,6 @@ defmodule Module.Types.Apply do
472472
Returns the type of a remote capture.
473473
"""
474474
def remote_capture(modules, fun, arity, meta, stack, context) do
475-
# TODO: Deal with :infer types
476475
if stack.mode == :traversal or modules == [] do
477476
{dynamic(fun(arity)), context}
478477
else
@@ -482,6 +481,9 @@ defmodule Module.Types.Apply do
482481
{{:strong, _, clauses}, context} ->
483482
{union(type, fun_from_non_overlapping_clauses(clauses)), fallback?, context}
484483

484+
{{:infer, _, clauses}, context} when length(clauses) <= @max_clauses ->
485+
{union(type, fun_from_overlapping_clauses(clauses)), fallback?, context}
486+
485487
{_, context} ->
486488
{type, true, context}
487489
end
@@ -694,13 +696,25 @@ defmodule Module.Types.Apply do
694696
{_kind, _info, context} when stack.mode == :traversal ->
695697
{dynamic(fun(arity)), context}
696698

697-
{kind, _info, context} ->
698-
if stack.mode != :infer and kind == :defp do
699-
# Mark all clauses as used, as the function is being exported.
700-
{dynamic(fun(arity)), put_in(context.local_used[fun_arity], [])}
701-
else
702-
{dynamic(fun(arity)), context}
703-
end
699+
{kind, info, context} ->
700+
result =
701+
case info do
702+
{:infer, _, clauses} when length(clauses) <= @max_clauses ->
703+
fun_from_overlapping_clauses(clauses)
704+
705+
_ ->
706+
dynamic(fun(arity))
707+
end
708+
709+
context =
710+
if stack.mode != :infer and kind == :defp do
711+
# Mark all clauses as used, as the function is being exported.
712+
put_in(context.local_used[fun_arity], [])
713+
else
714+
context
715+
end
716+
717+
{result, context}
704718
end
705719
end
706720

lib/elixir/lib/module/types/descr.ex

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,43 @@ defmodule Module.Types.Descr do
132132
end)
133133
end
134134

135+
@doc """
136+
Creates a function from overlapping function clauses.
137+
"""
138+
def fun_from_overlapping_clauses(args_clauses) do
139+
domain_clauses =
140+
Enum.reduce(args_clauses, [], fn {args, return}, acc ->
141+
pivot_overlapping_clause(args_to_domain(args), return, acc)
142+
end)
143+
144+
funs =
145+
for {domain, return} <- domain_clauses,
146+
args <- domain_to_args(domain),
147+
do: fun(args, return)
148+
149+
Enum.reduce(funs, &intersection/2)
150+
end
151+
152+
defp pivot_overlapping_clause(domain, return, [{acc_domain, acc_return} | acc]) do
153+
common = intersection(domain, acc_domain)
154+
155+
if empty?(common) do
156+
[{acc_domain, acc_return} | pivot_overlapping_clause(domain, return, acc)]
157+
else
158+
[{common, union(return, acc_return)} | acc]
159+
|> prepend_to_unless_empty(difference(domain, common), return)
160+
|> prepend_to_unless_empty(difference(acc_domain, common), acc_return)
161+
end
162+
end
163+
164+
defp pivot_overlapping_clause(domain, return, []) do
165+
[{domain, return}]
166+
end
167+
168+
defp prepend_to_unless_empty(acc, domain, return) do
169+
if empty?(domain), do: acc, else: [{domain, return} | acc]
170+
end
171+
135172
@doc """
136173
Converts a list of arguments into a domain.
137174

lib/elixir/test/elixir/module/types/descr_test.exs

Lines changed: 58 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -751,6 +751,64 @@ defmodule Module.Types.DescrTest do
751751
end
752752
end
753753

754+
describe "function creation" do
755+
test "fun_from_non_overlapping_clauses" do
756+
assert fun_from_non_overlapping_clauses([{[integer()], atom()}, {[float()], binary()}]) ==
757+
intersection(fun([integer()], atom()), fun([float()], binary()))
758+
end
759+
760+
test "fun_from_overlapping_clauses" do
761+
# No overlap
762+
assert fun_from_overlapping_clauses([{[integer()], atom()}, {[float()], binary()}])
763+
|> equal?(
764+
fun_from_non_overlapping_clauses([{[integer()], atom()}, {[float()], binary()}])
765+
)
766+
767+
# Subsets
768+
assert fun_from_overlapping_clauses([{[integer()], atom()}, {[number()], binary()}])
769+
|> equal?(
770+
fun_from_non_overlapping_clauses([
771+
{[integer()], union(atom(), binary())},
772+
{[float()], binary()}
773+
])
774+
)
775+
776+
assert fun_from_overlapping_clauses([{[number()], binary()}, {[integer()], atom()}])
777+
|> equal?(
778+
fun_from_non_overlapping_clauses([
779+
{[integer()], union(atom(), binary())},
780+
{[float()], binary()}
781+
])
782+
)
783+
784+
# Partial
785+
assert fun_from_overlapping_clauses([
786+
{[union(integer(), pid())], atom()},
787+
{[union(float(), pid())], binary()}
788+
])
789+
|> equal?(
790+
fun_from_non_overlapping_clauses([
791+
{[integer()], atom()},
792+
{[float()], binary()},
793+
{[pid()], union(atom(), binary())}
794+
])
795+
)
796+
797+
# Difference
798+
assert fun_from_overlapping_clauses([
799+
{[integer(), union(pid(), atom())], atom()},
800+
{[number(), pid()], binary()}
801+
])
802+
|> equal?(
803+
fun_from_non_overlapping_clauses([
804+
{[float(), pid()], binary()},
805+
{[integer(), atom()], atom()},
806+
{[integer(), pid()], union(atom(), binary())}
807+
])
808+
)
809+
end
810+
end
811+
754812
describe "function application" do
755813
defp none_fun(arity), do: fun(List.duplicate(none(), arity), term())
756814

lib/elixir/test/elixir/module/types/expr_test.exs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -449,6 +449,7 @@ defmodule Module.Types.ExprTest do
449449
describe "remote capture" do
450450
test "strong" do
451451
assert typecheck!(&String.to_atom/1) == fun([binary()], atom())
452+
assert typecheck!(&:erlang.element/2) == fun([integer(), open_tuple([])], dynamic())
452453
end
453454

454455
test "unknown" do

0 commit comments

Comments
 (0)