From 7b25db2a54c0040a2154b9b3c928f39d7312cb55 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Sun, 3 Nov 2024 18:54:37 +0100 Subject: [PATCH 01/10] Start typing map and struct updates --- lib/elixir/lib/module/types/descr.ex | 14 ++-- lib/elixir/lib/module/types/expr.ex | 47 +++++++------ lib/elixir/lib/module/types/of.ex | 66 +++++++++++-------- lib/elixir/lib/module/types/pattern.ex | 4 +- .../test/elixir/module/types/expr_test.exs | 20 ++++-- 5 files changed, 87 insertions(+), 64 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index 0131a7bf828..20ad4511aec 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -1256,7 +1256,7 @@ defmodule Module.Types.Descr do end %{map: map} -> - map_get(map, key) |> pop_optional_static() + map_fetch_dnf(map, key) |> pop_optional_static() %{} -> {false, none()} @@ -1281,22 +1281,22 @@ defmodule Module.Types.Descr do case :maps.take(:dynamic, descr) do :error -> if map_only?(descr) do - map_put_static_descr(descr, key, type) + map_put_static_shared(descr, key, type) else :badmap end {dynamic, static} when static == @none -> if descr_key?(dynamic, :map) do - dynamic(map_put_static_descr(dynamic, key, type)) + dynamic(map_put_static_shared(dynamic, key, type)) else :badmap end {dynamic, static} -> if descr_key?(dynamic, :map) and map_only?(static) do - dynamic = map_put_static_descr(dynamic, key, type) - static = map_put_static_descr(static, key, type) + dynamic = map_put_static_shared(dynamic, key, type) + static = map_put_static_shared(static, key, type) union(dynamic(dynamic), static) else :badmap @@ -1305,7 +1305,7 @@ defmodule Module.Types.Descr do end # Directly inserts a key of a given type into every positive and negative map - defp map_put_static_descr(descr, key, type) do + defp map_put_static_shared(descr, key, type) do case map_delete_static(descr, key) do %{map: dnf} = descr -> dnf = @@ -1558,7 +1558,7 @@ defmodule Module.Types.Descr do # Takes a map dnf and returns the union of types it can take for a given key. # If the key may be undefined, it will contain the `not_set()` type. - defp map_get(dnf, key) do + defp map_fetch_dnf(dnf, key) do Enum.reduce(dnf, none(), fn # Optimization: if there are no negatives, # we can return the value directly. diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 29ededaec9c..d6495229b4f 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -114,38 +114,36 @@ defmodule Module.Types.Expr do end # %{map | ...} + # TODO: Once we support typed structs, we need to type check them here. def of_expr({:%{}, _, [{:|, _, [map, args]}]}, stack, context) do - {_args_type, context} = Of.closed_map(args, stack, context, &of_expr/3) - {_map_type, context} = of_expr(map, stack, context) - # TODO: intersect map with keys of terms for args - # TODO: Merge args_type into map_type with dynamic/static key requirement - {dynamic(open_map()), context} + {map_type, context} = of_expr(map, stack, context) + Of.update_map(map_type, args, stack, context, &of_expr/3) end # %Struct{map | ...} + # Note this code, by definition, adds missing struct fields to `map` + # because at runtime we do not check for them (only for __struct__ itself). + # TODO: Once we support typed structs, we need to type check them here. def of_expr( {:%, struct_meta, [module, {:%{}, _, [{:|, update_meta, [map, args]}]}]} = expr, stack, context ) do - {args_types, context} = - Enum.map_reduce(args, context, fn {key, value}, context when is_atom(key) -> - {type, context} = of_expr(value, stack, context) - {{key, type}, context} - end) - - # TODO: args_types could be an empty list - {struct_type, context} = - Of.struct(module, args_types, :only_defaults, struct_meta, stack, context) - + {info, context} = Of.struct_info(module, struct_meta, stack, context) + struct_type = Of.struct_type(module, info) {map_type, context} = of_expr(map, stack, context) if disjoint?(struct_type, map_type) do warning = {:badupdate, :struct, expr, struct_type, map_type, context} {error_type(), error(__MODULE__, warning, update_meta, stack, context)} else - # TODO: Merge args_type into map_type with dynamic/static key requirement - Of.struct(module, args_types, :merge_defaults, struct_meta, stack, context) + map_type = map_put!(map_type, :__struct__, atom([module])) + + Enum.reduce(args, {map_type, context}, fn + {key, value}, {map_type, context} when is_atom(key) -> + {value_type, context} = of_expr(value, stack, context) + {map_put!(map_type, key, value_type), context} + end) end end @@ -155,9 +153,8 @@ defmodule Module.Types.Expr do end # %Struct{} - def of_expr({:%, _, [module, {:%{}, _, args}]} = expr, stack, context) do - # TODO: We should not skip defaults - Of.struct(expr, module, args, :skip_defaults, stack, context, &of_expr/3) + def of_expr({:%, meta, [module, {:%{}, _, args}]}, stack, context) do + Of.struct_instance(module, args, meta, stack, context, &of_expr/3) end # () @@ -375,7 +372,8 @@ defmodule Module.Types.Expr do # Exceptions are not validated in the compiler, # to avoid export dependencies. So we do it here. if Code.ensure_loaded?(exception) and function_exported?(exception, :__struct__, 0) do - Of.struct(exception, args, :merge_defaults, meta, stack, context) + {info, context} = Of.struct_info(exception, meta, stack, context) + {Of.struct_type(exception, info, args), context} else # If the exception cannot be found or is invalid, # we call Of.remote/5 to emit a warning. @@ -515,6 +513,13 @@ defmodule Module.Types.Expr do context end + defp map_put!(map_type, key, value_type) do + case map_put(map_type, key, value_type) do + descr when is_descr(descr) -> descr + error -> raise "unexpected #{inspect(error)}" + end + end + ## Warning formatting def format_diagnostic({:badupdate, type, expr, expected_type, actual_type, context}) do diff --git a/lib/elixir/lib/module/types/of.ex b/lib/elixir/lib/module/types/of.ex index cfed6facdbe..4f3c54a2e40 100644 --- a/lib/elixir/lib/module/types/of.ex +++ b/lib/elixir/lib/module/types/of.ex @@ -107,9 +107,29 @@ defmodule Module.Types.Of do @doc """ Builds a closed map. """ - def closed_map(pairs, extra \\ [], stack, context, of_fun) do + def closed_map(pairs, stack, context, of_fun) do + key_permutations(pairs, stack, context, of_fun, fn closed?, pairs -> + if closed?, do: closed_map(pairs), else: open_map(pairs) + end) + end + + @doc """ + Updates a map with the given keys. + """ + def update_map(map_type, pairs, stack, context, of_fun) do + key_permutations(pairs, stack, context, of_fun, fn _closed?, pairs -> + Enum.reduce(pairs, map_type, fn {key, type}, acc -> + case map_put(acc, key, type) do + descr when is_descr(descr) -> descr + error -> throw({error, key, type}) + end + end) + end) + end + + defp key_permutations(pairs, stack, context, of_fun, of_map) do {closed?, single, multiple, context} = - Enum.reduce(pairs, {true, extra, [], context}, fn + Enum.reduce(pairs, {true, [], [], context}, fn {key, value}, {closed?, single, multiple, context} -> {keys, context} = of_finite_key_type(key, stack, context, of_fun) {value_type, context} = of_fun.(value, stack, context) @@ -129,13 +149,11 @@ defmodule Module.Types.Of do map = case Enum.reverse(multiple) do [] -> - pairs = Enum.reverse(single) - if closed?, do: closed_map(pairs), else: open_map(pairs) + of_map.(closed?, Enum.reverse(single)) [{keys, type} | tail] -> for key <- keys, t <- cartesian_map(tail) do - pairs = Enum.reverse(single, [{key, type} | t]) - if closed?, do: closed_map(pairs), else: open_map(pairs) + of_map.(closed?, Enum.reverse(single, [{key, type} | t])) end |> Enum.reduce(&union/2) end @@ -167,9 +185,9 @@ defmodule Module.Types.Of do end @doc """ - Handles structs creation. + Handles instantiation of a new struct. """ - def struct({:%, meta, _}, struct, args, default_handling, stack, context, of_fun) + def struct_instance(struct, args, meta, stack, context, of_fun) when is_atom(struct) do # The compiler has already checked the keys are atoms and which ones are required. {args_types, context} = @@ -178,27 +196,8 @@ defmodule Module.Types.Of do {{key, type}, context} end) - struct(struct, args_types, default_handling, meta, stack, context) - end - - @doc """ - Struct handling assuming the args have already been converted. - """ - # TODO: Allow structs fields to be defined and validate args against the struct types. - # TODO: Use the struct default values to define the default types. - def struct(struct, args_types, default_handling, meta, stack, context) do {info, context} = struct_info(struct, meta, stack, context) - term = term() - defaults = for %{field: field} <- info, do: {field, term} - - pairs = - case default_handling do - :merge_defaults -> [{:__struct__, atom([struct])} | defaults] ++ args_types - :skip_defaults -> [{:__struct__, atom([struct])} | args_types] - :only_defaults -> [{:__struct__, atom([struct])} | defaults] - end - - {closed_map(pairs), context} + {struct_type(struct, info, args_types), context} end @doc """ @@ -214,6 +213,17 @@ defmodule Module.Types.Of do {info, context} end + @doc """ + Builds a type from the struct info. + """ + def struct_type(struct, info, args_types \\ []) do + term = term() + pairs = for %{field: field} <- info, do: {field, term} + pairs = [{:__struct__, atom([struct])} | pairs] + pairs = if args_types == [], do: pairs, else: pairs ++ args_types + closed_map(pairs) + end + ## Binary @doc """ diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 204f4950a3b..a0b6f60c9ec 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -657,10 +657,10 @@ defmodule Module.Types.Pattern do end # %Struct{...} - def of_guard({:%, _, [module, {:%{}, _, args}]} = struct, _expected, _expr, stack, context) + def of_guard({:%, meta, [module, {:%{}, _, args}]} = struct, _expected, _expr, stack, context) when is_atom(module) do fun = &of_guard(&1, dynamic(), struct, &2, &3) - Of.struct(struct, module, args, :skip_defaults, stack, context, fun) + Of.struct_instance(module, args, meta, stack, context, fun) end # %{...} diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index 10ef0e94f6a..8585638b091 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -515,9 +515,17 @@ defmodule Module.Types.ExprTest do test "updating structs" do assert typecheck!([x], %Point{x | x: :zero}) == - closed_map(__struct__: atom([Point]), x: atom([:zero]), y: term(), z: term()) + dynamic(open_map(__struct__: atom([Point]), x: atom([:zero]))) - assert typeerror!([x = :foo], %Point{x | x: :zero}) == + assert typecheck!([x], %Point{%Point{x | x: :zero} | y: :one}) == + dynamic(open_map(__struct__: atom([Point]), x: atom([:zero]), y: atom([:one]))) + + assert typeerror!( + ( + x = %{x: 0} + %Point{x | x: :zero} + ) + ) == ~l""" incompatible types in struct update: @@ -529,13 +537,13 @@ defmodule Module.Types.ExprTest do but got type: - dynamic(:foo) + %{x: integer()} where "x" was given the type: - # type: dynamic(:foo) - # from: types_test.ex:LINE-1 - x = :foo + # type: %{x: integer()} + # from: types_test.ex:LINE-4 + x = %{x: 0} """ end From 58a6253789526c1af1e961339f75ff7ef3ae9202 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Sun, 3 Nov 2024 19:11:25 +0100 Subject: [PATCH 02/10] Tests --- lib/elixir/lib/module/types/expr.ex | 42 ++++++++++++++++--- lib/elixir/lib/module/types/of.ex | 17 ++------ .../test/elixir/module/types/expr_test.exs | 24 +++++++++++ 3 files changed, 64 insertions(+), 19 deletions(-) diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index d6495229b4f..05f7bc988c3 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -115,9 +115,20 @@ defmodule Module.Types.Expr do # %{map | ...} # TODO: Once we support typed structs, we need to type check them here. - def of_expr({:%{}, _, [{:|, _, [map, args]}]}, stack, context) do + def of_expr({:%{}, meta, [{:|, _, [map, args]}]} = expr, stack, context) do {map_type, context} = of_expr(map, stack, context) - Of.update_map(map_type, args, stack, context, &of_expr/3) + + Of.permutate_map(args, stack, context, &of_expr/3, fn _closed?, pairs -> + # TODO: If closed? is false, we need to open up the map + Enum.reduce(pairs, map_type, fn {key, type}, acc -> + case map_put(acc, key, type) do + descr when is_descr(descr) -> descr + :badmap -> throw({:badmap, map_type, expr, context}) + end + end) + end) + catch + error -> {error_type(), error(__MODULE__, error, meta, stack, context)} end # %Struct{map | ...} @@ -134,7 +145,7 @@ defmodule Module.Types.Expr do {map_type, context} = of_expr(map, stack, context) if disjoint?(struct_type, map_type) do - warning = {:badupdate, :struct, expr, struct_type, map_type, context} + warning = {:badstruct, expr, struct_type, map_type, context} {error_type(), error(__MODULE__, warning, update_meta, stack, context)} else map_type = map_put!(map_type, :__struct__, atom([module])) @@ -522,7 +533,7 @@ defmodule Module.Types.Expr do ## Warning formatting - def format_diagnostic({:badupdate, type, expr, expected_type, actual_type, context}) do + def format_diagnostic({:badstruct, expr, expected_type, actual_type, context}) do traces = collect_traces(expr, context) %{ @@ -530,7 +541,7 @@ defmodule Module.Types.Expr do message: IO.iodata_to_binary([ """ - incompatible types in #{type} update: + incompatible types in struct update: #{expr_to_string(expr) |> indent(4)} @@ -547,6 +558,27 @@ defmodule Module.Types.Expr do } end + def format_diagnostic({:badmap, type, expr, context}) do + traces = collect_traces(expr, context) + + %{ + details: %{typing_traces: traces}, + message: + IO.iodata_to_binary([ + """ + expected a map within map update syntax: + + #{expr_to_string(expr) |> indent(4)} + + but got type: + + #{to_quoted_string(type) |> indent(4)} + """, + format_traces(traces) + ]) + } + end + def format_diagnostic({:badbinary, type, expr, context}) do traces = collect_traces(expr, context) diff --git a/lib/elixir/lib/module/types/of.ex b/lib/elixir/lib/module/types/of.ex index 4f3c54a2e40..16a13bf4f44 100644 --- a/lib/elixir/lib/module/types/of.ex +++ b/lib/elixir/lib/module/types/of.ex @@ -108,26 +108,15 @@ defmodule Module.Types.Of do Builds a closed map. """ def closed_map(pairs, stack, context, of_fun) do - key_permutations(pairs, stack, context, of_fun, fn closed?, pairs -> + permutate_map(pairs, stack, context, of_fun, fn closed?, pairs -> if closed?, do: closed_map(pairs), else: open_map(pairs) end) end @doc """ - Updates a map with the given keys. + Builds permutation of maps according to the given keys. """ - def update_map(map_type, pairs, stack, context, of_fun) do - key_permutations(pairs, stack, context, of_fun, fn _closed?, pairs -> - Enum.reduce(pairs, map_type, fn {key, type}, acc -> - case map_put(acc, key, type) do - descr when is_descr(descr) -> descr - error -> throw({error, key, type}) - end - end) - end) - end - - defp key_permutations(pairs, stack, context, of_fun, of_map) do + def permutate_map(pairs, stack, context, of_fun, of_map) do {closed?, single, multiple, context} = Enum.reduce(pairs, {true, [], [], context}, fn {key, value}, {closed?, single, multiple, context} -> diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index 8585638b091..0099a79a774 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -513,6 +513,30 @@ defmodule Module.Types.ExprTest do ) end + test "updating maps" do + assert typecheck!([x], %{x | x: :zero}) == + dynamic(open_map(x: atom([:zero]))) + + assert typecheck!([x], %{%{x | x: :zero} | y: :one}) == + dynamic(open_map(x: atom([:zero]), y: atom([:one]))) + + assert typeerror!([x = :foo], %{x | x: :zero}) == ~l""" + expected a map within map update syntax: + + %{x | x: :zero} + + but got type: + + dynamic(:foo) + + where "x" was given the type: + + # type: dynamic(:foo) + # from: types_test.ex:LINE + x = :foo + """ + end + test "updating structs" do assert typecheck!([x], %Point{x | x: :zero}) == dynamic(open_map(__struct__: atom([Point]), x: atom([:zero]))) From 725ff7eb0adc4fdf11dd0282f873cfc6f5278bce Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 4 Nov 2024 08:47:46 +0100 Subject: [PATCH 03/10] Consider keys may be overridden in a map --- lib/elixir/lib/module/types/expr.ex | 55 +++++++++++--- lib/elixir/lib/module/types/of.ex | 44 ++++++++---- .../test/elixir/module/types/expr_test.exs | 72 +++++++++++++++++-- 3 files changed, 144 insertions(+), 27 deletions(-) diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 05f7bc988c3..623dd27d277 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -118,14 +118,32 @@ defmodule Module.Types.Expr do def of_expr({:%{}, meta, [{:|, _, [map, args]}]} = expr, stack, context) do {map_type, context} = of_expr(map, stack, context) - Of.permutate_map(args, stack, context, &of_expr/3, fn _closed?, pairs -> - # TODO: If closed? is false, we need to open up the map - Enum.reduce(pairs, map_type, fn {key, type}, acc -> - case map_put(acc, key, type) do - descr when is_descr(descr) -> descr - :badmap -> throw({:badmap, map_type, expr, context}) - end - end) + Of.permutate_map(args, stack, context, &of_expr/3, fn fallback, keys, pairs -> + # If there is no fallback (i.e. it is closed), we can update the existing map, + # otherwise we only assert the existing keys. + keys = if fallback == none(), do: keys, else: Enum.map(pairs, &elem(&1, 0)) ++ keys + + # Assert the keys exist + fallback = + Enum.reduce(keys, fallback, fn key, acc -> + case map_fetch(map_type, key) do + {_, value_type} -> union(value_type, acc) + :badkey -> throw({:badkey, map_type, key, expr, context}) + :badmap -> throw({:badmap, map_type, expr, context}) + end + end) + + if fallback == none() do + Enum.reduce(pairs, map_type, fn {key, type}, acc -> + case map_put(acc, key, type) do + descr when is_descr(descr) -> descr + :badmap -> throw({:badmap, map_type, expr, context}) + end + end) + else + # TODO: Use the fallback type to actually indicate if open or closed. + open_map(pairs) + end end) catch error -> {error_type(), error(__MODULE__, error, meta, stack, context)} @@ -579,6 +597,27 @@ defmodule Module.Types.Expr do } end + def format_diagnostic({:badkey, type, key, expr, context}) do + traces = collect_traces(expr, context) + + %{ + details: %{typing_traces: traces}, + message: + IO.iodata_to_binary([ + """ + expected a map with key #{inspect(key)} in map update syntax: + + #{expr_to_string(expr) |> indent(4)} + + but got type: + + #{to_quoted_string(type) |> indent(4)} + """, + format_traces(traces) + ]) + } + end + def format_diagnostic({:badbinary, type, expr, context}) do traces = collect_traces(expr, context) diff --git a/lib/elixir/lib/module/types/of.ex b/lib/elixir/lib/module/types/of.ex index 16a13bf4f44..a6f91b602ab 100644 --- a/lib/elixir/lib/module/types/of.ex +++ b/lib/elixir/lib/module/types/of.ex @@ -108,8 +108,9 @@ defmodule Module.Types.Of do Builds a closed map. """ def closed_map(pairs, stack, context, of_fun) do - permutate_map(pairs, stack, context, of_fun, fn closed?, pairs -> - if closed?, do: closed_map(pairs), else: open_map(pairs) + permutate_map(pairs, stack, context, of_fun, fn fallback, _keys, pairs -> + # TODO: Use the fallback type to actually indicate if open or closed. + if fallback == none(), do: closed_map(pairs), else: open_map(pairs) end) end @@ -117,49 +118,62 @@ defmodule Module.Types.Of do Builds permutation of maps according to the given keys. """ def permutate_map(pairs, stack, context, of_fun, of_map) do - {closed?, single, multiple, context} = - Enum.reduce(pairs, {true, [], [], context}, fn - {key, value}, {closed?, single, multiple, context} -> - {keys, context} = of_finite_key_type(key, stack, context, of_fun) + {dynamic?, fallback, single, multiple, assert, context} = + Enum.reduce(pairs, {false, none(), [], [], [], context}, fn + {key, value}, {dynamic?, fallback, single, multiple, assert, context} -> + {dynamic_key?, keys, context} = of_finite_key_type(key, stack, context, of_fun) {value_type, context} = of_fun.(value, stack, context) + dynamic? = dynamic? or dynamic_key? or gradual?(value_type) case keys do :none -> - {false, single, multiple, context} + fallback = union(fallback, value_type) + + {fallback, assert} = + Enum.reduce(single, {fallback, assert}, fn {key, type}, {fallback, assert} -> + {union(fallback, type), [key | assert]} + end) + + {fallback, assert} = + Enum.reduce(multiple, {fallback, assert}, fn {keys, type}, {fallback, assert} -> + {union(fallback, type), keys ++ assert} + end) + + {dynamic?, fallback, [], [], assert, context} [key] when multiple == [] -> - {closed?, [{key, value_type} | single], multiple, context} + {dynamic?, fallback, [{key, value_type} | single], multiple, assert, context} keys -> - {closed?, single, [{keys, value_type} | multiple], context} + {dynamic?, fallback, single, [{keys, value_type} | multiple], assert, context} end end) map = case Enum.reverse(multiple) do [] -> - of_map.(closed?, Enum.reverse(single)) + of_map.(fallback, Enum.uniq(assert), Enum.reverse(single)) [{keys, type} | tail] -> for key <- keys, t <- cartesian_map(tail) do - of_map.(closed?, Enum.reverse(single, [{key, type} | t])) + of_map.(fallback, Enum.uniq(assert), Enum.reverse(single, [{key, type} | t])) end |> Enum.reduce(&union/2) end - {map, context} + if dynamic?, do: {dynamic(map), context}, else: {map, context} end defp of_finite_key_type(key, _stack, context, _of_fun) when is_atom(key) do - {[key], context} + {false, [key], context} end defp of_finite_key_type(key, stack, context, of_fun) do {key_type, context} = of_fun.(key, stack, context) case atom_fetch(key_type) do - {:finite, list} -> {list, context} - _ -> {:none, context} + {:finite, list} -> {gradual?(key_type), list, context} + _ -> {gradual?(key_type), :none, context} end end diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index 0099a79a774..a0d9f4c71d9 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -481,10 +481,8 @@ defmodule Module.Types.ExprTest do end describe "maps/structs" do - test "creating maps" do + test "creating closed maps" do assert typecheck!(%{foo: :bar}) == closed_map(foo: atom([:bar])) - assert typecheck!(%{123 => 456}) == open_map() - assert typecheck!(%{123 => 456, foo: :bar}) == open_map(foo: atom([:bar])) assert typecheck!([x], %{key: x}) == dynamic(closed_map(key: term())) assert typecheck!( @@ -495,6 +493,14 @@ defmodule Module.Types.ExprTest do ) == closed_map(foo: atom([:second])) end + test "creating open maps" do + assert typecheck!(%{123 => 456}) == open_map() + # Since key cannot override :foo, we preserve it + assert typecheck!([key], %{key => 456, foo: :bar}) == dynamic(open_map(foo: atom([:bar]))) + # Since key can override :foo, we do not preserve it + assert typecheck!([key], %{:foo => :bar, key => :baz}) == dynamic(open_map()) + end + test "creating structs" do assert typecheck!(%Point{}) == closed_map( @@ -513,7 +519,7 @@ defmodule Module.Types.ExprTest do ) end - test "updating maps" do + test "updating to closed maps" do assert typecheck!([x], %{x | x: :zero}) == dynamic(open_map(x: atom([:zero]))) @@ -537,6 +543,64 @@ defmodule Module.Types.ExprTest do """ end + test "updating to open maps" do + assert typecheck!( + [key], + ( + x = %{foo: :bar} + %{x | key => :baz} + ) + ) == dynamic(open_map()) + + # Since key cannot override :foo, we preserve it + assert typecheck!( + [key], + ( + x = %{foo: :bar} + %{x | key => :baz, foo: :bat} + ) + ) == dynamic(open_map(foo: atom([:bat]))) + + # Since key can override :foo, we do not preserve it + assert typecheck!( + [key], + ( + x = %{foo: :bar} + %{x | :foo => :baz, key => :bat} + ) + ) == dynamic(open_map()) + + # The goal of this test is to verufy we assert keys, + # even if they may be overridden later. + assert typeerror!( + [key], + ( + x = %{key: :value} + %{x | :foo => :baz, key => :bat} + ) + ) == ~l""" + expected a map with key :foo in map update syntax: + + %{x | :foo => :baz, key => :bat} + + but got type: + + %{key: :value} + + where "key" was given the type: + + # type: dynamic() + # from: types_test.ex:538 + key + + where "x" was given the type: + + # type: %{key: :value} + # from: types_test.ex:540 + x = %{key: :value} + """ + end + test "updating structs" do assert typecheck!([x], %Point{x | x: :zero}) == dynamic(open_map(__struct__: atom([Point]), x: atom([:zero]))) From 6d14ddf4d7958069825af66a1f1c67e5ae49cbd0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 4 Nov 2024 09:04:11 +0100 Subject: [PATCH 04/10] Update docs --- lib/elixir/lib/module/types/expr.ex | 17 +++++++++-------- 1 file changed, 9 insertions(+), 8 deletions(-) diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 623dd27d277..24cc630a7cc 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -124,14 +124,13 @@ defmodule Module.Types.Expr do keys = if fallback == none(), do: keys, else: Enum.map(pairs, &elem(&1, 0)) ++ keys # Assert the keys exist - fallback = - Enum.reduce(keys, fallback, fn key, acc -> - case map_fetch(map_type, key) do - {_, value_type} -> union(value_type, acc) - :badkey -> throw({:badkey, map_type, key, expr, context}) - :badmap -> throw({:badmap, map_type, expr, context}) - end - end) + Enum.each(keys, fn key -> + case map_fetch(map_type, key) do + {_, _} -> :ok + :badkey -> throw({:badkey, map_type, key, expr, context}) + :badmap -> throw({:badmap, map_type, expr, context}) + end + end) if fallback == none() do Enum.reduce(pairs, map_type, fn {key, type}, acc -> @@ -142,6 +141,8 @@ defmodule Module.Types.Expr do end) else # TODO: Use the fallback type to actually indicate if open or closed. + # The fallback must be unioned with the result of map_values with all + # `keys` deleted. open_map(pairs) end end) From 10f40dead19c57ca667d433daa50909b67acd7e5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 4 Nov 2024 09:58:17 +0100 Subject: [PATCH 05/10] Fix tests --- lib/elixir/test/elixir/module/types/expr_test.exs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index a0d9f4c71d9..23ac53e7509 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -570,7 +570,7 @@ defmodule Module.Types.ExprTest do ) ) == dynamic(open_map()) - # The goal of this test is to verufy we assert keys, + # The goal of this test is to verify we assert keys, # even if they may be overridden later. assert typeerror!( [key], @@ -590,13 +590,13 @@ defmodule Module.Types.ExprTest do where "key" was given the type: # type: dynamic() - # from: types_test.ex:538 + # from: types_test.ex:LINE-5 key where "x" was given the type: # type: %{key: :value} - # from: types_test.ex:540 + # from: types_test.ex:LINE-3 x = %{key: :value} """ end From 97ee5ec03c5529ae30b88b0acce682e7656b2435 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 4 Nov 2024 14:44:15 +0100 Subject: [PATCH 06/10] More tests --- .../test/elixir/module/types/expr_test.exs | 20 +++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index 23ac53e7509..d586369a528 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -484,13 +484,33 @@ defmodule Module.Types.ExprTest do test "creating closed maps" do assert typecheck!(%{foo: :bar}) == closed_map(foo: atom([:bar])) assert typecheck!([x], %{key: x}) == dynamic(closed_map(key: term())) + end + test "creating closed maps with dynamic keys" do assert typecheck!( ( foo = :foo %{foo => :first, foo => :second} ) ) == closed_map(foo: atom([:second])) + + assert typecheck!( + ( + foo_or_bar = + cond do + :rand.uniform() > 0.5 -> :foo + true -> :bar + end + + %{foo_or_bar => :first, foo_or_bar => :second} + ) + ) + |> equal?( + closed_map(foo: atom([:second])) + |> union(closed_map(bar: atom([:second]))) + |> union(closed_map(foo: atom([:first]), bar: atom([:second]))) + |> union(closed_map(bar: atom([:first]), foo: atom([:second]))) + ) end test "creating open maps" do From d30f483a6f644cf03e1692c7cb0f17ec87b090ed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 5 Nov 2024 09:40:58 +0100 Subject: [PATCH 07/10] Add map_take to descr --- lib/elixir/lib/module/types/descr.ex | 159 ++++++++++------ .../test/elixir/module/types/descr_test.exs | 179 ++++++++++++------ 2 files changed, 223 insertions(+), 115 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index 20ad4511aec..f80e7c0078a 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -83,8 +83,8 @@ defmodule Module.Types.Descr do @boolset :sets.from_list([true, false], version: 2) def boolean(), do: %{atom: {:union, @boolset}} - # Map helpers - # + ## Optional + # `not_set()` is a special base type that represents an not_set field in a map. # E.g., `%{a: integer(), b: not_set(), ...}` represents a map with an integer # field `a` and an not_set field `b`, and possibly other fields. @@ -153,12 +153,15 @@ defmodule Module.Types.Descr do ## Set operations - def term_type?(:term), do: true - def term_type?(descr), do: subtype_static?(unfolded_term(), Map.delete(descr, :dynamic)) - + @doc """ + Returns true if the type has a gradual part. + """ def gradual?(:term), do: false def gradual?(descr), do: is_map_key(descr, :dynamic) + @doc """ + Returns true if hte type only has a gradual part. + """ def only_gradual?(%{dynamic: _} = descr), do: map_size(descr) == 1 def only_gradual?(_), do: false @@ -175,11 +178,17 @@ defmodule Module.Types.Descr do end end + @compile {:inline, lazy_union: 2} + defp lazy_union(:term, _fun), do: :term + defp lazy_union(descr, fun), do: union(descr, fun.()) + @doc """ Computes the union of two descrs. """ def union(:term, other), do: optional_to_term(other) def union(other, :term), do: optional_to_term(other) + def union(none, other) when none == @none, do: other + def union(other, none) when none == @none, do: other def union(left, right) do left = unfold(left) @@ -201,7 +210,6 @@ defmodule Module.Types.Descr do end end - @compile {:inline, union: 3} defp union(:atom, v1, v2), do: atom_union(v1, v2) defp union(:bitmap, v1, v2), do: v1 ||| v2 defp union(:dynamic, v1, v2), do: dynamic_union(v1, v2) @@ -239,7 +247,6 @@ defmodule Module.Types.Descr do end # Returning 0 from the callback is taken as none() for that subtype. - @compile {:inline, intersection: 3} defp intersection(:atom, v1, v2), do: atom_intersection(v1, v2) defp intersection(:bitmap, v1, v2), do: v1 &&& v2 defp intersection(:dynamic, v1, v2), do: dynamic_intersection(v1, v2) @@ -299,7 +306,6 @@ defmodule Module.Types.Descr do defp iterator_difference_static(:none, map), do: map # Returning 0 from the callback is taken as none() for that subtype. - @compile {:inline, difference: 3} defp difference(:atom, v1, v2), do: atom_difference(v1, v2) defp difference(:bitmap, v1, v2), do: v1 - (v1 &&& v2) defp difference(:dynamic, v1, v2), do: dynamic_difference(v1, v2) @@ -378,7 +384,6 @@ defmodule Module.Types.Descr do end end - @compile {:inline, to_quoted: 2} defp to_quoted(:atom, val), do: atom_to_quoted(val) defp to_quoted(:bitmap, val), do: bitmap_to_quoted(val) defp to_quoted(:dynamic, descr), do: dynamic_to_quoted(descr) @@ -513,6 +518,12 @@ defmodule Module.Types.Descr do end end + @doc """ + Optimized version of `not empty?(term(), type)`. + """ + def term_type?(:term), do: true + def term_type?(descr), do: subtype_static?(unfolded_term(), Map.delete(descr, :dynamic)) + @doc """ Optimized version of `not empty?(intersection(empty_list(), type))`. """ @@ -1061,7 +1072,7 @@ defmodule Module.Types.Descr do end end - # TODO: Eliminate empty lists from the union + # TODO: Eliminate empty lists from the union. defp list_normalize(dnf), do: dnf # Enum.filter(dnf, fn {list_type, last_type, negs} -> # not Enum.any?(negs, fn neg -> subtype?(list_type, neg) end) @@ -1280,7 +1291,7 @@ defmodule Module.Types.Descr do defp map_put_static_value(descr, key, type) do case :maps.take(:dynamic, descr) do :error -> - if map_only?(descr) do + if descr_key?(descr, :map) and map_only?(descr) do map_put_static_shared(descr, key, type) else :badmap @@ -1306,8 +1317,8 @@ defmodule Module.Types.Descr do # Directly inserts a key of a given type into every positive and negative map defp map_put_static_shared(descr, key, type) do - case map_delete_static(descr, key) do - %{map: dnf} = descr -> + case map_take_static(descr, key, :term) do + {_, %{map: dnf} = descr} -> dnf = Enum.map(dnf, fn {tag, fields, negs} -> {tag, Map.put(fields, key, type), @@ -1318,7 +1329,7 @@ defmodule Module.Types.Descr do %{descr | map: dnf} - %{} -> + {_, %{}} -> descr end end @@ -1439,6 +1450,17 @@ defmodule Module.Types.Descr do @doc """ Removes a key from a map type. + """ + def map_delete(descr, key) do + # We pass :term as the initial value so we can avoid computing the unions. + case map_take(descr, key, :term) do + {_, descr} -> {:ok, descr} + error -> error + end + end + + @doc """ + Removes a key from a map type and return its type. ## Algorithm @@ -1448,26 +1470,38 @@ defmodule Module.Types.Descr do 3. Intersect this with an open record type where the key is explicitly absent. This step eliminates the key from open record types where it was implicitly present. """ - def map_delete(:term, _key), do: :badmap + def map_take(descr, key) do + map_take(descr, key, none()) + end + + defp map_take(:term, _key, _initial), do: :badmap - def map_delete(descr, key) when is_atom(key) do + defp map_take(descr, key, initial) when is_atom(key) do case :maps.take(:dynamic, descr) do :error -> - # Note: the empty typ is not a valid input + # Note: the empty type is not a valid input if descr_key?(descr, :map) and map_only?(descr) do - map_delete_static(descr, key) - |> intersection(open_map([{key, not_set()}])) + {taken, descr} = map_take_static(descr, key, initial) + {taken, intersection(descr, open_map([{key, not_set()}]))} else :badmap end {dynamic, static} -> if descr_key?(dynamic, :map) and map_only?(static) do - dynamic_result = map_delete_static(dynamic, key) - static_result = map_delete_static(static, key) + {dynamic_taken, dynamic_result} = map_take_static(dynamic, key, initial) + {static_taken, static_result} = map_take_static(static, key, initial) - union(dynamic(dynamic_result), static_result) - |> intersection(open_map([{key, not_set()}])) + taken = + if dynamic_taken == :term, + do: dynamic(), + else: union(dynamic(dynamic_taken), static_taken) + + result = + union(dynamic(dynamic_result), static_result) + |> intersection(open_map([{key, not_set()}])) + + {taken, result} else :badmap end @@ -1475,35 +1509,37 @@ defmodule Module.Types.Descr do end # Takes a static map type and removes a key from it. - defp map_delete_static(%{map: dnf}, key) do - Enum.reduce(dnf, none(), fn - # Optimization: if there are no negatives, we can directly remove the key. - {tag, fields, []}, acc -> - union(acc, %{map: map_new(tag, :maps.remove(key, fields))}) + defp map_take_static(%{map: dnf}, key, initial) do + {value, map} = + Enum.reduce(dnf, {initial, none()}, fn + # Optimization: if there are no negatives, we can directly remove the key. + {tag, fields, []}, {taken, map} -> + {fst, snd} = map_pop_key(tag, fields, key) + {lazy_union(taken, fn -> fst end), union(map, snd)} - {tag, fields, negs}, acc -> - {fst, snd} = map_pop_key(tag, fields, key) + {tag, fields, negs}, {taken, map} -> + {fst, snd} = map_pop_key(tag, fields, key) - union( - acc, case map_split_negative(negs, key) do :empty -> - none() + {taken, map} negative -> - negative |> pair_make_disjoint() |> pair_eliminate_negations_snd(fst, snd) + disjoint = pair_make_disjoint(negative) + + {lazy_union(taken, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end), + disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)} end - ) - end) + end) + + {remove_optional_static(value), map} end - defp map_delete_static(:term, key), do: open_map([{key, not_set()}]) + defp map_take_static(:term, key, _initial), do: {:term, open_map([{key, not_set()}])} # If there is no map part to this static type, there is nothing to delete. - defp map_delete_static(_type, _key), do: none() + defp map_take_static(_type, _key, initial), do: {initial, none()} - # Emptiness checking for maps. - # # Short-circuits if it finds a non-empty map literal in the union. # Since the algorithm is recursive, we implement the short-circuiting # as throw/catch. @@ -1574,10 +1610,15 @@ defmodule Module.Types.Descr do {fst, snd} = map_pop_key(tag, fields, key) case map_split_negative(negs, key) do - :empty -> none() - negative -> negative |> pair_make_disjoint() |> pair_eliminate_negations_fst(fst, snd) + :empty -> + acc + + negative -> + negative + |> pair_make_disjoint() + |> pair_eliminate_negations_fst(fst, snd) + |> union(acc) end - |> union(acc) end) end @@ -1597,7 +1638,7 @@ 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. + # 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])) @@ -1989,10 +2030,15 @@ defmodule Module.Types.Descr do {fst, snd} = tuple_pop_index(tag, elements, index) case tuple_split_negative(negs, index) do - :empty -> none() - negative -> negative |> pair_make_disjoint() |> pair_eliminate_negations_fst(fst, snd) + :empty -> + acc + + negative -> + negative + |> pair_make_disjoint() + |> pair_eliminate_negations_fst(fst, snd) + |> union(acc) end - |> union(acc) end) end @@ -2077,13 +2123,16 @@ defmodule Module.Types.Descr do {tag, elements, negs}, acc -> {fst, snd} = tuple_pop_index(tag, elements, index) - union( - acc, - case tuple_split_negative(negs, index) do - :empty -> none() - negative -> negative |> pair_make_disjoint() |> pair_eliminate_negations_snd(fst, snd) - end - ) + case tuple_split_negative(negs, index) do + :empty -> + acc + + negative -> + negative + |> pair_make_disjoint() + |> pair_eliminate_negations_snd(fst, snd) + |> union(acc) + end end) end @@ -2181,7 +2230,7 @@ defmodule Module.Types.Descr do end ## Pairs - # + # To simplify disjunctive normal forms of e.g., map types, it is useful to # convert them into disjunctive normal forms of pairs of types, and define # normalization algorithms on pairs. diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index 331eccec646..d28ae3d506f 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -945,96 +945,155 @@ defmodule Module.Types.DescrTest do assert map_delete(term(), :a) == :badmap assert map_delete(integer(), :a) == :badmap assert map_delete(union(open_map(), integer()), :a) == :badmap - assert map_delete(closed_map(a: integer(), b: atom()), :a) == closed_map(b: atom()) - assert map_delete(empty_map(), :a) == empty_map() - assert map_delete(closed_map(a: if_set(integer()), b: atom()), :a) == closed_map(b: atom()) + assert map_delete(closed_map(a: integer(), b: atom()), :a) == {:ok, closed_map(b: atom())} + assert map_delete(empty_map(), :a) == {:ok, empty_map()} + + assert map_delete(closed_map(a: if_set(integer()), b: atom()), :a) == + {:ok, closed_map(b: atom())} # Deleting a non-existent key assert map_delete(closed_map(a: integer(), b: atom()), :c) == - closed_map(a: integer(), b: atom()) + {:ok, closed_map(a: integer(), b: atom())} + + # Deleting from a dynamic map + assert map_delete(dynamic(), :a) == {:ok, dynamic(open_map(a: not_set()))} # Deleting from an open map - assert map_delete(open_map(a: integer(), b: atom()), :a) - |> equal?(open_map(a: not_set(), b: atom())) + {:ok, type} = map_delete(open_map(a: integer(), b: atom()), :a) + assert equal?(type, open_map(a: not_set(), b: atom())) # Deleting from a union of maps - assert map_delete(union(closed_map(a: integer()), closed_map(b: atom())), :a) - |> equal?(union(empty_map(), closed_map(b: atom()))) + {:ok, type} = map_delete(union(closed_map(a: integer()), closed_map(b: atom())), :a) + assert equal?(type, union(empty_map(), closed_map(b: atom()))) + + # Deleting from a gradual map + {:ok, type} = map_delete(union(dynamic(), closed_map(a: integer())), :a) + assert equal?(type, union(dynamic(open_map(a: not_set())), empty_map())) + + {:ok, type} = map_delete(dynamic(open_map(a: not_set())), :b) + assert equal?(type, dynamic(open_map(a: not_set(), b: not_set()))) + + # Deleting from an intersection of maps + {:ok, type} = map_delete(intersection(open_map(a: integer()), open_map(b: atom())), :a) + assert equal?(type, open_map(a: not_set(), b: atom())) + + # Deleting from a difference of maps + {:ok, type} = + map_delete(difference(closed_map(a: integer(), b: atom()), closed_map(a: integer())), :b) + + assert equal?(type, closed_map(a: integer())) + + {:ok, type} = map_delete(difference(open_map(), open_map(a: not_set())), :a) + assert equal?(type, open_map(a: not_set())) + end + + test "map_take" do + assert map_take(term(), :a) == :badmap + assert map_take(integer(), :a) == :badmap + assert map_take(union(open_map(), integer()), :a) == :badmap + + assert map_take(closed_map(a: integer(), b: atom()), :a) == + {integer(), closed_map(b: atom())} + + assert map_take(empty_map(), :a) == {none(), empty_map()} + + assert map_take(closed_map(a: if_set(integer()), b: atom()), :a) == + {integer(), closed_map(b: atom())} + + # Deleting a non-existent key + assert map_take(closed_map(a: integer(), b: atom()), :c) == + {none(), closed_map(a: integer(), b: atom())} # Deleting from a dynamic map - assert map_delete(dynamic(), :a) == dynamic(open_map(a: not_set())) + assert map_take(dynamic(), :a) == {dynamic(), dynamic(open_map(a: not_set()))} + + # Deleting from an open map + {value, type} = map_take(open_map(a: integer(), b: atom()), :a) + assert value == integer() + assert equal?(type, open_map(a: not_set(), b: atom())) + + # Deleting from a union of maps + {value, type} = map_take(union(closed_map(a: integer()), closed_map(b: atom())), :a) + assert value == integer() + assert equal?(type, union(empty_map(), closed_map(b: atom()))) # Deleting from a gradual map - assert map_delete(union(dynamic(), closed_map(a: integer())), :a) - |> equal?(union(dynamic(open_map(a: not_set())), empty_map())) + {value, type} = map_take(union(dynamic(), closed_map(a: integer())), :a) + assert value == dynamic() + assert equal?(type, union(dynamic(open_map(a: not_set())), empty_map())) - assert map_delete(dynamic(open_map(a: not_set())), :b) - |> equal?(dynamic(open_map(a: not_set(), b: not_set()))) + {value, type} = map_take(dynamic(open_map(a: not_set())), :b) + assert equal?(value, dynamic()) + assert equal?(type, dynamic(open_map(a: not_set(), b: not_set()))) # Deleting from an intersection of maps - assert map_delete(intersection(open_map(a: integer()), open_map(b: atom())), :a) == - open_map(a: not_set(), b: atom()) + {value, type} = map_take(intersection(open_map(a: integer()), open_map(b: atom())), :a) + assert value == integer() + assert equal?(type, open_map(a: not_set(), b: atom())) # Deleting from a difference of maps - assert difference(closed_map(a: integer(), b: atom()), closed_map(a: integer())) - |> map_delete(:b) - |> equal?(closed_map(a: integer())) + {value, type} = + map_take(difference(closed_map(a: integer(), b: atom()), closed_map(a: integer())), :b) - assert difference(open_map(), open_map(a: not_set())) - |> map_delete(:a) == open_map(a: not_set()) + assert value == atom() + assert equal?(type, closed_map(a: integer())) + + {value, type} = map_take(difference(open_map(), open_map(a: not_set())), :a) + assert equal?(value, term()) + assert equal?(type, open_map(a: not_set())) end - end - test "map_put" do - assert map_put(term(), :a, integer()) == :badmap - assert map_put(integer(), :a, integer()) == :badmap - assert map_put(dynamic(integer()), :a, atom()) == :badmap - assert map_put(union(integer(), dynamic()), :a, atom()) == :badmap - assert map_put(empty_map(), :a, integer()) == closed_map(a: integer()) + test "map_put" do + assert map_put(term(), :a, integer()) == :badmap + assert map_put(integer(), :a, integer()) == :badmap + assert map_put(dynamic(integer()), :a, atom()) == :badmap + assert map_put(union(integer(), dynamic()), :a, atom()) == :badmap + assert map_put(empty_map(), :a, integer()) == closed_map(a: integer()) - # Replace an existing key in a closed map - assert map_put(closed_map(a: integer()), :a, atom()) == closed_map(a: atom()) + # Replace an existing key in a closed map + assert map_put(closed_map(a: integer()), :a, atom()) == closed_map(a: atom()) - # Add a new key to a closed map - assert map_put(closed_map(a: integer()), :b, atom()) == closed_map(a: integer(), b: atom()) + # Add a new key to a closed map + assert map_put(closed_map(a: integer()), :b, atom()) == closed_map(a: integer(), b: atom()) - # Replace an existing key in an open map - assert map_put(open_map(a: integer()), :a, atom()) == open_map(a: atom()) + # Replace an existing key in an open map + assert map_put(open_map(a: integer()), :a, atom()) == open_map(a: atom()) - # Add a new key to an open map - assert map_put(open_map(a: integer()), :b, atom()) == open_map(a: integer(), b: atom()) + # Add a new key to an open map + assert map_put(open_map(a: integer()), :b, atom()) == open_map(a: integer(), b: atom()) - # Put a key-value pair in a union of maps - assert union(closed_map(a: integer()), closed_map(b: atom())) - |> map_put(:c, boolean()) - |> equal?( - union(closed_map(a: integer(), c: boolean()), closed_map(b: atom(), c: boolean())) - ) + # Put a key-value pair in a union of maps + assert union(closed_map(a: integer()), closed_map(b: atom())) + |> map_put(:c, boolean()) + |> equal?( + union(closed_map(a: integer(), c: boolean()), closed_map(b: atom(), c: boolean())) + ) - # Put a key-value pair in a dynamic map - assert map_put(dynamic(open_map()), :a, integer()) == dynamic(open_map(a: integer())) + # Put a key-value pair in a dynamic map + assert map_put(dynamic(open_map()), :a, integer()) == dynamic(open_map(a: integer())) - # Put a key-value pair in an intersection of maps - assert intersection(open_map(a: integer()), open_map(b: atom())) - |> map_put(:c, boolean()) - |> equal?(open_map(a: integer(), b: atom(), c: boolean())) + # Put a key-value pair in an intersection of maps + assert intersection(open_map(a: integer()), open_map(b: atom())) + |> map_put(:c, boolean()) + |> equal?(open_map(a: integer(), b: atom(), c: boolean())) - # Put a key-value pair in a difference of maps - assert difference(open_map(), closed_map(a: integer())) - |> map_put(:b, atom()) - |> equal?(difference(open_map(b: atom()), closed_map(a: integer()))) + # Put a key-value pair in a difference of maps + assert difference(open_map(), closed_map(a: integer())) + |> map_put(:b, atom()) + |> equal?(difference(open_map(b: atom()), closed_map(a: integer()))) - # Put a new key-value pair with dynamic type - # Note: setting a field to a dynamic type makes the whole map become dynamic. - assert map_put(open_map(), :a, dynamic()) == dynamic(open_map(a: term())) + # Put a new key-value pair with dynamic type + # Note: setting a field to a dynamic type makes the whole map become dynamic. + assert map_put(open_map(), :a, dynamic()) == dynamic(open_map(a: term())) - # Put a key-value pair in a map with optional fields - assert map_put(closed_map(a: if_set(integer())), :b, atom()) - |> equal?(closed_map(a: if_set(integer()), b: atom())) + # Put a key-value pair in a map with optional fields + assert map_put(closed_map(a: if_set(integer())), :b, atom()) + |> equal?(closed_map(a: if_set(integer()), b: atom())) - # Fetching on a key-value pair that was put to a given type returns {false, type} - {false, type} = union(dynamic(), empty_map()) |> map_put(:a, atom()) |> map_fetch(:a) - assert equal?(type, atom()) + # Fetching on a key-value pair that was put to a given type returns {false, type} + {false, type} = union(dynamic(), empty_map()) |> map_put(:a, atom()) |> map_fetch(:a) + assert equal?(type, atom()) + end end describe "disjoint" do From 1e551424b7180a39684d65345f4fa3016a94b1bf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 5 Nov 2024 10:24:16 +0100 Subject: [PATCH 08/10] Implement map_put on behalf of map_take --- lib/elixir/lib/module/types/descr.ex | 327 +++++++++--------- lib/elixir/lib/module/types/expr.ex | 4 +- .../test/elixir/module/types/descr_test.exs | 44 ++- 3 files changed, 182 insertions(+), 193 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index f80e7c0078a..bc54d4267d8 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -199,17 +199,22 @@ defmodule Module.Types.Descr do cond do is_gradual_left and not is_gradual_right -> right_with_dynamic = Map.put(right, :dynamic, right) - symmetrical_merge(left, right_with_dynamic, &union/3) + union_static(left, right_with_dynamic) is_gradual_right and not is_gradual_left -> left_with_dynamic = Map.put(left, :dynamic, left) - symmetrical_merge(left_with_dynamic, right, &union/3) + union_static(left_with_dynamic, right) true -> - symmetrical_merge(left, right, &union/3) + union_static(left, right) end end + @compile {:inline, union_static: 2} + defp union_static(left, right) do + symmetrical_merge(left, right, &union/3) + end + defp union(:atom, v1, v2), do: atom_union(v1, v2) defp union(:bitmap, v1, v2), do: v1 ||| v2 defp union(:dynamic, v1, v2), do: dynamic_union(v1, v2) @@ -235,17 +240,22 @@ defmodule Module.Types.Descr do cond do is_gradual_left and not is_gradual_right -> right_with_dynamic = Map.put(right, :dynamic, right) - symmetrical_intersection(left, right_with_dynamic, &intersection/3) + intersection_static(left, right_with_dynamic) is_gradual_right and not is_gradual_left -> left_with_dynamic = Map.put(left, :dynamic, left) - symmetrical_intersection(left_with_dynamic, right, &intersection/3) + intersection_static(left_with_dynamic, right) true -> - symmetrical_intersection(left, right, &intersection/3) + intersection_static(left, right) end end + @compile {:inline, intersection_static: 2} + defp intersection_static(left, right) do + symmetrical_intersection(left, right, &intersection/3) + end + # Returning 0 from the callback is taken as none() for that subtype. defp intersection(:atom, v1, v2), do: atom_intersection(v1, v2) defp intersection(:bitmap, v1, v2), do: v1 &&& v2 @@ -1210,130 +1220,8 @@ defmodule Module.Types.Descr do defp map_new(tag, fields = %{}), do: [{tag, fields, []}] - @doc """ - Fetches the type of the value returned by accessing `key` on `map` - with the assumption that the descr is exclusively a map (or dynamic). - - It returns a two element tuple or `:error`. The first element says - if the type is dynamically optional or not, the second element is - the type. In static mode, optional keys are not allowed. - """ - def map_fetch(:term, _key), do: :badmap - - def map_fetch(%{} = descr, key) when is_atom(key) do - case :maps.take(:dynamic, descr) do - :error -> - if descr_key?(descr, :map) and map_only?(descr) do - {static_optional?, static_type} = map_fetch_static(descr, key) - - if static_optional? or empty?(static_type) do - :badkey - else - {false, static_type} - end - else - :badmap - end - - {dynamic, static} -> - if descr_key?(dynamic, :map) and map_only?(static) do - {dynamic_optional?, dynamic_type} = map_fetch_static(dynamic, key) - {static_optional?, static_type} = map_fetch_static(static, key) - - if static_optional? or empty?(dynamic_type) do - :badkey - else - {dynamic_optional?, union(dynamic(dynamic_type), static_type)} - end - else - :badmap - end - end - end - defp map_only?(descr), do: empty?(Map.delete(descr, :map)) - defp map_fetch_static(:term, _key), do: {true, term()} - - defp map_fetch_static(descr, key) when is_atom(key) do - case descr do - # Optimization: if the key does not exist in the map, - # avoid building if_set/not_set pairs and return the - # popped value directly. - %{map: [{tag, fields, []}]} when not is_map_key(fields, key) -> - case tag do - :open -> {true, term()} - :closed -> {true, none()} - end - - %{map: map} -> - map_fetch_dnf(map, key) |> pop_optional_static() - - %{} -> - {false, none()} - end - end - - @doc """ - Adds a `key` of a given type, assuming that the descr is exclusively - a map (or dynamic). - """ - def map_put(:term, _key, _type), do: :badmap - def map_put(descr, key, :term) when is_atom(key), do: map_put_static_value(descr, key, :term) - - def map_put(descr, key, type) when is_atom(key) do - case :maps.take(:dynamic, type) do - :error -> map_put_static_value(descr, key, type) - {dynamic, _static} -> dynamic(map_put_static_value(descr, key, dynamic)) - end - end - - defp map_put_static_value(descr, key, type) do - case :maps.take(:dynamic, descr) do - :error -> - if descr_key?(descr, :map) and map_only?(descr) do - map_put_static_shared(descr, key, type) - else - :badmap - end - - {dynamic, static} when static == @none -> - if descr_key?(dynamic, :map) do - dynamic(map_put_static_shared(dynamic, key, type)) - else - :badmap - end - - {dynamic, static} -> - if descr_key?(dynamic, :map) and map_only?(static) do - dynamic = map_put_static_shared(dynamic, key, type) - static = map_put_static_shared(static, key, type) - union(dynamic(dynamic), static) - else - :badmap - end - end - end - - # Directly inserts a key of a given type into every positive and negative map - defp map_put_static_shared(descr, key, type) do - case map_take_static(descr, key, :term) do - {_, %{map: dnf} = descr} -> - dnf = - Enum.map(dnf, fn {tag, fields, negs} -> - {tag, Map.put(fields, key, type), - Enum.map(negs, fn {neg_tag, neg_fields} -> - {neg_tag, Map.put(neg_fields, key, type)} - end)} - end) - - %{descr | map: dnf} - - {_, %{}} -> - descr - end - end - # Union is list concatenation defp map_union(dnf1, dnf2), do: dnf1 ++ dnf2 @@ -1448,14 +1336,141 @@ defmodule Module.Types.Descr do end end + @doc """ + Fetches the type of the value returned by accessing `key` on `map` + with the assumption that the descr is exclusively a map (or dynamic). + + It returns a two element tuple or `:error`. The first element says + if the type is dynamically optional or not, the second element is + the type. In static mode, optional keys are not allowed. + """ + def map_fetch(:term, _key), do: :badmap + + def map_fetch(%{} = descr, key) when is_atom(key) do + case :maps.take(:dynamic, descr) do + :error -> + if descr_key?(descr, :map) and map_only?(descr) do + {static_optional?, static_type} = map_fetch_static(descr, key) + + if static_optional? or empty?(static_type) do + :badkey + else + {false, static_type} + end + else + :badmap + end + + {dynamic, static} -> + if descr_key?(dynamic, :map) and map_only?(static) do + {dynamic_optional?, dynamic_type} = map_fetch_static(dynamic, key) + {static_optional?, static_type} = map_fetch_static(static, key) + + if static_optional? or empty?(dynamic_type) do + :badkey + else + {dynamic_optional?, union(dynamic(dynamic_type), static_type)} + end + else + :badmap + end + end + end + + defp map_fetch_static(:term, _key), do: {true, term()} + + defp map_fetch_static(descr, key) when is_atom(key) do + case descr do + # Optimization: if the key does not exist in the map, + # avoid building if_set/not_set pairs and return the + # popped value directly. + %{map: [{tag, fields, []}]} when not is_map_key(fields, key) -> + case tag do + :open -> {true, term()} + :closed -> {true, none()} + end + + %{map: map} -> + map_fetch_dnf(map, key) |> pop_optional_static() + + %{} -> + {false, none()} + end + end + + # Takes a map dnf and returns the union of types it can take for a given key. + # If the key may be undefined, it will contain the `not_set()` type. + defp map_fetch_dnf(dnf, key) do + Enum.reduce(dnf, none(), fn + # Optimization: if there are no negatives, + # we can return the value directly. + {_tag, %{^key => value}, []}, acc -> + value |> union(acc) + + # Optimization: if there are no negatives + # and the key does not exist, return the default one. + {tag, %{}, []}, acc -> + tag_to_type(tag) |> union(acc) + + {tag, fields, negs}, acc -> + {fst, snd} = map_pop_key(tag, fields, key) + + case map_split_negative(negs, key) do + :empty -> + acc + + negative -> + negative + |> pair_make_disjoint() + |> pair_eliminate_negations_fst(fst, snd) + |> union(acc) + end + end) + end + + @doc """ + Adds a `key` of a given type, assuming that the descr is exclusively + a map (or dynamic). + """ + def map_put(:term, _key, _type), do: :badmap + def map_put(descr, key, :term) when is_atom(key), do: map_put_static_value(descr, key, :term) + + def map_put(descr, key, type) when is_atom(key) do + case :maps.take(:dynamic, type) do + :error -> map_put_static_value(descr, key, type) + {dynamic, _static} -> map_put_static_value(dynamic(descr), key, dynamic) + end + end + + defp map_put_static_value(descr, key, type) do + with {_value, descr} <- map_take(descr, key, :term, &map_put_static(&1, key, type)) do + {:ok, descr} + end + end + + # Directly inserts a key of a given type into every positive and negative map. + defp map_put_static(%{map: dnf} = descr, key, type) do + dnf = + Enum.map(dnf, fn {tag, fields, negs} -> + {tag, Map.put(fields, key, type), + Enum.map(negs, fn {neg_tag, neg_fields} -> + {neg_tag, Map.put(neg_fields, key, type)} + end)} + end) + + %{descr | map: dnf} + end + + defp map_put_static(descr, _key, _type), do: descr + @doc """ Removes a key from a map type. """ def map_delete(descr, key) do # We pass :term as the initial value so we can avoid computing the unions. - case map_take(descr, key, :term) do - {_, descr} -> {:ok, descr} - error -> error + with {_value, descr} <- + map_take(descr, key, :term, &intersection_static(&1, open_map([{key, not_set()}]))) do + {:ok, descr} end end @@ -1471,18 +1486,19 @@ defmodule Module.Types.Descr do This step eliminates the key from open record types where it was implicitly present. """ def map_take(descr, key) do - map_take(descr, key, none()) + map_take(descr, key, none(), &intersection_static(&1, open_map([{key, not_set()}]))) end - defp map_take(:term, _key, _initial), do: :badmap + @compile {:inline, map_take: 4} + defp map_take(:term, _key, _initial, _updater), do: :badmap - defp map_take(descr, key, initial) when is_atom(key) do + defp map_take(descr, key, initial, updater) when is_atom(key) do case :maps.take(:dynamic, descr) do :error -> # Note: the empty type is not a valid input if descr_key?(descr, :map) and map_only?(descr) do - {taken, descr} = map_take_static(descr, key, initial) - {taken, intersection(descr, open_map([{key, not_set()}]))} + {taken, result} = map_take_static(descr, key, initial) + {taken, updater.(result)} else :badmap end @@ -1497,11 +1513,7 @@ defmodule Module.Types.Descr do do: dynamic(), else: union(dynamic(dynamic_taken), static_taken) - result = - union(dynamic(dynamic_result), static_result) - |> intersection(open_map([{key, not_set()}])) - - {taken, result} + {taken, union(dynamic(updater.(dynamic_result)), updater.(static_result))} else :badmap end @@ -1509,6 +1521,7 @@ defmodule Module.Types.Descr do end # Takes a static map type and removes a key from it. + # This allows the key to be put or deleted later on. defp map_take_static(%{map: dnf}, key, initial) do {value, map} = Enum.reduce(dnf, {initial, none()}, fn @@ -1535,7 +1548,7 @@ defmodule Module.Types.Descr do {remove_optional_static(value), map} end - defp map_take_static(:term, key, _initial), do: {:term, open_map([{key, not_set()}])} + defp map_take_static(:term, _key, _initial), do: {:term, open_map()} # If there is no map part to this static type, there is nothing to delete. defp map_take_static(_type, _key, initial), do: {initial, none()} @@ -1592,36 +1605,6 @@ defmodule Module.Types.Descr do end)) or map_empty?(tag, fields, negs) end - # Takes a map dnf and returns the union of types it can take for a given key. - # If the key may be undefined, it will contain the `not_set()` type. - defp map_fetch_dnf(dnf, key) do - Enum.reduce(dnf, none(), fn - # Optimization: if there are no negatives, - # we can return the value directly. - {_tag, %{^key => value}, []}, acc -> - value |> union(acc) - - # Optimization: if there are no negatives - # and the key does not exist, return the default one. - {tag, %{}, []}, acc -> - tag_to_type(tag) |> union(acc) - - {tag, fields, negs}, acc -> - {fst, snd} = map_pop_key(tag, fields, key) - - case map_split_negative(negs, key) do - :empty -> - acc - - negative -> - negative - |> pair_make_disjoint() - |> pair_eliminate_negations_fst(fst, snd) - |> union(acc) - end - end) - end - defp map_pop_key(tag, fields, key) do case :maps.take(key, fields) do {value, fields} -> {value, %{map: map_new(tag, fields)}} diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 24cc630a7cc..00c57cd6c14 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -135,7 +135,7 @@ defmodule Module.Types.Expr do if fallback == none() do Enum.reduce(pairs, map_type, fn {key, type}, acc -> case map_put(acc, key, type) do - descr when is_descr(descr) -> descr + {:ok, descr} -> descr :badmap -> throw({:badmap, map_type, expr, context}) end end) @@ -545,7 +545,7 @@ defmodule Module.Types.Expr do defp map_put!(map_type, key, value_type) do case map_put(map_type, key, value_type) do - descr when is_descr(descr) -> descr + {:ok, descr} -> descr error -> raise "unexpected #{inspect(error)}" end end diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index d28ae3d506f..3b16b828212 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -1048,50 +1048,56 @@ defmodule Module.Types.DescrTest do assert map_put(integer(), :a, integer()) == :badmap assert map_put(dynamic(integer()), :a, atom()) == :badmap assert map_put(union(integer(), dynamic()), :a, atom()) == :badmap - assert map_put(empty_map(), :a, integer()) == closed_map(a: integer()) + assert map_put(empty_map(), :a, integer()) == {:ok, closed_map(a: integer())} # Replace an existing key in a closed map - assert map_put(closed_map(a: integer()), :a, atom()) == closed_map(a: atom()) + assert map_put(closed_map(a: integer()), :a, atom()) == {:ok, closed_map(a: atom())} # Add a new key to a closed map - assert map_put(closed_map(a: integer()), :b, atom()) == closed_map(a: integer(), b: atom()) + assert map_put(closed_map(a: integer()), :b, atom()) == + {:ok, closed_map(a: integer(), b: atom())} # Replace an existing key in an open map - assert map_put(open_map(a: integer()), :a, atom()) == open_map(a: atom()) + assert map_put(open_map(a: integer()), :a, atom()) == + {:ok, open_map(a: atom())} # Add a new key to an open map - assert map_put(open_map(a: integer()), :b, atom()) == open_map(a: integer(), b: atom()) + assert map_put(open_map(a: integer()), :b, atom()) == + {:ok, open_map(a: integer(), b: atom())} # Put a key-value pair in a union of maps - assert union(closed_map(a: integer()), closed_map(b: atom())) - |> map_put(:c, boolean()) - |> equal?( + {:ok, type} = + union(closed_map(a: integer()), closed_map(b: atom())) |> map_put(:c, boolean()) + + assert equal?( + type, union(closed_map(a: integer(), c: boolean()), closed_map(b: atom(), c: boolean())) ) # Put a key-value pair in a dynamic map - assert map_put(dynamic(open_map()), :a, integer()) == dynamic(open_map(a: integer())) + assert map_put(dynamic(open_map()), :a, integer()) == {:ok, dynamic(open_map(a: integer()))} # Put a key-value pair in an intersection of maps - assert intersection(open_map(a: integer()), open_map(b: atom())) - |> map_put(:c, boolean()) - |> equal?(open_map(a: integer(), b: atom(), c: boolean())) + {:ok, type} = + intersection(open_map(a: integer()), open_map(b: atom())) |> map_put(:c, boolean()) + + assert equal?(type, open_map(a: integer(), b: atom(), c: boolean())) # Put a key-value pair in a difference of maps - assert difference(open_map(), closed_map(a: integer())) - |> map_put(:b, atom()) - |> equal?(difference(open_map(b: atom()), closed_map(a: integer()))) + {:ok, type} = difference(open_map(), closed_map(a: integer())) |> map_put(:b, atom()) + assert equal?(type, difference(open_map(b: atom()), closed_map(a: integer()))) # Put a new key-value pair with dynamic type # Note: setting a field to a dynamic type makes the whole map become dynamic. - assert map_put(open_map(), :a, dynamic()) == dynamic(open_map(a: term())) + assert map_put(open_map(), :a, dynamic()) == {:ok, dynamic(open_map(a: term()))} # Put a key-value pair in a map with optional fields - assert map_put(closed_map(a: if_set(integer())), :b, atom()) - |> equal?(closed_map(a: if_set(integer()), b: atom())) + {:ok, type} = closed_map(a: if_set(integer())) |> map_put(:b, atom()) + assert equal?(type, closed_map(a: if_set(integer()), b: atom())) # Fetching on a key-value pair that was put to a given type returns {false, type} - {false, type} = union(dynamic(), empty_map()) |> map_put(:a, atom()) |> map_fetch(:a) + {:ok, map} = map_put(union(dynamic(), empty_map()), :a, atom()) + {false, type} = map_fetch(map, :a) assert equal?(type, atom()) end end From 0aa9a8f4b49c9f9b60813ab4f42a1a19dca66eeb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 5 Nov 2024 11:04:30 +0100 Subject: [PATCH 09/10] Add map_fetch_and_put --- lib/elixir/lib/module/types/descr.ex | 36 ++++++++++++++++--- lib/elixir/lib/module/types/expr.ex | 3 +- .../test/elixir/module/types/descr_test.exs | 16 +++++---- .../test/elixir/module/types/expr_test.exs | 21 +++++++++++ 4 files changed, 64 insertions(+), 12 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index bc54d4267d8..e8f7824d243 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -1429,20 +1429,46 @@ defmodule Module.Types.Descr do end @doc """ - Adds a `key` of a given type, assuming that the descr is exclusively + Fetches and puts a `key` of a given type, assuming that the descr is exclusively + a map (or dynamic). + """ + def map_fetch_and_put(:term, _key, _type), do: :badmap + + def map_fetch_and_put(descr, key, :term) when is_atom(key), + do: map_fetch_and_put_shared(descr, key, :term) + + def map_fetch_and_put(descr, key, type) when is_atom(key) do + case :maps.take(:dynamic, type) do + :error -> map_fetch_and_put_shared(descr, key, type) + {dynamic, _static} -> map_fetch_and_put_shared(dynamic(descr), key, dynamic) + end + end + + defp map_fetch_and_put_shared(descr, key, type) do + with {value, descr} <- map_take(descr, key, none(), &map_put_static(&1, key, type)) do + if empty?(value) do + :badkey + else + {value, descr} + end + end + end + + @doc """ + Puts a `key` of a given type, assuming that the descr is exclusively a map (or dynamic). """ def map_put(:term, _key, _type), do: :badmap - def map_put(descr, key, :term) when is_atom(key), do: map_put_static_value(descr, key, :term) + def map_put(descr, key, :term) when is_atom(key), do: map_put_shared(descr, key, :term) def map_put(descr, key, type) when is_atom(key) do case :maps.take(:dynamic, type) do - :error -> map_put_static_value(descr, key, type) - {dynamic, _static} -> map_put_static_value(dynamic(descr), key, dynamic) + :error -> map_put_shared(descr, key, type) + {dynamic, _static} -> map_put_shared(dynamic(descr), key, dynamic) end end - defp map_put_static_value(descr, key, type) do + defp map_put_shared(descr, key, type) do with {_value, descr} <- map_take(descr, key, :term, &map_put_static(&1, key, type)) do {:ok, descr} end diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 00c57cd6c14..63a0054dc27 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -135,7 +135,8 @@ defmodule Module.Types.Expr do if fallback == none() do Enum.reduce(pairs, map_type, fn {key, type}, acc -> case map_put(acc, key, type) do - {:ok, descr} -> descr + {_value, descr} -> descr + :badkey -> throw({:badkey, map_type, key, expr, context}) :badmap -> throw({:badmap, map_type, expr, context}) end end) diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index 3b16b828212..bef2c35ee13 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -852,13 +852,12 @@ defmodule Module.Types.DescrTest do assert map_fetch(term(), :a) == :badmap assert map_fetch(union(open_map(), integer()), :a) == :badmap - assert map_fetch(closed_map(a: integer()), :a) == {false, integer()} - - assert map_fetch(union(closed_map(a: integer()), closed_map(b: atom())), :a) == - :badkey + assert map_fetch(open_map(), :a) == :badkey + assert map_fetch(open_map(a: not_set()), :a) == :badkey + assert map_fetch(union(closed_map(a: integer()), closed_map(b: atom())), :a) == :badkey + assert map_fetch(difference(closed_map(a: integer()), closed_map(a: term())), :a) == :badkey - assert map_fetch(difference(closed_map(a: integer()), closed_map(a: term())), :a) == - :badkey + assert map_fetch(closed_map(a: integer()), :a) == {false, integer()} assert map_fetch(union(closed_map(a: integer()), closed_map(a: atom())), :a) == {false, union(integer(), atom())} @@ -1043,6 +1042,11 @@ defmodule Module.Types.DescrTest do assert equal?(type, open_map(a: not_set())) end + test "map_fetch_and_put" do + assert map_fetch_and_put(term(), :a, integer()) == :badmap + assert map_fetch_and_put(open_map(), :a, integer()) == :badkey + end + test "map_put" do assert map_put(term(), :a, integer()) == :badmap assert map_put(integer(), :a, integer()) == :badmap diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index d586369a528..410648bda1e 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -561,6 +561,27 @@ defmodule Module.Types.ExprTest do # from: types_test.ex:LINE x = :foo """ + + assert typeerror!( + ( + x = %{} + %{x | x: :zero} + ) + ) == ~l""" + expected a map within map update syntax: + + %{x | x: :zero} + + but got type: + + dynamic(:foo) + + where "x" was given the type: + + # type: dynamic(:foo) + # from: types_test.ex:LINE + x = :foo + """ end test "updating to open maps" do From 4fd800a7b8b29bedf6c65995a8767e36522bcb4f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 5 Nov 2024 11:36:53 +0100 Subject: [PATCH 10/10] Map/struct updates concluded --- lib/elixir/lib/module/types/descr.ex | 116 +++++++++--------- lib/elixir/lib/module/types/expr.ex | 2 +- .../test/elixir/module/types/descr_test.exs | 20 ++- .../test/elixir/module/types/expr_test.exs | 69 ++++++++++- 4 files changed, 134 insertions(+), 73 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index e8f7824d243..31954ae45c1 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -178,9 +178,9 @@ defmodule Module.Types.Descr do end end - @compile {:inline, lazy_union: 2} - defp lazy_union(:term, _fun), do: :term - defp lazy_union(descr, fun), do: union(descr, fun.()) + @compile {:inline, maybe_union: 2} + defp maybe_union(nil, _fun), do: nil + defp maybe_union(descr, fun), do: union(descr, fun.()) @doc """ Computes the union of two descrs. @@ -1377,31 +1377,20 @@ defmodule Module.Types.Descr do end end - defp map_fetch_static(:term, _key), do: {true, term()} - - defp map_fetch_static(descr, key) when is_atom(key) do - case descr do - # Optimization: if the key does not exist in the map, - # avoid building if_set/not_set pairs and return the - # popped value directly. - %{map: [{tag, fields, []}]} when not is_map_key(fields, key) -> - case tag do - :open -> {true, term()} - :closed -> {true, none()} - end - - %{map: map} -> - map_fetch_dnf(map, key) |> pop_optional_static() - - %{} -> - {false, none()} + # Optimization: if the key does not exist in the map, avoid building + # if_set/not_set pairs and return the popped value directly. + defp map_fetch_static(%{map: [{tag, fields, []}]}, key) when not is_map_key(fields, key) do + case tag do + :open -> {true, term()} + :closed -> {true, none()} end end # Takes a map dnf and returns the union of types it can take for a given key. # If the key may be undefined, it will contain the `not_set()` type. - defp map_fetch_dnf(dnf, key) do - Enum.reduce(dnf, none(), fn + defp map_fetch_static(%{map: dnf}, key) do + dnf + |> Enum.reduce(none(), fn # Optimization: if there are no negatives, # we can return the value directly. {_tag, %{^key => value}, []}, acc -> @@ -1426,8 +1415,12 @@ defmodule Module.Types.Descr do |> union(acc) end end) + |> pop_optional_static() end + defp map_fetch_static(%{}, _key), do: {false, none()} + defp map_fetch_static(:term, _key), do: {true, term()} + @doc """ Fetches and puts a `key` of a given type, assuming that the descr is exclusively a map (or dynamic). @@ -1445,13 +1438,7 @@ defmodule Module.Types.Descr do end defp map_fetch_and_put_shared(descr, key, type) do - with {value, descr} <- map_take(descr, key, none(), &map_put_static(&1, key, type)) do - if empty?(value) do - :badkey - else - {value, descr} - end - end + map_take(descr, key, none(), &map_put_static(&1, key, type)) end @doc """ @@ -1469,7 +1456,7 @@ defmodule Module.Types.Descr do end defp map_put_shared(descr, key, type) do - with {_value, descr} <- map_take(descr, key, :term, &map_put_static(&1, key, type)) do + with {nil, descr} <- map_take(descr, key, nil, &map_put_static(&1, key, type)) do {:ok, descr} end end @@ -1493,9 +1480,9 @@ defmodule Module.Types.Descr do Removes a key from a map type. """ def map_delete(descr, key) do - # We pass :term as the initial value so we can avoid computing the unions. - with {_value, descr} <- - map_take(descr, key, :term, &intersection_static(&1, open_map([{key, not_set()}]))) do + # We pass nil as the initial value so we can avoid computing the unions. + with {nil, descr} <- + map_take(descr, key, nil, &intersection_static(&1, open_map([{key, not_set()}]))) do {:ok, descr} end end @@ -1521,25 +1508,29 @@ defmodule Module.Types.Descr do defp map_take(descr, key, initial, updater) when is_atom(key) do case :maps.take(:dynamic, descr) do :error -> - # Note: the empty type is not a valid input if descr_key?(descr, :map) and map_only?(descr) do - {taken, result} = map_take_static(descr, key, initial) - {taken, updater.(result)} + {optional?, taken, result} = map_take_static(descr, key, initial) + + cond do + taken == nil -> {nil, updater.(result)} + optional? or empty?(taken) -> :badkey + true -> {taken, updater.(result)} + end else :badmap end {dynamic, static} -> if descr_key?(dynamic, :map) and map_only?(static) do - {dynamic_taken, dynamic_result} = map_take_static(dynamic, key, initial) - {static_taken, static_result} = map_take_static(static, key, initial) - - taken = - if dynamic_taken == :term, - do: dynamic(), - else: union(dynamic(dynamic_taken), static_taken) - - {taken, union(dynamic(updater.(dynamic_result)), updater.(static_result))} + {_, dynamic_taken, dynamic_result} = map_take_static(dynamic, key, initial) + {static_optional?, static_taken, static_result} = map_take_static(static, key, initial) + result = union(dynamic(updater.(dynamic_result)), updater.(static_result)) + + cond do + static_taken == nil and dynamic_taken == nil -> {nil, result} + static_optional? or empty?(dynamic_taken) -> :badkey + true -> {union(dynamic(dynamic_taken), static_taken), result} + end else :badmap end @@ -1548,36 +1539,51 @@ defmodule Module.Types.Descr do # Takes a static map type and removes a key from it. # This allows the key to be put or deleted later on. + defp map_take_static(%{map: [{tag, fields, []}]} = descr, key, initial) + when not is_map_key(fields, key) do + case tag do + :open -> {true, maybe_union(initial, fn -> term() end), descr} + :closed -> {true, initial, descr} + end + end + defp map_take_static(%{map: dnf}, key, initial) do {value, map} = Enum.reduce(dnf, {initial, none()}, fn # Optimization: if there are no negatives, we can directly remove the key. - {tag, fields, []}, {taken, map} -> + {tag, fields, []}, {value, map} -> {fst, snd} = map_pop_key(tag, fields, key) - {lazy_union(taken, fn -> fst end), union(map, snd)} + {maybe_union(value, fn -> fst end), union(map, snd)} - {tag, fields, negs}, {taken, map} -> + {tag, fields, negs}, {value, map} -> {fst, snd} = map_pop_key(tag, fields, key) case map_split_negative(negs, key) do :empty -> - {taken, map} + {value, map} negative -> disjoint = pair_make_disjoint(negative) - {lazy_union(taken, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end), + {maybe_union(value, fn -> pair_eliminate_negations_fst(disjoint, fst, snd) end), disjoint |> pair_eliminate_negations_snd(fst, snd) |> union(map)} end end) - {remove_optional_static(value), map} + if value == nil do + {false, value, map} + else + {optional?, value} = pop_optional_static(value) + {optional?, value, map} + end end - defp map_take_static(:term, _key, _initial), do: {:term, open_map()} - # If there is no map part to this static type, there is nothing to delete. - defp map_take_static(_type, _key, initial), do: {initial, none()} + defp map_take_static(%{}, _key, initial), do: {false, initial, none()} + + defp map_take_static(:term, _key, initial) do + {true, maybe_union(initial, fn -> term() end), open_map()} + end # Short-circuits if it finds a non-empty map literal in the union. # Since the algorithm is recursive, we implement the short-circuiting diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 63a0054dc27..ef46be2cc5d 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -134,7 +134,7 @@ defmodule Module.Types.Expr do if fallback == none() do Enum.reduce(pairs, map_type, fn {key, type}, acc -> - case map_put(acc, key, type) do + case map_fetch_and_put(acc, key, type) do {_value, descr} -> descr :badkey -> throw({:badkey, map_type, key, expr, context}) :badmap -> throw({:badmap, map_type, expr, context}) diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index bef2c35ee13..316087829d0 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -994,14 +994,10 @@ defmodule Module.Types.DescrTest do assert map_take(closed_map(a: integer(), b: atom()), :a) == {integer(), closed_map(b: atom())} - assert map_take(empty_map(), :a) == {none(), empty_map()} - - assert map_take(closed_map(a: if_set(integer()), b: atom()), :a) == - {integer(), closed_map(b: atom())} - # Deleting a non-existent key - assert map_take(closed_map(a: integer(), b: atom()), :c) == - {none(), closed_map(a: integer(), b: atom())} + assert map_take(empty_map(), :a) == :badkey + assert map_take(closed_map(a: integer(), b: atom()), :c) == :badkey + assert map_take(closed_map(a: if_set(integer()), b: atom()), :a) == :badkey # Deleting from a dynamic map assert map_take(dynamic(), :a) == {dynamic(), dynamic(open_map(a: not_set()))} @@ -1012,13 +1008,15 @@ defmodule Module.Types.DescrTest do assert equal?(type, open_map(a: not_set(), b: atom())) # Deleting from a union of maps - {value, type} = map_take(union(closed_map(a: integer()), closed_map(b: atom())), :a) - assert value == integer() - assert equal?(type, union(empty_map(), closed_map(b: atom()))) + union = union(closed_map(a: integer()), closed_map(b: atom())) + assert map_take(union, :a) == :badkey + {value, type} = map_take(dynamic(union), :a) + assert value == dynamic(integer()) + assert equal?(type, dynamic(union(empty_map(), closed_map(b: atom())))) # Deleting from a gradual map {value, type} = map_take(union(dynamic(), closed_map(a: integer())), :a) - assert value == dynamic() + assert value == union(dynamic(), integer()) assert equal?(type, union(dynamic(open_map(a: not_set())), empty_map())) {value, type} = map_take(dynamic(open_map(a: not_set())), :b) diff --git a/lib/elixir/test/elixir/module/types/expr_test.exs b/lib/elixir/test/elixir/module/types/expr_test.exs index 410648bda1e..d94c607a57b 100644 --- a/lib/elixir/test/elixir/module/types/expr_test.exs +++ b/lib/elixir/test/elixir/module/types/expr_test.exs @@ -546,6 +546,25 @@ defmodule Module.Types.ExprTest do assert typecheck!([x], %{%{x | x: :zero} | y: :one}) == dynamic(open_map(x: atom([:zero]), y: atom([:one]))) + assert typecheck!( + ( + foo_or_bar = + cond do + :rand.uniform() > 0.5 -> :key1 + true -> :key2 + end + + x = %{key1: :one, key2: :two} + %{x | foo_or_bar => :one!, foo_or_bar => :two!} + ) + ) + |> equal?( + closed_map(key1: atom([:one]), key2: atom([:two!])) + |> union(closed_map(key1: atom([:two!]), key2: atom([:one!]))) + |> union(closed_map(key1: atom([:one!]), key2: atom([:two!]))) + |> union(closed_map(key1: atom([:two!]), key2: atom([:two]))) + ) + assert typeerror!([x = :foo], %{x | x: :zero}) == ~l""" expected a map within map update syntax: @@ -568,19 +587,57 @@ defmodule Module.Types.ExprTest do %{x | x: :zero} ) ) == ~l""" - expected a map within map update syntax: + expected a map with key :x in map update syntax: %{x | x: :zero} but got type: - dynamic(:foo) + empty_map() where "x" was given the type: - # type: dynamic(:foo) - # from: types_test.ex:LINE - x = :foo + # type: empty_map() + # from: types_test.ex:LINE-3 + x = %{} + """ + + # Assert we check all possible combinations + assert typeerror!( + ( + foo_or_bar = + cond do + :rand.uniform() > 0.5 -> :foo + true -> :bar + end + + x = %{foo: :baz} + %{x | foo_or_bar => :bat} + ) + ) == ~l""" + expected a map with key :bar in map update syntax: + + %{x | foo_or_bar => :bat} + + but got type: + + %{foo: :baz} + + where "foo_or_bar" was given the type: + + # type: :bar or :foo + # from: types_test.ex:LINE-9 + foo_or_bar = + cond do + :rand.uniform() > 0.5 -> :foo + true -> :bar + end + + where "x" was given the type: + + # type: %{foo: :baz} + # from: types_test.ex:LINE-3 + x = %{foo: :baz} """ end @@ -611,7 +668,7 @@ defmodule Module.Types.ExprTest do ) ) == dynamic(open_map()) - # The goal of this test is to verify we assert keys, + # The goal of this assertion is to verify we assert keys, # even if they may be overridden later. assert typeerror!( [key],