@@ -962,6 +962,11 @@ defmodule Module.Types.Descr do
962962 defp atom_only? ( descr ) , do: empty? ( Map . delete ( descr , :atom ) )
963963 defp atom_new ( as ) when is_list ( as ) , do: { :union , :sets . from_list ( as , version: 2 ) }
964964
965+ defp infinite_atoms? ( :term ) , do: true
966+ defp infinite_atoms? ( % { dynamic: dynamic } ) , do: infinite_atoms? ( dynamic )
967+ defp infinite_atoms? ( % { atom: { :negation , _ } } ) , do: true
968+ defp infinite_atoms? ( % { } ) , do: false
969+
965970 defp atom_intersection ( { tag1 , s1 } , { tag2 , s2 } ) do
966971 { tag , s } =
967972 case { tag1 , tag2 } do
@@ -2705,7 +2710,7 @@ defmodule Module.Types.Descr do
27052710 end
27062711
27072712 defp map_fetch_key_static ( % { map: bdd } , key ) do
2708- map_bdd_to_dnf ( bdd ) |> map_dnf_fetch_static ( key )
2713+ map_bdd_to_dnf ( bdd ) |> map_dnf_fetch_static ( key ) |> pop_optional_static ( )
27092714 end
27102715
27112716 defp map_fetch_key_static ( % { } , _key ) , do: { false , none ( ) }
@@ -2737,7 +2742,6 @@ defmodule Module.Types.Descr do
27372742 |> union ( acc )
27382743 end
27392744 end )
2740- |> pop_optional_static ( )
27412745 end
27422746
27432747 @ doc """
@@ -2975,7 +2979,7 @@ defmodule Module.Types.Descr do
29752979 if Map . has_key? ( seen , key ) do
29762980 { seen , acc }
29772981 else
2978- { _ , value } = map_dnf_fetch_static ( dnf , key )
2982+ value = dnf |> map_dnf_fetch_static ( key ) |> remove_optional ( )
29792983 { Map . put ( seen , key , [ ] ) , union ( acc , value ) }
29802984 end
29812985 end )
@@ -2990,8 +2994,8 @@ defmodule Module.Types.Descr do
29902994 if Map . has_key? ( acc , key ) do
29912995 acc
29922996 else
2993- { _ , value } = map_dnf_fetch_static ( dnf , key )
2994- not empty ?( value ) and throw ( :found_key )
2997+ value = map_dnf_fetch_static ( dnf , key )
2998+ not empty_or_optional ?( value ) and throw ( :found_key )
29952999 Map . put ( acc , key , [ ] )
29963000 end
29973001 end )
@@ -3183,59 +3187,39 @@ defmodule Module.Types.Descr do
31833187 @ doc """
31843188 Computes the union of types for keys matching `key_type` within the `map_type`.
31853189
3186- This generalizes `map_fetch_key/2` (which operates on a single literal key) to
3187- work with a key type (e.g., `atom()`, `integer()`, `:a or :b`). It's based
3188- on the map-selection operator t.[t'] described in Section 4.2 of "Typing Records,
3189- Maps, and Structs" (Castagna et al., ICFP 2023).
3190-
3191- ## Return Values
3192-
3193- The function returns a tuple indicating the outcome and the resulting type union:
3194-
3195- * `{:ok, type}`: Standard success. `type` is the resulting union of types
3196- found for the matching keys. This covers two sub-cases:
3197- * **Keys definitely exist:** If `disjoint?(type, not_set())` is true,
3198- all keys matching `key_type` are guaranteed to exist.
3199- * **Keys may exist:** If `type` includes `not_set()`, some keys
3200- matching `key_type` might exist (contributing their types) while
3201- others might be absent (contributing `not_set()`).
3202-
3203- * `{:ok_absent, type}`: Success, but the resulting `type` is `none()` or a
3204- subtype of `not_set()`. This indicates that no key matching `key_type`
3205- can exist with a value other than `not_set()`. The caller may wish to
3206- issue a warning, as this often implies selecting a field that is
3207- effectively undefined.
3208-
3209- # TODO: implement/decide if worth it (it's from the paper)
3210- * `{:ok_spillover, type}`: Success, and `type` is the resulting union.
3211- However, this indicates that the `key_type` included keys not explicitly
3212- covered by the `map_type`'s fields or domain specifications. The
3213- projection relied on the map's default behavior (e.g., the `term()`
3214- value type for unspecified keys in an open map). The caller may wish to
3215- issue a warning, as this could conceal issues like selecting keys
3216- not intended by the map's definition.
3217-
3218- * `:badmap`: The input `map_type` was invalid (e.g., not a map type or
3219- a dynamic type wrapping a map type).
3220-
3221- * `:badkeytype`: The input `key_type` was invalid (e.g., not a subtype
3222- of the allowed key types like `atom()`, `integer()`, etc.).
3190+ Returns `{optional?, descr}`, `:error` (if no value across the whole domain is found),
3191+ or `:badmap`.
3192+
3193+ This is called `map_get/2` but it can be used to power `Map.fetch`, `Map.fetch!`,
3194+ `Map.get`, etc. except `map.key`.
32233195 """
3224- # TODO: Figure out how to use this operation from Elixir
32253196 def map_get ( :term , _key_descr ) , do: :badmap
32263197
32273198 def map_get ( % { } = descr , key_descr ) do
32283199 split_keys = map_split_keys_and_domains ( key_descr )
32293200
3201+ # If we are looking for infinite atoms, then either there are required/optional
3202+ # keys which may be selected, so we use not_set().
3203+ #
3204+ # In case, there are no keys, which will fail unless there are domain keys,
3205+ # so `not_set()` is still correct.
3206+ acc =
3207+ if infinite_atoms? ( key_descr ) do
3208+ not_set ( )
3209+ else
3210+ none ( )
3211+ end
3212+
32303213 case :maps . take ( :dynamic , descr ) do
32313214 :error ->
32323215 if descr_key? ( descr , :map ) and map_only? ( descr ) do
3233- { optional? , type_selected } = map_get_static ( descr , split_keys ) |> pop_optional_static ( )
3216+ { optional? , type_selected } =
3217+ map_get_static ( descr , split_keys , acc ) |> pop_optional_static ( )
32343218
3235- cond do
3236- empty? ( type_selected ) -> { :ok_absent , atom ( [ nil ] ) }
3237- optional? -> { :ok , nil_or_type ( type_selected ) }
3238- true -> { :ok_present , type_selected }
3219+ if empty? ( type_selected ) do
3220+ :error
3221+ else
3222+ { optional? , type_selected }
32393223 end
32403224 else
32413225 :badmap
@@ -3244,33 +3228,28 @@ defmodule Module.Types.Descr do
32443228 { dynamic , static } ->
32453229 if descr_key? ( dynamic , :map ) and map_only? ( static ) do
32463230 { optional_dynamic? , dynamic_type } =
3247- map_get_static ( dynamic , split_keys ) |> pop_optional_static ( )
3231+ map_get_static ( dynamic , split_keys , acc ) |> pop_optional_static ( )
32483232
32493233 { optional_static? , static_type } =
3250- map_get_static ( static , split_keys ) |> pop_optional_static ( )
3234+ map_get_static ( static , split_keys , acc ) |> pop_optional_static ( )
32513235
3252- type_selected = union ( dynamic ( dynamic_type ) , static_type )
3253-
3254- cond do
3255- empty? ( type_selected ) -> { :ok_absent , atom ( [ nil ] ) }
3256- optional_dynamic? or optional_static? -> { :ok , nil_or_type ( type_selected ) }
3257- true -> { :ok_present , type_selected }
3236+ if empty? ( dynamic_type ) do
3237+ :error
3238+ else
3239+ { optional_dynamic? or optional_static? , union ( dynamic ( dynamic_type ) , static_type ) }
32583240 end
32593241 else
32603242 :badmap
32613243 end
32623244 end
32633245 end
32643246
3265- defp nil_or_type ( type ) , do: union ( type , atom ( [ nil ] ) )
3266-
3267- defp map_get_static ( % { map: bdd } , split_keys ) do
3247+ defp map_get_static ( % { map: bdd } , split_keys , acc ) do
32683248 { required_keys , optional_keys , maybe_negated_set , required_domains , optional_domains } =
32693249 split_keys
32703250
32713251 dnf = map_bdd_to_dnf ( bdd )
32723252
3273- acc = none ( )
32743253 acc = map_get_keys ( dnf , required_keys , acc )
32753254 acc = map_get_keys ( dnf , optional_keys , acc )
32763255 acc = map_get_keys ( dnf , map_materialize_negated_set ( maybe_negated_set , bdd ) , acc )
@@ -3279,18 +3258,12 @@ defmodule Module.Types.Descr do
32793258 acc
32803259 end
32813260
3282- defp map_get_static ( % { } , _key ) , do: not_set ( )
3283- defp map_get_static ( :term , _key ) , do: term_or_optional ( )
3261+ defp map_get_static ( % { } , _split_keys , acc ) , do: acc
3262+ defp map_get_static ( :term , _split_keys , _acc ) , do: term_or_optional ( )
32843263
32853264 defp map_get_keys ( dnf , keys , acc ) do
32863265 Enum . reduce ( keys , acc , fn atom , acc ->
3287- { static_optional? , type } = map_dnf_fetch_static ( dnf , atom )
3288-
3289- if static_optional? do
3290- union ( type , acc ) |> nil_or_type ( ) |> if_set ( )
3291- else
3292- union ( type , acc )
3293- end
3266+ union ( map_dnf_fetch_static ( dnf , atom ) , acc )
32943267 end )
32953268 end
32963269
0 commit comments