Skip to content

Commit ab843d0

Browse files
committed
Add type checking for Map.from_keys/2
1 parent 79c2842 commit ab843d0

File tree

4 files changed

+107
-25
lines changed

4 files changed

+107
-25
lines changed

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

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -244,6 +244,8 @@ defmodule Module.Types.Apply do
244244
{:erlang, :tuple_to_list, [{[open_tuple([])], dynamic(list(term()))}]},
245245

246246
## Map
247+
{:maps, :from_keys, [{[list(term()), term()], open_map()}]},
248+
{:maps, :is_key, [{[term(), open_map()], boolean()}]},
247249
{:maps, :keys, [{[open_map()], dynamic(list(term()))}]},
248250
{:maps, :to_list, [{[open_map()], dynamic(list(tuple([term(), term()])))}]},
249251
{:maps, :values, [{[open_map()], dynamic(list(term()))}]}
@@ -372,6 +374,40 @@ defmodule Module.Types.Apply do
372374
end
373375
end
374376

377+
defp remote_apply(:maps, :from_keys, _info, [list, value_type] = args_types, stack) do
378+
case list_of(list) do
379+
{true, nil} ->
380+
{:ok, return(empty_map(), args_types, stack)}
381+
382+
{empty_list?, key_type} ->
383+
if key_type == dynamic() or key_type == term() do
384+
{:ok, return(open_map(), args_types, stack)}
385+
else
386+
value_type = if_set(value_type)
387+
domain_keys = to_domain_keys(key_type)
388+
389+
keys =
390+
case atom_fetch(key_type) do
391+
{:finite, atom_keys} -> [List.delete(domain_keys, :atom) | atom_keys]
392+
_ -> [domain_keys]
393+
end
394+
395+
map = closed_map(Enum.map(keys, &{&1, value_type}))
396+
397+
map_and_maybe_empty_map =
398+
case empty_list? do
399+
true -> map
400+
false -> difference(map, empty_map())
401+
end
402+
403+
{:ok, return(map_and_maybe_empty_map, args_types, stack)}
404+
end
405+
406+
:badproperlist ->
407+
{:error, badremote(:maps, :from_keys, 2)}
408+
end
409+
end
410+
375411
defp remote_apply(:maps, :keys, _info, [map], stack) do
376412
case map_to_list(map, fn key, _value -> key end) do
377413
{:ok, list_type} -> {:ok, return(list_type, [map], stack)}

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

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1884,32 +1884,33 @@ defmodule Module.Types.Descr do
18841884
It returns a two-element tuple. The first element dictates the
18851885
empty list type. The second element returns the value type.
18861886
1887-
{:static or :dynamic or nil, t() or nil}
1887+
{boolean(), t() or nil}
18881888
18891889
If the value is `nil`, it means that component is missing.
1890-
However, both cannot be `nil` together. In such cases,
1891-
we return `:badproperlist`.
1890+
Note `{false, nil}` is not a valid return type, instead it
1891+
returns `:badproperlist`.
18921892
"""
18931893
def list_of(:term), do: :badproperlist
18941894

18951895
def list_of(descr) do
18961896
case :maps.take(:dynamic, descr) do
18971897
:error ->
1898-
with {empty_list, value} <- list_of_static(descr) do
1899-
if empty?(value) and empty_list == nil do
1898+
with {empty_list?, value} <- list_of_static(descr) do
1899+
if empty?(value) and empty_list? == false do
19001900
:badproperlist
19011901
else
1902-
{empty_list, value}
1902+
{empty_list?, value}
19031903
end
19041904
end
19051905

19061906
{dynamic, static} ->
1907-
with {empty_list, static_value} <- list_of_static(static) do
1908-
empty_list =
1909-
case dynamic do
1910-
%{bitmap: bitmap} when (bitmap &&& @bit_empty_list) != 0 -> :dynamic
1911-
_ -> empty_list
1912-
end
1907+
with {empty_list?, static_value} <- list_of_static(static) do
1908+
empty_list? =
1909+
empty_list? or
1910+
match?(
1911+
%{bitmap: bitmap} when (bitmap &&& @bit_empty_list) != 0,
1912+
dynamic
1913+
)
19131914

19141915
dynamic_value =
19151916
case dynamic do
@@ -1932,13 +1933,12 @@ defmodule Module.Types.Descr do
19321933
if empty?(dynamic_value) do
19331934
# list_bdd_to_pos_dnf guarantees the lists actually exists,
19341935
# so we can match on none() rather than empty.
1935-
if empty_list == nil do
1936-
:badproperlist
1937-
else
1938-
{empty_list, nil}
1936+
case empty_list? do
1937+
false -> :badproperlist
1938+
true -> {empty_list?, nil}
19391939
end
19401940
else
1941-
{empty_list, union(static_value, dynamic(dynamic_value))}
1941+
{empty_list?, union(static_value, dynamic(dynamic_value))}
19421942
end
19431943
end
19441944
end
@@ -1948,7 +1948,7 @@ defmodule Module.Types.Descr do
19481948
case descr do
19491949
%{bitmap: @bit_empty_list} ->
19501950
case empty?(Map.drop(descr, [:bitmap, :list])) do
1951-
true -> list_of_static(descr, :static)
1951+
true -> list_of_static(descr, true)
19521952
false -> :badproperlist
19531953
end
19541954

@@ -1957,7 +1957,7 @@ defmodule Module.Types.Descr do
19571957

19581958
%{} ->
19591959
case empty?(Map.delete(descr, :list)) do
1960-
true -> list_of_static(descr, nil)
1960+
true -> list_of_static(descr, false)
19611961
false -> :badproperlist
19621962
end
19631963
end

lib/elixir/test/elixir/module/types/descr_test.exs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1271,18 +1271,18 @@ defmodule Module.Types.DescrTest do
12711271
test "list_of" do
12721272
assert list_of(term()) == :badproperlist
12731273
assert list_of(none()) == :badproperlist
1274-
assert list_of(empty_list()) == {:static, none()}
1274+
assert list_of(empty_list()) == {true, none()}
12751275
assert list_of(union(empty_list(), integer())) == :badproperlist
1276-
assert list_of(non_empty_list(integer())) == {nil, integer()}
1276+
assert list_of(non_empty_list(integer())) == {false, integer()}
12771277
assert list_of(non_empty_list(integer(), atom())) == :badproperlist
12781278
assert list_of(non_empty_list(integer(), term())) == :badproperlist
1279-
assert list_of(non_empty_list(integer(), list(term()))) == {nil, term()}
1279+
assert list_of(non_empty_list(integer(), list(term()))) == {false, term()}
12801280
assert list_of(list(integer()) |> union(list(integer(), integer()))) == :badproperlist
12811281
assert list_of(list(integer()) |> union(integer())) == :badproperlist
1282-
assert list_of(dynamic(list(integer()))) == {:dynamic, dynamic(integer())}
1283-
assert list_of(dynamic(list(integer(), atom()))) == {:dynamic, nil}
1282+
assert list_of(dynamic(list(integer()))) == {true, dynamic(integer())}
1283+
assert list_of(dynamic(list(integer(), atom()))) == {true, nil}
12841284
assert list_of(dynamic(non_empty_list(integer(), atom()))) == :badproperlist
1285-
assert list_of(dynamic(union(empty_list(), integer()))) == {:dynamic, nil}
1285+
assert list_of(dynamic(union(empty_list(), integer()))) == {true, nil}
12861286

12871287
# A list that the difference resolves to nothing
12881288
list_with_tail =

lib/elixir/test/elixir/module/types/map_test.exs

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,52 @@ defmodule Module.Types.MapTest do
6969
end
7070
end
7171

72+
describe "Map.from_keys/2" do
73+
test "checking" do
74+
assert typecheck!([], Map.from_keys([], :value)) ==
75+
empty_map()
76+
77+
assert typecheck!([x], Map.from_keys(x, :value)) ==
78+
open_map()
79+
80+
assert typecheck!(
81+
(
82+
x = [:key1, :key2]
83+
Map.from_keys(x, 123)
84+
)
85+
) ==
86+
closed_map(key1: if_set(integer()), key2: if_set(integer()))
87+
|> difference(empty_map())
88+
89+
assert typecheck!(
90+
[condition?],
91+
(
92+
x = if condition?, do: [123, "123"], else: []
93+
Map.from_keys(x, 123)
94+
)
95+
) ==
96+
closed_map([
97+
{domain_key(:integer), if_set(integer())},
98+
{domain_key(:binary), if_set(integer())}
99+
])
100+
end
101+
102+
test "inference" do
103+
assert typecheck!(
104+
[x],
105+
(
106+
_ = Map.from_keys(x, :value)
107+
x
108+
)
109+
) == dynamic(list(term()))
110+
end
111+
112+
test "errors" do
113+
assert typeerror!([x = %{}], Map.from_keys(x, :value)) =~
114+
"incompatible types given to Map.from_keys/2"
115+
end
116+
end
117+
72118
describe "Map.keys/1" do
73119
test "checking" do
74120
assert typecheck!([x = %{}], Map.keys(x)) == dynamic(list(term()))

0 commit comments

Comments
 (0)