Skip to content

Commit c8a9dd4

Browse files
committed
Fix
1 parent 9775f4f commit c8a9dd4

File tree

1 file changed

+10
-29
lines changed

1 file changed

+10
-29
lines changed

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

Lines changed: 10 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -90,15 +90,15 @@ defmodule Module.Types.Descr do
9090
def atom(as), do: %{atom: atom_new(as)}
9191
def atom(), do: %{atom: @atom_top}
9292
def binary(), do: %{bitmap: @bit_binary}
93-
def closed_map(pairs), do: map_descr(:closed, pairs, @term_or_optional, false)
93+
def closed_map(pairs), do: map_descr(:closed, pairs, term_or_optional(), false)
9494
def empty_list(), do: %{bitmap: @bit_empty_list}
9595
def empty_map(), do: %{map: @map_empty}
9696
def integer(), do: %{bitmap: @bit_integer}
9797
def float(), do: %{bitmap: @bit_float}
9898
def list(type), do: list_descr(type, @empty_list, true)
9999
def non_empty_list(type, tail \\ @empty_list), do: list_descr(type, tail, false)
100100
def open_map(), do: %{map: @map_top}
101-
def open_map(pairs), do: map_descr(:open, pairs, @term_or_optional, false)
101+
def open_map(pairs), do: map_descr(:open, pairs, term_or_optional(), false)
102102
def open_map(pairs, default), do: map_descr(:open, pairs, if_set(default), true)
103103
def open_tuple(elements, _fallback \\ term()), do: tuple_descr(:open, elements)
104104
def pid(), do: %{bitmap: @bit_pid}
@@ -2993,28 +2993,6 @@ defmodule Module.Types.Descr do
29932993

29942994
defp nil_or_type(type), do: union(type, atom([nil]))
29952995

2996-
defp unfold_domains(:open), do: Map.from_keys(@domain_key_types, @term_or_optional)
2997-
defp unfold_domains(:closed), do: %{}
2998-
defp unfold_domains(domains = %{}), do: domains
2999-
3000-
defp map_get_static(%{map: bdd_leaf(tag_or_domains, fields)}, key_descr) do
3001-
# For each non-empty kind of type in the key_descr, we add the corresponding key domain in a union.
3002-
domains = unfold_domains(tag_or_domains)
3003-
3004-
{key_descr, acc} =
3005-
case :maps.take(:atom, key_descr) do
3006-
{atom, key_descr} -> {key_descr, map_get_atom([{domains, fields, []}], atom)}
3007-
:error -> {key_descr, none()}
3008-
end
3009-
3010-
key_descr
3011-
|> to_domain_keys()
3012-
|> Enum.reduce(acc, fn
3013-
key_type, acc ->
3014-
Map.get(domains, key_type, not_set()) |> union(acc)
3015-
end)
3016-
end
3017-
30182996
defp map_get_static(%{map: bdd}, key_descr) do
30192997
dnf = map_bdd_to_dnf(bdd)
30202998

@@ -3096,16 +3074,19 @@ defmodule Module.Types.Descr do
30963074
# Take a map bdd and return the union of types for the given key domain.
30973075
defp map_get_domain(dnf, domain_key(_) = domain_key) do
30983076
Enum.reduce(dnf, none(), fn
3099-
{tag, _fields, []}, acc when is_atom(tag) ->
3100-
map_key_tag_to_type(tag) |> union(acc)
3077+
{:open, _fields, []}, acc ->
3078+
union(term_or_optional(), acc)
3079+
3080+
{:closed, _fields, []}, acc ->
3081+
acc
31013082

31023083
# Optimization: if there are no negatives and domains exists, return its value
31033084
{%{^domain_key => value}, _fields, []}, acc ->
31043085
value |> union(acc)
31053086

3106-
# Optimization: if there are no negatives and the key does not exist, return the default type.
3107-
{domains = %{}, _fields, []}, acc ->
3108-
map_key_tag_to_type(domains) |> union(acc)
3087+
# Optimization: if there are no negatives and the key does not exist, skip it
3088+
{_domains, _fields, []}, acc ->
3089+
acc
31093090

31103091
{tag_or_domains, fields, negs}, acc ->
31113092
{fst, snd} = map_pop_domain(tag_or_domains, fields, domain_key)

0 commit comments

Comments
 (0)