Skip to content

Commit 261a3ed

Browse files
committed
Verify the right side of binary generators
1 parent 13cab5f commit 261a3ed

File tree

3 files changed

+85
-41
lines changed

3 files changed

+85
-41
lines changed

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

+34-13
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,7 @@ defmodule Module.Types.Expr do
125125
# TODO: left = right
126126
def of_expr({:=, _meta, [left_expr, right_expr]} = expr, stack, context) do
127127
with {:ok, right_type, context} <- of_expr(right_expr, stack, context) do
128-
Pattern.of_pattern(left_expr, {right_type, expr}, stack, context)
128+
Pattern.of_match(left_expr, {right_type, expr}, stack, context)
129129
end
130130
end
131131

@@ -415,22 +415,22 @@ defmodule Module.Types.Expr do
415415
defp for_clause({:<-, meta, [left, expr]}, stack, context) do
416416
{pattern, guards} = extract_head([left])
417417

418-
with {:ok, _pattern_type, context} <-
418+
with {:ok, _expr_type, context} <- of_expr(expr, stack, context),
419+
{:ok, _pattern_type, context} <-
419420
Pattern.of_head([pattern], guards, meta, stack, context),
420-
{:ok, _expr_type, context} <- of_expr(expr, stack, context),
421-
do: {:ok, context}
422-
end
423-
424-
defp for_clause({:<<>>, _, [{:<-, _, [pattern, expr]}]}, stack, context) do
425-
# TODO: the compiler guarantees pattern is a binary but we need to check expr is a binary
426-
with {:ok, _pattern_type, context} <-
427-
Pattern.of_pattern(pattern, stack, context),
428-
{:ok, _expr_type, context} <- of_expr(expr, stack, context),
429421
do: {:ok, context}
430422
end
431423

432-
defp for_clause(list, stack, context) when is_list(list) do
433-
reduce_ok(list, context, &for_option(&1, stack, &2))
424+
defp for_clause({:<<>>, _, [{:<-, meta, [left, right]}]}, stack, context) do
425+
with {:ok, right_type, context} <- of_expr(right, stack, context),
426+
{:ok, _pattern_type, context} <- Pattern.of_match(left, {binary(), left}, stack, context) do
427+
if binary_type?(right_type) do
428+
{:ok, context}
429+
else
430+
warning = {:badbinary, right_type, right, context}
431+
{:ok, warn(__MODULE__, warning, meta, stack, context)}
432+
end
433+
end
434434
end
435435

436436
defp for_clause(expr, stack, context) do
@@ -559,4 +559,25 @@ defmodule Module.Types.Expr do
559559
])
560560
}
561561
end
562+
563+
def format_diagnostic({:badbinary, type, expr, context}) do
564+
traces = Of.collect_traces(expr, context)
565+
566+
%{
567+
details: %{typing_traces: traces},
568+
message:
569+
IO.iodata_to_binary([
570+
"""
571+
expected the right side of <- in a binary generator to be a binary:
572+
573+
#{expr_to_string(expr) |> indent(4)}
574+
575+
but got type:
576+
577+
#{to_quoted_string(type) |> indent(4)}
578+
""",
579+
Of.format_traces(traces)
580+
])
581+
}
582+
end
562583
end

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

+27-28
Original file line numberDiff line numberDiff line change
@@ -21,31 +21,30 @@ defmodule Module.Types.Pattern do
2121
do: {:ok, types, context}
2222
end
2323

24-
## Patterns
25-
2624
@doc """
27-
Return the type and typing context of a pattern expression
28-
with no {expected, expr} pair. of_pattern/4 must be preferred
29-
whenever possible as it adds more context to errors.
25+
Return the type and typing context of a pattern expression with
26+
the given {expected, expr} pair or an error in case of a typing conflict.
3027
"""
31-
def of_pattern(expr, stack, context) do
28+
def of_match(expr, expected_expr, stack, context) do
29+
of_pattern(expr, expected_expr, stack, context)
30+
end
31+
32+
## Patterns
33+
34+
defp of_pattern(expr, stack, context) do
3235
# TODO: Remove the hardcoding of dynamic
36+
# TODO: Possibly remove this function
3337
of_pattern(expr, {dynamic(), expr}, stack, context)
3438
end
3539

36-
@doc """
37-
Return the type and typing context of a pattern expression with
38-
the given {expected, expr} pair or an error in case of a typing conflict.
39-
"""
40-
4140
# ^var
42-
def of_pattern({:^, _meta, [var]}, expected_expr, stack, context) do
41+
defp of_pattern({:^, _meta, [var]}, expected_expr, stack, context) do
4342
Of.intersect(Of.var(var, context), expected_expr, stack, context)
4443
end
4544

