Skip to content

Commit 82983cf

Browse files
committed
Remove improper_list from type specification
1 parent 904adda commit 82983cf

File tree

6 files changed

+58
-45
lines changed

6 files changed

+58
-45
lines changed

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -360,14 +360,14 @@ defmodule Module.Types.Apply do
360360

361361
defp remote_apply(:erlang, :hd, _info, [list], _stack) do
362362
case list_hd(list) do
363-
{_, value_type} -> {:ok, value_type}
363+
{:ok, value_type} -> {:ok, value_type}
364364
:badnonemptylist -> {:error, badremote(:erlang, :hd, 1)}
365365
end
366366
end
367367

368368
defp remote_apply(:erlang, :tl, _info, [list], _stack) do
369369
case list_tl(list) do
370-
{_, value_type} -> {:ok, value_type}
370+
{:ok, value_type} -> {:ok, value_type}
371371
:badnonemptylist -> {:error, badremote(:erlang, :tl, 1)}
372372
end
373373
end

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

Lines changed: 10 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,6 @@ defmodule Module.Types.Descr do
5454
@list_top %{bitmap: @bit_empty_list, list: @non_empty_list_top}
5555
@empty_list %{bitmap: @bit_empty_list}
5656
@not_non_empty_list Map.delete(@term, :list)
57-
@not_list Map.replace!(@not_non_empty_list, :bitmap, @bit_top - @bit_empty_list)
5857

5958
@not_set %{optional: 1}
6059
@term_or_optional Map.put(@term, :optional, 1)
@@ -1972,7 +1971,7 @@ defmodule Module.Types.Descr do
19721971
static_value = list_hd_static(descr)
19731972

19741973
if non_empty_list_only?(descr) and not empty?(static_value) do
1975-
{false, static_value}
1974+
{:ok, static_value}
19761975
else
19771976
:badnonemptylist
19781977
end
@@ -1981,7 +1980,7 @@ defmodule Module.Types.Descr do
19811980
dynamic_value = list_hd_static(dynamic)
19821981

19831982
if non_empty_list_only?(static) and not empty?(dynamic_value) do
1984-
{true, union(dynamic(dynamic_value), list_hd_static(static))}
1983+
{:ok, union(dynamic(dynamic_value), list_hd_static(static))}
19851984
else
19861985
:badnonemptylist
19871986
end
@@ -2015,7 +2014,7 @@ defmodule Module.Types.Descr do
20152014
static_value = list_tl_static(descr)
20162015

20172016
if non_empty_list_only?(descr) and not empty?(static_value) do
2018-
{false, static_value}
2017+
{:ok, static_value}
20192018
else
20202019
:badnonemptylist
20212020
end
@@ -2024,7 +2023,7 @@ defmodule Module.Types.Descr do
20242023
dynamic_value = list_tl_static(dynamic)
20252024

20262025
if non_empty_list_only?(static) and not empty?(dynamic_value) do
2027-
{true, union(dynamic(dynamic_value), list_tl_static(static))}
2026+
{:ok, union(dynamic(dynamic_value), list_tl_static(static))}
20282027
else
20292028
:badnonemptylist
20302029
end
@@ -2048,28 +2047,19 @@ defmodule Module.Types.Descr do
20482047

20492048
defp list_tl_static(%{}), do: none()
20502049

2051-
defp list_improper_static?(:term), do: false
2052-
defp list_improper_static?(%{bitmap: bitmap}) when (bitmap &&& @bit_empty_list) != 0, do: false
2053-
defp list_improper_static?(term), do: equal?(term, @not_list)
2054-
20552050
defp list_to_quoted(bdd, empty?, opts) do
20562051
dnf = list_normalize(bdd)
20572052

