Skip to content

Commit 368306e

Browse files
committed
Rename and reorder
1 parent ae51b34 commit 368306e

File tree

6 files changed

+227
-226
lines changed

6 files changed

+227
-226
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -437,7 +437,7 @@ defmodule Module.Types.Apply do
437437
empty?(common) and not (number_type?(left) and number_type?(right)) ->
438438
{:error, :mismatched_comparison}
439439

440-
match?({false, _}, map_fetch(dynamic(common), :__struct__)) ->
440+
match?({false, _}, map_fetch_key(dynamic(common), :__struct__)) ->
441441
{:error, :struct_comparison}
442442

443443
true ->

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

Lines changed: 157 additions & 156 deletions
Original file line numberDiff line numberDiff line change
@@ -2668,6 +2668,8 @@ defmodule Module.Types.Descr do
26682668
end)
26692669
end
26702670

2671+
## Map key functions
2672+
26712673
@doc """
26722674
Fetches the type of the value returned by accessing `key` on `map`
26732675
with the assumption that the descr is exclusively a map (or dynamic).
@@ -2676,13 +2678,13 @@ defmodule Module.Types.Descr do
26762678
if the type is dynamically optional or not, the second element is
26772679
the type. In static mode, optional keys are not allowed.
26782680
"""
2679-
def map_fetch(:term, _key), do: :badmap
2681+
def map_fetch_key(:term, _key), do: :badmap
26802682

2681-
def map_fetch(%{} = descr, key) when is_atom(key) do
2683+
def map_fetch_key(%{} = descr, key) when is_atom(key) do
26822684
case :maps.take(:dynamic, descr) do
26832685
:error ->
26842686
if descr_key?(descr, :map) and non_empty_map_only?(descr) do
2685-
{static_optional?, static_type} = map_fetch_static(descr, key)
2687+
{static_optional?, static_type} = map_fetch_key_static(descr, key)
26862688

26872689
if static_optional? or empty?(static_type) do
26882690
:badkey
@@ -2695,8 +2697,8 @@ defmodule Module.Types.Descr do
26952697

26962698
{dynamic, static} ->
26972699
if descr_key?(dynamic, :map) and map_only?(static) do
2698-
{dynamic_optional?, dynamic_type} = map_fetch_static(dynamic, key)
2699-
{static_optional?, static_type} = map_fetch_static(static, key)
2700+
{dynamic_optional?, dynamic_type} = map_fetch_key_static(dynamic, key)
2701+
{static_optional?, static_type} = map_fetch_key_static(static, key)
27002702

27012703
if static_optional? or empty?(dynamic_type) do
27022704
:badkey
@@ -2711,17 +2713,17 @@ defmodule Module.Types.Descr do
27112713

27122714
# Optimization: if the key does not exist in the map, avoid building
27132715
# if_set/not_set pairs and return the popped value directly.
2714-
defp map_fetch_static(%{map: bdd_leaf(tag_or_domains, fields)}, key)
2716+
defp map_fetch_key_static(%{map: bdd_leaf(tag_or_domains, fields)}, key)
27152717
when not is_map_key(fields, key) do
27162718
map_key_tag_to_type(tag_or_domains) |> pop_optional_static()
27172719
end
27182720

2719-
defp map_fetch_static(%{map: bdd}, key) do
2721+
defp map_fetch_key_static(%{map: bdd}, key) do
27202722
map_bdd_to_dnf(bdd) |> map_dnf_fetch_static(key)
27212723
end
27222724

2723-
defp map_fetch_static(%{}, _key), do: {false, none()}
2724-
defp map_fetch_static(:term, _key), do: {true, term()}
2725+
defp map_fetch_key_static(%{}, _key), do: {false, none()}
2726+
defp map_fetch_key_static(:term, _key), do: {true, term()}
27252727

27262728
# Takes a map DNF and returns the union of types it can take for a given key.
27272729
# If the key may be undefined, it will contain the `not_set()` type.
@@ -2752,6 +2754,150 @@ defmodule Module.Types.Descr do
27522754
|> pop_optional_static()
27532755
end
27542756

