Skip to content

Commit a13f38e

Browse files
committed
Implement map_put_key using new domain aware map_put
1 parent 31c9c84 commit a13f38e

File tree

2 files changed

+364
-205
lines changed

2 files changed

+364
-205
lines changed

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

Lines changed: 158 additions & 135 deletions
Original file line numberDiff line numberDiff line change
@@ -2743,129 +2743,6 @@ defmodule Module.Types.Descr do
27432743
|> pop_optional_static()
27442744
end
27452745

2746-
@doc """
2747-
Puts a `key` of a given type, assuming that the descr is exclusively
2748-
a map (or dynamic).
2749-
"""
2750-
def map_put_key(:term, _key, _type), do: :badmap
2751-
def map_put_key(descr, key, :term) when is_atom(key), do: map_put_key_shared(descr, key, :term)
2752-
2753-
def map_put_key(descr, key, type) when is_atom(key) do
2754-
case :maps.take(:dynamic, type) do
2755-
:error -> map_put_key_shared(descr, key, type)
2756-
{dynamic, _static} -> map_put_key_shared(dynamic(descr), key, dynamic)
2757-
end
2758-
end
2759-
2760-
defp map_put_key_shared(descr, key, type) do
2761-
with {nil, descr} <- map_take_key(descr, key, nil, &map_put_key_static(&1, key, type)) do
2762-
{:ok, descr}
2763-
end
2764-
end
2765-
2766-
# Directly inserts a key of a given type into every positive and negative map.
2767-
defp map_put_key_static(%{map: bdd} = descr, key, type) do
2768-
bdd = bdd_map(bdd, fn {tag, fields} -> {tag, Map.put(fields, key, type)} end)
2769-
%{descr | map: bdd}
2770-
end
2771-
2772-
defp map_put_key_static(descr, _key, _type), do: descr
2773-
2774-
# Removes a key from a map type and return its type.
2775-
#
2776-
# ## Algorithm
2777-
#
2778-
# 1. Split the map type based on the presence of the key.
2779-
# 2. Take the second part of the split, which represents the union of all
2780-
# record types where the key has been explicitly removed.
2781-
# 3. Intersect this with an open record type where the key is explicitly absent.
2782-
# This step eliminates the key from open record types where it was implicitly present.
2783-
#
2784-
# Note: if initial is nil, it means the value is not required.
2785-
# So we don't compute it for performance.
2786-
defp map_take_key(:term, _key, _initial, _updater), do: :badmap
2787-
2788-
defp map_take_key(descr, key, initial, updater) when is_atom(key) do
2789-
case :maps.take(:dynamic, descr) do
2790-
:error ->
2791-
if descr_key?(descr, :map) and map_only?(descr) do
2792-
{taken, result} = map_take_key_static(descr, key, initial)
2793-
2794-
if taken == nil do
2795-
{nil, updater.(result)}
2796-
else
2797-
{optional?, taken} = pop_optional_static(taken)
2798-
if optional? or empty?(taken), do: :badkey, else: {taken, updater.(result)}
2799-
end
2800-
else
2801-
:badmap
2802-
end
2803-
2804-
{dynamic, static} ->
2805-
if descr_key?(dynamic, :map) and map_only?(static) do
2806-
{dynamic_taken, dynamic_result} = map_take_key_static(dynamic, key, initial)
2807-
{static_taken, static_result} = map_take_key_static(static, key, initial)
2808-
result = union(dynamic(updater.(dynamic_result)), updater.(static_result))
2809-
2810-
if static_taken == nil and dynamic_taken == nil do
2811-
{nil, result}
2812-
else
2813-
{static_optional?, static_taken} = pop_optional_static(static_taken)
2814-
{_dynamic_optional?, dynamic_taken} = pop_optional_static(dynamic_taken)
2815-
2816-
if static_optional? or empty?(dynamic_taken) do
2817-
:badkey
2818-
else
2819-
{union(dynamic(dynamic_taken), static_taken), result}
2820-
end
2821-
end
2822-
else
2823-
:badmap
2824-
end
2825-
end
2826-
end
2827-
2828-
# Takes a static map type and removes a key from it.
2829-
# This allows the key to be put or deleted later on.
2830-
defp map_take_key_static(%{map: bdd}, key, initial) do
2831-
map_dnf_take_key_static(map_bdd_to_dnf(bdd), key, initial)
2832-
end
2833-
2834-
# If there is no map part to this static type, there is nothing to delete.
2835-
defp map_take_key_static(%{}, _key, initial) do
2836-
{initial, none()}
2837-
end
2838-
2839-
defp map_take_key_static(:term, _key, initial) do
2840-
{maybe_union(initial, fn -> term() end), open_map()}
2841-
end
2842-
2843-
defp map_dnf_take_key_static(dnf, key, initial) do
2844-
{value, descr} =
2845-
Enum.reduce(dnf, {initial, none()}, fn
2846-
# Optimization: if there are no negatives, we can directly remove the key.
2847-
{tag, fields, []}, {value, map} ->
2848-
{fst, snd} = map_pop_key(tag, fields, key)
2849-
{maybe_union(value, fn -> fst end), union(map, snd)}
2850-
2851-
{tag, fields, negs}, {value, map} ->
2852-
{fst, snd} = map_pop_key(tag, fields, key)
2853-
2854-
case map_split_negative_key(negs, key) do
2855-
:empty ->
2856-
{value, map}
2857-
2858-
negative ->
2859-
disjoint = pair_make_disjoint(negative)
2860-
2861-
{maybe_union(value, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end),
2862-
disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)}
2863-
end
2864-
end)
2865-
2866-
{value, descr}
2867-
end
2868-
28692746
@doc """
28702747
Updates the `key_descr` with `type`.
28712748
@@ -2874,16 +2751,16 @@ defmodule Module.Types.Descr do
28742751
def map_update(:term, _key_descr, _type), do: :badmap
28752752

28762753
def map_update(descr, key_descr, :term),
2877-
do: map_update_shared(descr, key_descr, :term)
2754+
do: map_update_static_value(descr, key_descr, :term)
28782755

28792756
def map_update(descr, key_descr, type) do
28802757
case :maps.take(:dynamic, type) do
2881-
:error -> map_update_shared(descr, key_descr, type)
2882-
{dynamic, _static} -> map_update_shared(dynamic(descr), key_descr, dynamic)
2758+
:error -> map_update_static_value(descr, key_descr, type)
2759+
{dynamic, _static} -> map_update_static_value(dynamic(descr), key_descr, dynamic)
28832760
end
28842761
end
28852762

2886-
defp map_update_shared(descr, key_descr, type) do
2763+
defp map_update_static_value(descr, key_descr, type) do
28872764
split_keys = map_split_keys_and_domains(key_descr)
28882765

28892766
case :maps.take(:dynamic, descr) do
@@ -2926,7 +2803,7 @@ defmodule Module.Types.Descr do
29262803
{required_keys, optional_keys, maybe_negated_set, required_domains, optional_domains} =
29272804
split_keys
29282805

2929-
bdd = map_update_negated(bdd, maybe_negated_set, type)
2806+
bdd = map_update_put_negated(bdd, maybe_negated_set, type)
29302807
dnf = map_bdd_to_dnf(bdd)
29312808

29322809
callback = fn ->
@@ -2947,15 +2824,15 @@ defmodule Module.Types.Descr do
29472824
acc =
29482825
if found_optional? or found_required? do
29492826
# If any of required or optional domains are satisfied, then we compute the
2950-
# initial return type. `map_update_static_keys` will then union into the
2827+
# initial return type. `map_update_keys_static` will then union into the
29512828
# computed type below, using the original bdd/dnf, not the one with updated domains.
29522829
descr = map_update_put_domains(bdd, required_domains ++ optional_domains, type)
29532830
{value, descr}
29542831
else
29552832
{value, none()}
29562833
end
29572834

2958-
map_update_static_keys(dnf, required_keys, optional_keys, type, missing_fun, acc)
2835+
map_update_keys_static(dnf, required_keys, optional_keys, type, missing_fun, acc)
29592836

29602837
{_, _, [missing_domain | _], _} ->
29612838
{:baddomain, domain_key_to_descr(missing_domain)}
@@ -2978,11 +2855,11 @@ defmodule Module.Types.Descr do
29782855
else
29792856
acc = {none(), none()}
29802857
dnf = map_bdd_to_dnf(@map_top)
2981-
map_update_static_keys(dnf, required_keys, optional_keys, type, missing_fun, acc)
2858+
map_update_keys_static(dnf, required_keys, optional_keys, type, missing_fun, acc)
29822859
end
29832860
end
29842861

2985-
defp map_update_static_keys(dnf, required, optional, type, missing_fun, acc) do
2862+
defp map_update_keys_static(dnf, required, optional, type, missing_fun, acc) do
29862863
acc = map_update_keys(dnf, required, type, :required, missing_fun, acc)
29872864
acc = map_update_keys(dnf, optional, type, :optional, missing_fun, acc)
29882865
{:ok, acc}
@@ -2992,7 +2869,7 @@ defmodule Module.Types.Descr do
29922869

29932870
defp map_update_keys(dnf, keys, type, required_or_optional, missing_fun, acc) do
29942871
Enum.reduce(keys, acc, fn key, {acc_value, acc_descr} ->
2995-
{value, descr} = map_dnf_take_key_static(dnf, key, none())
2872+
{value, descr} = map_dnf_pop_key_static(dnf, key, none())
29962873

29972874
cond do
29982875
not missing_fun.(value) ->
@@ -3009,11 +2886,57 @@ defmodule Module.Types.Descr do
30092886
end)
30102887
end
30112888

2889+
# Directly inserts a key of a given type into every positive and negative map.
2890+
defp map_put_key_static(%{map: bdd} = descr, key, type) do
2891+
bdd = bdd_map(bdd, fn {tag, fields} -> {tag, Map.put(fields, key, type)} end)
2892+
%{descr | map: bdd}
2893+
end
2894+
2895+
defp map_put_key_static(descr, _key, _type), do: descr
2896+
2897+
# Removes a key from a map type and return its type.
2898+
#
2899+
# ## Algorithm
2900+
#
2901+
# 1. Split the map type based on the presence of the key.
2902+
# 2. Take the second part of the split, which represents the union of all
2903+
# record types where the key has been explicitly removed.
2904+
# 3. Intersect this with an open record type where the key is explicitly absent.
2905+
# This step eliminates the key from open record types where it was implicitly present.
2906+
#
2907+
# Note: if initial is nil, it means the value is not required.
2908+
# So we don't compute it for performance.
2909+
defp map_dnf_pop_key_static(dnf, key, initial) do
2910+
{value, descr} =
2911+
Enum.reduce(dnf, {initial, none()}, fn
2912+
# Optimization: if there are no negatives, we can directly remove the key.
2913+
{tag, fields, []}, {value, map} ->
2914+
{fst, snd} = map_pop_key(tag, fields, key)
2915+
{maybe_union(value, fn -> fst end), union(map, snd)}
2916+
2917+
{tag, fields, negs}, {value, map} ->
2918+
{fst, snd} = map_pop_key(tag, fields, key)
2919+
2920+
case map_split_negative_key(negs, key) do
2921+
:empty ->
2922+
{value, map}
2923+
2924+
negative ->
2925+
disjoint = pair_make_disjoint(negative)
2926+
2927+
{maybe_union(value, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end),
2928+
disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)}
2929+
end
2930+
end)
2931+
2932+
{value, descr}
2933+
end
2934+
30122935
# For keys with `not :foo`, we generate an approximation
30132936
# by adding the type to all keys, except `:foo`.
3014-
defp map_update_negated(bdd, nil, _type), do: bdd
2937+
defp map_update_put_negated(bdd, nil, _type), do: bdd
30152938

3016-
defp map_update_negated(bdd, negated, type) do
2939+
defp map_update_put_negated(bdd, negated, type) do
30172940
bdd_map(bdd, fn {tag, fields} ->
30182941
fields =
30192942
Map.new(fields, fn {key, value} ->
@@ -3110,6 +3033,106 @@ defmodule Module.Types.Descr do
31103033
end
31113034
end
31123035

3036+
@doc """
3037+
Puts a static key into `descr`.
3038+
3039+
Shortcut around `map_put/3`.
3040+
"""
3041+
def map_put_key(:term, key, _) when is_atom(key),
3042+
do: :badmap
3043+
3044+
def map_put_key(descr, key, type) when is_atom(key),
3045+
do: map_put_shared(descr, {[key], [], nil, [], []}, type)
3046+
3047+
@doc """
3048+
Puts the `key_descr` with `type`.
3049+
3050+
`key_descr` is split into optional and required keys and tracked accordingly.
3051+
3052+
Returns `{:ok, descr}` or `:badmap`.
3053+
"""
3054+
def map_put(:term, _, _), do: :badmap
3055+
3056+
def map_put(descr, key_descr, type) do
3057+
if key_descr in [:term, %{dynamic: :term}] and type in [:term, %{dynamic: :term}] do
3058+
{:ok, if(gradual?(type) or gradual?(descr), do: dynamic(open_map()), else: open_map())}
3059+
else
3060+
map_put_shared(descr, map_split_keys_and_domains(key_descr), type)
3061+
end
3062+
end
3063+
3064+
defp map_put_shared(%{} = descr, split_keys, :term),
3065+
do: map_put_static_value(descr, split_keys, :term)
3066+
3067+
defp map_put_shared(%{} = descr, split_keys, type) do
3068+
case :maps.take(:dynamic, type) do
3069+
:error -> map_put_static_value(descr, split_keys, type)
3070+
{dynamic, _static} -> map_put_static_value(dynamic(descr), split_keys, dynamic)
3071+
end
3072+
end
3073+
3074+
defp map_put_static_value(descr, split_keys, type) do
3075+
case :maps.take(:dynamic, descr) do
3076+
:error ->
3077+
if descr_key?(descr, :map) and map_only?(descr) do
3078+
{:ok, map_put_static(descr, split_keys, type)}
3079+
else
3080+
:badmap
3081+
end
3082+
3083+
{dynamic, static} ->
3084+
if descr_key?(dynamic, :map) and map_only?(static) do
3085+
static_descr = map_put_static(static, split_keys, type)
3086+
dynamic_descr = map_put_static(dynamic, split_keys, type)
3087+
{:ok, union(static_descr, dynamic(dynamic_descr))}
3088+
else
3089+
:badmap
3090+
end
3091+
end
3092+
end
3093+
3094+
defp map_put_static(%{map: bdd}, split_keys, type) do
3095+
{required_keys, optional_keys, maybe_negated_set, required_domains, optional_domains} =
3096+
split_keys
3097+
3098+
bdd = map_update_put_negated(bdd, maybe_negated_set, type)
3099+
3100+
descr =
3101+
case required_domains ++ optional_domains do
3102+
[] -> none()
3103+
domains -> map_update_put_domains(bdd, domains, type)
3104+
end
3105+
3106+
dnf = map_bdd_to_dnf(bdd)
3107+
map_put_keys_static(dnf, required_keys ++ optional_keys, type, descr)
3108+
end
3109+
3110+
defp map_put_static(%{}, _split_keys, _type) do
3111+
none()
3112+
end
3113+
3114+
defp map_put_static(:term, split_keys, type) do
3115+
# Since it is an open map, we don't need to check the domains.
3116+
# The negated set will also be empty, because there are no fields.
3117+
# Finally, merged required_keys into optional_keys.
3118+
{required_keys, optional_keys, _maybe_negated_set, required_domains, optional_domains} =
3119+
split_keys
3120+
3121+
if required_domains != [] or optional_domains != [] do
3122+
open_map()
3123+
else
3124+
dnf = map_bdd_to_dnf(@map_top)
3125+
map_put_keys_static(dnf, required_keys ++ optional_keys, type, none())
3126+
end
3127+
end
3128+
3129+
defp map_put_keys_static(dnf, keys, type, acc) do
3130+
Enum.reduce(keys, acc, fn key, acc ->
3131+
{nil, descr} = map_dnf_pop_key_static(dnf, key, nil)
3132+
union(map_put_key_static(descr, key, type), acc)
3133+
end)
3134+
end
3135+
31133136
@doc """
31143137
Computes the union of types for keys matching `key_type` within the `map_type`.
31153138

0 commit comments

Comments
 (0)