4645
# left = right
4746
# TODO: Track variables and handle nesting
48-
def of_pattern({:=, _meta, [left_expr, right_expr]}, {expected, expr}, stack, context) do
47+
defp of_pattern({:=, _meta, [left_expr, right_expr]}, {expected, expr}, stack, context) do
4948
case {is_var(left_expr), is_var(right_expr)} do
5049
{true, false} ->
5150
with {:ok, type, context} <- of_pattern(right_expr, {expected, expr}, stack, context) do
@@ -65,13 +64,13 @@ defmodule Module.Types.Pattern do
6564
end
6665

6766
# %var{...} and %^var{...}
68-
def of_pattern(
69-
{:%, _meta, [struct_var, {:%{}, _meta2, args}]} = expr,
70-
expected_expr,
71-
stack,
72-
context
73-
)
74-
when not is_atom(struct_var) do
67+
defp of_pattern(
68+
{:%, _meta, [struct_var, {:%{}, _meta2, args}]} = expr,
69+
expected_expr,
70+
stack,
71+
context
72+
)
73+
when not is_atom(struct_var) do
7574
with {:ok, struct_type, context} <-
7675
of_pattern(struct_var, {atom(), expr}, %{stack | refine: false}, context),
7776
{:ok, map_type, context} <-
@@ -84,35 +83,35 @@ defmodule Module.Types.Pattern do
8483
end
8584

8685
# %Struct{...}
87-
def of_pattern({:%, _meta, [module, {:%{}, _, args}]} = expr, expected_expr, stack, context)
88-
when is_atom(module) do
86+
defp of_pattern({:%, _meta, [module, {:%{}, _, args}]} = expr, expected_expr, stack, context)
87+
when is_atom(module) do
8988
with {:ok, actual, context} <-
9089
Of.struct(expr, module, args, :merge_defaults, stack, context, &of_pattern/3) do
9190
Of.intersect(actual, expected_expr, stack, context)
9291
end
9392
end
9493

9594
# %{...}
96-
def of_pattern({:%{}, _meta, args}, expected_expr, stack, context) do
95+
defp of_pattern({:%{}, _meta, args}, expected_expr, stack, context) do
9796
of_open_map(args, [], expected_expr, stack, context)
9897
end
9998

10099
# <<...>>>
101-
def of_pattern({:<<>>, _meta, args}, _expected_expr, stack, context) do
100+
defp of_pattern({:<<>>, _meta, args}, _expected_expr, stack, context) do
102101
case Of.binary(args, :pattern, stack, context, &of_pattern/4) do
103102
{:ok, context} -> {:ok, binary(), context}
104103
{:error, context} -> {:error, context}
105104
end
106105
end
107106

108107
# _
109-
def of_pattern({:_, _meta, _var_context}, {expected, _expr}, _stack, context) do
108+
defp of_pattern({:_, _meta, _var_context}, {expected, _expr}, _stack, context) do
110109
{:ok, expected, context}
111110
end
112111

113112
# var
114-
def of_pattern({name, meta, ctx} = var, {expected, expr}, stack, context)
115-
when is_atom(name) and is_atom(ctx) do
113+
defp of_pattern({name, meta, ctx} = var, {expected, expr}, stack, context)
114+
when is_atom(name) and is_atom(ctx) do
116115
case stack do
117116
%{refine: true} ->
118117
Of.refine_var(var, expected, expr, stack, context)
@@ -130,7 +129,7 @@ defmodule Module.Types.Pattern do
130129
end
131130
end
132131

133-
def of_pattern(expr, expected_expr, stack, context) do
132+
defp of_pattern(expr, expected_expr, stack, context) do
134133
of_shared(expr, expected_expr, stack, context, &of_pattern/4)
135134
end
136135

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

+24
Original file line numberDiff line numberDiff line change
@@ -527,4 +527,28 @@ defmodule Module.Types.ExprTest do
527527
"""}
528528
end
529529
end
530+
531+
describe "comprehensions" do
532+
test "binary generators" do
533+
assert typewarn!([<<x>>], for(<<y <- x>>, do: y)) ==
534+
{dynamic(),
535+
~l"""
536+
expected the right side of <- in a binary generator to be a binary:
537+
538+
x
539+
540+
but got type:
541+
542+
integer()
543+
544+
where "x" was given the type:
545+
546+
# type: integer()
547+
# from: types_test.ex:533
548+
<<x>>
549+
550+
#{hints(:inferred_bitstring_spec)}
551+
"""}
552+
end
553+
end
530554
end

0 commit comments

Comments
 (0)