2757+
@doc """
2758+
Puts a `key` of a given type, assuming that the descr is exclusively
2759+
a map (or dynamic).
2760+
"""
2761+
def map_put_key(:term, _key, _type), do: :badmap
2762+
def map_put_key(descr, key, :term) when is_atom(key), do: map_put_key_shared(descr, key, :term)
2763+
2764+
def map_put_key(descr, key, type) when is_atom(key) do
2765+
case :maps.take(:dynamic, type) do
2766+
:error -> map_put_key_shared(descr, key, type)
2767+
{dynamic, _static} -> map_put_key_shared(dynamic(descr), key, dynamic)
2768+
end
2769+
end
2770+
2771+
defp map_put_key_shared(descr, key, type) do
2772+
with {nil, descr} <- map_take(descr, key, nil, &map_put_key_static(&1, key, type)) do
2773+
{:ok, descr}
2774+
end
2775+
end
2776+
2777+
# Directly inserts a key of a given type into every positive and negative map.
2778+
defp map_put_key_static(%{map: bdd} = descr, key, type) do
2779+
bdd = bdd_map(bdd, fn {tag, fields} -> {tag, Map.put(fields, key, type)} end)
2780+
%{descr | map: bdd}
2781+
end
2782+
2783+
defp map_put_key_static(descr, _key, _type), do: descr
2784+
2785+
@doc """
2786+
Removes a key from a map type.
2787+
"""
2788+
def map_delete(descr, key) do
2789+
# We pass nil as the initial value so we can avoid computing the unions.
2790+
with {nil, descr} <-
2791+
map_take(descr, key, nil, &intersection_static(&1, open_map([{key, not_set()}]))) do
2792+
{:ok, descr}
2793+
end
2794+
end
2795+
2796+
@doc """
2797+
Removes a key from a map type and return its type.
2798+
2799+
## Algorithm
2800+
2801+
1. Split the map type based on the presence of the key.
2802+
2. Take the second part of the split, which represents the union of all
2803+
record types where the key has been explicitly removed.
2804+
3. Intersect this with an open record type where the key is explicitly absent.
2805+
This step eliminates the key from open record types where it was implicitly present.
2806+
"""
2807+
def map_take(descr, key) do
2808+
map_take(descr, key, none(), &intersection_static(&1, open_map([{key, not_set()}])))
2809+
end
2810+
2811+
# If initial is nil, note we don't compute the value.
2812+
defp map_take(:term, _key, _initial, _updater), do: :badmap
2813+
2814+
defp map_take(descr, key, initial, updater) when is_atom(key) do
2815+
case :maps.take(:dynamic, descr) do
2816+
:error ->
2817+
if descr_key?(descr, :map) and map_only?(descr) do
2818+
{optional?, taken, result} =
2819+
map_take_static(descr, key, initial)
2820+
2821+
cond do
2822+
taken == nil -> {nil, updater.(result)}
2823+
optional? or empty?(taken) -> :badkey
2824+
true -> {taken, updater.(result)}
2825+
end
2826+
else
2827+
:badmap
2828+
end
2829+
2830+
{dynamic, static} ->
2831+
if descr_key?(dynamic, :map) and map_only?(static) do
2832+
{_, dynamic_taken, dynamic_result} = map_take_static(dynamic, key, initial)
2833+
{static_optional?, static_taken, static_result} = map_take_static(static, key, initial)
2834+
result = union(dynamic(updater.(dynamic_result)), updater.(static_result))
2835+
2836+
cond do
2837+
static_taken == nil and dynamic_taken == nil ->
2838+
{nil, result}
2839+
2840+
static_optional? or empty?(dynamic_taken) ->
2841+
:badkey
2842+
2843+
true ->
2844+
{union(dynamic(dynamic_taken), static_taken), result}
2845+
end
2846+
else
2847+
:badmap
2848+
end
2849+
end
2850+
end
2851+
2852+
# Takes a static map type and removes a key from it.
2853+
# This allows the key to be put or deleted later on.
2854+
defp map_take_static(%{map: bdd_leaf(tag, fields)} = descr, key, initial)
2855+
when not is_map_key(fields, key) do
2856+
case tag do
2857+
:open -> {true, maybe_union(initial, fn -> term() end), descr}
2858+
:closed -> {true, initial, descr}
2859+
end
2860+
end
2861+
2862+
defp map_take_static(%{map: bdd}, key, initial) do
2863+
{value, map} =
2864+
map_bdd_to_dnf(bdd)
2865+
|> Enum.reduce({initial, none()}, fn
2866+
# Optimization: if there are no negatives, we can directly remove the key.
2867+
{tag, fields, []}, {value, map} ->
2868+
{fst, snd} = map_pop_key(tag, fields, key)
2869+
{maybe_union(value, fn -> fst end), union(map, snd)}
2870+
2871+
{tag, fields, negs}, {value, map} ->
2872+
{fst, snd} = map_pop_key(tag, fields, key)
2873+
2874+
case map_split_negative(negs, key) do
2875+
:empty ->
2876+
{value, map}
2877+
2878+
negative ->
2879+
disjoint = pair_make_disjoint(negative)
2880+
2881+
{maybe_union(value, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end),
2882+
disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)}
2883+
end
2884+
end)
2885+
2886+
if value == nil do
2887+
{false, value, map}
2888+
else
2889+
{optional?, value} = pop_optional_static(value)
2890+
{optional?, value, map}
2891+
end
2892+
end
2893+
2894+
# If there is no map part to this static type, there is nothing to delete.
2895+
defp map_take_static(%{}, _key, initial), do: {false, initial, none()}
2896+
2897+
defp map_take_static(:term, _key, initial) do
2898+
{true, maybe_union(initial, fn -> term() end), open_map()}
2899+
end
2900+
27552901
@doc """
27562902
Fetches and puts a `key_or_domains`, assuming that the descr is exclusively
27572903
a map (or dynamic).
@@ -2771,7 +2917,7 @@ defmodule Module.Types.Descr do
27712917
end
27722918

27732919
defp map_put_existing_shared(descr, key, type) when is_atom(key) do
2774-
with {_, type} <- map_take(descr, key, none(), &map_put_static(&1, key, type)) do
2920+
with {_, type} <- map_take(descr, key, none(), &map_put_key_static(&1, key, type)) do
27752921
{:ok, type}
27762922
end
27772923
end
@@ -2871,50 +3017,10 @@ defmodule Module.Types.Descr do
28713017
end
28723018
end
28733019

2874-
@doc """
2875-
Puts a `key` of a given type, assuming that the descr is exclusively
2876-
a map (or dynamic).
2877-
"""
2878-
def map_put(:term, _key, _type), do: :badmap
2879-
def map_put(descr, key, :term) when is_atom(key), do: map_put_shared(descr, key, :term)
2880-
2881-
def map_put(descr, key, type) when is_atom(key) do
2882-
case :maps.take(:dynamic, type) do
2883-
:error -> map_put_shared(descr, key, type)
2884-
{dynamic, _static} -> map_put_shared(dynamic(descr), key, dynamic)
2885-
end
2886-
end
2887-
2888-
defp map_put_shared(descr, key, type) do
2889-
with {nil, descr} <- map_take(descr, key, nil, &map_put_static(&1, key, type)) do
2890-
{:ok, descr}
2891-
end
2892-
end
2893-
2894-
# Directly inserts a key of a given type into every positive and negative map.
2895-
defp map_put_static(%{map: bdd} = descr, key, type) do
2896-
bdd = bdd_map(bdd, fn {tag, fields} -> {tag, Map.put(fields, key, type)} end)
2897-
2898-
%{descr | map: bdd}
2899-
end
2900-
2901-
defp map_put_static(descr, _key, _type), do: descr
2902-
2903-
@doc """
2904-
Removes a key from a map type.
2905-
"""
2906-
def map_delete(descr, key) do
2907-
# We pass nil as the initial value so we can avoid computing the unions.
2908-
with {nil, descr} <-
2909-
map_take(descr, key, nil, &intersection_static(&1, open_map([{key, not_set()}]))) do
2910-
{:ok, descr}
2911-
end
2912-
end
2913-
29143020
@doc """
29153021
Computes the union of types for keys matching `key_type` within the `map_type`.
29163022
2917-
This generalizes `map_fetch/2` (which operates on a single literal key) to
3023+
This generalizes `map_fetch_key/2` (which operates on a single literal key) to
29183024
work with a key type (e.g., `atom()`, `integer()`, `:a or :b`). It's based
29193025
on the map-selection operator t.[t'] described in Section 4.2 of "Typing Records,
29203026
Maps, and Structs" (Castagna et al., ICFP 2023).
@@ -3104,111 +3210,6 @@ defmodule Module.Types.Descr do
31043210
end)
31053211
end
31063212

