Skip to content

Commit dc753d6

Browse files
committed
Show hint if comparing different but equivalent strings
Closes #11256.
1 parent 12ab3d3 commit dc753d6

File tree

3 files changed

+54
-21
lines changed

3 files changed

+54
-21
lines changed

lib/ex_unit/lib/ex_unit/diff.ex

Lines changed: 22 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -33,10 +33,10 @@ defmodule ExUnit.Diff do
3333
end
3434

3535
defp context_to_env({:match, pins}),
36-
do: %{pins: Map.new(pins), context: :match, current_vars: %{}}
36+
do: %{pins: Map.new(pins), context: :match, current_vars: %{}, hints: []}
3737

3838
defp context_to_env(op) when op in [:==, :===],
39-
do: %{pins: %{}, context: op, current_vars: %{}}
39+
do: %{pins: %{}, context: op, current_vars: %{}, hints: []}
4040

4141
# Main entry point for recursive diff
4242

@@ -725,20 +725,27 @@ defmodule ExUnit.Diff do
725725
left = IO.iodata_to_binary(escaped_left)
726726
right = IO.iodata_to_binary(escaped_right)
727727

728-
diff =
729-
cond do
730-
diff_string?(left, right) ->
728+
cond do
729+
left == right ->
730+
{string_script_to_diff([eq: left], delimiter, true, [], []), env}
731+
732+
diff_string?(left, right) ->
733+
diff =
731734
String.myers_difference(left, right)
732735
|> string_script_to_diff(delimiter, true, [], [])
733736

734-
left == right ->
735-
string_script_to_diff([eq: left], delimiter, true, [], [])
737+
env =
738+
if String.equivalent?(left, right) do
739+
add_hint(env, :equivalent_but_different_strings)
740+
else
741+
env
742+
end
736743

737-
true ->
738-
string_script_to_diff([del: left, ins: right], delimiter, true, [], [])
739-
end
744+
{diff, env}
740745

741-
{diff, env}
746+
true ->
747+
{string_script_to_diff([del: left, ins: right], delimiter, true, [], []), env}
748+
end
742749
end
743750

744751
# Concat all the literals on `left` and split `right` based on the size of
@@ -1031,6 +1038,10 @@ defmodule ExUnit.Diff do
10311038

10321039
# Diff helpers
10331040

1041+
defp add_hint(%{hints: hints} = env, hint) do
1042+
if hint in hints, do: env, else: %{env | hints: [hint | hints]}
1043+
end
1044+
10341045
# The left side is only escaped if it is a value
10351046
defp maybe_escape(other, %{context: :match}), do: other
10361047
defp maybe_escape(other, _env), do: escape(other)

lib/ex_unit/lib/ex_unit/formatter.ex

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -388,7 +388,7 @@ defmodule ExUnit.Formatter do
388388
) do
389389
formatted_mailbox =
390390
for message <- mailbox do
391-
{pattern, value} =
391+
{pattern, value, _warnings} =
392392
format_sides(
393393
left,
394394
message,
@@ -419,16 +419,16 @@ defmodule ExUnit.Formatter do
419419
padding_size,
420420
width
421421
) do
422-
{left, right} = format_sides(left, right, context, formatter, padding_size, width)
423-
[left: left, right: right]
422+
{left, right, extras} = format_sides(left, right, context, formatter, padding_size, width)
423+
[left: left, right: right] ++ extras
424424
end
425425

426426
defp format_sides(left, right, context, formatter, padding_size, width) do
427427
inspect = &inspect_multiline(&1, padding_size, width)
428428
content_width = if width == :infinity, do: width, else: width - padding_size
429429

430430
case format_diff(left, right, context, formatter) do
431-
{result, _env} ->
431+
{result, env} ->
432432
left =
433433
result.left
434434
|> Diff.to_algebra(&colorize_diff_delete(&1, formatter))
@@ -441,16 +441,20 @@ defmodule ExUnit.Formatter do
441441
|> Algebra.nest(padding_size)
442442
|> Algebra.format(content_width)
443443

444-
{left, right}
444+
{left, right, Enum.map(env.hints, &{:hint, format_hint(&1)})}
445445

446446
nil when is_atom(context) ->
447-
{if_value(left, inspect), if_value(right, inspect)}
447+
{if_value(left, inspect), if_value(right, inspect), []}
448448

449449
nil ->
450-
{if_value(left, &code_multiline(&1, padding_size)), if_value(right, inspect)}
450+
{if_value(left, &code_multiline(&1, padding_size)), if_value(right, inspect), []}
451451
end
452452
end
453453

454+
defp format_hint(:equivalent_but_different_strings) do
455+
"you are comparing strings that have the same visual representation but are made of different Unicode codepoints"
456+
end
457+
454458
defp format_diff(left, right, context, formatter) do
455459
if has_value?(left) and has_value?(right) and formatter.(:diff_enabled?, false) do
456460
find_diff(left, right, context)

lib/ex_unit/test/ex_unit/formatter_test.exs

Lines changed: 21 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,10 @@ defmodule ExUnit.FormatterTest do
2828
false
2929
end
3030

31-
defp formatter(_kind, message) do
32-
message
33-
end
31+
defp formatter(_key, value), do: value
32+
33+
defp diff_formatter(:diff_enabled?, _default), do: true
34+
defp diff_formatter(_key, value), do: value
3435

3536
test "formats test case filters" do
3637
filters = [run: true, slow: false]
@@ -274,6 +275,23 @@ defmodule ExUnit.FormatterTest do
274275
"""
275276
end
276277

278+
nfc_hello = String.normalize("héllo", :nfc)
279+
nfd_hello = String.normalize("héllo", :nfd)
280+
281+
test "formats assertions with hints" do
282+
failure = [{:error, catch_assertion(assert unquote(nfc_hello) == unquote(nfd_hello)), []}]
283+
284+
assert format_test_failure(test(), failure, 1, 80, &diff_formatter/2) =~ """
285+
1) world (Hello)
286+
test/ex_unit/formatter_test.exs:1
287+
Assertion with == failed
288+
code: assert "#{unquote(nfc_hello)}" == "#{unquote(nfd_hello)}"
289+
left: "#{unquote(nfc_hello)}"
290+
right: "#{unquote(nfd_hello)}"
291+
hint: you are comparing strings that have the same visual representation but are made of different Unicode codepoints
292+
"""
293+
end
294+
277295
test "formats multiple assertions" do
278296
failure = [
279297
{:error, catch_assertion(assert ExUnit.FormatterTest.falsy()), []},

0 commit comments

Comments
 (0)