20582053
{unions, list_rendered?} =
20592054
dnf
20602055
|> Enum.reduce({[], false}, fn {list_type, last_type, negs}, {acc, list_rendered?} ->
20612056
{name, arguments, list_rendered?} =
2062-
cond do
2063-
list_type == term() and list_improper_static?(last_type) ->
2064-
{:improper_list, [], list_rendered?}
2065-
2066-
subtype?(last_type, @empty_list) ->
2067-
name = if empty?, do: :list, else: :non_empty_list
2068-
{name, [to_quoted(list_type, opts)], empty?}
2069-
2070-
true ->
2071-
args = [to_quoted(list_type, opts), to_quoted(last_type, opts)]
2072-
{:non_empty_list, args, list_rendered?}
2057+
if subtype?(last_type, @empty_list) do
2058+
name = if empty?, do: :list, else: :non_empty_list
2059+
{name, [to_quoted(list_type, opts)], empty?}
2060+
else
2061+
args = [to_quoted(list_type, opts), to_quoted(last_type, opts)]
2062+
{:non_empty_list, args, list_rendered?}
20732063
end
20742064

20752065
acc =

lib/elixir/lib/module/types/expr.ex

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ defmodule Module.Types.Expr do
9494
else
9595
hd_type =
9696
case list_hd(expected) do
97-
{_, type} -> type
97+
{:ok, type} -> type
9898
_ -> term()
9999
end
100100

@@ -106,8 +106,8 @@ defmodule Module.Types.Expr do
106106
else
107107
tl_type =
108108
case list_tl(expected) do
109-
{_, type} -> type
110-
_ -> term()
109+
{:ok, type} -> type
110+
:badnonemptylist -> term()
111111
end
112112

113113
of_expr(suffix, tl_type, expr, stack, context)

lib/elixir/lib/module/types/pattern.ex

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -305,7 +305,7 @@ defmodule Module.Types.Pattern do
305305

306306
defp of_pattern_var([{:head, counter} | rest], type, _reachable_var?, info, context) do
307307
case list_hd(type) do
308-
{_, head} ->
308+
{:ok, head} ->
309309
tree = Map.fetch!(info, -counter)
310310
type = intersection(of_pattern_tree(tree, context), head)
311311
of_pattern_var(rest, type, false, info, context)
@@ -317,8 +317,8 @@ defmodule Module.Types.Pattern do
317317

318318
defp of_pattern_var([:tail | rest], type, reachable_var?, info, context) do
319319
case list_tl(type) do
320-
{_, tail} -> of_pattern_var(rest, tail, reachable_var?, info, context)
321-
_ -> :error
320+
{:ok, tail} -> of_pattern_var(rest, tail, reachable_var?, info, context)
321+
:badnonemptylist -> :error
322322
end
323323
end
324324

lib/elixir/pages/cheatsheets/types-cheat.cheatmd

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,32 @@
55

66
# Set-theoretic types cheatsheet
77

8+
## Set operators
9+
10+
#### Union
11+
12+
```elixir
13+
type1 or type2
14+
```
15+
16+
#### Intersection
17+
18+
```elixir
19+
type1 and type2
20+
```
21+
22+
#### Difference
23+
24+
```elixir
25+
type1 and not type2
26+
```
27+
28+
#### Negation
29+
30+
```elixir
31+
not type
32+
```
33+
834
## Data types
935

1036
### Indivisible types

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

Lines changed: 14 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1246,25 +1246,25 @@ defmodule Module.Types.DescrTest do
12461246
assert list_hd(term()) == :badnonemptylist
12471247
assert list_hd(list(term())) == :badnonemptylist
12481248
assert list_hd(empty_list()) == :badnonemptylist
1249-
assert list_hd(non_empty_list(term())) == {false, term()}
1250-
assert list_hd(non_empty_list(integer())) == {false, integer()}
1251-
assert list_hd(difference(list(number()), list(integer()))) == {false, number()}
1249+
assert list_hd(non_empty_list(term())) == {:ok, term()}
1250+
assert list_hd(non_empty_list(integer())) == {:ok, integer()}
1251+
assert list_hd(difference(list(number()), list(integer()))) == {:ok, number()}
12521252

1253-
assert list_hd(dynamic()) == {true, dynamic()}
1254-
assert list_hd(dynamic(list(integer()))) == {true, dynamic(integer())}
1253+
assert list_hd(dynamic()) == {:ok, dynamic()}
1254+
assert list_hd(dynamic(list(integer()))) == {:ok, dynamic(integer())}
12551255
assert list_hd(union(dynamic(), atom())) == :badnonemptylist
12561256
assert list_hd(union(dynamic(), list(term()))) == :badnonemptylist
12571257

12581258
assert list_hd(difference(list(number()), list(number()))) == :badnonemptylist
12591259
assert list_hd(dynamic(difference(list(number()), list(number())))) == :badnonemptylist
12601260

12611261
assert list_hd(union(dynamic(list(float())), non_empty_list(atom()))) ==
1262-
{true, union(dynamic(float()), atom())}
1262+
{:ok, union(dynamic(float()), atom())}
12631263

12641264
# If term() is in the tail, it means list(term()) is in the tail
12651265
# and therefore any term can be returned from hd.
1266-
assert list_hd(non_empty_list(atom(), term())) == {false, term()}
1267-
assert list_hd(non_empty_list(atom(), negation(list(term(), term())))) == {false, atom()}
1266+
assert list_hd(non_empty_list(atom(), term())) == {:ok, term()}
1267+
assert list_hd(non_empty_list(atom(), negation(list(term(), term())))) == {:ok, atom()}
12681268
end
12691269

12701270
test "list_tl" do
@@ -1274,27 +1274,27 @@ defmodule Module.Types.DescrTest do
12741274
assert list_tl(list(integer())) == :badnonemptylist
12751275
assert list_tl(difference(list(number()), list(number()))) == :badnonemptylist
12761276

1277-
assert list_tl(non_empty_list(integer())) == {false, list(integer())}
1277+
assert list_tl(non_empty_list(integer())) == {:ok, list(integer())}
12781278

12791279
assert list_tl(non_empty_list(integer(), atom())) ==
1280-
{false, union(atom(), non_empty_list(integer(), atom()))}
1280+
{:ok, union(atom(), non_empty_list(integer(), atom()))}
12811281

12821282
# The tail of either a (non empty) list of integers with an atom tail or a (non empty) list
12831283
# of tuples with a float tail is either an atom, or a float, or a (possibly empty) list of
12841284
# integers with an atom tail, or a (possibly empty) list of tuples with a float tail.
12851285
assert list_tl(union(non_empty_list(integer(), atom()), non_empty_list(tuple(), float()))) ==
1286-
{false,
1286+
{:ok,
12871287
atom()
12881288
|> union(float())
12891289
|> union(
12901290
union(non_empty_list(integer(), atom()), non_empty_list(tuple(), float()))
12911291
)}
12921292

1293-
assert list_tl(dynamic()) == {true, dynamic()}
1294-
assert list_tl(dynamic(list(integer()))) == {true, dynamic(list(integer()))}
1293+
assert list_tl(dynamic()) == {:ok, dynamic()}
1294+
assert list_tl(dynamic(list(integer()))) == {:ok, dynamic(list(integer()))}
12951295

12961296
assert list_tl(dynamic(list(integer(), atom()))) ==
1297-
{true, dynamic(union(atom(), list(integer(), atom())))}
1297+
{:ok, dynamic(union(atom(), list(integer(), atom())))}
12981298
end
12991299

13001300
test "tuple_fetch" do
@@ -2374,9 +2374,6 @@ defmodule Module.Types.DescrTest do
23742374
assert list(term(), term()) |> to_quoted_string() ==
23752375
"empty_list() or non_empty_list(term(), term())"
23762376

2377-
assert non_empty_list(term(), difference(term(), list(term()))) |> to_quoted_string() ==
2378-
"improper_list()"
2379-
23802377
# Test normalization
23812378

23822379
# Remove duplicates

0 commit comments

Comments
 (0)