3107-
@doc """
3108-
Removes a key from a map type and return its type.
3109-
3110-
## Algorithm
3111-
3112-
1. Split the map type based on the presence of the key.
3113-
2. Take the second part of the split, which represents the union of all
3114-
record types where the key has been explicitly removed.
3115-
3. Intersect this with an open record type where the key is explicitly absent.
3116-
This step eliminates the key from open record types where it was implicitly present.
3117-
"""
3118-
def map_take(descr, key) do
3119-
map_take(descr, key, none(), &intersection_static(&1, open_map([{key, not_set()}])))
3120-
end
3121-
3122-
# If initial is nil, note we don't compute the value.
3123-
defp map_take(:term, _key, _initial, _updater), do: :badmap
3124-
3125-
defp map_take(descr, key, initial, updater) when is_atom(key) do
3126-
case :maps.take(:dynamic, descr) do
3127-
:error ->
3128-
if descr_key?(descr, :map) and map_only?(descr) do
3129-
{optional?, taken, result} =
3130-
map_take_static(descr, key, initial)
3131-
3132-
cond do
3133-
taken == nil -> {nil, updater.(result)}
3134-
optional? or empty?(taken) -> :badkey
3135-
true -> {taken, updater.(result)}
3136-
end
3137-
else
3138-
:badmap
3139-
end
3140-
3141-
{dynamic, static} ->
3142-
if descr_key?(dynamic, :map) and map_only?(static) do
3143-
{_, dynamic_taken, dynamic_result} = map_take_static(dynamic, key, initial)
3144-
{static_optional?, static_taken, static_result} = map_take_static(static, key, initial)
3145-
result = union(dynamic(updater.(dynamic_result)), updater.(static_result))
3146-
3147-
cond do
3148-
static_taken == nil and dynamic_taken == nil ->
3149-
{nil, result}
3150-
3151-
static_optional? or empty?(dynamic_taken) ->
3152-
:badkey
3153-
3154-
true ->
3155-
{union(dynamic(dynamic_taken), static_taken), result}
3156-
end
3157-
else
3158-
:badmap
3159-
end
3160-
end
3161-
end
3162-
3163-
# Takes a static map type and removes a key from it.
3164-
# This allows the key to be put or deleted later on.
3165-
defp map_take_static(%{map: bdd_leaf(tag, fields)} = descr, key, initial)
3166-
when not is_map_key(fields, key) do
3167-
case tag do
3168-
:open -> {true, maybe_union(initial, fn -> term() end), descr}
3169-
:closed -> {true, initial, descr}
3170-
end
3171-
end
3172-
3173-
defp map_take_static(%{map: bdd}, key, initial) do
3174-
{value, map} =
3175-
map_bdd_to_dnf(bdd)
3176-
|> Enum.reduce({initial, none()}, fn
3177-
# Optimization: if there are no negatives, we can directly remove the key.
3178-
{tag, fields, []}, {value, map} ->
3179-
{fst, snd} = map_pop_key(tag, fields, key)
3180-
{maybe_union(value, fn -> fst end), union(map, snd)}
3181-
3182-
{tag, fields, negs}, {value, map} ->
3183-
{fst, snd} = map_pop_key(tag, fields, key)
3184-
3185-
case map_split_negative(negs, key) do
3186-
:empty ->
3187-
{value, map}
3188-
3189-
negative ->
3190-
disjoint = pair_make_disjoint(negative)
3191-
3192-
{maybe_union(value, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end),
3193-
disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)}
3194-
end
3195-
end)
3196-
3197-
if value == nil do
3198-
{false, value, map}
3199-
else
3200-
{optional?, value} = pop_optional_static(value)
3201-
{optional?, value, map}
3202-
end
3203-
end
3204-
3205-
# If there is no map part to this static type, there is nothing to delete.
3206-
defp map_take_static(%{}, _key, initial), do: {false, initial, none()}
3207-
3208-
defp map_take_static(:term, _key, initial) do
3209-
{true, maybe_union(initial, fn -> term() end), open_map()}
3210-
end
3211-
32123213
defp non_empty_map_literals_intersection(maps) do
32133214
try do
32143215
Enum.reduce(maps, {:open, %{}}, fn {next_tag, next_fields}, {tag, fields} ->

0 commit comments

Comments
 (0)