Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
38 changes: 35 additions & 3 deletions lib/elixir/lib/module/types/descr.ex
Original file line number Diff line number Diff line change
Expand Up @@ -1252,7 +1252,7 @@ defmodule Module.Types.Descr do
defp map_only?(descr), do: empty?(Map.delete(descr, :map))

# Union is list concatenation
defp map_union(dnf1, dnf2), do: dnf1 ++ dnf2
defp map_union(dnf1, dnf2), do: dnf1 ++ (dnf2 -- dnf1)

# Given two unions of maps, intersects each pair of maps.
defp map_intersection(dnf1, dnf2) do
Expand Down Expand Up @@ -1682,15 +1682,47 @@ defmodule Module.Types.Descr do
end

# Use heuristics to normalize a map dnf for pretty printing.
# TODO: Eliminate some simple negations, those which have only zero or one key in common.
defp map_normalize(dnf) do
dnf
|> Enum.reject(&map_empty?([&1]))
|> Enum.map(fn {tag, fields, negs} ->
{tag, fields, Enum.reject(negs, &map_empty_negation?(tag, fields, &1))}
{fields, negs} =
Enum.reduce(negs, {fields, []}, fn neg = {neg_tag, neg_fields}, {acc_fields, acc_negs} ->
if map_empty_negation?(tag, acc_fields, neg) do
{acc_fields, acc_negs}
else
case all_but_one?(tag, acc_fields, neg_tag, neg_fields) do
{:one, diff_key} ->
{Map.update!(acc_fields, diff_key, &difference(&1, neg_fields[diff_key])),
acc_negs}

_ ->
{acc_fields, [neg | acc_negs]}
end
end
end)

{tag, fields, negs}
end)
end

# If all fields are the same except one, we can optimize map difference.
defp all_but_one?(tag1, fields1, tag2, fields2) do
keys1 = Map.keys(fields1)
keys2 = Map.keys(fields2)

if {tag1, tag2} == {:open, :closed} or
:sets.from_list(keys1, version: 2) != :sets.from_list(keys2, version: 2) do
:no
else
Enum.count(keys1, fn key -> Map.get(fields1, key) != Map.get(fields2, key) end)
|> case do
1 -> {:one, Enum.find(keys1, &(Map.get(fields1, &1) != Map.get(fields2, &1)))}
_ -> :no
end
end
end

# Adapted from `map_empty?` to remove useless negations.
defp map_empty_negation?(tag, fields, {neg_tag, neg_fields}) do
(tag == :closed and
Expand Down
94 changes: 88 additions & 6 deletions lib/elixir/test/elixir/module/types/descr_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -1263,6 +1263,11 @@ defmodule Module.Types.DescrTest do

assert tuple([closed_map(a: integer()), open_map()]) |> to_quoted_string() ==
"{%{a: integer()}, %{...}}"

# TODO: eliminate tuple differences
# assert difference(tuple([number(), term()]), tuple([integer(), atom()]))
# |> to_quoted_string() ==
# "{float(), term()} or {number(), term() and not atom()}"
end

test "map" do
Expand All @@ -1278,9 +1283,8 @@ defmodule Module.Types.DescrTest do
assert open_map("Elixir.Foo.Bar": float()) |> to_quoted_string() ==
"%{..., Foo.Bar => float()}"

# TODO: support this simplification
# assert difference(open_map(), open_map(a: term())) |> to_quoted_string() ==
# "%{..., a: not_set()}"
assert difference(open_map(), open_map(a: term())) |> to_quoted_string() ==
"%{..., a: not_set()}"

assert closed_map(a: integer(), b: atom()) |> to_quoted_string() ==
"%{a: integer(), b: atom()}"
Expand All @@ -1295,13 +1299,40 @@ defmodule Module.Types.DescrTest do
assert closed_map(foo: union(integer(), not_set())) |> to_quoted_string() ==
"%{foo: if_set(integer())}"

assert difference(open_map(a: integer()), closed_map(b: boolean())) |> to_quoted_string() ==
"%{..., a: integer()}"

# Test normalization
assert open_map(a: integer(), b: atom())
|> difference(open_map(b: atom()))
|> union(open_map(a: integer()))
|> to_quoted_string() == "%{..., a: integer()}"

assert union(open_map(a: integer()), open_map(a: integer())) |> to_quoted_string() ==
"%{..., a: integer()}"

assert difference(open_map(a: number(), b: atom()), open_map(a: integer()))
|> to_quoted_string() == "%{..., a: float(), b: atom()}"

# Test complex combinations
assert intersection(open_map(a: number(), b: atom()), open_map(a: integer(), c: boolean()))
|> union(difference(open_map(x: atom()), open_map(x: boolean())))
|> to_quoted_string() ==
"%{..., a: integer(), b: atom(), c: boolean()} or %{..., x: atom() and not boolean()}"

assert closed_map(a: number(), b: atom(), c: pid())
|> difference(closed_map(a: integer(), b: atom(), c: pid()))
|> to_quoted_string() == "%{a: float(), b: atom(), c: pid()}"

# No simplification compared to above, as it is an open map
assert open_map(a: number(), b: atom())
|> difference(closed_map(a: integer(), b: atom()))
|> to_quoted_string() ==
"%{..., a: float() or integer(), b: atom()} and not %{a: integer(), b: atom()}"

# Remark: this simplification is order dependent. Having the first difference
# after the second gives a different result.
assert open_map(a: number(), b: atom(), c: union(pid(), port()))
|> difference(open_map(a: float(), b: atom(), c: pid()))
|> difference(open_map(a: integer(), b: atom(), c: union(pid(), port())))
|> to_quoted_string() == "%{..., a: float(), b: atom(), c: port()}"
end

test "structs" do
Expand Down Expand Up @@ -1344,5 +1375,56 @@ defmodule Module.Types.DescrTest do
assert subtype?(descr1, descr2)
refute subtype?(descr2, descr1)
end

test "map difference" do
# Create a large map with various types
map1 =
open_map([
{:id, integer()},
{:name, binary()},
{:age, union(integer(), atom())},
{:email, binary()},
{:active, boolean()},
{:tags, list(atom())}
])

# Create another large map with some differences and many more entries
map2 =
open_map(
[
{:id, integer()},
{:name, binary()},
{:age, integer()},
{:email, binary()},
{:active, boolean()},
{:tags, non_empty_list(atom())},
{:meta,
open_map([
{:created_at, binary()},
{:updated_at, binary()},
{:status, atom()}
])},
{:permissions, tuple([atom(), integer(), atom()])},
{:profile,
open_map([
{:bio, binary()},
{:interests, non_empty_list(binary())},
{:social_media,
open_map([
{:twitter, binary()},
{:instagram, binary()},
{:linkedin, binary()}
])}
])},
{:notifications, boolean()}
] ++
Enum.map(1..50, fn i ->
{:"field_#{i}", atom([:"value_#{i}"])}
end)
)

refute subtype?(map1, map2)
assert subtype?(map2, map1)
end
end
end
Loading