Skip to content

Commit 17d51d1

Browse files
authored
Add tuple elimination of negations (#14531)
1 parent 336627d commit 17d51d1

File tree

2 files changed

+106
-34
lines changed

2 files changed

+106
-34
lines changed

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

Lines changed: 76 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -3118,75 +3118,117 @@ defmodule Module.Types.Descr do
31183118
end
31193119

31203120
defp process_tuples_values(dnf) do
3121-
Enum.reduce(dnf, none(), fn {tag, elements, negs}, acc ->
3122-
union(tuple_values(tag, elements, negs), acc)
3121+
tuple_reduce(dnf, none(), &union/2, fn tag, elements ->
3122+
cond do
3123+
Enum.any?(elements, &empty?/1) -> none()
3124+
tag == :open -> term()
3125+
tag == :closed -> Enum.reduce(elements, none(), &union/2)
3126+
end
31233127
end)
31243128
end
31253129

3126-
defp tuple_values(tag, elements, []) do
3127-
cond do
3128-
Enum.any?(elements, &empty?/1) -> none()
3129-
tag == :open -> term()
3130-
tag == :closed -> Enum.reduce(elements, none(), &union/2)
3131-
end
3130+
defp tuple_reduce(dnf, initial, join, transform) do
3131+
Enum.reduce(dnf, initial, fn {tag, elements, negs}, acc ->
3132+
join.(acc, tuple_reduce(tag, elements, negs, initial, join, transform))
3133+
end)
31323134
end
31333135

3134-
defp tuple_values(_tag, _elements, [{:open, []} | _]), do: none()
3136+
defp tuple_reduce(tag, elements, [], _init, _join, transform), do: transform.(tag, elements)
3137+
defp tuple_reduce(_tag, _elements, [{:open, []} | _], initial, _join, _transform), do: initial
31353138

3136-
defp tuple_values(tag, elements, [{neg_tag, neg_elements} | negs]) do
3139+
defp tuple_reduce(tag, elements, [{neg_tag, neg_elements} | negs], initial, join, transform) do
31373140
n = length(elements)
31383141
m = length(neg_elements)
31393142

31403143
if (tag == :closed and n < m) or (neg_tag == :closed and n > m) do
3141-
tuple_values(tag, elements, negs)
3144+
tuple_reduce(tag, elements, negs, initial, join, transform)
31423145
else
31433146
# Those two functions eliminate the negations, transforming into
31443147
# a union of tuples to compute their values.
3145-
values_elements([], tag, elements, neg_elements, negs)
3146-
|> union(values_size(n, m, tag, elements, neg_tag, negs))
3148+
elim_content([], tag, elements, neg_elements, negs, initial, join, transform)
3149+
|> join.(elim_size(n, m, tag, elements, neg_tag, negs, initial, join, transform))
31473150
end
31483151
end
31493152

3153+
# Eliminates negations according to tuple content.
31503154
# This means that there are no more neg_elements to subtract -- end the recursion.
3151-
defp values_elements(_acc, _tag, _elements, [], _), do: none()
3155+
defp elim_content(_acc, _tag, _elements, [], _, initial, _join, _transform), do: initial
31523156

3153-
# Eliminates negations according to tuple content.
31543157
# Subtracts each element of a negative tuple to build a new tuple with the difference.
31553158
# Example: {number(), atom()} and not {float(), :foo} contains types {integer(), :foo}
31563159
# as well as {float(), atom() and not :foo}
31573160
# Same process as tuple_elements_empty?
3158-
defp values_elements(acc, tag, elements, [neg_type | neg_elements], negs) do
3161+
defp elim_content(acc, tag, elements, [neg_type | neg_elements], negs, init, join, transform) do
31593162
{ty, elements} = List.pop_at(elements, 0, term())
31603163
diff = difference(ty, neg_type)
31613164

31623165
if empty?(diff) do
3163-
none()
3166+
init
31643167
else
3165-
tuple_values(tag, Enum.reverse(acc, [diff | elements]), negs)
3168+
tuple_reduce(tag, Enum.reverse(acc, [diff | elements]), negs, init, join, transform)
31663169
end
3167-
|> union(values_elements([ty | acc], tag, elements, neg_elements, negs))
3170+
|> join.(elim_content([ty | acc], tag, elements, neg_elements, negs, init, join, transform))
31683171
end
31693172

31703173
# Eliminates negations according to size
31713174
# Example: {integer(), ...} and not {term(), term(), ...} contains {integer()}
3172-
defp values_size(n, m, tag, elements, neg_tag, negs) do
3173-
if tag == :closed do
3174-
none()
3175-
else
3176-
n..(m - 1)//1
3177-
|> Enum.reduce(none(), fn i, acc ->
3178-
tuple_values(:closed, tuple_fill(elements, i), negs) |> union(acc)
3179-
end)
3180-
|> union(
3181-
if neg_tag == :open do
3182-
none()
3183-
else
3184-
tuple_values(tag, tuple_fill(elements, m + 1), negs)
3185-
end
3186-
)
3175+
defp elim_size(_, _, :closed, _, _, _, initial, _join, _transfo), do: initial
3176+
3177+
defp elim_size(n, m, tag, elements, neg_tag, negs, initial, join, transform) do
3178+
n..(m - 1)//1
3179+
|> Enum.reduce(initial, fn i, acc ->
3180+
tuple_reduce(:closed, tuple_fill(elements, i), negs, initial, join, transform)
3181+
|> join.(acc)
3182+
end)
3183+
|> join.(
3184+
if neg_tag == :open do
3185+
initial
3186+
else
3187+
tuple_reduce(tag, tuple_fill(elements, m + 1), negs, initial, join, transform)
3188+
end
3189+
)
3190+
end
3191+
3192+
@doc """
3193+
Converts a tuple type to a simple union by eliminating negations.
3194+
3195+
Takes a tuple type with complex negations and simplifies it to a union of
3196+
positive tuple literals only.
3197+
3198+
For static tuple types: eliminates all negations from the DNF representation.
3199+
For gradual tuple types: processes both dynamic and static components separately,
3200+
then combines them.
3201+
3202+
Uses `tuple_reduce/4` with concatenation as the join function and a transform
3203+
that is simply the identity.
3204+
3205+
Returns the descriptor unchanged for non-tuple types, or a descriptor with
3206+
simplified tuple DNF containing only positive literals. If simplification
3207+
results in an empty tuple list, removes the `:tuple` key entirely.
3208+
"""
3209+
def tuple_elim_negations(descr) do
3210+
case :maps.take(:dynamic, descr) do
3211+
:error ->
3212+
tuple_elim_negations_static(descr)
3213+
3214+
{dynamic, static} ->
3215+
tuple_elim_negations_static(static)
3216+
|> union(dynamic(tuple_elim_negations_static(dynamic)))
31873217
end
31883218
end
31893219

3220+
# Call tuple_reduce to build the simple union of tuples that come from each map literal.
3221+
# Thus, initial is `[]`, join is concatenation, and the transform of a map literal
3222+
# with no negations is just to keep the map literal as is.
3223+
defp tuple_elim_negations_static(%{tuple: dnf} = descr) do
3224+
case tuple_reduce(dnf, [], &Kernel.++/2, fn tag, elements -> [{tag, elements, []}] end) do
3225+
[] -> Map.delete(descr, :tuple)
3226+
new_dnf -> %{descr | tuple: new_dnf}
3227+
end
3228+
end
3229+
3230+
defp tuple_elim_negations_static(descr), do: descr
3231+
31903232
defp tuple_pop_index(tag, elements, index) do
31913233
case List.pop_at(elements, index) do
31923234
{nil, _} -> {tag_to_type(tag), %{tuple: [{tag, elements, []}]}}

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

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1193,6 +1193,36 @@ defmodule Module.Types.DescrTest do
11931193
|> equal?(integer())
11941194
end
11951195

1196+
test "tuple_elim_negations" do
1197+
# take complex tuples, normalize them, and check if they are still equal
1198+
complex_tuples = [
1199+
tuple([term(), atom(), number()])
1200+
|> difference(tuple([atom(), atom(), float()])),
1201+
# overlapping union and difference producing multiple variants
1202+
difference(
1203+
tuple([union(atom(), pid()), union(integer(), float())]),
1204+
tuple([union(atom(), pid()), float()])
1205+
),
1206+
# open_tuple case with union in elements
1207+
difference(
1208+
open_tuple([union(boolean(), pid()), union(atom(), integer())]),
1209+
open_tuple([pid(), integer()])
1210+
),
1211+
open_tuple([term(), term(), term()])
1212+
|> difference(open_tuple([term(), integer(), atom(), atom()]))
1213+
|> difference(tuple([float(), float(), float(), float(), float()]))
1214+
|> difference(tuple([term(), term(), term(), term(), term(), term()]))
1215+
]
1216+
1217+
Enum.each(complex_tuples, fn orig ->
1218+
norm = tuple_elim_negations(orig)
1219+
# should split into multiple simple tuples
1220+
assert equal?(norm, orig)
1221+
assert Enum.all?(norm.tuple, fn {_, _, neg} -> neg == [] end)
1222+
assert not Enum.all?(orig.tuple, fn {_, _, neg} -> neg == [] end)
1223+
end)
1224+
end
1225+
11961226
test "map_fetch" do
11971227
assert map_fetch(term(), :a) == :badmap
11981228
assert map_fetch(union(open_map(), integer()), :a) == :badmap

0 commit comments

Comments
 (0)